diff options
author | Alberto Ruiz <aruiz@um.es> | 2007-06-13 16:35:02 +0000 |
---|---|---|
committer | Alberto Ruiz <aruiz@um.es> | 2007-06-13 16:35:02 +0000 |
commit | 713d4056abb2e786b4084e7e220d359b06dcaf1f (patch) | |
tree | 4535b87da8756ca89f07e46181891df2b90406dc /lib/Data/Packed/Internal/Matrix.hs | |
parent | 8c5be977858723aac8b8f47f57ce98d82fe249b4 (diff) |
refactoring
Diffstat (limited to 'lib/Data/Packed/Internal/Matrix.hs')
-rw-r--r-- | lib/Data/Packed/Internal/Matrix.hs | 109 |
1 files changed, 25 insertions, 84 deletions
diff --git a/lib/Data/Packed/Internal/Matrix.hs b/lib/Data/Packed/Internal/Matrix.hs index bae56f1..2c0acdf 100644 --- a/lib/Data/Packed/Internal/Matrix.hs +++ b/lib/Data/Packed/Internal/Matrix.hs | |||
@@ -1,4 +1,4 @@ | |||
1 | {-# OPTIONS_GHC -fglasgow-exts -fallow-undecidable-instances #-} | 1 | {-# OPTIONS_GHC -fglasgow-exts #-} |
2 | ----------------------------------------------------------------------------- | 2 | ----------------------------------------------------------------------------- |
3 | -- | | 3 | -- | |
4 | -- Module : Data.Packed.Internal.Matrix | 4 | -- Module : Data.Packed.Internal.Matrix |
@@ -15,18 +15,16 @@ | |||
15 | 15 | ||
16 | module Data.Packed.Internal.Matrix where | 16 | module Data.Packed.Internal.Matrix where |
17 | 17 | ||
18 | import Data.Packed.Internal.Common | ||
18 | import Data.Packed.Internal.Vector | 19 | import Data.Packed.Internal.Vector |
19 | 20 | ||
20 | import Foreign hiding (xor) | 21 | import Foreign hiding (xor) |
21 | import Complex | 22 | import Complex |
22 | import Control.Monad(when) | 23 | import Control.Monad(when) |
23 | import Debug.Trace | ||
24 | import Data.List(transpose,intersperse) | 24 | import Data.List(transpose,intersperse) |
25 | import Data.Typeable | 25 | import Data.Typeable |
26 | import Data.Maybe(fromJust) | 26 | import Data.Maybe(fromJust) |
27 | 27 | ||
28 | debug x = trace (show x) x | ||
29 | |||
30 | 28 | ||
31 | data MatrixOrder = RowMajor | ColumnMajor deriving (Show,Eq) | 29 | data MatrixOrder = RowMajor | ColumnMajor deriving (Show,Eq) |
32 | 30 | ||
@@ -39,7 +37,7 @@ data Matrix t = M { rows :: Int | |||
39 | , order :: MatrixOrder | 37 | , order :: MatrixOrder |
40 | } deriving Typeable | 38 | } deriving Typeable |
41 | 39 | ||
42 | xor a b = a && not b || b && not a | 40 | |
43 | 41 | ||
44 | fortran m = order m == ColumnMajor | 42 | fortran m = order m == ColumnMajor |
45 | 43 | ||
@@ -57,25 +55,12 @@ type t ::> s = Mt t s | |||
57 | 55 | ||
58 | mat d m f = f (rows m) (cols m) (ptr (d m)) | 56 | mat d m f = f (rows m) (cols m) (ptr (d m)) |
59 | 57 | ||
58 | toLists m = partit (cols m) . toList . cdat $ m | ||
59 | |||
60 | instance (Show a, Storable a) => (Show (Matrix a)) where | 60 | instance (Show a, Storable a) => (Show (Matrix a)) where |
61 | show m = (sizes++) . dsp . map (map show) . toLists $ m | 61 | show m = (sizes++) . dsp . map (map show) . toLists $ m |
62 | where sizes = "("++show (rows m)++"><"++show (cols m)++")\n" | 62 | where sizes = "("++show (rows m)++"><"++show (cols m)++")\n" |
63 | 63 | ||
64 | partit :: Int -> [a] -> [[a]] | ||
65 | partit _ [] = [] | ||
66 | partit n l = take n l : partit n (drop n l) | ||
67 | |||
68 | -- | obtains the common value of a property of a list | ||
69 | common :: (Eq a) => (b->a) -> [b] -> Maybe a | ||
70 | common f = commonval . map f where | ||
71 | commonval :: (Eq a) => [a] -> Maybe a | ||
72 | commonval [] = Nothing | ||
73 | commonval [a] = Just a | ||
74 | commonval (a:b:xs) = if a==b then commonval (b:xs) else Nothing | ||
75 | |||
76 | |||
77 | toLists m = partit (cols m) . toList . cdat $ m | ||
78 | |||
79 | dsp as = (++" ]") . (" ["++) . init . drop 2 . unlines . map (" , "++) . map unwords' $ transpose mtp | 64 | dsp as = (++" ]") . (" ["++) . init . drop 2 . unlines . map (" , "++) . map unwords' $ transpose mtp |
80 | where | 65 | where |
81 | mt = transpose as | 66 | mt = transpose as |
@@ -146,62 +131,6 @@ transdata c1 d c2 | isReal baseOf d = scast $ transdataR c1 (scast d) c2 | |||
146 | --{-# RULES "transdataR" transdata=transdataR #-} | 131 | --{-# RULES "transdataR" transdata=transdataR #-} |
147 | --{-# RULES "transdataC" transdata=transdataC #-} | 132 | --{-# RULES "transdataC" transdata=transdataC #-} |
148 | 133 | ||
149 | ----------------------------------------------------------------------------- | ||
150 | |||
151 | -- | creates a Matrix from a list of vectors | ||
152 | fromRows :: Field t => [Vector t] -> Matrix t | ||
153 | fromRows vs = case common dim vs of | ||
154 | Nothing -> error "fromRows applied to [] or to vectors with different sizes" | ||
155 | Just c -> reshape c (join vs) | ||
156 | |||
157 | -- | extracts the rows of a matrix as a list of vectors | ||
158 | toRows :: Storable t => Matrix t -> [Vector t] | ||
159 | toRows m = toRows' 0 where | ||
160 | v = cdat m | ||
161 | r = rows m | ||
162 | c = cols m | ||
163 | toRows' k | k == r*c = [] | ||
164 | | otherwise = subVector k c v : toRows' (k+c) | ||
165 | |||
166 | -- | Creates a matrix from a list of vectors, as columns | ||
167 | fromColumns :: Field t => [Vector t] -> Matrix t | ||
168 | fromColumns m = trans . fromRows $ m | ||
169 | |||
170 | -- | Creates a list of vectors from the columns of a matrix | ||
171 | toColumns :: Field t => Matrix t -> [Vector t] | ||
172 | toColumns m = toRows . trans $ m | ||
173 | |||
174 | -- | creates a matrix from a vertical list of matrices | ||
175 | joinVert :: Field t => [Matrix t] -> Matrix t | ||
176 | joinVert ms = case common cols ms of | ||
177 | Nothing -> error "joinVert on matrices with different number of columns" | ||
178 | Just c -> reshape c $ join (map cdat ms) | ||
179 | |||
180 | -- | creates a matrix from a horizontal list of matrices | ||
181 | joinHoriz :: Field t => [Matrix t] -> Matrix t | ||
182 | joinHoriz ms = trans. joinVert . map trans $ ms | ||
183 | |||
184 | -- | creates a complex vector from vectors with real and imaginary parts | ||
185 | toComplex :: (Vector Double, Vector Double) -> Vector (Complex Double) | ||
186 | toComplex (r,i) = asComplex $ cdat $ fromColumns [r,i] | ||
187 | |||
188 | -- | obtains the complex conjugate of a complex vector | ||
189 | conj :: Vector (Complex Double) -> Vector (Complex Double) | ||
190 | conj v = asComplex $ cdat $ reshape 2 (asReal v) `mulC` diag (fromList [1,-1]) | ||
191 | where mulC = multiply RowMajor | ||
192 | |||
193 | comp v = toComplex (v,constant (dim v) 0) | ||
194 | |||
195 | ------------------------------------------------------------------------------ | ||
196 | |||
197 | -- | Reverse rows | ||
198 | flipud :: Field t => Matrix t -> Matrix t | ||
199 | flipud m = fromRows . reverse . toRows $ m | ||
200 | |||
201 | -- | Reverse columns | ||
202 | fliprl :: Field t => Matrix t -> Matrix t | ||
203 | fliprl m = fromColumns . reverse . toColumns $ m | ||
204 | |||
205 | ----------------------------------------------------------------- | 134 | ----------------------------------------------------------------- |
206 | 135 | ||
207 | liftMatrix f m = m { dat = f (dat m), tdat = f (tdat m) } -- check sizes | 136 | liftMatrix f m = m { dat = f (dat m), tdat = f (tdat m) } -- check sizes |
@@ -330,13 +259,25 @@ diagG v = reshape c $ fromList $ [ l!!(i-1) * delta k i | k <- [1..c], i <- [1.. | |||
330 | delta i j | i==j = 1 | 259 | delta i j | i==j = 1 |
331 | | otherwise = 0 | 260 | | otherwise = 0 |
332 | 261 | ||
333 | diagRect s r c | 262 | -- | creates a Matrix from a list of vectors |
334 | | dim s < min r c = error "diagRect" | 263 | fromRows :: Field t => [Vector t] -> Matrix t |
335 | | r == c = diag s | 264 | fromRows vs = case common dim vs of |
336 | | r < c = trans $ diagRect s c r | 265 | Nothing -> error "fromRows applied to [] or to vectors with different sizes" |
337 | | r > c = joinVert [diag s , zeros (r-c,c)] | 266 | Just c -> reshape c (join vs) |
338 | where zeros (r,c) = reshape c $ constant (r*c) 0 | ||
339 | 267 | ||
340 | takeDiag m = fromList [cdat m `at` (k*cols m+k) | k <- [0 .. min (rows m) (cols m) -1]] | 268 | -- | extracts the rows of a matrix as a list of vectors |
269 | toRows :: Storable t => Matrix t -> [Vector t] | ||
270 | toRows m = toRows' 0 where | ||
271 | v = cdat m | ||
272 | r = rows m | ||
273 | c = cols m | ||
274 | toRows' k | k == r*c = [] | ||
275 | | otherwise = subVector k c v : toRows' (k+c) | ||
341 | 276 | ||
342 | ident n = diag (constant n 1) | 277 | -- | Creates a matrix from a list of vectors, as columns |
278 | fromColumns :: Field t => [Vector t] -> Matrix t | ||
279 | fromColumns m = trans . fromRows $ m | ||
280 | |||
281 | -- | Creates a list of vectors from the columns of a matrix | ||
282 | toColumns :: Field t => Matrix t -> [Vector t] | ||
283 | toColumns m = toRows . trans $ m | ||