diff options
-rw-r--r-- | hmatrix.cabal | 4 | ||||
-rw-r--r-- | lib/Data/Packed.hs | 1 | ||||
-rw-r--r-- | lib/Data/Packed/Matrix.hs | 181 | ||||
-rw-r--r-- | lib/Data/Packed/Random.hs | 2 | ||||
-rw-r--r-- | lib/Graphics/Plot.hs | 4 | ||||
-rw-r--r-- | lib/Numeric/Container.hs | 219 | ||||
-rw-r--r-- | lib/Numeric/LinearAlgebra.hs | 2 | ||||
-rw-r--r-- | lib/Numeric/LinearAlgebra/Algorithms.hs | 2 | ||||
-rw-r--r-- | lib/Numeric/LinearAlgebra/Interface.hs | 4 | ||||
-rw-r--r-- | lib/Numeric/LinearAlgebra/LAPACK.hs | 1 | ||||
-rw-r--r-- | lib/Numeric/LinearAlgebra/Linear.hs | 143 | ||||
-rw-r--r-- | lib/Numeric/LinearAlgebra/Tests.hs | 1 | ||||
-rw-r--r-- | lib/Numeric/Matrix.hs | 97 | ||||
-rw-r--r-- | lib/Numeric/Vector.hs | 317 |
14 files changed, 685 insertions, 293 deletions
diff --git a/hmatrix.cabal b/hmatrix.cabal index 146cf1a..736c443 100644 --- a/hmatrix.cabal +++ b/hmatrix.cabal | |||
@@ -95,11 +95,13 @@ library | |||
95 | Numeric.GSL.ODE, | 95 | Numeric.GSL.ODE, |
96 | Numeric.GSL.Vector, | 96 | Numeric.GSL.Vector, |
97 | Numeric.GSL, | 97 | Numeric.GSL, |
98 | Numeric.Vector, | ||
99 | Numeric.Matrix, | ||
100 | Numeric.Container, | ||
98 | Numeric.LinearAlgebra, | 101 | Numeric.LinearAlgebra, |
99 | Numeric.LinearAlgebra.LAPACK, | 102 | Numeric.LinearAlgebra.LAPACK, |
100 | Numeric.LinearAlgebra.Interface, | 103 | Numeric.LinearAlgebra.Interface, |
101 | Numeric.LinearAlgebra.Linear, | 104 | Numeric.LinearAlgebra.Linear, |
102 | Numeric.LinearAlgebra.Instances, | ||
103 | Numeric.LinearAlgebra.Algorithms, | 105 | Numeric.LinearAlgebra.Algorithms, |
104 | Graphics.Plot, | 106 | Graphics.Plot, |
105 | -- Data.Packed.Convert, | 107 | -- Data.Packed.Convert, |
diff --git a/lib/Data/Packed.hs b/lib/Data/Packed.hs index 50a5eb6..8128667 100644 --- a/lib/Data/Packed.hs +++ b/lib/Data/Packed.hs | |||
@@ -24,4 +24,3 @@ import Data.Packed.Vector | |||
24 | import Data.Packed.Matrix | 24 | import Data.Packed.Matrix |
25 | import Data.Packed.Random | 25 | import Data.Packed.Random |
26 | import Data.Complex | 26 | import Data.Complex |
27 | import Numeric.LinearAlgebra.Instances() | ||
diff --git a/lib/Data/Packed/Matrix.hs b/lib/Data/Packed/Matrix.hs index 2855a90..07258f8 100644 --- a/lib/Data/Packed/Matrix.hs +++ b/lib/Data/Packed/Matrix.hs | |||
@@ -19,10 +19,7 @@ | |||
19 | ----------------------------------------------------------------------------- | 19 | ----------------------------------------------------------------------------- |
20 | 20 | ||
21 | module Data.Packed.Matrix ( | 21 | module Data.Packed.Matrix ( |
22 | Element, RealElement, Container(..), | 22 | Element(..), |
23 | Convert(..), RealOf, ComplexOf, SingleOf, DoubleOf, ElementOf, | ||
24 | Precision(..), comp, | ||
25 | AutoReal(..), | ||
26 | Matrix,rows,cols, | 23 | Matrix,rows,cols, |
27 | (><), | 24 | (><), |
28 | trans, | 25 | trans, |
@@ -55,7 +52,7 @@ import Data.Complex | |||
55 | import Data.Binary | 52 | import Data.Binary |
56 | import Foreign.Storable | 53 | import Foreign.Storable |
57 | import Control.Monad(replicateM) | 54 | import Control.Monad(replicateM) |
58 | import Control.Arrow((***)) | 55 | --import Control.Arrow((***)) |
59 | --import GHC.Float(double2Float,float2Double) | 56 | --import GHC.Float(double2Float,float2Double) |
60 | 57 | ||
61 | ------------------------------------------------------------------- | 58 | ------------------------------------------------------------------- |
@@ -75,6 +72,33 @@ instance (Binary a, Element a, Storable a) => Binary (Matrix a) where | |||
75 | 72 | ||
76 | ------------------------------------------------------------------- | 73 | ------------------------------------------------------------------- |
77 | 74 | ||
75 | instance (Show a, Element a) => (Show (Matrix a)) where | ||
76 | show m = (sizes++) . dsp . map (map show) . toLists $ m | ||
77 | where sizes = "("++show (rows m)++"><"++show (cols m)++")\n" | ||
78 | |||
79 | dsp as = (++" ]") . (" ["++) . init . drop 2 . unlines . map (" , "++) . map unwords' $ transpose mtp | ||
80 | where | ||
81 | mt = transpose as | ||
82 | longs = map (maximum . map length) mt | ||
83 | mtp = zipWith (\a b -> map (pad a) b) longs mt | ||
84 | pad n str = replicate (n - length str) ' ' ++ str | ||
85 | unwords' = concat . intersperse ", " | ||
86 | |||
87 | ------------------------------------------------------------------ | ||
88 | |||
89 | instance (Element a, Read a) => Read (Matrix a) where | ||
90 | readsPrec _ s = [((rs><cs) . read $ listnums, rest)] | ||
91 | where (thing,rest) = breakAt ']' s | ||
92 | (dims,listnums) = breakAt ')' thing | ||
93 | cs = read . init . fst. breakAt ')' . snd . breakAt '<' $ dims | ||
94 | rs = read . snd . breakAt '(' .init . fst . breakAt '>' $ dims | ||
95 | |||
96 | |||
97 | breakAt c l = (a++[c],tail b) where | ||
98 | (a,b) = break (==c) l | ||
99 | |||
100 | ------------------------------------------------------------------ | ||
101 | |||
78 | -- | creates a matrix from a vertical list of matrices | 102 | -- | creates a matrix from a vertical list of matrices |
79 | joinVert :: Element t => [Matrix t] -> Matrix t | 103 | joinVert :: Element t => [Matrix t] -> Matrix t |
80 | joinVert ms = case common cols ms of | 104 | joinVert ms = case common cols ms of |
@@ -470,150 +494,3 @@ toBlocksEvery r c m = toBlocks rs cs m where | |||
470 | cs = replicate qc c ++ if rc > 0 then [rc] else [] | 494 | cs = replicate qc c ++ if rc > 0 then [rc] else [] |
471 | 495 | ||
472 | ------------------------------------------------------------------- | 496 | ------------------------------------------------------------------- |
473 | |||
474 | -- | Supported single-double precision type pairs | ||
475 | class (Element s, Element d) => Precision s d | s -> d, d -> s where | ||
476 | double2FloatG :: Vector d -> Vector s | ||
477 | float2DoubleG :: Vector s -> Vector d | ||
478 | |||
479 | instance Precision Float Double where | ||
480 | double2FloatG = double2FloatV | ||
481 | float2DoubleG = float2DoubleV | ||
482 | |||
483 | instance Precision (Complex Float) (Complex Double) where | ||
484 | double2FloatG = asComplex . double2FloatV . asReal | ||
485 | float2DoubleG = asComplex . float2DoubleV . asReal | ||
486 | |||
487 | -- | Supported real types | ||
488 | class (Element t, Element (Complex t), RealFloat t | ||
489 | -- , RealOf t ~ t, RealOf (Complex t) ~ t | ||
490 | ) | ||
491 | => RealElement t | ||
492 | |||
493 | instance RealElement Double | ||
494 | |||
495 | instance RealElement Float | ||
496 | |||
497 | -- | Conversion utilities | ||
498 | class Container c where | ||
499 | toComplex :: (RealElement e) => (c e, c e) -> c (Complex e) | ||
500 | fromComplex :: (RealElement e) => c (Complex e) -> (c e, c e) | ||
501 | complex' :: (RealElement e) => c e -> c (Complex e) | ||
502 | conj :: (RealElement e) => c (Complex e) -> c (Complex e) | ||
503 | cmap :: (Element a, Element b) => (a -> b) -> c a -> c b | ||
504 | single' :: Precision a b => c b -> c a | ||
505 | double' :: Precision a b => c a -> c b | ||
506 | |||
507 | comp x = complex' x | ||
508 | |||
509 | instance Container Vector where | ||
510 | toComplex = toComplexV | ||
511 | fromComplex = fromComplexV | ||
512 | complex' v = toComplex (v,constantD 0 (dim v)) | ||
513 | conj = conjV | ||
514 | cmap = mapVector | ||
515 | single' = double2FloatG | ||
516 | double' = float2DoubleG | ||
517 | |||
518 | instance Container Matrix where | ||
519 | toComplex = uncurry $ liftMatrix2 $ curry toComplex | ||
520 | fromComplex z = (reshape c *** reshape c) . fromComplex . flatten $ z | ||
521 | where c = cols z | ||
522 | complex' = liftMatrix complex' | ||
523 | conj = liftMatrix conj | ||
524 | cmap f = liftMatrix (cmap f) | ||
525 | single' = liftMatrix single' | ||
526 | double' = liftMatrix double' | ||
527 | |||
528 | ------------------------------------------------------------------- | ||
529 | |||
530 | type family RealOf x | ||
531 | |||
532 | type instance RealOf Double = Double | ||
533 | type instance RealOf (Complex Double) = Double | ||
534 | |||
535 | type instance RealOf Float = Float | ||
536 | type instance RealOf (Complex Float) = Float | ||
537 | |||
538 | type family ComplexOf x | ||
539 | |||
540 | type instance ComplexOf Double = Complex Double | ||
541 | type instance ComplexOf (Complex Double) = Complex Double | ||
542 | |||
543 | type instance ComplexOf Float = Complex Float | ||
544 | type instance ComplexOf (Complex Float) = Complex Float | ||
545 | |||
546 | type family SingleOf x | ||
547 | |||
548 | type instance SingleOf Double = Float | ||
549 | type instance SingleOf Float = Float | ||
550 | |||
551 | type instance SingleOf (Complex a) = Complex (SingleOf a) | ||
552 | |||
553 | type family DoubleOf x | ||
554 | |||
555 | type instance DoubleOf Double = Double | ||
556 | type instance DoubleOf Float = Double | ||
557 | |||
558 | type instance DoubleOf (Complex a) = Complex (DoubleOf a) | ||
559 | |||
560 | type family ElementOf c | ||
561 | |||
562 | type instance ElementOf (Vector a) = a | ||
563 | type instance ElementOf (Matrix a) = a | ||
564 | |||
565 | ------------------------------------------------------------------- | ||
566 | |||
567 | -- | generic conversion functions | ||
568 | class Convert t where | ||
569 | real :: Container c => c (RealOf t) -> c t | ||
570 | complex :: Container c => c t -> c (ComplexOf t) | ||
571 | single :: Container c => c t -> c (SingleOf t) | ||
572 | double :: Container c => c t -> c (DoubleOf t) | ||
573 | |||
574 | instance Convert Double where | ||
575 | real = id | ||
576 | complex = complex' | ||
577 | single = single' | ||
578 | double = id | ||
579 | |||
580 | instance Convert Float where | ||
581 | real = id | ||
582 | complex = complex' | ||
583 | single = id | ||
584 | double = double' | ||
585 | |||
586 | instance Convert (Complex Double) where | ||
587 | real = complex' | ||
588 | complex = id | ||
589 | single = single' | ||
590 | double = id | ||
591 | |||
592 | instance Convert (Complex Float) where | ||
593 | real = complex' | ||
594 | complex = id | ||
595 | single = id | ||
596 | double = double' | ||
597 | |||
598 | ------------------------------------------------------------------- | ||
599 | |||
600 | -- | to be replaced by Convert | ||
601 | class Convert t => AutoReal t where | ||
602 | real'' :: Container c => c Double -> c t | ||
603 | complex'' :: Container c => c t -> c (Complex Double) | ||
604 | |||
605 | instance AutoReal Double where | ||
606 | real'' = real | ||
607 | complex'' = complex | ||
608 | |||
609 | instance AutoReal (Complex Double) where | ||
610 | real'' = real | ||
611 | complex'' = complex | ||
612 | |||
613 | instance AutoReal Float where | ||
614 | real'' = real . single | ||
615 | complex'' = double . complex | ||
616 | |||
617 | instance AutoReal (Complex Float) where | ||
618 | real'' = real . single | ||
619 | complex'' = double . complex | ||
diff --git a/lib/Data/Packed/Random.hs b/lib/Data/Packed/Random.hs index 33a11d7..579d13c 100644 --- a/lib/Data/Packed/Random.hs +++ b/lib/Data/Packed/Random.hs | |||
@@ -22,8 +22,8 @@ module Data.Packed.Random ( | |||
22 | import Numeric.GSL.Vector | 22 | import Numeric.GSL.Vector |
23 | import Data.Packed.Matrix | 23 | import Data.Packed.Matrix |
24 | import Data.Packed.Vector | 24 | import Data.Packed.Vector |
25 | import Numeric.LinearAlgebra.Algorithms | ||
26 | import Numeric.LinearAlgebra.Linear | 25 | import Numeric.LinearAlgebra.Linear |
26 | import Numeric.LinearAlgebra.Algorithms | ||
27 | 27 | ||
28 | -- | Obtains a matrix whose rows are pseudorandom samples from a multivariate | 28 | -- | Obtains a matrix whose rows are pseudorandom samples from a multivariate |
29 | -- Gaussian distribution. | 29 | -- Gaussian distribution. |
diff --git a/lib/Graphics/Plot.hs b/lib/Graphics/Plot.hs index 2dc0553..478b4ad 100644 --- a/lib/Graphics/Plot.hs +++ b/lib/Graphics/Plot.hs | |||
@@ -150,8 +150,8 @@ matrixToPGM m = header ++ unlines (map unwords ll) where | |||
150 | r = rows m | 150 | r = rows m |
151 | header = "P2 "++show c++" "++show r++" "++show (round maxgray :: Int)++"\n" | 151 | header = "P2 "++show c++" "++show r++" "++show (round maxgray :: Int)++"\n" |
152 | maxgray = 255.0 | 152 | maxgray = 255.0 |
153 | maxval = vectorMax $ flatten $ m | 153 | maxval = maxElement m |
154 | minval = vectorMin $ flatten $ m | 154 | minval = minElement m |
155 | scale' = if (maxval == minval) | 155 | scale' = if (maxval == minval) |
156 | then 0.0 | 156 | then 0.0 |
157 | else maxgray / (maxval - minval) | 157 | else maxgray / (maxval - minval) |
diff --git a/lib/Numeric/Container.hs b/lib/Numeric/Container.hs new file mode 100644 index 0000000..0bec2e8 --- /dev/null +++ b/lib/Numeric/Container.hs | |||
@@ -0,0 +1,219 @@ | |||
1 | {-# LANGUAGE TypeFamilies #-} | ||
2 | {-# LANGUAGE FlexibleContexts #-} | ||
3 | {-# LANGUAGE FlexibleInstances #-} | ||
4 | {-# LANGUAGE MultiParamTypeClasses #-} | ||
5 | {-# LANGUAGE FunctionalDependencies #-} | ||
6 | |||
7 | ----------------------------------------------------------------------------- | ||
8 | -- | | ||
9 | -- Module : Numeric.Container | ||
10 | -- Copyright : (c) Alberto Ruiz 2007 | ||
11 | -- License : GPL-style | ||
12 | -- | ||
13 | -- Maintainer : Alberto Ruiz <aruiz@um.es> | ||
14 | -- Stability : provisional | ||
15 | -- Portability : portable | ||
16 | -- | ||
17 | -- Numeric classes for containers of numbers, including conversion routines | ||
18 | -- | ||
19 | ----------------------------------------------------------------------------- | ||
20 | |||
21 | module Numeric.Container ( | ||
22 | RealElement, AutoReal(..), | ||
23 | Container(..), Linear(..), | ||
24 | Convert(..), RealOf, ComplexOf, SingleOf, DoubleOf, ElementOf, IndexOf, | ||
25 | Precision(..), comp, | ||
26 | module Data.Complex | ||
27 | ) where | ||
28 | |||
29 | import Data.Packed.Vector | ||
30 | import Data.Packed.Matrix | ||
31 | import Data.Packed.Internal.Vector | ||
32 | import Data.Packed.Internal.Matrix | ||
33 | --import qualified Data.Packed.ST as ST | ||
34 | |||
35 | import Control.Arrow((***)) | ||
36 | |||
37 | import Data.Complex | ||
38 | |||
39 | ------------------------------------------------------------------- | ||
40 | |||
41 | -- | Supported single-double precision type pairs | ||
42 | class (Element s, Element d) => Precision s d | s -> d, d -> s where | ||
43 | double2FloatG :: Vector d -> Vector s | ||
44 | float2DoubleG :: Vector s -> Vector d | ||
45 | |||
46 | instance Precision Float Double where | ||
47 | double2FloatG = double2FloatV | ||
48 | float2DoubleG = float2DoubleV | ||
49 | |||
50 | instance Precision (Complex Float) (Complex Double) where | ||
51 | double2FloatG = asComplex . double2FloatV . asReal | ||
52 | float2DoubleG = asComplex . float2DoubleV . asReal | ||
53 | |||
54 | -- | Supported real types | ||
55 | class (Element t, Element (Complex t), RealFloat t | ||
56 | -- , RealOf t ~ t, RealOf (Complex t) ~ t | ||
57 | ) | ||
58 | => RealElement t | ||
59 | |||
60 | instance RealElement Double | ||
61 | |||
62 | instance RealElement Float | ||
63 | |||
64 | -- | Conversion utilities | ||
65 | class Container c where | ||
66 | toComplex :: (RealElement e) => (c e, c e) -> c (Complex e) | ||
67 | fromComplex :: (RealElement e) => c (Complex e) -> (c e, c e) | ||
68 | complex' :: (RealElement e) => c e -> c (Complex e) | ||
69 | conj :: (RealElement e) => c (Complex e) -> c (Complex e) | ||
70 | cmap :: (Element a, Element b) => (a -> b) -> c a -> c b | ||
71 | single' :: Precision a b => c b -> c a | ||
72 | double' :: Precision a b => c a -> c b | ||
73 | |||
74 | comp x = complex' x | ||
75 | |||
76 | instance Container Vector where | ||
77 | toComplex = toComplexV | ||
78 | fromComplex = fromComplexV | ||
79 | complex' v = toComplex (v,constantD 0 (dim v)) | ||
80 | conj = conjV | ||
81 | cmap = mapVector | ||
82 | single' = double2FloatG | ||
83 | double' = float2DoubleG | ||
84 | |||
85 | instance Container Matrix where | ||
86 | toComplex = uncurry $ liftMatrix2 $ curry toComplex | ||
87 | fromComplex z = (reshape c *** reshape c) . fromComplex . flatten $ z | ||
88 | where c = cols z | ||
89 | complex' = liftMatrix complex' | ||
90 | conj = liftMatrix conj | ||
91 | cmap f = liftMatrix (cmap f) | ||
92 | single' = liftMatrix single' | ||
93 | double' = liftMatrix double' | ||
94 | |||
95 | ------------------------------------------------------------------- | ||
96 | |||
97 | type family RealOf x | ||
98 | |||
99 | type instance RealOf Double = Double | ||
100 | type instance RealOf (Complex Double) = Double | ||
101 | |||
102 | type instance RealOf Float = Float | ||
103 | type instance RealOf (Complex Float) = Float | ||
104 | |||
105 | type family ComplexOf x | ||
106 | |||
107 | type instance ComplexOf Double = Complex Double | ||
108 | type instance ComplexOf (Complex Double) = Complex Double | ||
109 | |||
110 | type instance ComplexOf Float = Complex Float | ||
111 | type instance ComplexOf (Complex Float) = Complex Float | ||
112 | |||
113 | type family SingleOf x | ||
114 | |||
115 | type instance SingleOf Double = Float | ||
116 | type instance SingleOf Float = Float | ||
117 | |||
118 | type instance SingleOf (Complex a) = Complex (SingleOf a) | ||
119 | |||
120 | type family DoubleOf x | ||
121 | |||
122 | type instance DoubleOf Double = Double | ||
123 | type instance DoubleOf Float = Double | ||
124 | |||
125 | type instance DoubleOf (Complex a) = Complex (DoubleOf a) | ||
126 | |||
127 | type family ElementOf c | ||
128 | |||
129 | type instance ElementOf (Vector a) = a | ||
130 | type instance ElementOf (Matrix a) = a | ||
131 | |||
132 | type family IndexOf c | ||
133 | |||
134 | type instance IndexOf Vector = Int | ||
135 | type instance IndexOf Matrix = (Int,Int) | ||
136 | |||
137 | ------------------------------------------------------------------- | ||
138 | |||
139 | -- | generic conversion functions | ||
140 | class Convert t where | ||
141 | real :: Container c => c (RealOf t) -> c t | ||
142 | complex :: Container c => c t -> c (ComplexOf t) | ||
143 | single :: Container c => c t -> c (SingleOf t) | ||
144 | double :: Container c => c t -> c (DoubleOf t) | ||
145 | |||
146 | instance Convert Double where | ||
147 | real = id | ||
148 | complex = complex' | ||
149 | single = single' | ||
150 | double = id | ||
151 | |||
152 | instance Convert Float where | ||
153 | real = id | ||
154 | complex = complex' | ||
155 | single = id | ||
156 | double = double' | ||
157 | |||
158 | instance Convert (Complex Double) where | ||
159 | real = complex' | ||
160 | complex = id | ||
161 | single = single' | ||
162 | double = id | ||
163 | |||
164 | instance Convert (Complex Float) where | ||
165 | real = complex' | ||
166 | complex = id | ||
167 | single = id | ||
168 | double = double' | ||
169 | |||
170 | ------------------------------------------------------------------- | ||
171 | |||
172 | -- | to be replaced by Convert | ||
173 | class Convert t => AutoReal t where | ||
174 | real'' :: Container c => c Double -> c t | ||
175 | complex'' :: Container c => c t -> c (Complex Double) | ||
176 | |||
177 | instance AutoReal Double where | ||
178 | real'' = real | ||
179 | complex'' = complex | ||
180 | |||
181 | instance AutoReal (Complex Double) where | ||
182 | real'' = real | ||
183 | complex'' = complex | ||
184 | |||
185 | instance AutoReal Float where | ||
186 | real'' = real . single | ||
187 | complex'' = double . complex | ||
188 | |||
189 | instance AutoReal (Complex Float) where | ||
190 | real'' = real . single | ||
191 | complex'' = double . complex | ||
192 | |||
193 | ------------------------------------------------------------------- | ||
194 | |||
195 | -- | Basic element-by-element functions. | ||
196 | class (Element e, Container c) => Linear c e where | ||
197 | -- | create a structure with a single element | ||
198 | scalar :: e -> c e | ||
199 | scale :: e -> c e -> c e | ||
200 | -- | scale the element by element reciprocal of the object: | ||
201 | -- | ||
202 | -- @scaleRecip 2 (fromList [5,i]) == 2 |> [0.4 :+ 0.0,0.0 :+ (-2.0)]@ | ||
203 | scaleRecip :: e -> c e -> c e | ||
204 | addConstant :: e -> c e -> c e | ||
205 | add :: c e -> c e -> c e | ||
206 | sub :: c e -> c e -> c e | ||
207 | -- | element by element multiplication | ||
208 | mul :: c e -> c e -> c e | ||
209 | -- | element by element division | ||
210 | divide :: c e -> c e -> c e | ||
211 | equal :: c e -> c e -> Bool | ||
212 | -- | ||
213 | minIndex :: c e -> IndexOf c | ||
214 | maxIndex :: c e -> IndexOf c | ||
215 | minElement :: c e -> e | ||
216 | maxElement :: c e -> e | ||
217 | |||
218 | |||
219 | |||
diff --git a/lib/Numeric/LinearAlgebra.hs b/lib/Numeric/LinearAlgebra.hs index e8a14d6..3df9bd7 100644 --- a/lib/Numeric/LinearAlgebra.hs +++ b/lib/Numeric/LinearAlgebra.hs | |||
@@ -13,13 +13,11 @@ This module reexports all normally required functions for Linear Algebra applica | |||
13 | -} | 13 | -} |
14 | ----------------------------------------------------------------------------- | 14 | ----------------------------------------------------------------------------- |
15 | module Numeric.LinearAlgebra ( | 15 | module Numeric.LinearAlgebra ( |
16 | module Data.Packed, | ||
17 | module Numeric.LinearAlgebra.Algorithms, | 16 | module Numeric.LinearAlgebra.Algorithms, |
18 | module Numeric.LinearAlgebra.Interface, | 17 | module Numeric.LinearAlgebra.Interface, |
19 | module Numeric.LinearAlgebra.Linear | 18 | module Numeric.LinearAlgebra.Linear |
20 | ) where | 19 | ) where |
21 | 20 | ||
22 | import Data.Packed | ||
23 | import Numeric.LinearAlgebra.Algorithms | 21 | import Numeric.LinearAlgebra.Algorithms |
24 | import Numeric.LinearAlgebra.Interface | 22 | import Numeric.LinearAlgebra.Interface |
25 | import Numeric.LinearAlgebra.Linear | 23 | import Numeric.LinearAlgebra.Linear |
diff --git a/lib/Numeric/LinearAlgebra/Algorithms.hs b/lib/Numeric/LinearAlgebra/Algorithms.hs index 7d2f84d..14bf5d8 100644 --- a/lib/Numeric/LinearAlgebra/Algorithms.hs +++ b/lib/Numeric/LinearAlgebra/Algorithms.hs | |||
@@ -77,8 +77,8 @@ module Numeric.LinearAlgebra.Algorithms ( | |||
77 | import Data.Packed.Internal hiding ((//)) | 77 | import Data.Packed.Internal hiding ((//)) |
78 | import Data.Packed.Matrix | 78 | import Data.Packed.Matrix |
79 | import Data.Complex | 79 | import Data.Complex |
80 | import Numeric.LinearAlgebra.LAPACK as LAPACK | ||
81 | import Numeric.LinearAlgebra.Linear | 80 | import Numeric.LinearAlgebra.Linear |
81 | import Numeric.LinearAlgebra.LAPACK as LAPACK | ||
82 | import Data.List(foldl1') | 82 | import Data.List(foldl1') |
83 | import Data.Array | 83 | import Data.Array |
84 | 84 | ||
diff --git a/lib/Numeric/LinearAlgebra/Interface.hs b/lib/Numeric/LinearAlgebra/Interface.hs index 13d175b..fa3e209 100644 --- a/lib/Numeric/LinearAlgebra/Interface.hs +++ b/lib/Numeric/LinearAlgebra/Interface.hs | |||
@@ -25,8 +25,8 @@ module Numeric.LinearAlgebra.Interface( | |||
25 | (<|>),(<->), | 25 | (<|>),(<->), |
26 | ) where | 26 | ) where |
27 | 27 | ||
28 | import Data.Packed.Vector | 28 | import Numeric.Vector |
29 | import Data.Packed.Matrix | 29 | import Numeric.Matrix |
30 | import Numeric.LinearAlgebra.Algorithms | 30 | import Numeric.LinearAlgebra.Algorithms |
31 | import Numeric.LinearAlgebra.Linear | 31 | import Numeric.LinearAlgebra.Linear |
32 | 32 | ||
diff --git a/lib/Numeric/LinearAlgebra/LAPACK.hs b/lib/Numeric/LinearAlgebra/LAPACK.hs index eec3035..8888712 100644 --- a/lib/Numeric/LinearAlgebra/LAPACK.hs +++ b/lib/Numeric/LinearAlgebra/LAPACK.hs | |||
@@ -44,6 +44,7 @@ module Numeric.LinearAlgebra.LAPACK ( | |||
44 | import Data.Packed.Internal | 44 | import Data.Packed.Internal |
45 | import Data.Packed.Matrix | 45 | import Data.Packed.Matrix |
46 | import Data.Complex | 46 | import Data.Complex |
47 | import Numeric.Container | ||
47 | import Numeric.GSL.Vector(vectorMapValR, FunCodeSV(Scale)) | 48 | import Numeric.GSL.Vector(vectorMapValR, FunCodeSV(Scale)) |
48 | import Foreign | 49 | import Foreign |
49 | import Foreign.C.Types (CInt) | 50 | import Foreign.C.Types (CInt) |
diff --git a/lib/Numeric/LinearAlgebra/Linear.hs b/lib/Numeric/LinearAlgebra/Linear.hs index 778b976..9048204 100644 --- a/lib/Numeric/LinearAlgebra/Linear.hs +++ b/lib/Numeric/LinearAlgebra/Linear.hs | |||
@@ -19,33 +19,31 @@ Basic optimized operations on vectors and matrices. | |||
19 | module Numeric.LinearAlgebra.Linear ( | 19 | module Numeric.LinearAlgebra.Linear ( |
20 | -- * Linear Algebra Typeclasses | 20 | -- * Linear Algebra Typeclasses |
21 | Vectors(..), | 21 | Vectors(..), |
22 | Linear(..), | ||
23 | -- * Products | 22 | -- * Products |
24 | Product(..), | 23 | Product(..), |
25 | mXm,mXv,vXm, | 24 | mXm,mXv,vXm, |
26 | outer, kronecker, | 25 | outer, kronecker, |
27 | -- * Creation of numeric vectors | 26 | -- * Modules |
28 | constant, linspace | 27 | module Numeric.Vector, |
28 | module Numeric.Matrix, | ||
29 | module Numeric.Container | ||
29 | ) where | 30 | ) where |
30 | 31 | ||
31 | import Data.Packed.Internal | 32 | import Data.Packed.Internal.Common |
32 | import Data.Packed.Matrix | 33 | import Data.Packed.Matrix |
33 | import Data.Complex | 34 | import Data.Complex |
35 | import Numeric.Container | ||
36 | import Numeric.Vector | ||
37 | import Numeric.Matrix | ||
34 | import Numeric.GSL.Vector | 38 | import Numeric.GSL.Vector |
35 | import Numeric.LinearAlgebra.LAPACK(multiplyR,multiplyC,multiplyF,multiplyQ) | 39 | import Numeric.LinearAlgebra.LAPACK(multiplyR,multiplyC,multiplyF,multiplyQ) |
36 | 40 | ||
37 | import Control.Monad(ap) | ||
38 | |||
39 | -- | basic Vector functions | 41 | -- | basic Vector functions |
40 | class Num e => Vectors a e where | 42 | class Num e => Vectors a e where |
41 | -- the C functions sumX are twice as fast as using foldVector | 43 | -- the C functions sumX are twice as fast as using foldVector |
42 | vectorSum :: a e -> e | 44 | vectorSum :: a e -> e |
43 | vectorProd :: a e -> e | 45 | vectorProd :: a e -> e |
44 | absSum :: a e -> e | 46 | absSum :: a e -> e |
45 | vectorMin :: a e -> e | ||
46 | vectorMax :: a e -> e | ||
47 | minIdx :: a e -> Int | ||
48 | maxIdx :: a e -> Int | ||
49 | dot :: a e -> a e -> e | 47 | dot :: a e -> a e -> e |
50 | norm1 :: a e -> e | 48 | norm1 :: a e -> e |
51 | norm2 :: a e -> e | 49 | norm2 :: a e -> e |
@@ -57,153 +55,36 @@ instance Vectors Vector Float where | |||
57 | vectorProd = prodF | 55 | vectorProd = prodF |
58 | norm2 = toScalarF Norm2 | 56 | norm2 = toScalarF Norm2 |
59 | absSum = toScalarF AbsSum | 57 | absSum = toScalarF AbsSum |
60 | vectorMin = toScalarF Min | ||
61 | vectorMax = toScalarF Max | ||
62 | minIdx = round . toScalarF MinIdx | ||
63 | maxIdx = round . toScalarF MaxIdx | ||
64 | dot = dotF | 58 | dot = dotF |
65 | norm1 = toScalarF AbsSum | 59 | norm1 = toScalarF AbsSum |
66 | normInf = vectorMax . vectorMapF Abs | 60 | normInf = maxElement . vectorMapF Abs |
67 | 61 | ||
68 | instance Vectors Vector Double where | 62 | instance Vectors Vector Double where |
69 | vectorSum = sumR | 63 | vectorSum = sumR |
70 | vectorProd = prodR | 64 | vectorProd = prodR |
71 | norm2 = toScalarR Norm2 | 65 | norm2 = toScalarR Norm2 |
72 | absSum = toScalarR AbsSum | 66 | absSum = toScalarR AbsSum |
73 | vectorMin = toScalarR Min | ||
74 | vectorMax = toScalarR Max | ||
75 | minIdx = round . toScalarR MinIdx | ||
76 | maxIdx = round . toScalarR MaxIdx | ||
77 | dot = dotR | 67 | dot = dotR |
78 | norm1 = toScalarR AbsSum | 68 | norm1 = toScalarR AbsSum |
79 | normInf = vectorMax . vectorMapR Abs | 69 | normInf = maxElement . vectorMapR Abs |
80 | 70 | ||
81 | instance Vectors Vector (Complex Float) where | 71 | instance Vectors Vector (Complex Float) where |
82 | vectorSum = sumQ | 72 | vectorSum = sumQ |
83 | vectorProd = prodQ | 73 | vectorProd = prodQ |
84 | norm2 = (:+ 0) . toScalarQ Norm2 | 74 | norm2 = (:+ 0) . toScalarQ Norm2 |
85 | absSum = (:+ 0) . toScalarQ AbsSum | 75 | absSum = (:+ 0) . toScalarQ AbsSum |
86 | vectorMin = ap (@>) minIdx | ||
87 | vectorMax = ap (@>) maxIdx | ||
88 | minIdx = minIdx . fst . fromComplex . (zipVectorWith (*) `ap` mapVector conjugate) | ||
89 | maxIdx = maxIdx . fst . fromComplex . (zipVectorWith (*) `ap` mapVector conjugate) | ||
90 | dot = dotQ | 76 | dot = dotQ |
91 | norm1 = (:+ 0) . vectorSum . fst . fromComplex . vectorMapQ Abs | 77 | norm1 = (:+ 0) . vectorSum . fst . fromComplex . vectorMapQ Abs |
92 | normInf = (:+ 0) . vectorMax . fst . fromComplex . vectorMapQ Abs | 78 | normInf = (:+ 0) . maxElement . fst . fromComplex . vectorMapQ Abs |
93 | 79 | ||
94 | instance Vectors Vector (Complex Double) where | 80 | instance Vectors Vector (Complex Double) where |
95 | vectorSum = sumC | 81 | vectorSum = sumC |
96 | vectorProd = prodC | 82 | vectorProd = prodC |
97 | norm2 = (:+ 0) . toScalarC Norm2 | 83 | norm2 = (:+ 0) . toScalarC Norm2 |
98 | absSum = (:+ 0) . toScalarC AbsSum | 84 | absSum = (:+ 0) . toScalarC AbsSum |
99 | vectorMin = ap (@>) minIdx | ||
100 | vectorMax = ap (@>) maxIdx | ||
101 | minIdx = minIdx . fst . fromComplex . (zipVectorWith (*) `ap` mapVector conjugate) | ||
102 | maxIdx = maxIdx . fst . fromComplex . (zipVectorWith (*) `ap` mapVector conjugate) | ||
103 | dot = dotC | 85 | dot = dotC |
104 | norm1 = (:+ 0) . vectorSum . fst . fromComplex . vectorMapC Abs | 86 | norm1 = (:+ 0) . vectorSum . fst . fromComplex . vectorMapC Abs |
105 | normInf = (:+ 0) . vectorMax . fst . fromComplex . vectorMapC Abs | 87 | normInf = (:+ 0) . maxElement . fst . fromComplex . vectorMapC Abs |
106 | |||
107 | ---------------------------------------------------- | ||
108 | |||
109 | -- | Basic element-by-element functions. | ||
110 | class (Element e, Container c) => Linear c e where | ||
111 | -- | create a structure with a single element | ||
112 | scalar :: e -> c e | ||
113 | scale :: e -> c e -> c e | ||
114 | -- | scale the element by element reciprocal of the object: | ||
115 | -- | ||
116 | -- @scaleRecip 2 (fromList [5,i]) == 2 |> [0.4 :+ 0.0,0.0 :+ (-2.0)]@ | ||
117 | scaleRecip :: e -> c e -> c e | ||
118 | addConstant :: e -> c e -> c e | ||
119 | add :: c e -> c e -> c e | ||
120 | sub :: c e -> c e -> c e | ||
121 | -- | element by element multiplication | ||
122 | mul :: c e -> c e -> c e | ||
123 | -- | element by element division | ||
124 | divide :: c e -> c e -> c e | ||
125 | equal :: c e -> c e -> Bool | ||
126 | |||
127 | |||
128 | instance Linear Vector Float where | ||
129 | scale = vectorMapValF Scale | ||
130 | scaleRecip = vectorMapValF Recip | ||
131 | addConstant = vectorMapValF AddConstant | ||
132 | add = vectorZipF Add | ||
133 | sub = vectorZipF Sub | ||
134 | mul = vectorZipF Mul | ||
135 | divide = vectorZipF Div | ||
136 | equal u v = dim u == dim v && vectorMax (vectorMapF Abs (sub u v)) == 0.0 | ||
137 | scalar x = fromList [x] | ||
138 | |||
139 | instance Linear Vector Double where | ||
140 | scale = vectorMapValR Scale | ||
141 | scaleRecip = vectorMapValR Recip | ||
142 | addConstant = vectorMapValR AddConstant | ||
143 | add = vectorZipR Add | ||
144 | sub = vectorZipR Sub | ||
145 | mul = vectorZipR Mul | ||
146 | divide = vectorZipR Div | ||
147 | equal u v = dim u == dim v && vectorMax (vectorMapR Abs (sub u v)) == 0.0 | ||
148 | scalar x = fromList [x] | ||
149 | |||
150 | instance Linear Vector (Complex Double) where | ||
151 | scale = vectorMapValC Scale | ||
152 | scaleRecip = vectorMapValC Recip | ||
153 | addConstant = vectorMapValC AddConstant | ||
154 | add = vectorZipC Add | ||
155 | sub = vectorZipC Sub | ||
156 | mul = vectorZipC Mul | ||
157 | divide = vectorZipC Div | ||
158 | equal u v = dim u == dim v && vectorMax (mapVector magnitude (sub u v)) == 0.0 | ||
159 | scalar x = fromList [x] | ||
160 | |||
161 | instance Linear Vector (Complex Float) where | ||
162 | scale = vectorMapValQ Scale | ||
163 | scaleRecip = vectorMapValQ Recip | ||
164 | addConstant = vectorMapValQ AddConstant | ||
165 | add = vectorZipQ Add | ||
166 | sub = vectorZipQ Sub | ||
167 | mul = vectorZipQ Mul | ||
168 | divide = vectorZipQ Div | ||
169 | equal u v = dim u == dim v && vectorMax (mapVector magnitude (sub u v)) == 0.0 | ||
170 | scalar x = fromList [x] | ||
171 | |||
172 | instance (Linear Vector a, Container Matrix) => (Linear Matrix a) where | ||
173 | scale x = liftMatrix (scale x) | ||
174 | scaleRecip x = liftMatrix (scaleRecip x) | ||
175 | addConstant x = liftMatrix (addConstant x) | ||
176 | add = liftMatrix2 add | ||
177 | sub = liftMatrix2 sub | ||
178 | mul = liftMatrix2 mul | ||
179 | divide = liftMatrix2 divide | ||
180 | equal a b = cols a == cols b && flatten a `equal` flatten b | ||
181 | scalar x = (1><1) [x] | ||
182 | |||
183 | |||
184 | ---------------------------------------------------- | ||
185 | |||
186 | {- | creates a vector with a given number of equal components: | ||
187 | |||
188 | @> constant 2 7 | ||
189 | 7 |> [2.0,2.0,2.0,2.0,2.0,2.0,2.0]@ | ||
190 | -} | ||
191 | constant :: Element a => a -> Int -> Vector a | ||
192 | -- constant x n = runSTVector (newVector x n) | ||
193 | constant = constantD -- about 2x faster | ||
194 | |||
195 | {- | Creates a real vector containing a range of values: | ||
196 | |||
197 | @\> linspace 5 (-3,7) | ||
198 | 5 |> [-3.0,-0.5,2.0,4.5,7.0]@ | ||
199 | |||
200 | Logarithmic spacing can be defined as follows: | ||
201 | |||
202 | @logspace n (a,b) = 10 ** linspace n (a,b)@ | ||
203 | -} | ||
204 | linspace :: (Enum e, Linear Vector e) => Int -> (e, e) -> Vector e | ||
205 | linspace n (a,b) = addConstant a $ scale s $ fromList [0 .. fromIntegral n-1] | ||
206 | where s = (b-a)/fromIntegral (n-1) | ||
207 | 88 | ||
208 | ---------------------------------------------------- | 89 | ---------------------------------------------------- |
209 | 90 | ||
diff --git a/lib/Numeric/LinearAlgebra/Tests.hs b/lib/Numeric/LinearAlgebra/Tests.hs index 43a62e5..5b42226 100644 --- a/lib/Numeric/LinearAlgebra/Tests.hs +++ b/lib/Numeric/LinearAlgebra/Tests.hs | |||
@@ -21,6 +21,7 @@ module Numeric.LinearAlgebra.Tests( | |||
21 | --, runBigTests | 21 | --, runBigTests |
22 | ) where | 22 | ) where |
23 | 23 | ||
24 | import Data.Packed.Random | ||
24 | import Numeric.LinearAlgebra | 25 | import Numeric.LinearAlgebra |
25 | import Numeric.LinearAlgebra.LAPACK | 26 | import Numeric.LinearAlgebra.LAPACK |
26 | import Numeric.LinearAlgebra.Tests.Instances | 27 | import Numeric.LinearAlgebra.Tests.Instances |
diff --git a/lib/Numeric/Matrix.hs b/lib/Numeric/Matrix.hs new file mode 100644 index 0000000..8d3764a --- /dev/null +++ b/lib/Numeric/Matrix.hs | |||
@@ -0,0 +1,97 @@ | |||
1 | {-# LANGUAGE TypeFamilies #-} | ||
2 | {-# LANGUAGE FlexibleContexts #-} | ||
3 | {-# LANGUAGE FlexibleInstances #-} | ||
4 | {-# LANGUAGE UndecidableInstances #-} | ||
5 | {-# LANGUAGE MultiParamTypeClasses #-} | ||
6 | |||
7 | ----------------------------------------------------------------------------- | ||
8 | -- | | ||
9 | -- Module : Numeric.Matrix | ||
10 | -- Copyright : (c) Alberto Ruiz 2007 | ||
11 | -- License : GPL-style | ||
12 | -- | ||
13 | -- Maintainer : Alberto Ruiz <aruiz@um.es> | ||
14 | -- Stability : provisional | ||
15 | -- Portability : portable | ||
16 | -- | ||
17 | -- Numeric instances and functions for 'Data.Packed.Matrix's | ||
18 | -- | ||
19 | ----------------------------------------------------------------------------- | ||
20 | |||
21 | module Numeric.Matrix ( | ||
22 | module Data.Packed.Matrix, | ||
23 | ) where | ||
24 | |||
25 | ------------------------------------------------------------------- | ||
26 | |||
27 | import Data.Packed.Vector | ||
28 | import Data.Packed.Matrix | ||
29 | import Numeric.Container | ||
30 | import Numeric.Vector() | ||
31 | |||
32 | import Control.Monad(ap) | ||
33 | |||
34 | ------------------------------------------------------------------- | ||
35 | |||
36 | instance Linear Matrix a => Eq (Matrix a) where | ||
37 | (==) = equal | ||
38 | |||
39 | instance (Linear Matrix a, Num (Vector a)) => Num (Matrix a) where | ||
40 | (+) = liftMatrix2Auto (+) | ||
41 | (-) = liftMatrix2Auto (-) | ||
42 | negate = liftMatrix negate | ||
43 | (*) = liftMatrix2Auto (*) | ||
44 | signum = liftMatrix signum | ||
45 | abs = liftMatrix abs | ||
46 | fromInteger = (1><1) . return . fromInteger | ||
47 | |||
48 | --------------------------------------------------- | ||
49 | |||
50 | instance (Linear Vector a, Fractional (Vector a), Num (Matrix a)) => Fractional (Matrix a) where | ||
51 | fromRational n = (1><1) [fromRational n] | ||
52 | (/) = liftMatrix2Auto (/) | ||
53 | |||
54 | --------------------------------------------------------- | ||
55 | |||
56 | instance (Linear Vector a, Floating (Vector a), Fractional (Matrix a)) => Floating (Matrix a) where | ||
57 | sin = liftMatrix sin | ||
58 | cos = liftMatrix cos | ||
59 | tan = liftMatrix tan | ||
60 | asin = liftMatrix asin | ||
61 | acos = liftMatrix acos | ||
62 | atan = liftMatrix atan | ||
63 | sinh = liftMatrix sinh | ||
64 | cosh = liftMatrix cosh | ||
65 | tanh = liftMatrix tanh | ||
66 | asinh = liftMatrix asinh | ||
67 | acosh = liftMatrix acosh | ||
68 | atanh = liftMatrix atanh | ||
69 | exp = liftMatrix exp | ||
70 | log = liftMatrix log | ||
71 | (**) = liftMatrix2Auto (**) | ||
72 | sqrt = liftMatrix sqrt | ||
73 | pi = (1><1) [pi] | ||
74 | |||
75 | --------------------------------------------------------------- | ||
76 | |||
77 | instance (Linear Vector a, Container Matrix) => (Linear Matrix a) where | ||
78 | scale x = liftMatrix (scale x) | ||
79 | scaleRecip x = liftMatrix (scaleRecip x) | ||
80 | addConstant x = liftMatrix (addConstant x) | ||
81 | add = liftMatrix2 add | ||
82 | sub = liftMatrix2 sub | ||
83 | mul = liftMatrix2 mul | ||
84 | divide = liftMatrix2 divide | ||
85 | equal a b = cols a == cols b && flatten a `equal` flatten b | ||
86 | scalar x = (1><1) [x] | ||
87 | minIndex m = let (r,c) = (rows m,cols m) | ||
88 | i = 1 + (minIndex $ flatten m) | ||
89 | in (i `div` r,i `mod` r) | ||
90 | maxIndex m = let (r,c) = (rows m,cols m) | ||
91 | i = 1 + (maxIndex $ flatten m) | ||
92 | in (i `div` r,i `mod` r) | ||
93 | minElement = ap (@@>) minIndex | ||
94 | maxElement = ap (@@>) maxIndex | ||
95 | |||
96 | ---------------------------------------------------- | ||
97 | |||
diff --git a/lib/Numeric/Vector.hs b/lib/Numeric/Vector.hs new file mode 100644 index 0000000..ced202f --- /dev/null +++ b/lib/Numeric/Vector.hs | |||
@@ -0,0 +1,317 @@ | |||
1 | {-# LANGUAGE TypeFamilies #-} | ||
2 | {-# LANGUAGE FlexibleContexts #-} | ||
3 | {-# LANGUAGE FlexibleInstances #-} | ||
4 | {-# LANGUAGE UndecidableInstances #-} | ||
5 | {-# LANGUAGE MultiParamTypeClasses #-} | ||
6 | --{-# LANGUAGE FunctionalDependencies #-} | ||
7 | ----------------------------------------------------------------------------- | ||
8 | -- | | ||
9 | -- Module : Numeric.Vector | ||
10 | -- Copyright : (c) Alberto Ruiz 2007 | ||
11 | -- License : GPL-style | ||
12 | -- | ||
13 | -- Maintainer : Alberto Ruiz <aruiz@um.es> | ||
14 | -- Stability : provisional | ||
15 | -- Portability : portable | ||
16 | -- | ||
17 | -- Numeric instances and functions for 'Data.Packed.Vector's | ||
18 | -- | ||
19 | ----------------------------------------------------------------------------- | ||
20 | |||
21 | module Numeric.Vector ( | ||
22 | -- * Vector creation | ||
23 | constant, linspace, | ||
24 | module Data.Packed.Vector | ||
25 | ) where | ||
26 | |||
27 | import Data.Complex | ||
28 | |||
29 | import Control.Monad(ap) | ||
30 | |||
31 | import Data.Packed.Vector | ||
32 | import Data.Packed.Matrix(Element(..)) | ||
33 | import Numeric.GSL.Vector | ||
34 | |||
35 | import Numeric.Container | ||
36 | |||
37 | ------------------------------------------------------------------- | ||
38 | |||
39 | #ifndef VECTOR | ||
40 | import Foreign(Storable) | ||
41 | #endif | ||
42 | |||
43 | ------------------------------------------------------------------ | ||
44 | |||
45 | #ifndef VECTOR | ||
46 | |||
47 | instance (Show a, Storable a) => (Show (Vector a)) where | ||
48 | show v = (show (dim v))++" |> " ++ show (toList v) | ||
49 | |||
50 | #endif | ||
51 | |||
52 | #ifdef VECTOR | ||
53 | |||
54 | instance (Element a, Read a) => Read (Vector a) where | ||
55 | readsPrec _ s = [(fromList . read $ listnums, rest)] | ||
56 | where (thing,trest) = breakAt ']' s | ||
57 | (dims,listnums) = breakAt ' ' (dropWhile (==' ') thing) | ||
58 | rest = drop 31 trest | ||
59 | #else | ||
60 | |||
61 | instance (Element a, Read a) => Read (Vector a) where | ||
62 | readsPrec _ s = [((d |>) . read $ listnums, rest)] | ||
63 | where (thing,rest) = breakAt ']' s | ||
64 | (dims,listnums) = breakAt '>' thing | ||
65 | d = read . init . fst . breakAt '|' $ dims | ||
66 | |||
67 | #endif | ||
68 | |||
69 | breakAt c l = (a++[c],tail b) where | ||
70 | (a,b) = break (==c) l | ||
71 | |||
72 | ------------------------------------------------------------------ | ||
73 | |||
74 | {- | creates a vector with a given number of equal components: | ||
75 | |||
76 | @> constant 2 7 | ||
77 | 7 |> [2.0,2.0,2.0,2.0,2.0,2.0,2.0]@ | ||
78 | -} | ||
79 | constant :: Element a => a -> Int -> Vector a | ||
80 | -- constant x n = runSTVector (newVector x n) | ||
81 | constant = constantD -- about 2x faster | ||
82 | |||
83 | {- | Creates a real vector containing a range of values: | ||
84 | |||
85 | @\> linspace 5 (-3,7) | ||
86 | 5 |> [-3.0,-0.5,2.0,4.5,7.0]@ | ||
87 | |||
88 | Logarithmic spacing can be defined as follows: | ||
89 | |||
90 | @logspace n (a,b) = 10 ** linspace n (a,b)@ | ||
91 | -} | ||
92 | linspace :: (Enum e, Linear Vector e) => Int -> (e, e) -> Vector e | ||
93 | linspace n (a,b) = addConstant a $ scale s $ fromList [0 .. fromIntegral n-1] | ||
94 | where s = (b-a)/fromIntegral (n-1) | ||
95 | |||
96 | ------------------------------------------------------------------ | ||
97 | |||
98 | adaptScalar f1 f2 f3 x y | ||
99 | | dim x == 1 = f1 (x@>0) y | ||
100 | | dim y == 1 = f3 x (y@>0) | ||
101 | | otherwise = f2 x y | ||
102 | |||
103 | ------------------------------------------------------------------ | ||
104 | |||
105 | #ifndef VECTOR | ||
106 | |||
107 | instance Linear Vector a => Eq (Vector a) where | ||
108 | (==) = equal | ||
109 | |||
110 | #endif | ||
111 | |||
112 | instance Num (Vector Float) where | ||
113 | (+) = adaptScalar addConstant add (flip addConstant) | ||
114 | negate = scale (-1) | ||
115 | (*) = adaptScalar scale mul (flip scale) | ||
116 | signum = vectorMapF Sign | ||
117 | abs = vectorMapF Abs | ||
118 | fromInteger = fromList . return . fromInteger | ||
119 | |||
120 | instance Num (Vector Double) where | ||
121 | (+) = adaptScalar addConstant add (flip addConstant) | ||
122 | negate = scale (-1) | ||
123 | (*) = adaptScalar scale mul (flip scale) | ||
124 | signum = vectorMapR Sign | ||
125 | abs = vectorMapR Abs | ||
126 | fromInteger = fromList . return . fromInteger | ||
127 | |||
128 | instance Num (Vector (Complex Double)) where | ||
129 | (+) = adaptScalar addConstant add (flip addConstant) | ||
130 | negate = scale (-1) | ||
131 | (*) = adaptScalar scale mul (flip scale) | ||
132 | signum = vectorMapC Sign | ||
133 | abs = vectorMapC Abs | ||
134 | fromInteger = fromList . return . fromInteger | ||
135 | |||
136 | instance Num (Vector (Complex Float)) where | ||
137 | (+) = adaptScalar addConstant add (flip addConstant) | ||
138 | negate = scale (-1) | ||
139 | (*) = adaptScalar scale mul (flip scale) | ||
140 | signum = vectorMapQ Sign | ||
141 | abs = vectorMapQ Abs | ||
142 | fromInteger = fromList . return . fromInteger | ||
143 | |||
144 | --------------------------------------------------- | ||
145 | |||
146 | instance (Linear Vector a, Num (Vector a)) => Fractional (Vector a) where | ||
147 | fromRational n = fromList [fromRational n] | ||
148 | (/) = adaptScalar f divide g where | ||
149 | r `f` v = scaleRecip r v | ||
150 | v `g` r = scale (recip r) v | ||
151 | |||
152 | ------------------------------------------------------- | ||
153 | |||
154 | instance Floating (Vector Float) where | ||
155 | sin = vectorMapF Sin | ||
156 | cos = vectorMapF Cos | ||
157 | tan = vectorMapF Tan | ||
158 | asin = vectorMapF ASin | ||
159 | acos = vectorMapF ACos | ||
160 | atan = vectorMapF ATan | ||
161 | sinh = vectorMapF Sinh | ||
162 | cosh = vectorMapF Cosh | ||
163 | tanh = vectorMapF Tanh | ||
164 | asinh = vectorMapF ASinh | ||
165 | acosh = vectorMapF ACosh | ||
166 | atanh = vectorMapF ATanh | ||
167 | exp = vectorMapF Exp | ||
168 | log = vectorMapF Log | ||
169 | sqrt = vectorMapF Sqrt | ||
170 | (**) = adaptScalar (vectorMapValF PowSV) (vectorZipF Pow) (flip (vectorMapValF PowVS)) | ||
171 | pi = fromList [pi] | ||
172 | |||
173 | ------------------------------------------------------------- | ||
174 | |||
175 | instance Floating (Vector Double) where | ||
176 | sin = vectorMapR Sin | ||
177 | cos = vectorMapR Cos | ||
178 | tan = vectorMapR Tan | ||
179 | asin = vectorMapR ASin | ||
180 | acos = vectorMapR ACos | ||
181 | atan = vectorMapR ATan | ||
182 | sinh = vectorMapR Sinh | ||
183 | cosh = vectorMapR Cosh | ||
184 | tanh = vectorMapR Tanh | ||
185 | asinh = vectorMapR ASinh | ||
186 | acosh = vectorMapR ACosh | ||
187 | atanh = vectorMapR ATanh | ||
188 | exp = vectorMapR Exp | ||
189 | log = vectorMapR Log | ||
190 | sqrt = vectorMapR Sqrt | ||
191 | (**) = adaptScalar (vectorMapValR PowSV) (vectorZipR Pow) (flip (vectorMapValR PowVS)) | ||
192 | pi = fromList [pi] | ||
193 | |||
194 | ------------------------------------------------------------- | ||
195 | |||
196 | instance Floating (Vector (Complex Double)) where | ||
197 | sin = vectorMapC Sin | ||
198 | cos = vectorMapC Cos | ||
199 | tan = vectorMapC Tan | ||
200 | asin = vectorMapC ASin | ||
201 | acos = vectorMapC ACos | ||
202 | atan = vectorMapC ATan | ||
203 | sinh = vectorMapC Sinh | ||
204 | cosh = vectorMapC Cosh | ||
205 | tanh = vectorMapC Tanh | ||
206 | asinh = vectorMapC ASinh | ||
207 | acosh = vectorMapC ACosh | ||
208 | atanh = vectorMapC ATanh | ||
209 | exp = vectorMapC Exp | ||
210 | log = vectorMapC Log | ||
211 | sqrt = vectorMapC Sqrt | ||
212 | (**) = adaptScalar (vectorMapValC PowSV) (vectorZipC Pow) (flip (vectorMapValC PowVS)) | ||
213 | pi = fromList [pi] | ||
214 | |||
215 | ----------------------------------------------------------- | ||
216 | |||
217 | instance Floating (Vector (Complex Float)) where | ||
218 | sin = vectorMapQ Sin | ||
219 | cos = vectorMapQ Cos | ||
220 | tan = vectorMapQ Tan | ||
221 | asin = vectorMapQ ASin | ||
222 | acos = vectorMapQ ACos | ||
223 | atan = vectorMapQ ATan | ||
224 | sinh = vectorMapQ Sinh | ||
225 | cosh = vectorMapQ Cosh | ||
226 | tanh = vectorMapQ Tanh | ||
227 | asinh = vectorMapQ ASinh | ||
228 | acosh = vectorMapQ ACosh | ||
229 | atanh = vectorMapQ ATanh | ||
230 | exp = vectorMapQ Exp | ||
231 | log = vectorMapQ Log | ||
232 | sqrt = vectorMapQ Sqrt | ||
233 | (**) = adaptScalar (vectorMapValQ PowSV) (vectorZipQ Pow) (flip (vectorMapValQ PowVS)) | ||
234 | pi = fromList [pi] | ||
235 | |||
236 | ----------------------------------------------------------- | ||
237 | |||
238 | |||
239 | -- instance (Storable a, Num (Vector a)) => Monoid (Vector a) where | ||
240 | -- mempty = 0 { idim = 0 } | ||
241 | -- mappend a b = mconcat [a,b] | ||
242 | -- mconcat = j . filter ((>0).dim) | ||
243 | -- where j [] = mempty | ||
244 | -- j l = join l | ||
245 | |||
246 | --------------------------------------------------------------- | ||
247 | |||
248 | -- instance (NFData a, Storable a) => NFData (Vector a) where | ||
249 | -- rnf = rnf . (@>0) | ||
250 | -- | ||
251 | -- instance (NFData a, Element a) => NFData (Matrix a) where | ||
252 | -- rnf = rnf . flatten | ||
253 | |||
254 | --------------------------------------------------------------- | ||
255 | |||
256 | instance Linear Vector Float where | ||
257 | scale = vectorMapValF Scale | ||
258 | scaleRecip = vectorMapValF Recip | ||
259 | addConstant = vectorMapValF AddConstant | ||
260 | add = vectorZipF Add | ||
261 | sub = vectorZipF Sub | ||
262 | mul = vectorZipF Mul | ||
263 | divide = vectorZipF Div | ||
264 | equal u v = dim u == dim v && maxElement (vectorMapF Abs (sub u v)) == 0.0 | ||
265 | scalar x = fromList [x] | ||
266 | minIndex = round . toScalarF MinIdx | ||
267 | maxIndex = round . toScalarF MaxIdx | ||
268 | minElement = toScalarF Min | ||
269 | maxElement = toScalarF Max | ||
270 | |||
271 | |||
272 | instance Linear Vector Double where | ||
273 | scale = vectorMapValR Scale | ||
274 | scaleRecip = vectorMapValR Recip | ||
275 | addConstant = vectorMapValR AddConstant | ||
276 | add = vectorZipR Add | ||
277 | sub = vectorZipR Sub | ||
278 | mul = vectorZipR Mul | ||
279 | divide = vectorZipR Div | ||
280 | equal u v = dim u == dim v && maxElement (vectorMapR Abs (sub u v)) == 0.0 | ||
281 | scalar x = fromList [x] | ||
282 | minIndex = round . toScalarR MinIdx | ||
283 | maxIndex = round . toScalarR MaxIdx | ||
284 | minElement = toScalarR Min | ||
285 | maxElement = toScalarR Max | ||
286 | |||
287 | instance Linear Vector (Complex Double) where | ||
288 | scale = vectorMapValC Scale | ||
289 | scaleRecip = vectorMapValC Recip | ||
290 | addConstant = vectorMapValC AddConstant | ||
291 | add = vectorZipC Add | ||
292 | sub = vectorZipC Sub | ||
293 | mul = vectorZipC Mul | ||
294 | divide = vectorZipC Div | ||
295 | equal u v = dim u == dim v && maxElement (mapVector magnitude (sub u v)) == 0.0 | ||
296 | scalar x = fromList [x] | ||
297 | minIndex = minIndex . fst . fromComplex . (zipVectorWith (*) `ap` mapVector conjugate) | ||
298 | maxIndex = maxIndex . fst . fromComplex . (zipVectorWith (*) `ap` mapVector conjugate) | ||
299 | minElement = ap (@>) minIndex | ||
300 | maxElement = ap (@>) maxIndex | ||
301 | |||
302 | instance Linear Vector (Complex Float) where | ||
303 | scale = vectorMapValQ Scale | ||
304 | scaleRecip = vectorMapValQ Recip | ||
305 | addConstant = vectorMapValQ AddConstant | ||
306 | add = vectorZipQ Add | ||
307 | sub = vectorZipQ Sub | ||
308 | mul = vectorZipQ Mul | ||
309 | divide = vectorZipQ Div | ||
310 | equal u v = dim u == dim v && maxElement (mapVector magnitude (sub u v)) == 0.0 | ||
311 | scalar x = fromList [x] | ||
312 | minIndex = minIndex . fst . fromComplex . (zipVectorWith (*) `ap` mapVector conjugate) | ||
313 | maxIndex = maxIndex . fst . fromComplex . (zipVectorWith (*) `ap` mapVector conjugate) | ||
314 | minElement = ap (@>) minIndex | ||
315 | maxElement = ap (@>) maxIndex | ||
316 | |||
317 | --------------------------------------------------------------- | ||