summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorAlberto Ruiz <aruiz@um.es>2010-09-21 19:25:04 +0000
committerAlberto Ruiz <aruiz@um.es>2010-09-21 19:25:04 +0000
commit0c739613926ac44254a9de9ea81351a974805c45 (patch)
tree5c91176bcae62354b365e927f6bce98b2dda51e9
parent3290b56b975ec151a389223f720c071b6404f6cc (diff)
move display/IO
-rw-r--r--hmatrix.cabal1
-rw-r--r--lib/Data/Packed/Matrix.hs149
-rw-r--r--lib/Data/Packed/Vector.hs1
-rw-r--r--lib/Numeric/IO.hs160
-rw-r--r--lib/Numeric/Matrix.hs7
-rw-r--r--lib/Numeric/Vector.hs5
6 files changed, 174 insertions, 149 deletions
diff --git a/hmatrix.cabal b/hmatrix.cabal
index 9934b6e..ae03b0f 100644
--- a/hmatrix.cabal
+++ b/hmatrix.cabal
@@ -116,6 +116,7 @@ library
116 Numeric.GSL.Internal, 116 Numeric.GSL.Internal,
117 Numeric.Conversion 117 Numeric.Conversion
118 Numeric.MatrixBoot 118 Numeric.MatrixBoot
119 Numeric.IO
119 Numeric.Chain 120 Numeric.Chain
120 121
121 C-sources: lib/Numeric/LinearAlgebra/LAPACK/lapack-aux.c, 122 C-sources: lib/Numeric/LinearAlgebra/LAPACK/lapack-aux.c,
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
diff --git a/lib/Data/Packed/Vector.hs b/lib/Data/Packed/Vector.hs
index 49448b2..2e0a9f5 100644
--- a/lib/Data/Packed/Vector.hs
+++ b/lib/Data/Packed/Vector.hs
@@ -20,7 +20,6 @@ module Data.Packed.Vector (
20 subVector, takesV, join, 20 subVector, takesV, join,
21 mapVector, zipVector, zipVectorWith, unzipVector, unzipVectorWith, 21 mapVector, zipVector, zipVectorWith, unzipVector, unzipVectorWith,
22 mapVectorM, mapVectorM_, mapVectorWithIndexM, mapVectorWithIndexM_, 22 mapVectorM, mapVectorM_, mapVectorWithIndexM, mapVectorWithIndexM_,
23 fscanfVector, fprintfVector, freadVector, fwriteVector,
24 foldLoop, foldVector, foldVectorG, foldVectorWithIndex 23 foldLoop, foldVector, foldVectorG, foldVectorWithIndex
25) where 24) where
26 25
diff --git a/lib/Numeric/IO.hs b/lib/Numeric/IO.hs
new file mode 100644
index 0000000..dacfa8b
--- /dev/null
+++ b/lib/Numeric/IO.hs
@@ -0,0 +1,160 @@
1-----------------------------------------------------------------------------
2-- |
3-- Module : Numeric.IO
4-- Copyright : (c) Alberto Ruiz 2010
5-- License : GPL
6--
7-- Maintainer : Alberto Ruiz <aruiz@um.es>
8-- Stability : provisional
9-- Portability : portable
10--
11-- Display, formatting and IO functions for numeric 'Vector' and 'Matrix'
12--
13-----------------------------------------------------------------------------
14
15module Numeric.IO (
16 dispf, disps, dispcf, vecdisp, latexFormat, format,
17 loadMatrix, saveMatrix, fromFile, fileDimensions,
18 readMatrix, fromArray2D,
19 fscanfVector, fprintfVector, freadVector, fwriteVector
20) where
21
22import Data.Packed
23import Data.Packed.Internal
24import System.Process(readProcess)
25import Text.Printf(printf)
26import Data.List(intersperse)
27import Data.Complex
28
29{- | Creates a string from a matrix given a separator and a function to show each entry. Using
30this function the user can easily define any desired display function:
31
32@import Text.Printf(printf)@
33
34@disp = putStr . format \" \" (printf \"%.2f\")@
35
36-}
37format :: (Element t) => String -> (t -> String) -> Matrix t -> String
38format sep f m = table sep . map (map f) . toLists $ m
39
40{- | Show a matrix with \"autoscaling\" and a given number of decimal places.
41
42@disp = putStr . disps 2
43
44\> disp $ 120 * (3><4) [1..]
453x4 E3
46 0.12 0.24 0.36 0.48
47 0.60 0.72 0.84 0.96
48 1.08 1.20 1.32 1.44
49@
50-}
51disps :: Int -> Matrix Double -> String
52disps d x = sdims x ++ " " ++ formatScaled d x
53
54{- | Show a matrix with a given number of decimal places.
55
56@disp = putStr . dispf 3
57
58\> disp (1/3 + ident 4)
594x4
601.333 0.333 0.333 0.333
610.333 1.333 0.333 0.333
620.333 0.333 1.333 0.333
630.333 0.333 0.333 1.333
64@
65-}
66dispf :: Int -> Matrix Double -> String
67dispf d x = sdims x ++ "\n" ++ formatFixed (if isInt x then 0 else d) x
68
69sdims x = show (rows x) ++ "x" ++ show (cols x)
70
71formatFixed d x = format " " (printf ("%."++show d++"f")) $ x
72
73isInt = all lookslikeInt . toList . flatten
74
75formatScaled dec t = "E"++show o++"\n" ++ ss
76 where ss = format " " (printf fmt. g) t
77 g x | o >= 0 = x/10^(o::Int)
78 | otherwise = x*10^(-o)
79 o = floor $ maximum $ map (logBase 10 . abs) $ toList $ flatten t
80 fmt = '%':show (dec+3) ++ '.':show dec ++"f"
81
82{- | Show a vector using a function for showing matrices.
83
84@disp = putStr . vecdisp ('dispf' 2)
85
86\> disp ('linspace' 10 (0,1))
8710 |> 0.00 0.11 0.22 0.33 0.44 0.56 0.67 0.78 0.89 1.00
88@
89-}
90vecdisp :: (Element t) => (Matrix t -> String) -> Vector t -> String
91vecdisp f v
92 = ((show (dim v) ++ " |> ") ++) . (++"\n")
93 . unwords . lines . tail . dropWhile (not . (`elem` " \n"))
94 . f . trans . reshape 1
95 $ v
96
97-- | Tool to display matrices with latex syntax.
98latexFormat :: String -- ^ type of braces: \"matrix\", \"bmatrix\", \"pmatrix\", etc.
99 -> String -- ^ Formatted matrix, with elements separated by spaces and newlines
100 -> String
101latexFormat del tab = "\\begin{"++del++"}\n" ++ f tab ++ "\\end{"++del++"}"
102 where f = unlines . intersperse "\\\\" . map unwords . map (intersperse " & " . words) . tail . lines
103
104-- | Pretty print a complex number with at most n decimal digits.
105showComplex :: Int -> Complex Double -> String
106showComplex d (a:+b)
107 | isZero a && isZero b = "0"
108 | isZero b = sa
109 | isZero a && isOne b = s2++"i"
110 | isZero a = sb++"i"
111 | isOne b = sa++s3++"i"
112 | otherwise = sa++s1++sb++"i"
113 where
114 sa = shcr d a
115 sb = shcr d b
116 s1 = if b<0 then "" else "+"
117 s2 = if b<0 then "-" else ""
118 s3 = if b<0 then "-" else "+"
119
120shcr d a | lookslikeInt a = printf "%.0f" a
121 | otherwise = printf ("%."++show d++"f") a
122
123
124lookslikeInt x = show (round x :: Int) ++".0" == shx || "-0.0" == shx
125 where shx = show x
126
127isZero x = show x `elem` ["0.0","-0.0"]
128isOne x = show x `elem` ["1.0","-1.0"]
129
130-- | Pretty print a complex matrix with at most n decimal digits.
131dispcf :: Int -> Matrix (Complex Double) -> String
132dispcf d m = sdims m ++ "\n" ++ format " " (showComplex d) m
133
134--------------------------------------------------------------------
135
136-- | reads a matrix from a string containing a table of numbers.
137readMatrix :: String -> Matrix Double
138readMatrix = fromLists . map (map read). map words . filter (not.null) . lines
139
140{- | obtains the number of rows and columns in an ASCII data file
141 (provisionally using unix's wc).
142-}
143fileDimensions :: FilePath -> IO (Int,Int)
144fileDimensions fname = do
145 wcres <- readProcess "wc" ["-w",fname] ""
146 contents <- readFile fname
147 let tot = read . head . words $ wcres
148 c = length . head . dropWhile null . map words . lines $ contents
149 if tot > 0
150 then return (tot `div` c, c)
151 else return (0,0)
152
153-- | Loads a matrix from an ASCII file formatted as a 2D table.
154loadMatrix :: FilePath -> IO (Matrix Double)
155loadMatrix file = fromFile file =<< fileDimensions file
156
157-- | Loads a matrix from an ASCII file (the number of rows and columns must be known in advance).
158fromFile :: FilePath -> (Int,Int) -> IO (Matrix Double)
159fromFile filename (r,c) = reshape c `fmap` fscanfVector filename (r*c)
160
diff --git a/lib/Numeric/Matrix.hs b/lib/Numeric/Matrix.hs
index 26d6d6b..7bb79f3 100644
--- a/lib/Numeric/Matrix.hs
+++ b/lib/Numeric/Matrix.hs
@@ -34,7 +34,11 @@ module Numeric.Matrix (
34 ctrans, 34 ctrans,
35 optimiseMult, 35 optimiseMult,
36 -- * Operators 36 -- * Operators
37 (<>), (<\>) 37 (<>), (<\>),
38 -- * IO
39 dispf, disps, dispcf, vecdisp, latexFormat, format,
40 loadMatrix, saveMatrix, fromFile, fileDimensions,
41 readMatrix
38 ) where 42 ) where
39 43
40------------------------------------------------------------------- 44-------------------------------------------------------------------
@@ -43,6 +47,7 @@ import Data.Packed.Matrix
43import Numeric.Vector 47import Numeric.Vector
44import Numeric.Chain 48import Numeric.Chain
45import Numeric.MatrixBoot 49import Numeric.MatrixBoot
50import Numeric.IO
46import Numeric.LinearAlgebra.Algorithms 51import Numeric.LinearAlgebra.Algorithms
47 52
48------------------------------------------------------------------- 53-------------------------------------------------------------------
diff --git a/lib/Numeric/Vector.hs b/lib/Numeric/Vector.hs
index 3d7f350..9acd6f0 100644
--- a/lib/Numeric/Vector.hs
+++ b/lib/Numeric/Vector.hs
@@ -27,13 +27,16 @@ module Numeric.Vector (
27 -- * Vector creation 27 -- * Vector creation
28 constant, linspace, 28 constant, linspace,
29 -- * Operators 29 -- * Operators
30 (<.>) 30 (<.>),
31 -- * IO
32 fscanfVector, fprintfVector, freadVector, fwriteVector
31 ) where 33 ) where
32 34
33import Data.Packed.Vector 35import Data.Packed.Vector
34import Data.Packed.Internal.Matrix 36import Data.Packed.Internal.Matrix
35import Numeric.GSL.Vector 37import Numeric.GSL.Vector
36import Numeric.Container 38import Numeric.Container
39import Numeric.IO
37 40
38------------------------------------------------------------------- 41-------------------------------------------------------------------
39 42