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 | |
parent | 8c5be977858723aac8b8f47f57ce98d82fe249b4 (diff) |
refactoring
Diffstat (limited to 'lib/Data')
-rw-r--r-- | lib/Data/Packed/Internal/Common.hs | 84 | ||||
-rw-r--r-- | lib/Data/Packed/Internal/Matrix.hs | 109 | ||||
-rw-r--r-- | lib/Data/Packed/Internal/Tensor.hs | 12 | ||||
-rw-r--r-- | lib/Data/Packed/Internal/Vector.hs | 62 | ||||
-rw-r--r-- | lib/Data/Packed/Matrix.hs | 72 | ||||
-rw-r--r-- | lib/Data/Packed/Vector.hs | 41 |
6 files changed, 235 insertions, 145 deletions
diff --git a/lib/Data/Packed/Internal/Common.hs b/lib/Data/Packed/Internal/Common.hs new file mode 100644 index 0000000..dddd269 --- /dev/null +++ b/lib/Data/Packed/Internal/Common.hs | |||
@@ -0,0 +1,84 @@ | |||
1 | {-# OPTIONS_GHC -fglasgow-exts -fallow-undecidable-instances #-} | ||
2 | ----------------------------------------------------------------------------- | ||
3 | -- | | ||
4 | -- Module : Data.Packed.Internal.Common | ||
5 | -- Copyright : (c) Alberto Ruiz 2007 | ||
6 | -- License : GPL-style | ||
7 | -- | ||
8 | -- Maintainer : Alberto Ruiz <aruiz@um.es> | ||
9 | -- Stability : provisional | ||
10 | -- Portability : portable (uses FFI) | ||
11 | -- | ||
12 | -- Common tools | ||
13 | -- | ||
14 | ----------------------------------------------------------------------------- | ||
15 | |||
16 | module Data.Packed.Internal.Common where | ||
17 | |||
18 | import Foreign | ||
19 | import Complex | ||
20 | import Control.Monad(when) | ||
21 | import Debug.Trace | ||
22 | import Data.List(transpose,intersperse) | ||
23 | import Data.Typeable | ||
24 | import Data.Maybe(fromJust) | ||
25 | |||
26 | debug x = trace (show x) x | ||
27 | |||
28 | data Vector t = V { dim :: Int | ||
29 | , fptr :: ForeignPtr t | ||
30 | , ptr :: Ptr t | ||
31 | } deriving Typeable | ||
32 | |||
33 | ---------------------------------------------------------------------- | ||
34 | instance (Storable a, RealFloat a) => Storable (Complex a) where -- | ||
35 | alignment x = alignment (realPart x) -- | ||
36 | sizeOf x = 2 * sizeOf (realPart x) -- | ||
37 | peek p = do -- | ||
38 | [re,im] <- peekArray 2 (castPtr p) -- | ||
39 | return (re :+ im) -- | ||
40 | poke p (a :+ b) = pokeArray (castPtr p) [a,b] -- | ||
41 | ---------------------------------------------------------------------- | ||
42 | |||
43 | on f g = \x y -> f (g x) (g y) | ||
44 | |||
45 | partit :: Int -> [a] -> [[a]] | ||
46 | partit _ [] = [] | ||
47 | partit n l = take n l : partit n (drop n l) | ||
48 | |||
49 | -- | obtains the common value of a property of a list | ||
50 | common :: (Eq a) => (b->a) -> [b] -> Maybe a | ||
51 | common f = commonval . map f where | ||
52 | commonval :: (Eq a) => [a] -> Maybe a | ||
53 | commonval [] = Nothing | ||
54 | commonval [a] = Just a | ||
55 | commonval (a:b:xs) = if a==b then commonval (b:xs) else Nothing | ||
56 | |||
57 | xor a b = a && not b || b && not a | ||
58 | |||
59 | (//) :: x -> (x -> y) -> y | ||
60 | infixl 0 // | ||
61 | (//) = flip ($) | ||
62 | |||
63 | errorCode 1000 = "bad size" | ||
64 | errorCode 1001 = "bad function code" | ||
65 | errorCode 1002 = "memory problem" | ||
66 | errorCode 1003 = "bad file" | ||
67 | errorCode 1004 = "singular" | ||
68 | errorCode 1005 = "didn't converge" | ||
69 | errorCode n = "code "++show n | ||
70 | |||
71 | check msg ls f = do | ||
72 | err <- f | ||
73 | when (err/=0) (error (msg++": "++errorCode err)) | ||
74 | mapM_ (touchForeignPtr . fptr) ls | ||
75 | return () | ||
76 | |||
77 | class (Storable a, Typeable a) => Field a where | ||
78 | instance (Storable a, Typeable a) => Field a where | ||
79 | |||
80 | isReal w x = typeOf (undefined :: Double) == typeOf (w x) | ||
81 | isComp w x = typeOf (undefined :: Complex Double) == typeOf (w x) | ||
82 | |||
83 | scast :: forall a . forall b . (Typeable a, Typeable b) => a -> b | ||
84 | scast = fromJust . cast | ||
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 | ||
diff --git a/lib/Data/Packed/Internal/Tensor.hs b/lib/Data/Packed/Internal/Tensor.hs index 67dcb09..123270d 100644 --- a/lib/Data/Packed/Internal/Tensor.hs +++ b/lib/Data/Packed/Internal/Tensor.hs | |||
@@ -1,4 +1,3 @@ | |||
1 | --{-# OPTIONS_GHC -fglasgow-exts -fallow-undecidable-instances #-} | ||
2 | ----------------------------------------------------------------------------- | 1 | ----------------------------------------------------------------------------- |
3 | -- | | 2 | -- | |
4 | -- Module : Data.Packed.Internal.Tensor | 3 | -- Module : Data.Packed.Internal.Tensor |
@@ -9,15 +8,17 @@ | |||
9 | -- Stability : provisional | 8 | -- Stability : provisional |
10 | -- Portability : portable (uses FFI) | 9 | -- Portability : portable (uses FFI) |
11 | -- | 10 | -- |
12 | -- Fundamental types | 11 | -- basic tensor operations |
13 | -- | 12 | -- |
14 | ----------------------------------------------------------------------------- | 13 | ----------------------------------------------------------------------------- |
15 | 14 | ||
16 | module Data.Packed.Internal.Tensor where | 15 | module Data.Packed.Internal.Tensor where |
17 | 16 | ||
17 | import Data.Packed.Internal | ||
18 | import Data.Packed.Internal.Vector | 18 | import Data.Packed.Internal.Vector |
19 | import Data.Packed.Internal.Matrix | 19 | import Data.Packed.Internal.Matrix |
20 | import Foreign.Storable | 20 | import Foreign.Storable |
21 | import Data.List(sort) | ||
21 | 22 | ||
22 | data IdxTp = Covariant | Contravariant deriving (Show,Eq) | 23 | data IdxTp = Covariant | Contravariant deriving (Show,Eq) |
23 | 24 | ||
@@ -99,3 +100,10 @@ compatIdxAux (n1,(t1,_)) (n2, (t2,_)) = t1 /= t2 && n1 == n2 | |||
99 | compatIdx t1 n1 t2 n2 = compatIdxAux d1 d2 where | 100 | compatIdx t1 n1 t2 n2 = compatIdxAux d1 d2 where |
100 | d1 = head $ snd $ fst $ findIdx n1 t1 | 101 | d1 = head $ snd $ fst $ findIdx n1 t1 |
101 | d2 = head $ snd $ fst $ findIdx n2 t2 | 102 | d2 = head $ snd $ fst $ findIdx n2 t2 |
103 | |||
104 | names t = sort $ map (snd.snd) (dims t) | ||
105 | |||
106 | normal t = tridx (names t) t | ||
107 | |||
108 | contractions t1 t2 = [ contraction t1 n1 t2 n2 | n1 <- names t1, n2 <- names t2, compatIdx t1 n1 t2 n2 ] | ||
109 | |||
diff --git a/lib/Data/Packed/Internal/Vector.hs b/lib/Data/Packed/Internal/Vector.hs index 4836bdb..125df1e 100644 --- a/lib/Data/Packed/Internal/Vector.hs +++ b/lib/Data/Packed/Internal/Vector.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.Vector | 4 | -- Module : Data.Packed.Internal.Vector |
@@ -9,70 +9,16 @@ | |||
9 | -- Stability : provisional | 9 | -- Stability : provisional |
10 | -- Portability : portable (uses FFI) | 10 | -- Portability : portable (uses FFI) |
11 | -- | 11 | -- |
12 | -- Fundamental types | 12 | -- Vector implementation |
13 | -- | 13 | -- |
14 | ----------------------------------------------------------------------------- | 14 | ----------------------------------------------------------------------------- |
15 | 15 | ||
16 | module Data.Packed.Internal.Vector where | 16 | module Data.Packed.Internal.Vector where |
17 | 17 | ||
18 | import Data.Packed.Internal.Common | ||
18 | import Foreign | 19 | import Foreign |
19 | import Complex | 20 | import Complex |
20 | import Control.Monad(when) | 21 | import Control.Monad(when) |
21 | import Debug.Trace | ||
22 | import Data.List(transpose,intersperse) | ||
23 | import Data.Typeable | ||
24 | import Data.Maybe(fromJust) | ||
25 | |||
26 | debug x = trace (show x) x | ||
27 | |||
28 | ---------------------------------------------------------------------- | ||
29 | instance (Storable a, RealFloat a) => Storable (Complex a) where -- | ||
30 | alignment x = alignment (realPart x) -- | ||
31 | sizeOf x = 2 * sizeOf (realPart x) -- | ||
32 | peek p = do -- | ||
33 | [re,im] <- peekArray 2 (castPtr p) -- | ||
34 | return (re :+ im) -- | ||
35 | poke p (a :+ b) = pokeArray (castPtr p) [a,b] -- | ||
36 | ---------------------------------------------------------------------- | ||
37 | |||
38 | on f g = \x y -> f (g x) (g y) | ||
39 | |||
40 | (//) :: x -> (x -> y) -> y | ||
41 | infixl 0 // | ||
42 | (//) = flip ($) | ||
43 | |||
44 | errorCode 1000 = "bad size" | ||
45 | errorCode 1001 = "bad function code" | ||
46 | errorCode 1002 = "memory problem" | ||
47 | errorCode 1003 = "bad file" | ||
48 | errorCode 1004 = "singular" | ||
49 | errorCode 1005 = "didn't converge" | ||
50 | errorCode n = "code "++show n | ||
51 | |||
52 | check msg ls f = do | ||
53 | err <- f | ||
54 | when (err/=0) (error (msg++": "++errorCode err)) | ||
55 | mapM_ (touchForeignPtr . fptr) ls | ||
56 | return () | ||
57 | |||
58 | class (Storable a, Typeable a) => Field a where | ||
59 | instance (Storable a, Typeable a) => Field a where | ||
60 | |||
61 | isReal w x = typeOf (undefined :: Double) == typeOf (w x) | ||
62 | isComp w x = typeOf (undefined :: Complex Double) == typeOf (w x) | ||
63 | baseOf v = (v `at` 0) | ||
64 | |||
65 | scast :: forall a . forall b . (Typeable a, Typeable b) => a -> b | ||
66 | scast = fromJust . cast | ||
67 | |||
68 | |||
69 | |||
70 | ---------------------------------------------------------------------- | ||
71 | |||
72 | data Vector t = V { dim :: Int | ||
73 | , fptr :: ForeignPtr t | ||
74 | , ptr :: Ptr t | ||
75 | } deriving Typeable | ||
76 | 22 | ||
77 | type Vc t s = Int -> Ptr t -> s | 23 | type Vc t s = Int -> Ptr t -> s |
78 | infixr 5 :> | 24 | infixr 5 :> |
@@ -81,6 +27,8 @@ type t :> s = Vc t s | |||
81 | vec :: Vector t -> (Vc t s) -> s | 27 | vec :: Vector t -> (Vc t s) -> s |
82 | vec v f = f (dim v) (ptr v) | 28 | vec v f = f (dim v) (ptr v) |
83 | 29 | ||
30 | baseOf v = (v `at` 0) | ||
31 | |||
84 | createVector :: Storable a => Int -> IO (Vector a) | 32 | createVector :: Storable a => Int -> IO (Vector a) |
85 | createVector n = do | 33 | createVector n = do |
86 | when (n <= 0) $ error ("trying to createVector of dim "++show n) | 34 | when (n <= 0) $ error ("trying to createVector of dim "++show n) |
diff --git a/lib/Data/Packed/Matrix.hs b/lib/Data/Packed/Matrix.hs index 8d1c8b6..6ea76c0 100644 --- a/lib/Data/Packed/Matrix.hs +++ b/lib/Data/Packed/Matrix.hs | |||
@@ -1 +1,71 @@ | |||
1 | 1 | ----------------------------------------------------------------------------- | |
2 | -- | | ||
3 | -- Module : Data.Packed.Matrix | ||
4 | -- Copyright : (c) Alberto Ruiz 2007 | ||
5 | -- License : GPL-style | ||
6 | -- | ||
7 | -- Maintainer : Alberto Ruiz <aruiz@um.es> | ||
8 | -- Stability : provisional | ||
9 | -- Portability : portable | ||
10 | -- | ||
11 | -- Matrices | ||
12 | -- | ||
13 | ----------------------------------------------------------------------------- | ||
14 | |||
15 | module Data.Packed.Matrix ( | ||
16 | Matrix(rows,cols), Field, | ||
17 | toLists, (><), (>|<), | ||
18 | trans, | ||
19 | reshape, | ||
20 | fromRows, toRows, fromColumns, toColumns, | ||
21 | joinVert, joinHoriz, | ||
22 | flipud, fliprl, | ||
23 | liftMatrix, liftMatrix2, | ||
24 | multiply, | ||
25 | subMatrix, diag, takeDiag, diagRect, ident | ||
26 | ) where | ||
27 | |||
28 | import Data.Packed.Internal | ||
29 | |||
30 | -- | creates a matrix from a vertical list of matrices | ||
31 | joinVert :: Field t => [Matrix t] -> Matrix t | ||
32 | joinVert ms = case common cols ms of | ||
33 | Nothing -> error "joinVert on matrices with different number of columns" | ||
34 | Just c -> reshape c $ join (map cdat ms) | ||
35 | |||
36 | -- | creates a matrix from a horizontal list of matrices | ||
37 | joinHoriz :: Field t => [Matrix t] -> Matrix t | ||
38 | joinHoriz ms = trans. joinVert . map trans $ ms | ||
39 | |||
40 | -- | Reverse rows | ||
41 | flipud :: Field t => Matrix t -> Matrix t | ||
42 | flipud m = fromRows . reverse . toRows $ m | ||
43 | |||
44 | -- | Reverse columns | ||
45 | fliprl :: Field t => Matrix t -> Matrix t | ||
46 | fliprl m = fromColumns . reverse . toColumns $ m | ||
47 | |||
48 | ------------------------------------------------------------ | ||
49 | |||
50 | diagRect s r c | ||
51 | | dim s < min r c = error "diagRect" | ||
52 | | r == c = diag s | ||
53 | | r < c = trans $ diagRect s c r | ||
54 | | r > c = joinVert [diag s , zeros (r-c,c)] | ||
55 | where zeros (r,c) = reshape c $ constant (r*c) 0 | ||
56 | |||
57 | takeDiag m = fromList [cdat m `at` (k*cols m+k) | k <- [0 .. min (rows m) (cols m) -1]] | ||
58 | |||
59 | ident n = diag (constant n 1) | ||
60 | |||
61 | r >< c = f where | ||
62 | f l | dim v == r*c = matrixFromVector RowMajor c v | ||
63 | | otherwise = error $ "inconsistent list size = " | ||
64 | ++show (dim v) ++"in ("++show r++"><"++show c++")" | ||
65 | where v = fromList l | ||
66 | |||
67 | r >|< c = f where | ||
68 | f l | dim v == r*c = matrixFromVector ColumnMajor c v | ||
69 | | otherwise = error $ "inconsistent list size = " | ||
70 | ++show (dim v) ++"in ("++show r++"><"++show c++")" | ||
71 | where v = fromList l | ||
diff --git a/lib/Data/Packed/Vector.hs b/lib/Data/Packed/Vector.hs index 8d1c8b6..992301a 100644 --- a/lib/Data/Packed/Vector.hs +++ b/lib/Data/Packed/Vector.hs | |||
@@ -1 +1,40 @@ | |||
1 | 1 | ----------------------------------------------------------------------------- | |
2 | -- | | ||
3 | -- Module : Data.Packed.Vector | ||
4 | -- Copyright : (c) Alberto Ruiz 2007 | ||
5 | -- License : GPL-style | ||
6 | -- | ||
7 | -- Maintainer : Alberto Ruiz <aruiz@um.es> | ||
8 | -- Stability : provisional | ||
9 | -- Portability : portable | ||
10 | -- | ||
11 | -- Vectors | ||
12 | -- | ||
13 | ----------------------------------------------------------------------------- | ||
14 | |||
15 | module Data.Packed.Vector ( | ||
16 | Vector(dim), Field, | ||
17 | fromList, toList, | ||
18 | at, | ||
19 | subVector, join, | ||
20 | constant, | ||
21 | toComplex, comp, | ||
22 | conj, | ||
23 | dot | ||
24 | ) where | ||
25 | |||
26 | import Data.Packed.Internal | ||
27 | import Complex | ||
28 | |||
29 | -- | creates a complex vector from vectors with real and imaginary parts | ||
30 | toComplex :: (Vector Double, Vector Double) -> Vector (Complex Double) | ||
31 | toComplex (r,i) = asComplex $ cdat $ fromColumns [r,i] | ||
32 | |||
33 | -- | obtains the complex conjugate of a complex vector | ||
34 | conj :: Vector (Complex Double) -> Vector (Complex Double) | ||
35 | conj v = asComplex $ cdat $ reshape 2 (asReal v) `mulC` diag (fromList [1,-1]) | ||
36 | where mulC = multiply RowMajor | ||
37 | |||
38 | comp v = toComplex (v,constant (dim v) 0) | ||
39 | |||
40 | |||