summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--packages/base/hmatrix.cabal1
-rw-r--r--packages/base/src/Numeric/HMatrix.hs2
-rw-r--r--packages/base/src/Numeric/LinearAlgebra/Data.hs16
-rw-r--r--packages/base/src/Numeric/LinearAlgebra/Util.hs14
-rw-r--r--packages/base/src/Numeric/LinearAlgebra/Util/Static.hs70
5 files changed, 97 insertions, 6 deletions
diff --git a/packages/base/hmatrix.cabal b/packages/base/hmatrix.cabal
index 01e3c26..e958de0 100644
--- a/packages/base/hmatrix.cabal
+++ b/packages/base/hmatrix.cabal
@@ -67,6 +67,7 @@ library
67 Numeric.LinearAlgebra.Random 67 Numeric.LinearAlgebra.Random
68 Numeric.Conversion 68 Numeric.Conversion
69 Numeric.Sparse 69 Numeric.Sparse
70 Numeric.LinearAlgebra.Util.Static
70 71
71 C-sources: src/C/lapack-aux.c 72 C-sources: src/C/lapack-aux.c
72 src/C/vector-aux.c 73 src/C/vector-aux.c
diff --git a/packages/base/src/Numeric/HMatrix.hs b/packages/base/src/Numeric/HMatrix.hs
index a56c3d2..d5c66fb 100644
--- a/packages/base/src/Numeric/HMatrix.hs
+++ b/packages/base/src/Numeric/HMatrix.hs
@@ -134,7 +134,7 @@ module Numeric.HMatrix (
134 -- * Misc 134 -- * Misc
135 meanCov, peps, relativeError, haussholder, optimiseMult, dot, udot, mXm, mXv, smXv, (<>), (◇), Seed, checkT, 135 meanCov, peps, relativeError, haussholder, optimiseMult, dot, udot, mXm, mXv, smXv, (<>), (◇), Seed, checkT,
136 -- * Auxiliary classes 136 -- * Auxiliary classes
137 Element, Container, Product, Contraction, LSDiv, 137 Element, Container, Product, Numeric, Contraction, LSDiv,
138 Complexable, RealElement, 138 Complexable, RealElement,
139 RealOf, ComplexOf, SingleOf, DoubleOf, 139 RealOf, ComplexOf, SingleOf, DoubleOf,
140 IndexOf, 140 IndexOf,
diff --git a/packages/base/src/Numeric/LinearAlgebra/Data.hs b/packages/base/src/Numeric/LinearAlgebra/Data.hs
index 89bebbe..3128a24 100644
--- a/packages/base/src/Numeric/LinearAlgebra/Data.hs
+++ b/packages/base/src/Numeric/LinearAlgebra/Data.hs
@@ -48,16 +48,20 @@ module Numeric.LinearAlgebra.Data(
48 -- * Find elements 48 -- * Find elements
49 find, maxIndex, minIndex, maxElement, minElement, atIndex, 49 find, maxIndex, minIndex, maxElement, minElement, atIndex,
50 50
51 -- * Sparse
52 SMatrix, AssocMatrix, mkCSR, toDense,
53 mkDiag,
54
55 -- * Static dimensions
56
57 Static, ddata, R, vect0, sScalar, vect2, vect3, (&),
58
51 -- * IO 59 -- * IO
52 disp, 60 disp,
53 loadMatrix, saveMatrix, 61 loadMatrix, saveMatrix,
54 latexFormat, 62 latexFormat,
55 dispf, disps, dispcf, format, 63 dispf, disps, dispcf, format,
56 64
57 -- * Sparse
58 SMatrix, AssocMatrix, mkCSR, toDense,
59 mkDiag,
60
61-- * Conversion 65-- * Conversion
62 Convert(..), 66 Convert(..),
63 67
@@ -75,7 +79,9 @@ module Numeric.LinearAlgebra.Data(
75import Data.Packed.Vector 79import Data.Packed.Vector
76import Data.Packed.Matrix 80import Data.Packed.Matrix
77import Data.Packed.Numeric 81import Data.Packed.Numeric
78import Numeric.LinearAlgebra.Util 82import Numeric.LinearAlgebra.Util hiding ((&))
79import Data.Complex 83import Data.Complex
80import Numeric.Sparse 84import Numeric.Sparse
85import Numeric.LinearAlgebra.Util.Static
86
81 87
diff --git a/packages/base/src/Numeric/LinearAlgebra/Util.hs b/packages/base/src/Numeric/LinearAlgebra/Util.hs
index a7d6946..a319785 100644
--- a/packages/base/src/Numeric/LinearAlgebra/Util.hs
+++ b/packages/base/src/Numeric/LinearAlgebra/Util.hs
@@ -28,6 +28,7 @@ module Numeric.LinearAlgebra.Util(
28 (&), (¦), (——), (#), 28 (&), (¦), (——), (#),
29 (?), (¿), 29 (?), (¿),
30 Indexable(..), size, 30 Indexable(..), size,
31 Numeric,
31 rand, randn, 32 rand, randn,
32 cross, 33 cross,
33 norm, 34 norm,
@@ -101,6 +102,19 @@ mat
101 -> Matrix ℝ 102 -> Matrix ℝ
102mat c = reshape c . fromList 103mat c = reshape c . fromList
103 104
105
106
107class ( Container Vector t
108 , Container Matrix t
109 , Konst t Int Vector
110 , Konst t (Int,Int) Matrix
111 ) => Numeric t
112
113instance Numeric Double
114instance Numeric (Complex Double)
115
116
117
104{- | print a real matrix with given number of digits after the decimal point 118{- | print a real matrix with given number of digits after the decimal point
105 119
106>>> disp 5 $ ident 2 / 3 120>>> disp 5 $ ident 2 / 3
diff --git a/packages/base/src/Numeric/LinearAlgebra/Util/Static.hs b/packages/base/src/Numeric/LinearAlgebra/Util/Static.hs
new file mode 100644
index 0000000..a3f8eb0
--- /dev/null
+++ b/packages/base/src/Numeric/LinearAlgebra/Util/Static.hs
@@ -0,0 +1,70 @@
1{-# LANGUAGE DataKinds #-}
2{-# LANGUAGE KindSignatures #-}
3{-# LANGUAGE GeneralizedNewtypeDeriving #-}
4{-# LANGUAGE MultiParamTypeClasses #-}
5{-# LANGUAGE FlexibleContexts #-}
6{-# LANGUAGE ScopedTypeVariables #-}
7{-# LANGUAGE EmptyDataDecls #-}
8{-# LANGUAGE Rank2Types #-}
9{-# LANGUAGE FlexibleInstances #-}
10{-# LANGUAGE TypeOperators #-}
11
12module Numeric.LinearAlgebra.Util.Static(
13 Static (ddata),
14 R,
15 vect0, sScalar, vect2, vect3, (&)
16) where
17
18
19import GHC.TypeLits
20import Data.Packed.Numeric
21import Numeric.Vector()
22import Numeric.LinearAlgebra.Util(Numeric,ℝ)
23
24lift1F :: (Vector t -> Vector t) -> Static n (Vector t) -> Static n (Vector t)
25lift1F f (Static v) = Static (f v)
26
27lift2F :: (Vector t -> Vector t -> Vector t) -> Static n (Vector t) -> Static n (Vector t) -> Static n (Vector t)
28lift2F f (Static u) (Static v) = Static (f u v)
29
30newtype Static (n :: Nat) t = Static { ddata :: t } deriving Show
31
32type R n = Static n (Vector ℝ)
33
34
35infixl 4 &
36(&) :: R n -> ℝ -> R (n+1)
37Static v & x = Static (vjoin [v, scalar x])
38
39vect0 :: R 0
40vect0 = Static (fromList[])
41
42sScalar :: ℝ -> R 1
43sScalar = Static . scalar
44
45
46vect2 :: ℝ -> ℝ -> R 2
47vect2 x1 x2 = Static (fromList [x1,x2])
48
49vect3 :: ℝ -> ℝ -> ℝ -> R 3
50vect3 x1 x2 x3 = Static (fromList [x1,x2,x3])
51
52
53
54
55
56
57instance forall n t . (KnownNat n, Num (Vector t), Numeric t )=> Num (Static n (Vector t))
58 where
59 (+) = lift2F add
60 (*) = lift2F mul
61 (-) = lift2F sub
62 abs = lift1F abs
63 signum = lift1F signum
64 negate = lift1F (scale (-1))
65 fromInteger x = Static (konst (fromInteger x) d)
66 where
67 d = fromIntegral . natVal $ (undefined :: Proxy n)
68
69data Proxy :: Nat -> *
70