diff options
Diffstat (limited to 'lib/Numeric')
-rw-r--r-- | lib/Numeric/LinearAlgebra/Algorithms.hs | 22 | ||||
-rw-r--r-- | lib/Numeric/LinearAlgebra/Linear.hs | 6 | ||||
-rw-r--r-- | lib/Numeric/LinearAlgebra/Tests.hs | 19 | ||||
-rw-r--r-- | lib/Numeric/LinearAlgebra/Tests/Instances.hs | 11 |
4 files changed, 49 insertions, 9 deletions
diff --git a/lib/Numeric/LinearAlgebra/Algorithms.hs b/lib/Numeric/LinearAlgebra/Algorithms.hs index 1109296..f4b7ee9 100644 --- a/lib/Numeric/LinearAlgebra/Algorithms.hs +++ b/lib/Numeric/LinearAlgebra/Algorithms.hs | |||
@@ -1,4 +1,4 @@ | |||
1 | {-# OPTIONS_GHC -XFlexibleContexts -XFlexibleInstances #-} | 1 | {-# LANGUAGE FlexibleContexts, FlexibleInstances #-} |
2 | {-# LANGUAGE CPP #-} | 2 | {-# LANGUAGE CPP #-} |
3 | ----------------------------------------------------------------------------- | 3 | ----------------------------------------------------------------------------- |
4 | {- | | 4 | {- | |
@@ -85,7 +85,6 @@ import Numeric.LinearAlgebra.Linear | |||
85 | import Data.List(foldl1') | 85 | import Data.List(foldl1') |
86 | import Data.Array | 86 | import Data.Array |
87 | 87 | ||
88 | |||
89 | -- | Auxiliary typeclass used to define generic computations for both real and complex matrices. | 88 | -- | Auxiliary typeclass used to define generic computations for both real and complex matrices. |
90 | class (Normed (Matrix t), Linear Vector t, Linear Matrix t) => Field t where | 89 | class (Normed (Matrix t), Linear Vector t, Linear Matrix t) => Field t where |
91 | svd' :: Matrix t -> (Matrix t, Vector Double, Matrix t) | 90 | svd' :: Matrix t -> (Matrix t, Vector Double, Matrix t) |
@@ -397,6 +396,10 @@ ranksv teps maxdim s = k where | |||
397 | eps :: Double | 396 | eps :: Double |
398 | eps = 2.22044604925031e-16 | 397 | eps = 2.22044604925031e-16 |
399 | 398 | ||
399 | peps :: RealFloat x => x -> x | ||
400 | peps x = 2.0**(fromIntegral $ 1-floatDigits x) | ||
401 | |||
402 | |||
400 | -- | The imaginary unit: @i = 0.0 :+ 1.0@ | 403 | -- | The imaginary unit: @i = 0.0 :+ 1.0@ |
401 | i :: Complex Double | 404 | i :: Complex Double |
402 | i = 0:+1 | 405 | i = 0:+1 |
@@ -467,6 +470,21 @@ instance Normed (Matrix (Complex Double)) where | |||
467 | pnorm = pnormCM | 470 | pnorm = pnormCM |
468 | 471 | ||
469 | ----------------------------------------------------------------------- | 472 | ----------------------------------------------------------------------- |
473 | -- to be optimized | ||
474 | |||
475 | instance Normed (Vector Float) where | ||
476 | pnorm t = pnorm t . double | ||
477 | |||
478 | instance Normed (Vector (Complex Float)) where | ||
479 | pnorm t = pnorm t . double | ||
480 | |||
481 | instance Normed (Matrix Float) where | ||
482 | pnorm t = pnorm t . double | ||
483 | |||
484 | instance Normed (Matrix (Complex Float)) where | ||
485 | pnorm t = pnorm t . double | ||
486 | |||
487 | ----------------------------------------------------------------------- | ||
470 | 488 | ||
471 | -- | The nullspace of a matrix from its SVD decomposition. | 489 | -- | The nullspace of a matrix from its SVD decomposition. |
472 | nullspaceSVD :: Field t | 490 | nullspaceSVD :: Field t |
diff --git a/lib/Numeric/LinearAlgebra/Linear.hs b/lib/Numeric/LinearAlgebra/Linear.hs index 9a7e65f..51e93fb 100644 --- a/lib/Numeric/LinearAlgebra/Linear.hs +++ b/lib/Numeric/LinearAlgebra/Linear.hs | |||
@@ -17,7 +17,7 @@ Basic optimized operations on vectors and matrices. | |||
17 | 17 | ||
18 | module Numeric.LinearAlgebra.Linear ( | 18 | module Numeric.LinearAlgebra.Linear ( |
19 | -- * Linear Algebra Typeclasses | 19 | -- * Linear Algebra Typeclasses |
20 | Vectors(..), | 20 | Vectors(..), |
21 | Linear(..), | 21 | Linear(..), |
22 | -- * Creation of numeric vectors | 22 | -- * Creation of numeric vectors |
23 | constant, linspace | 23 | constant, linspace |
@@ -86,7 +86,7 @@ instance Vectors Vector (Complex Double) where | |||
86 | ---------------------------------------------------- | 86 | ---------------------------------------------------- |
87 | 87 | ||
88 | -- | Basic element-by-element functions. | 88 | -- | Basic element-by-element functions. |
89 | class (Container c e) => Linear c e where | 89 | class (Element e, AutoReal e, Convert e, Container c) => Linear c e where |
90 | -- | create a structure with a single element | 90 | -- | create a structure with a single element |
91 | scalar :: e -> c e | 91 | scalar :: e -> c e |
92 | scale :: e -> c e -> c e | 92 | scale :: e -> c e -> c e |
@@ -148,7 +148,7 @@ instance Linear Vector (Complex Float) where | |||
148 | equal u v = dim u == dim v && vectorMax (mapVector magnitude (sub u v)) == 0.0 | 148 | equal u v = dim u == dim v && vectorMax (mapVector magnitude (sub u v)) == 0.0 |
149 | scalar x = fromList [x] | 149 | scalar x = fromList [x] |
150 | 150 | ||
151 | instance (Linear Vector a, Container Matrix a) => (Linear Matrix a) where | 151 | instance (Linear Vector a, Container Matrix) => (Linear Matrix a) where |
152 | scale x = liftMatrix (scale x) | 152 | scale x = liftMatrix (scale x) |
153 | scaleRecip x = liftMatrix (scaleRecip x) | 153 | scaleRecip x = liftMatrix (scaleRecip x) |
154 | addConstant x = liftMatrix (addConstant x) | 154 | addConstant x = liftMatrix (addConstant x) |
diff --git a/lib/Numeric/LinearAlgebra/Tests.hs b/lib/Numeric/LinearAlgebra/Tests.hs index 5c5135c..e3b6e1f 100644 --- a/lib/Numeric/LinearAlgebra/Tests.hs +++ b/lib/Numeric/LinearAlgebra/Tests.hs | |||
@@ -45,6 +45,8 @@ a ~~ b = fromList a |~| fromList b | |||
45 | 45 | ||
46 | feye n = flipud (ident n) :: Matrix Double | 46 | feye n = flipud (ident n) :: Matrix Double |
47 | 47 | ||
48 | ----------------------------------------------------------- | ||
49 | |||
48 | detTest1 = det m == 26 | 50 | detTest1 = det m == 26 |
49 | && det mc == 38 :+ (-3) | 51 | && det mc == 38 :+ (-3) |
50 | && det (feye 2) == -1 | 52 | && det (feye 2) == -1 |
@@ -314,17 +316,27 @@ runTests n = do | |||
314 | test (expmDiagProp . cSqWC) | 316 | test (expmDiagProp . cSqWC) |
315 | putStrLn "------ fft" | 317 | putStrLn "------ fft" |
316 | test (\v -> ifft (fft v) |~| v) | 318 | test (\v -> ifft (fft v) |~| v) |
317 | putStrLn "------ vector operations" | 319 | putStrLn "------ vector operations - Double" |
318 | test (\u -> sin u ^ 2 + cos u ^ 2 |~| (1::RM)) | 320 | test (\u -> sin u ^ 2 + cos u ^ 2 |~| (1::RM)) |
319 | test $ (\u -> sin u ^ 2 + cos u ^ 2 |~| (1::CM)) . liftMatrix makeUnitary | 321 | test $ (\u -> sin u ^ 2 + cos u ^ 2 |~| (1::CM)) . liftMatrix makeUnitary |
320 | test (\u -> sin u ** 2 + cos u ** 2 |~| (1::RM)) | 322 | test (\u -> sin u ** 2 + cos u ** 2 |~| (1::RM)) |
321 | test (\u -> cos u * tan u |~| sin (u::RM)) | 323 | test (\u -> cos u * tan u |~| sin (u::RM)) |
322 | test $ (\u -> cos u * tan u |~| sin (u::CM)) . liftMatrix makeUnitary | 324 | test $ (\u -> cos u * tan u |~| sin (u::CM)) . liftMatrix makeUnitary |
325 | putStrLn "------ vector operations - Float" | ||
326 | test (\u -> sin u ^ 2 + cos u ^ 2 |~~| (1::FM)) | ||
327 | test $ (\u -> sin u ^ 2 + cos u ^ 2 |~~| (1::ZM)) . liftMatrix makeUnitary | ||
328 | test (\u -> sin u ** 2 + cos u ** 2 |~~| (1::FM)) | ||
329 | test (\u -> cos u * tan u |~~| sin (u::FM)) | ||
330 | test $ (\u -> cos u * tan u |~~| sin (u::ZM)) . liftMatrix makeUnitary | ||
323 | putStrLn "------ read . show" | 331 | putStrLn "------ read . show" |
324 | test (\m -> (m::RM) == read (show m)) | 332 | test (\m -> (m::RM) == read (show m)) |
325 | test (\m -> (m::CM) == read (show m)) | 333 | test (\m -> (m::CM) == read (show m)) |
326 | test (\m -> toRows (m::RM) == read (show (toRows m))) | 334 | test (\m -> toRows (m::RM) == read (show (toRows m))) |
327 | test (\m -> toRows (m::CM) == read (show (toRows m))) | 335 | test (\m -> toRows (m::CM) == read (show (toRows m))) |
336 | test (\m -> (m::FM) == read (show m)) | ||
337 | test (\m -> (m::ZM) == read (show m)) | ||
338 | test (\m -> toRows (m::FM) == read (show (toRows m))) | ||
339 | test (\m -> toRows (m::ZM) == read (show (toRows m))) | ||
328 | putStrLn "------ some unit tests" | 340 | putStrLn "------ some unit tests" |
329 | _ <- runTestTT $ TestList | 341 | _ <- runTestTT $ TestList |
330 | [ utest "1E5 rots" rotTest | 342 | [ utest "1E5 rots" rotTest |
@@ -358,6 +370,11 @@ runTests n = do | |||
358 | ] | 370 | ] |
359 | return () | 371 | return () |
360 | 372 | ||
373 | |||
374 | -- single precision approximate equality | ||
375 | infixl 4 |~~| | ||
376 | a |~~| b = a :~6~: b | ||
377 | |||
361 | makeUnitary v | realPart n > 1 = v / scalar n | 378 | makeUnitary v | realPart n > 1 = v / scalar n |
362 | | otherwise = v | 379 | | otherwise = v |
363 | where n = sqrt (conj v <.> v) | 380 | where n = sqrt (conj v <.> v) |
diff --git a/lib/Numeric/LinearAlgebra/Tests/Instances.hs b/lib/Numeric/LinearAlgebra/Tests/Instances.hs index bfe6871..ad59b25 100644 --- a/lib/Numeric/LinearAlgebra/Tests/Instances.hs +++ b/lib/Numeric/LinearAlgebra/Tests/Instances.hs | |||
@@ -22,12 +22,11 @@ module Numeric.LinearAlgebra.Tests.Instances( | |||
22 | SqWC(..), rSqWC, cSqWC, | 22 | SqWC(..), rSqWC, cSqWC, |
23 | PosDef(..), rPosDef, cPosDef, | 23 | PosDef(..), rPosDef, cPosDef, |
24 | Consistent(..), rConsist, cConsist, | 24 | Consistent(..), rConsist, cConsist, |
25 | RM,CM, rM,cM | 25 | RM,CM, rM,cM, |
26 | FM,ZM, fM,zM | ||
26 | ) where | 27 | ) where |
27 | 28 | ||
28 | 29 | ||
29 | |||
30 | |||
31 | import Numeric.LinearAlgebra | 30 | import Numeric.LinearAlgebra |
32 | import Control.Monad(replicateM) | 31 | import Control.Monad(replicateM) |
33 | #include "quickCheckCompat.h" | 32 | #include "quickCheckCompat.h" |
@@ -212,9 +211,15 @@ instance (Field a, Arbitrary a) => Arbitrary (Consistent a) where | |||
212 | 211 | ||
213 | type RM = Matrix Double | 212 | type RM = Matrix Double |
214 | type CM = Matrix (Complex Double) | 213 | type CM = Matrix (Complex Double) |
214 | type FM = Matrix Float | ||
215 | type ZM = Matrix (Complex Float) | ||
216 | |||
215 | 217 | ||
216 | rM m = m :: RM | 218 | rM m = m :: RM |
217 | cM m = m :: CM | 219 | cM m = m :: CM |
220 | fM m = m :: FM | ||
221 | zM m = m :: ZM | ||
222 | |||
218 | 223 | ||
219 | rHer (Her m) = m :: RM | 224 | rHer (Her m) = m :: RM |
220 | cHer (Her m) = m :: CM | 225 | cHer (Her m) = m :: CM |