summaryrefslogtreecommitdiff
path: root/lib/Data/Packed/Matrix.hs
diff options
context:
space:
mode:
Diffstat (limited to 'lib/Data/Packed/Matrix.hs')
-rw-r--r--lib/Data/Packed/Matrix.hs149
1 files changed, 3 insertions, 146 deletions
diff --git a/lib/Data/Packed/Matrix.hs b/lib/Data/Packed/Matrix.hs
index ea16748..e046ead 100644
--- a/lib/Data/Packed/Matrix.hs
+++ b/lib/Data/Packed/Matrix.hs
@@ -34,20 +34,14 @@ module Data.Packed.Matrix (
34 subMatrix, takeRows, dropRows, takeColumns, dropColumns, 34 subMatrix, takeRows, dropRows, takeColumns, dropColumns,
35 extractRows, 35 extractRows,
36 diagRect, takeDiag, 36 diagRect, takeDiag,
37 liftMatrix, liftMatrix2, liftMatrix2Auto, 37 liftMatrix, liftMatrix2, liftMatrix2Auto,fromArray2D
38 dispf, disps, dispcf, vecdisp, latexFormat, format,
39 loadMatrix, saveMatrix, fromFile, fileDimensions,
40 readMatrix, fromArray2D
41) where 38) where
42 39
43import Data.Packed.Internal 40import Data.Packed.Internal
44import qualified Data.Packed.ST as ST 41import qualified Data.Packed.ST as ST
45--import Data.Packed.Vector
46import Data.Array
47import System.Process(readProcess)
48import Text.Printf(printf)
49import Data.List(transpose,intersperse) 42import Data.List(transpose,intersperse)
50import Data.Complex 43import Data.Array
44
51 45
52import Data.Binary 46import Data.Binary
53import Foreign.Storable 47import Foreign.Storable
@@ -280,143 +274,6 @@ fromArray2D m = (r><c) (elems m)
280 c = c1-c0+1 274 c = c1-c0+1
281 275
282 276
283-------------------------------------------------------------------
284-- display utilities
285
286
287{- | Creates a string from a matrix given a separator and a function to show each entry. Using
288this function the user can easily define any desired display function:
289
290@import Text.Printf(printf)@
291
292@disp = putStr . format \" \" (printf \"%.2f\")@
293
294-}
295format :: (Element t) => String -> (t -> String) -> Matrix t -> String
296format sep f m = table sep . map (map f) . toLists $ m
297
298{- | Show a matrix with \"autoscaling\" and a given number of decimal places.
299
300@disp = putStr . disps 2
301
302\> disp $ 120 * (3><4) [1..]
3033x4 E3
304 0.12 0.24 0.36 0.48
305 0.60 0.72 0.84 0.96
306 1.08 1.20 1.32 1.44
307@
308-}
309disps :: Int -> Matrix Double -> String
310disps d x = sdims x ++ " " ++ formatScaled d x
311
312{- | Show a matrix with a given number of decimal places.
313
314@disp = putStr . dispf 3
315
316\> disp (1/3 + ident 4)
3174x4
3181.333 0.333 0.333 0.333
3190.333 1.333 0.333 0.333
3200.333 0.333 1.333 0.333
3210.333 0.333 0.333 1.333
322@
323-}
324dispf :: Int -> Matrix Double -> String
325dispf d x = sdims x ++ "\n" ++ formatFixed (if isInt x then 0 else d) x
326
327sdims x = show (rows x) ++ "x" ++ show (cols x)
328
329formatFixed d x = format " " (printf ("%."++show d++"f")) $ x
330
331isInt = all lookslikeInt . toList . flatten
332
333formatScaled dec t = "E"++show o++"\n" ++ ss
334 where ss = format " " (printf fmt. g) t
335 g x | o >= 0 = x/10^(o::Int)
336 | otherwise = x*10^(-o)
337 o = floor $ maximum $ map (logBase 10 . abs) $ toList $ flatten t
338 fmt = '%':show (dec+3) ++ '.':show dec ++"f"
339
340{- | Show a vector using a function for showing matrices.
341
342@disp = putStr . vecdisp ('dispf' 2)
343
344\> disp ('linspace' 10 (0,1))
34510 |> 0.00 0.11 0.22 0.33 0.44 0.56 0.67 0.78 0.89 1.00
346@
347-}
348vecdisp :: (Element t) => (Matrix t -> String) -> Vector t -> String
349vecdisp f v
350 = ((show (dim v) ++ " |> ") ++) . (++"\n")
351 . unwords . lines . tail . dropWhile (not . (`elem` " \n"))
352 . f . trans . reshape 1
353 $ v
354
355-- | Tool to display matrices with latex syntax.
356latexFormat :: String -- ^ type of braces: \"matrix\", \"bmatrix\", \"pmatrix\", etc.
357 -> String -- ^ Formatted matrix, with elements separated by spaces and newlines
358 -> String
359latexFormat del tab = "\\begin{"++del++"}\n" ++ f tab ++ "\\end{"++del++"}"
360 where f = unlines . intersperse "\\\\" . map unwords . map (intersperse " & " . words) . tail . lines
361
362-- | Pretty print a complex number with at most n decimal digits.
363showComplex :: Int -> Complex Double -> String
364showComplex d (a:+b)
365 | isZero a && isZero b = "0"
366 | isZero b = sa
367 | isZero a && isOne b = s2++"i"
368 | isZero a = sb++"i"
369 | isOne b = sa++s3++"i"
370 | otherwise = sa++s1++sb++"i"
371 where
372 sa = shcr d a
373 sb = shcr d b
374 s1 = if b<0 then "" else "+"
375 s2 = if b<0 then "-" else ""
376 s3 = if b<0 then "-" else "+"
377
378shcr d a | lookslikeInt a = printf "%.0f" a
379 | otherwise = printf ("%."++show d++"f") a
380
381
382lookslikeInt x = show (round x :: Int) ++".0" == shx || "-0.0" == shx
383 where shx = show x
384
385isZero x = show x `elem` ["0.0","-0.0"]
386isOne x = show x `elem` ["1.0","-1.0"]
387
388-- | Pretty print a complex matrix with at most n decimal digits.
389dispcf :: Int -> Matrix (Complex Double) -> String
390dispcf d m = sdims m ++ "\n" ++ format " " (showComplex d) m
391
392--------------------------------------------------------------------
393
394-- | reads a matrix from a string containing a table of numbers.
395readMatrix :: String -> Matrix Double
396readMatrix = fromLists . map (map read). map words . filter (not.null) . lines
397
398{- | obtains the number of rows and columns in an ASCII data file
399 (provisionally using unix's wc).
400-}
401fileDimensions :: FilePath -> IO (Int,Int)
402fileDimensions fname = do
403 wcres <- readProcess "wc" ["-w",fname] ""
404 contents <- readFile fname
405 let tot = read . head . words $ wcres
406 c = length . head . dropWhile null . map words . lines $ contents
407 if tot > 0
408 then return (tot `div` c, c)
409 else return (0,0)
410
411-- | Loads a matrix from an ASCII file formatted as a 2D table.
412loadMatrix :: FilePath -> IO (Matrix Double)
413loadMatrix file = fromFile file =<< fileDimensions file
414
415-- | Loads a matrix from an ASCII file (the number of rows and columns must be known in advance).
416fromFile :: FilePath -> (Int,Int) -> IO (Matrix Double)
417fromFile filename (r,c) = reshape c `fmap` fscanfVector filename (r*c)
418
419
420-- | rearranges the rows of a matrix according to the order given in a list of integers. 277-- | rearranges the rows of a matrix according to the order given in a list of integers.
421extractRows :: Element t => [Int] -> Matrix t -> Matrix t 278extractRows :: Element t => [Int] -> Matrix t -> Matrix t
422extractRows l m = fromRows $ extract (toRows $ m) l 279extractRows l m = fromRows $ extract (toRows $ m) l