summaryrefslogtreecommitdiff
path: root/lib/Data
diff options
context:
space:
mode:
authorAlberto Ruiz <aruiz@um.es>2007-06-23 20:21:03 +0000
committerAlberto Ruiz <aruiz@um.es>2007-06-23 20:21:03 +0000
commit3d5d6f06598aac00906c93ac5358e68697c47fc7 (patch)
tree77a76afcd561b8beee33c39b4eafe72b4fa10b86 /lib/Data
parent978e6d038239af50d70bae2c303f4e45b1879b7a (diff)
more refactoring
Diffstat (limited to 'lib/Data')
-rw-r--r--lib/Data/Packed/Internal/Matrix.hs10
-rw-r--r--lib/Data/Packed/Matrix.hs20
-rw-r--r--lib/Data/Packed/Plot.hs3
-rw-r--r--lib/Data/Packed/Vector.hs1
4 files changed, 29 insertions, 5 deletions
diff --git a/lib/Data/Packed/Internal/Matrix.hs b/lib/Data/Packed/Internal/Matrix.hs
index 32dc603..9309d1d 100644
--- a/lib/Data/Packed/Internal/Matrix.hs
+++ b/lib/Data/Packed/Internal/Matrix.hs
@@ -28,7 +28,6 @@ import Data.Maybe(fromJust)
28 28
29data MatrixOrder = RowMajor | ColumnMajor deriving (Show,Eq) 29data MatrixOrder = RowMajor | ColumnMajor deriving (Show,Eq)
30 30
31-- | 2D array
32data Matrix t = M { rows :: Int 31data Matrix t = M { rows :: Int
33 , cols :: Int 32 , cols :: Int
34 , dat :: Vector t 33 , dat :: Vector t
@@ -44,6 +43,7 @@ fortran m = order m == ColumnMajor
44cdat m = if fortran m `xor` isTrans m then tdat m else dat m 43cdat m = if fortran m `xor` isTrans m then tdat m else dat m
45fdat m = if fortran m `xor` isTrans m then dat m else tdat m 44fdat m = if fortran m `xor` isTrans m then dat m else tdat m
46 45
46trans :: Matrix t -> Matrix t
47trans m = m { rows = cols m 47trans m = m { rows = cols m
48 , cols = rows m 48 , cols = rows m
49 , isTrans = not (isTrans m) 49 , isTrans = not (isTrans m)
@@ -56,6 +56,7 @@ type Mt t s = Int -> Int -> Ptr t -> s
56 56
57mat d m f = f (rows m) (cols m) (ptr (d m)) 57mat d m f = f (rows m) (cols m) (ptr (d m))
58 58
59toLists :: (Storable t) => Matrix t -> [[t]]
59toLists m = partit (cols m) . toList . cdat $ m 60toLists m = partit (cols m) . toList . cdat $ m
60 61
61instance (Show a, Storable a) => (Show (Matrix a)) where 62instance (Show a, Storable a) => (Show (Matrix a)) where
@@ -92,6 +93,7 @@ createMatrix order r c = do
92 p <- createVector (r*c) 93 p <- createVector (r*c)
93 return (matrixFromVector order c p) 94 return (matrixFromVector order c p)
94 95
96reshape :: (Field t) => Int -> Vector t -> Matrix t
95reshape c v = matrixFromVector RowMajor c v 97reshape c v = matrixFromVector RowMajor c v
96 98
97singleton x = reshape 1 (fromList [x]) 99singleton x = reshape 1 (fromList [x])
@@ -133,8 +135,10 @@ transdata c1 d c2 | isReal baseOf d = scast $ transdataR c1 (scast d) c2
133--{-# RULES "transdataC" transdata=transdataC #-} 135--{-# RULES "transdataC" transdata=transdataC #-}
134 136
135----------------------------------------------------------------- 137-----------------------------------------------------------------
136 138liftMatrix :: (Vector a -> Vector b) -> Matrix a -> Matrix b
137liftMatrix f m = m { dat = f (dat m), tdat = f (tdat m) } -- check sizes 139liftMatrix f m = m { dat = f (dat m), tdat = f (tdat m) } -- check sizes
140
141liftMatrix2 :: (Field t) => (Vector a -> Vector b -> Vector t) -> Matrix a -> Matrix b -> Matrix t
138liftMatrix2 f m1 m2 = reshape (cols m1) (f (cdat m1) (cdat m2)) -- check sizes 142liftMatrix2 f m1 m2 = reshape (cols m1) (f (cdat m1) (cdat m2)) -- check sizes
139 143
140------------------------------------------------------------------ 144------------------------------------------------------------------
@@ -196,10 +200,12 @@ multiplyD order a b
196 200
197outer' u v = dat (outer u v) 201outer' u v = dat (outer u v)
198 202
203outer :: (Num t, Field t) => Vector t -> Vector t -> Matrix t
199outer u v = multiply RowMajor r c 204outer u v = multiply RowMajor r c
200 where r = matrixFromVector RowMajor 1 u 205 where r = matrixFromVector RowMajor 1 u
201 c = matrixFromVector RowMajor (dim v) v 206 c = matrixFromVector RowMajor (dim v) v
202 207
208dot :: (Field t, Num t) => Vector t -> Vector t -> t
203dot u v = dat (multiply RowMajor r c) `at` 0 209dot u v = dat (multiply RowMajor r c) `at` 0
204 where r = matrixFromVector RowMajor (dim u) u 210 where r = matrixFromVector RowMajor (dim u) u
205 c = matrixFromVector RowMajor 1 v 211 c = matrixFromVector RowMajor 1 v
diff --git a/lib/Data/Packed/Matrix.hs b/lib/Data/Packed/Matrix.hs
index c7d5cfa..0f9d998 100644
--- a/lib/Data/Packed/Matrix.hs
+++ b/lib/Data/Packed/Matrix.hs
@@ -14,8 +14,8 @@
14 14
15module Data.Packed.Matrix ( 15module Data.Packed.Matrix (
16 Matrix(rows,cols), Field, 16 Matrix(rows,cols), Field,
17 toLists, (><), (>|<), (@@>), 17 fromLists, toLists, (><), (>|<), (@@>),
18 trans, 18 trans, conjTrans,
19 reshape, flatten, 19 reshape, flatten,
20 fromRows, toRows, fromColumns, toColumns, 20 fromRows, toRows, fromColumns, toColumns,
21 joinVert, joinHoriz, 21 joinVert, joinHoriz,
@@ -29,6 +29,9 @@ module Data.Packed.Matrix (
29) where 29) where
30 30
31import Data.Packed.Internal 31import Data.Packed.Internal
32import Foreign(Storable)
33import Complex
34import Data.Packed.Vector
32 35
33-- | creates a matrix from a vertical list of matrices 36-- | creates a matrix from a vertical list of matrices
34joinVert :: Field t => [Matrix t] -> Matrix t 37joinVert :: Field t => [Matrix t] -> Matrix t
@@ -50,6 +53,7 @@ fliprl m = fromColumns . reverse . toColumns $ m
50 53
51------------------------------------------------------------ 54------------------------------------------------------------
52 55
56diagRect :: (Field t, Num t) => Vector t -> Int -> Int -> Matrix t
53diagRect s r c 57diagRect s r c
54 | dim s < min r c = error "diagRect" 58 | dim s < min r c = error "diagRect"
55 | r == c = diag s 59 | r == c = diag s
@@ -57,16 +61,20 @@ diagRect s r c
57 | r > c = joinVert [diag s , zeros (r-c,c)] 61 | r > c = joinVert [diag s , zeros (r-c,c)]
58 where zeros (r,c) = reshape c $ constant 0 (r*c) 62 where zeros (r,c) = reshape c $ constant 0 (r*c)
59 63
64takeDiag :: (Storable t) => Matrix t -> Vector t
60takeDiag m = fromList [cdat m `at` (k*cols m+k) | k <- [0 .. min (rows m) (cols m) -1]] 65takeDiag m = fromList [cdat m `at` (k*cols m+k) | k <- [0 .. min (rows m) (cols m) -1]]
61 66
67ident :: (Num t, Field t) => Int -> Matrix t
62ident n = diag (constant 1 n) 68ident n = diag (constant 1 n)
63 69
70(><) :: (Field a) => Int -> Int -> [a] -> Matrix a
64r >< c = f where 71r >< c = f where
65 f l | dim v == r*c = matrixFromVector RowMajor c v 72 f l | dim v == r*c = matrixFromVector RowMajor c v
66 | otherwise = error $ "inconsistent list size = " 73 | otherwise = error $ "inconsistent list size = "
67 ++show (dim v) ++"in ("++show r++"><"++show c++")" 74 ++show (dim v) ++"in ("++show r++"><"++show c++")"
68 where v = fromList l 75 where v = fromList l
69 76
77(>|<) :: (Field a) => Int -> Int -> [a] -> Matrix a
70r >|< c = f where 78r >|< c = f where
71 f l | dim v == r*c = matrixFromVector ColumnMajor c v 79 f l | dim v == r*c = matrixFromVector ColumnMajor c v
72 | otherwise = error $ "inconsistent list size = " 80 | otherwise = error $ "inconsistent list size = "
@@ -90,4 +98,12 @@ dropColumns n mat = subMatrix (0,n) (rows mat, cols mat - n) mat
90 98
91---------------------------------------------------------------- 99----------------------------------------------------------------
92 100
101flatten :: Matrix t -> Vector t
93flatten = cdat 102flatten = cdat
103
104-- | Creates a 'Matrix' from a list of lists (considered as rows).
105fromLists :: Field t => [[t]] -> Matrix t
106fromLists = fromRows . map fromList
107
108conjTrans :: Matrix (Complex Double) -> Matrix (Complex Double)
109conjTrans = trans . liftMatrix conj \ No newline at end of file
diff --git a/lib/Data/Packed/Plot.hs b/lib/Data/Packed/Plot.hs
index 9eddc9f..a0a4aae 100644
--- a/lib/Data/Packed/Plot.hs
+++ b/lib/Data/Packed/Plot.hs
@@ -51,7 +51,7 @@ toFile filename matrix = writeFile filename (unlines . map unwords. map (map sho
51meshdom :: Vector Double -> Vector Double -> (Matrix Double , Matrix Double) 51meshdom :: Vector Double -> Vector Double -> (Matrix Double , Matrix Double)
52meshdom r1 r2 = (outer r1 (constant 1 (size r2)), outer (constant 1 (size r1)) r2) 52meshdom r1 r2 = (outer r1 (constant 1 (size r2)), outer (constant 1 (size r1)) r2)
53 53
54 54gnuplotX :: String -> IO ()
55gnuplotX command = do {system cmdstr; return()} where 55gnuplotX command = do {system cmdstr; return()} where
56 cmdstr = "echo \""++command++"\" | gnuplot -persist" 56 cmdstr = "echo \""++command++"\" | gnuplot -persist"
57 57
@@ -72,6 +72,7 @@ mesh m = gnuplotX (command++dat) where
72 command = "splot "++datafollows++" matrix with lines\n" 72 command = "splot "++datafollows++" matrix with lines\n"
73 dat = prep $ toLists $ m 73 dat = prep $ toLists $ m
74 74
75mesh' :: Matrix Double -> IO ()
75mesh' m = do 76mesh' m = do
76 writeFile "splot-gnu-command" "splot \"splot-tmp.txt\" matrix with lines; pause -1"; 77 writeFile "splot-gnu-command" "splot \"splot-tmp.txt\" matrix with lines; pause -1";
77 toFile "splot-tmp.txt" m 78 toFile "splot-tmp.txt" m
diff --git a/lib/Data/Packed/Vector.hs b/lib/Data/Packed/Vector.hs
index aa1b489..9d9d879 100644
--- a/lib/Data/Packed/Vector.hs
+++ b/lib/Data/Packed/Vector.hs
@@ -36,6 +36,7 @@ conj :: Vector (Complex Double) -> Vector (Complex Double)
36conj v = asComplex $ cdat $ reshape 2 (asReal v) `mulC` diag (fromList [1,-1]) 36conj v = asComplex $ cdat $ reshape 2 (asReal v) `mulC` diag (fromList [1,-1])
37 where mulC = multiply RowMajor 37 where mulC = multiply RowMajor
38 38
39comp :: Vector Double -> Vector (Complex Double)
39comp v = toComplex (v,constant 0 (dim v)) 40comp v = toComplex (v,constant 0 (dim v))
40 41
41{- | Creates a real vector containing a range of values: 42{- | Creates a real vector containing a range of values: