summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--CHANGELOG6
-rw-r--r--examples/multiply.hs66
-rw-r--r--hmatrix.cabal3
-rw-r--r--lib/Numeric/Container.hs99
-rw-r--r--packages/tests/src/Numeric/LinearAlgebra/Tests/Instances.hs6
5 files changed, 81 insertions, 99 deletions
diff --git a/CHANGELOG b/CHANGELOG
index dea29a9..8388e5e 100644
--- a/CHANGELOG
+++ b/CHANGELOG
@@ -2,12 +2,12 @@
2-------- 2--------
3 3
4 * join deprecated, use vjoin 4 * join deprecated, use vjoin
5 * dot and (<.>) deprecated, use udot or (×) 5 * dot and (<.>) deprecated, use udot or (<>)
6 6
7 * added udot (unconjugated dot product) 7 * added udot (unconjugated dot product)
8 * added () = cdot, which conjugates the first input vector 8 * added (·) = cdot, which conjugates the first input vector
9 9
10 * added a general multiplication operator (×) 10 * more general multiplication operator (<>)
11 11
12 * improved build and konst 12 * improved build and konst
13 13
diff --git a/examples/multiply.hs b/examples/multiply.hs
index fbfb9d7..572961c 100644
--- a/examples/multiply.hs
+++ b/examples/multiply.hs
@@ -6,26 +6,13 @@
6-- , OverlappingInstances 6-- , OverlappingInstances
7 , UndecidableInstances #-} 7 , UndecidableInstances #-}
8 8
9import Numeric.LinearAlgebra hiding (Contraction(..)) 9import Numeric.LinearAlgebra
10 10
11class Scaling a b c | a b -> c where 11class Scaling a b c | a b -> c where
12 -- ^ 0x22C5 8901 DOT OPERATOR, scaling 12 -- ^ 0x22C5 8901 DOT OPERATOR, scaling
13 infixl 7 ⋅ 13 infixl 7 ⋅
14 (⋅) :: a -> b -> c 14 (⋅) :: a -> b -> c
15 15
16class Contraction a b c | a b -> c where
17 -- ^ 0x00D7 215 MULTIPLICATION SIGN ×, contraction
18 infixl 7 ×
19 (×) :: a -> b -> c
20
21class Outer a b c | a b -> c where
22 -- ^ 0x2297 8855 CIRCLED TIMES ⊗, outer product (not associative)
23 infixl 7 ⊗
24 (⊗) :: a -> b -> c
25
26
27-------
28
29instance (Num t) => Scaling t t t where 16instance (Num t) => Scaling t t t where
30 (⋅) = (*) 17 (⋅) = (*)
31 18
@@ -42,37 +29,49 @@ instance Container Vector t => Scaling (Matrix t) t (Matrix t) where
42 (⋅) = flip scale 29 (⋅) = flip scale
43 30
44 31
45instance Product t => Contraction (Vector t) (Vector t) t where 32class Mul a b c | a b -> c, a c -> b, b c -> a where
33 -- ^ 0x00D7 215 MULTIPLICATION SIGN ×, contraction
34 infixl 7 ×
35 (×) :: a -> b -> c
36
37
38-------
39
40
41
42instance Product t => Mul (Vector t) (Vector t) t where
46 (×) = udot 43 (×) = udot
47 44
48instance Product t => Contraction (Matrix t) (Vector t) (Vector t) where 45instance Product t => Mul (Matrix t) (Vector t) (Vector t) where
49 (×) = mXv 46 (×) = mXv
50 47
51instance Product t => Contraction (Vector t) (Matrix t) (Vector t) where 48instance Product t => Mul (Vector t) (Matrix t) (Vector t) where
52 (×) = vXm 49 (×) = vXm
53 50
54instance Product t => Contraction (Matrix t) (Matrix t) (Matrix t) where 51instance Product t => Mul (Matrix t) (Matrix t) (Matrix t) where
55 (×) = mXm 52 (×) = mXm
56 53
57 54
58--instance Scaling a b c => Contraction a b c where 55--instance Scaling a b c => Contraction a b c where
59-- (×) = (⋅) 56-- (×) = (⋅)
60 57
61----- 58--------------------------------------------------------------------------------
62
63instance Product t => Outer (Vector t) (Vector t) (Matrix t) where
64 (⊗) = outer
65 59
66instance Product t => Outer (Vector t) (Matrix t) (Matrix t) where 60class Outer a
67 v ⊗ m = kronecker (asColumn v) m 61 where
62 infixl 7 ⊗
63 -- | unicode 0x2297 8855 CIRCLED TIMES ⊗
64 --
65 -- vector outer product and matrix Kronecker product
66 (⊗) :: Product t => a t -> a t -> Matrix t
68 67
69instance Product t => Outer (Matrix t) (Vector t) (Matrix t) where 68instance Outer Vector where
70 m v = kronecker m (asRow v) 69 () = outer
71 70
72instance Product t => Outer (Matrix t) (Matrix t) (Matrix t) where 71instance Outer Matrix where
73 (⊗) = kronecker 72 (⊗) = kronecker
74 73
75----- 74--------------------------------------------------------------------------------
76 75
77 76
78v = 3 |> [1..] :: Vector Double 77v = 3 |> [1..] :: Vector Double
@@ -83,18 +82,23 @@ s = 3 :: Double
83 82
84a = s ⋅ v × m × m × v ⋅ s 83a = s ⋅ v × m × m × v ⋅ s
85 84
86b = (v ⊗ m) ⊗ (v ⊗ m) 85--b = (v ⊗ m) ⊗ (v ⊗ m)
87 86
88c = v ⊗ m ⊗ v ⊗ m 87--c = v ⊗ m ⊗ v ⊗ m
89 88
90d = s ⋅ (3 |> [10,20..] :: Vector Double) 89d = s ⋅ (3 |> [10,20..] :: Vector Double)
91 90
91u = fromList [3,0,5]
92w = konst 1 (2,3) :: Matrix Double
93
92main = do 94main = do
93 print $ (scale s v <> m) `udot` v 95 print $ (scale s v <> m) `udot` v
94 print $ scale s v `udot` (m <> v) 96 print $ scale s v `udot` (m <> v)
95 print $ s * ((v <> m) `udot` v) 97 print $ s * ((v <> m) `udot` v)
96 print $ s ⋅ v × m × v 98 print $ s ⋅ v × m × v
97 print a 99 print a
98 print (b == c) 100-- print (b == c)
99 print d 101 print d
102 print $ asColumn u ⊗ w
103 print $ w ⊗ asColumn u
100 104
diff --git a/hmatrix.cabal b/hmatrix.cabal
index e9107f3..127f359 100644
--- a/hmatrix.cabal
+++ b/hmatrix.cabal
@@ -20,6 +20,9 @@ Description: Purely functional interface to basic linear algebra
20 - "Numeric.LinearAlgebra.Algorithms": matrix computations 20 - "Numeric.LinearAlgebra.Algorithms": matrix computations
21 . 21 .
22 - "Numeric.LinearAlgebra": everything + instances of standard Haskell numeric classes 22 - "Numeric.LinearAlgebra": everything + instances of standard Haskell numeric classes
23 .
24 - "Numeric.LinearAlgebra.Util": additional functions
25
23Category: Math 26Category: Math
24tested-with: GHC ==7.8 27tested-with: GHC ==7.8
25 28
diff --git a/lib/Numeric/Container.hs b/lib/Numeric/Container.hs
index aac8c10..a612aa1 100644
--- a/lib/Numeric/Container.hs
+++ b/lib/Numeric/Container.hs
@@ -38,7 +38,7 @@ module Numeric.Container (
38 Product(..), 38 Product(..),
39 Contraction(..), 39 Contraction(..),
40 optimiseMult, 40 optimiseMult,
41 mXm,mXv,vXm,Mul(..),LSDiv(..), cdot, (), dot, (<.>), 41 mXm,mXv,vXm,LSDiv(..), cdot, (·), dot, (<.>),
42 outer, kronecker, 42 outer, kronecker,
43 -- * Random numbers 43 -- * Random numbers
44 RandDist(..), 44 RandDist(..),
@@ -55,7 +55,7 @@ module Numeric.Container (
55 55
56 IndexOf, 56 IndexOf,
57 module Data.Complex, 57 module Data.Complex,
58 -- * Input / Output 58 -- * IO
59 dispf, disps, dispcf, vecdisp, latexFormat, format, 59 dispf, disps, dispcf, vecdisp, latexFormat, format,
60 loadMatrix, saveMatrix, fromFile, fileDimensions, 60 loadMatrix, saveMatrix, fromFile, fileDimensions,
61 readMatrix, 61 readMatrix,
@@ -101,19 +101,23 @@ cdot u v = udot (conj u) v
101 101
102-------------------------------------------------------- 102--------------------------------------------------------
103 103
104class Mul a b c | a b -> c where 104class Contraction a b c | a b -> c, a c -> b, b c -> a
105 infixl 7 <> 105 where
106 -- | Matrix-matrix, matrix-vector, and vector-matrix products. 106 infixl 7 <>
107 (<>) :: Product t => a t -> b t -> c t 107 -- | matrix-matrix product, matrix-vector product, unconjugated dot product
108 (<>) :: a -> b -> c
108 109
109instance Mul Matrix Matrix Matrix where 110instance Product t => Contraction (Vector t) (Vector t) t where
110 (<>) = mXm 111 (<>) = udot
111 112
112instance Mul Matrix Vector Vector where 113instance Product t => Contraction (Matrix t) (Vector t) (Vector t) where
113 (<>) m v = flatten $ m <> asColumn v 114 (<>) = mXv
114 115
115instance Mul Vector Matrix Vector where 116instance Product t => Contraction (Vector t) (Matrix t) (Vector t) where
116 (<>) v m = flatten $ asRow v <> m 117 (<>) = vXm
118
119instance Product t => Contraction (Matrix t) (Matrix t) (Matrix t) where
120 (<>) = mXm
117 121
118-------------------------------------------------------- 122--------------------------------------------------------
119 123
@@ -130,55 +134,12 @@ instance LSDiv Matrix Matrix where
130 134
131-------------------------------------------------------- 135--------------------------------------------------------
132 136
133-- | Compute mean vector and covariance matrix of the rows of a matrix. 137-- | dot product : @u · v = 'cdot' u v@
134meanCov :: Matrix Double -> (Vector Double, Matrix Double) 138--
135meanCov x = (med,cov) where 139-- unicode 0x00b7, Alt-Gr .
136 r = rows x 140(·) :: (Container Vector t, Product t) => Vector t -> Vector t -> t
137 k = 1 / fromIntegral r 141infixl 7 ·
138 med = konst k r `vXm` x 142u · v = cdot u v
139 meds = konst 1 r `outer` med
140 xc = x `sub` meds
141 cov = scale (recip (fromIntegral (r-1))) (trans xc `mXm` xc)
142
143--------------------------------------------------------------------------------
144
145-- | matrix-matrix product, matrix-vector product, unconjugated dot product, and scaling
146class Contraction a b c | a b -> c
147 where
148 -- ^ 0x00d7 multiplication sign
149 infixl 7 ×
150 (×) :: a -> b -> c
151
152instance Product t => Contraction (Vector t) (Vector t) t where
153 (×) = udot
154
155instance Product t => Contraction (Matrix t) (Vector t) (Vector t) where
156 (×) = mXv
157
158instance Product t => Contraction (Vector t) (Matrix t) (Vector t) where
159 (×) = vXm
160
161instance Product t => Contraction (Matrix t) (Matrix t) (Matrix t) where
162 (×) = mXm
163
164instance Container Vector t => Contraction t (Vector t) (Vector t) where
165 (×) = scale
166
167instance Container Vector t => Contraction (Vector t) t (Vector t) where
168 (×) = flip scale
169
170instance Container Matrix t => Contraction t (Matrix t) (Matrix t) where
171 (×) = scale
172
173instance Container Matrix t => Contraction (Matrix t) t (Matrix t) where
174 (×) = flip scale
175
176--------------------------------------------------------------------------------
177
178-- | dot product (0x22C5): @u ⋅ v = 'cdot' u v@
179(⋅) :: (Container Vector t, Product t) => Vector t -> Vector t -> t
180infixl 7 ⋅
181u ⋅ v = cdot u v
182 143
183-------------------------------------------------------------------------------- 144--------------------------------------------------------------------------------
184 145
@@ -195,6 +156,8 @@ instance Container Vector e => Konst e (Int,Int) Matrix
195 where 156 where
196 konst = konst' 157 konst = konst'
197 158
159--------------------------------------------------------------------------------
160
198class Build d f c e | d -> c, c -> d, f -> e, f -> d, f -> c, c e -> f, d e -> f 161class Build d f c e | d -> c, c -> d, f -> e, f -> d, f -> c, c e -> f, d e -> f
199 where 162 where
200 build :: d -> f -> c e 163 build :: d -> f -> c e
@@ -209,11 +172,23 @@ instance Container Matrix e => Build (Int,Int) (e -> e -> e) Matrix e
209 172
210-------------------------------------------------------------------------------- 173--------------------------------------------------------------------------------
211 174
175-- | Compute mean vector and covariance matrix of the rows of a matrix.
176meanCov :: Matrix Double -> (Vector Double, Matrix Double)
177meanCov x = (med,cov) where
178 r = rows x
179 k = 1 / fromIntegral r
180 med = konst k r `vXm` x
181 meds = konst 1 r `outer` med
182 xc = x `sub` meds
183 cov = scale (recip (fromIntegral (r-1))) (trans xc `mXm` xc)
184
185--------------------------------------------------------------------------------
186
212{-# DEPRECATED dot "use udot" #-} 187{-# DEPRECATED dot "use udot" #-}
213dot :: Product e => Vector e -> Vector e -> e 188dot :: Product e => Vector e -> Vector e -> e
214dot = udot 189dot = udot
215 190
216{-# DEPRECATED (<.>) "use udot or (×)" #-} 191{-# DEPRECATED (<.>) "use udot or (<>)" #-}
217infixl 7 <.> 192infixl 7 <.>
218(<.>) :: Product e => Vector e -> Vector e -> e 193(<.>) :: Product e => Vector e -> Vector e -> e
219(<.>) = udot 194(<.>) = udot
diff --git a/packages/tests/src/Numeric/LinearAlgebra/Tests/Instances.hs b/packages/tests/src/Numeric/LinearAlgebra/Tests/Instances.hs
index 647a06c..30bf690 100644
--- a/packages/tests/src/Numeric/LinearAlgebra/Tests/Instances.hs
+++ b/packages/tests/src/Numeric/LinearAlgebra/Tests/Instances.hs
@@ -153,7 +153,7 @@ instance (ArbitraryField a) => Arbitrary (WC a) where
153 n = min r c 153 n = min r c
154 sv' <- replicateM n (choose (1,100)) 154 sv' <- replicateM n (choose (1,100))
155 let s = diagRect 0 (fromList sv') r c 155 let s = diagRect 0 (fromList sv') r c
156 return $ WC (u <> real s <> trans v) 156 return $ WC (u `mXm` real s `mXm` trans v)
157 157
158#if MIN_VERSION_QuickCheck(2,0,0) 158#if MIN_VERSION_QuickCheck(2,0,0)
159#else 159#else
@@ -170,7 +170,7 @@ instance (ArbitraryField a) => Arbitrary (SqWC a) where
170 n = rows m 170 n = rows m
171 sv' <- replicateM n (choose (1,100)) 171 sv' <- replicateM n (choose (1,100))
172 let s = diag (fromList sv') 172 let s = diag (fromList sv')
173 return $ SqWC (u <> real s <> trans v) 173 return $ SqWC (u `mXm` real s `mXm` trans v)
174 174
175#if MIN_VERSION_QuickCheck(2,0,0) 175#if MIN_VERSION_QuickCheck(2,0,0)
176#else 176#else
@@ -188,7 +188,7 @@ instance (ArbitraryField a, Num (Vector a))
188 n = rows m 188 n = rows m
189 l <- replicateM n (choose (0,100)) 189 l <- replicateM n (choose (0,100))
190 let s = diag (fromList l) 190 let s = diag (fromList l)
191 p = v <> real s <> ctrans v 191 p = v `mXm` real s `mXm` ctrans v
192 return $ PosDef (0.5 * p + 0.5 * ctrans p) 192 return $ PosDef (0.5 * p + 0.5 * ctrans p)
193 193
194#if MIN_VERSION_QuickCheck(2,0,0) 194#if MIN_VERSION_QuickCheck(2,0,0)