diff options
Diffstat (limited to 'lib/Numeric')
-rw-r--r-- | lib/Numeric/Container.hs | 6 | ||||
-rw-r--r-- | lib/Numeric/ContainerBoot.hs | 89 | ||||
-rw-r--r-- | lib/Numeric/GSL/Fitting.hs | 2 | ||||
-rw-r--r-- | lib/Numeric/LinearAlgebra/Algorithms.hs | 15 |
4 files changed, 12 insertions, 100 deletions
diff --git a/lib/Numeric/Container.hs b/lib/Numeric/Container.hs index 90155fe..eded19c 100644 --- a/lib/Numeric/Container.hs +++ b/lib/Numeric/Container.hs | |||
@@ -59,11 +59,7 @@ module Numeric.Container ( | |||
59 | readMatrix, | 59 | readMatrix, |
60 | fscanfVector, fprintfVector, freadVector, fwriteVector, | 60 | fscanfVector, fprintfVector, freadVector, fwriteVector, |
61 | -- * Experimental | 61 | -- * Experimental |
62 | build', konst', | 62 | build', konst' |
63 | -- * Deprecated | ||
64 | (.*),(*/),(<|>),(<->), | ||
65 | vectorMax,vectorMin, | ||
66 | vectorMaxIndex, vectorMinIndex | ||
67 | ) where | 63 | ) where |
68 | 64 | ||
69 | import Data.Packed | 65 | import Data.Packed |
diff --git a/lib/Numeric/ContainerBoot.hs b/lib/Numeric/ContainerBoot.hs index a605545..d913435 100644 --- a/lib/Numeric/ContainerBoot.hs +++ b/lib/Numeric/ContainerBoot.hs | |||
@@ -3,6 +3,7 @@ | |||
3 | {-# LANGUAGE FlexibleInstances #-} | 3 | {-# LANGUAGE FlexibleInstances #-} |
4 | {-# LANGUAGE MultiParamTypeClasses #-} | 4 | {-# LANGUAGE MultiParamTypeClasses #-} |
5 | {-# LANGUAGE UndecidableInstances #-} | 5 | {-# LANGUAGE UndecidableInstances #-} |
6 | {-# LANGUAGE PolyKinds #-} | ||
6 | 7 | ||
7 | ----------------------------------------------------------------------------- | 8 | ----------------------------------------------------------------------------- |
8 | -- | | 9 | -- | |
@@ -37,11 +38,7 @@ module Numeric.ContainerBoot ( | |||
37 | IndexOf, | 38 | IndexOf, |
38 | module Data.Complex, | 39 | module Data.Complex, |
39 | -- * Experimental | 40 | -- * Experimental |
40 | build', konst', | 41 | build', konst' |
41 | -- * Deprecated | ||
42 | (.*),(*/),(<|>),(<->), | ||
43 | vectorMax,vectorMin, | ||
44 | vectorMaxIndex, vectorMinIndex | ||
45 | ) where | 42 | ) where |
46 | 43 | ||
47 | import Data.Packed | 44 | import Data.Packed |
@@ -49,7 +46,7 @@ import Data.Packed.ST as ST | |||
49 | import Numeric.Conversion | 46 | import Numeric.Conversion |
50 | import Data.Packed.Internal | 47 | import Data.Packed.Internal |
51 | import Numeric.GSL.Vector | 48 | import Numeric.GSL.Vector |
52 | 49 | import Foreign.C.Types(CInt(..)) | |
53 | import Data.Complex | 50 | import Data.Complex |
54 | import Control.Monad(ap) | 51 | import Control.Monad(ap) |
55 | 52 | ||
@@ -526,86 +523,6 @@ conjugateC :: Vector (Complex Double) -> Vector (Complex Double) | |||
526 | conjugateC = conjugateAux c_conjugateC | 523 | conjugateC = conjugateAux c_conjugateC |
527 | foreign import ccall "conjugateC" c_conjugateC :: TCVCV | 524 | foreign import ccall "conjugateC" c_conjugateC :: TCVCV |
528 | 525 | ||
529 | ---------------------------------------------------- | ||
530 | |||
531 | {-# DEPRECATED (.*) "use scale a x or scalar a * x" #-} | ||
532 | |||
533 | -- -- | @x .* a = scale x a@ | ||
534 | -- (.*) :: (Linear c a) => a -> c a -> c a | ||
535 | infixl 7 .* | ||
536 | a .* x = scale a x | ||
537 | |||
538 | ---------------------------------------------------- | ||
539 | |||
540 | {-# DEPRECATED (*/) "use scale (recip a) x or x / scalar a" #-} | ||
541 | |||
542 | -- -- | @a *\/ x = scale (recip x) a@ | ||
543 | -- (*/) :: (Linear c a) => c a -> a -> c a | ||
544 | infixl 7 */ | ||
545 | v */ x = scale (recip x) v | ||
546 | |||
547 | |||
548 | ------------------------------------------------ | ||
549 | |||
550 | {-# DEPRECATED (<|>) "define operator a & b = fromBlocks[[a,b]] and use asRow/asColumn to join vectors" #-} | ||
551 | {-# DEPRECATED (<->) "define operator a // b = fromBlocks[[a],[b]] and use asRow/asColumn to join vectors" #-} | ||
552 | |||
553 | class Joinable a b where | ||
554 | joinH :: Element t => a t -> b t -> Matrix t | ||
555 | joinV :: Element t => a t -> b t -> Matrix t | ||
556 | |||
557 | instance Joinable Matrix Matrix where | ||
558 | joinH m1 m2 = fromBlocks [[m1,m2]] | ||
559 | joinV m1 m2 = fromBlocks [[m1],[m2]] | ||
560 | |||
561 | instance Joinable Matrix Vector where | ||
562 | joinH m v = joinH m (asColumn v) | ||
563 | joinV m v = joinV m (asRow v) | ||
564 | |||
565 | instance Joinable Vector Matrix where | ||
566 | joinH v m = joinH (asColumn v) m | ||
567 | joinV v m = joinV (asRow v) m | ||
568 | |||
569 | infixl 4 <|> | ||
570 | infixl 3 <-> | ||
571 | |||
572 | {-- - | Horizontal concatenation of matrices and vectors: | ||
573 | |||
574 | @> (ident 3 \<-\> 3 * ident 3) \<|\> fromList [1..6.0] | ||
575 | (6><4) | ||
576 | [ 1.0, 0.0, 0.0, 1.0 | ||
577 | , 0.0, 1.0, 0.0, 2.0 | ||
578 | , 0.0, 0.0, 1.0, 3.0 | ||
579 | , 3.0, 0.0, 0.0, 4.0 | ||
580 | , 0.0, 3.0, 0.0, 5.0 | ||
581 | , 0.0, 0.0, 3.0, 6.0 ]@ | ||
582 | -} | ||
583 | -- (<|>) :: (Element t, Joinable a b) => a t -> b t -> Matrix t | ||
584 | a <|> b = joinH a b | ||
585 | |||
586 | -- -- | Vertical concatenation of matrices and vectors. | ||
587 | -- (<->) :: (Element t, Joinable a b) => a t -> b t -> Matrix t | ||
588 | a <-> b = joinV a b | ||
589 | |||
590 | ------------------------------------------------------------------- | ||
591 | |||
592 | {-# DEPRECATED vectorMin "use minElement" #-} | ||
593 | vectorMin :: (Container Vector t, Element t) => Vector t -> t | ||
594 | vectorMin = minElement | ||
595 | |||
596 | {-# DEPRECATED vectorMax "use maxElement" #-} | ||
597 | vectorMax :: (Container Vector t, Element t) => Vector t -> t | ||
598 | vectorMax = maxElement | ||
599 | |||
600 | |||
601 | {-# DEPRECATED vectorMaxIndex "use minIndex" #-} | ||
602 | vectorMaxIndex :: Vector Double -> Int | ||
603 | vectorMaxIndex = round . toScalarR MaxIdx | ||
604 | |||
605 | {-# DEPRECATED vectorMinIndex "use maxIndex" #-} | ||
606 | vectorMinIndex :: Vector Double -> Int | ||
607 | vectorMinIndex = round . toScalarR MinIdx | ||
608 | |||
609 | ----------------------------------------------------- | 526 | ----------------------------------------------------- |
610 | 527 | ||
611 | class Build f where | 528 | class Build f where |
diff --git a/lib/Numeric/GSL/Fitting.hs b/lib/Numeric/GSL/Fitting.hs index 337dc6a..da5c0fc 100644 --- a/lib/Numeric/GSL/Fitting.hs +++ b/lib/Numeric/GSL/Fitting.hs | |||
@@ -54,7 +54,7 @@ import Numeric.LinearAlgebra | |||
54 | import Numeric.GSL.Internal | 54 | import Numeric.GSL.Internal |
55 | 55 | ||
56 | import Foreign.Ptr(FunPtr, freeHaskellFunPtr) | 56 | import Foreign.Ptr(FunPtr, freeHaskellFunPtr) |
57 | import Foreign.C.Types(CInt) | 57 | import Foreign.C.Types(CInt(..)) |
58 | import System.IO.Unsafe(unsafePerformIO) | 58 | import System.IO.Unsafe(unsafePerformIO) |
59 | 59 | ||
60 | ------------------------------------------------------------------------- | 60 | ------------------------------------------------------------------------- |
diff --git a/lib/Numeric/LinearAlgebra/Algorithms.hs b/lib/Numeric/LinearAlgebra/Algorithms.hs index bea33ea..9806d6f 100644 --- a/lib/Numeric/LinearAlgebra/Algorithms.hs +++ b/lib/Numeric/LinearAlgebra/Algorithms.hs | |||
@@ -3,6 +3,7 @@ | |||
3 | {-# LANGUAGE MultiParamTypeClasses #-} | 3 | {-# LANGUAGE MultiParamTypeClasses #-} |
4 | {-# LANGUAGE UndecidableInstances #-} | 4 | {-# LANGUAGE UndecidableInstances #-} |
5 | {-# LANGUAGE TypeFamilies #-} | 5 | {-# LANGUAGE TypeFamilies #-} |
6 | |||
6 | ----------------------------------------------------------------------------- | 7 | ----------------------------------------------------------------------------- |
7 | {- | | 8 | {- | |
8 | Module : Numeric.LinearAlgebra.Algorithms | 9 | Module : Numeric.LinearAlgebra.Algorithms |
@@ -82,7 +83,7 @@ import Data.Packed.Matrix | |||
82 | import Numeric.LinearAlgebra.LAPACK as LAPACK | 83 | import Numeric.LinearAlgebra.LAPACK as LAPACK |
83 | import Data.List(foldl1') | 84 | import Data.List(foldl1') |
84 | import Data.Array | 85 | import Data.Array |
85 | import Numeric.ContainerBoot hiding ((.*),(*/)) | 86 | import Numeric.ContainerBoot |
86 | 87 | ||
87 | 88 | ||
88 | {- | Class used to define generic linear algebra computations for both real and complex matrices. Only double precision is supported in this version (we can | 89 | {- | Class used to define generic linear algebra computations for both real and complex matrices. Only double precision is supported in this version (we can |
@@ -567,7 +568,11 @@ epslist = [ (fromIntegral k, golubeps k k) | k <- [1..]] | |||
567 | 568 | ||
568 | geps delta = head [ k | (k,g) <- epslist, g<delta] | 569 | geps delta = head [ k | (k,g) <- epslist, g<delta] |
569 | 570 | ||
570 | expGolub m = iterate msq f !! j | 571 | {- | Matrix exponential. It uses a direct translation of Algorithm 11.3.1 in Golub & Van Loan, |
572 | based on a scaled Pade approximation. | ||
573 | -} | ||
574 | expm :: Field t => Matrix t -> Matrix t | ||
575 | expm m = iterate msq f !! j | ||
571 | where j = max 0 $ floor $ logBase 2 $ pnorm Infinity m | 576 | where j = max 0 $ floor $ logBase 2 $ pnorm Infinity m |
572 | a = m */ fromIntegral ((2::Int)^j) | 577 | a = m */ fromIntegral ((2::Int)^j) |
573 | q = geps eps -- 7 steps | 578 | q = geps eps -- 7 steps |
@@ -587,12 +592,6 @@ expGolub m = iterate msq f !! j | |||
587 | (.*) = scale | 592 | (.*) = scale |
588 | (|+|) = add | 593 | (|+|) = add |
589 | 594 | ||
590 | {- | Matrix exponential. It uses a direct translation of Algorithm 11.3.1 in Golub & Van Loan, | ||
591 | based on a scaled Pade approximation. | ||
592 | -} | ||
593 | expm :: Field t => Matrix t -> Matrix t | ||
594 | expm = expGolub | ||
595 | |||
596 | -------------------------------------------------------------- | 595 | -------------------------------------------------------------- |
597 | 596 | ||
598 | {- | Matrix square root. Currently it uses a simple iterative algorithm described in Wikipedia. | 597 | {- | Matrix square root. Currently it uses a simple iterative algorithm described in Wikipedia. |