diff options
-rw-r--r-- | CHANGES | 6 | ||||
-rw-r--r-- | examples/multiply.hs | 100 | ||||
-rw-r--r-- | hmatrix.cabal | 3 | ||||
-rw-r--r-- | lib/Data/Packed/Matrix.hs | 55 | ||||
-rw-r--r-- | lib/Numeric/Container.hs | 2 |
5 files changed, 164 insertions, 2 deletions
@@ -1,3 +1,9 @@ | |||
1 | 0.11.1.0 | ||
2 | ======== | ||
3 | |||
4 | - exported Mul | ||
5 | - mapMatrixWithIndex{,M,M_} | ||
6 | |||
1 | 0.11.0.0 | 7 | 0.11.0.0 |
2 | ======== | 8 | ======== |
3 | 9 | ||
diff --git a/examples/multiply.hs b/examples/multiply.hs new file mode 100644 index 0000000..d7c74ee --- /dev/null +++ b/examples/multiply.hs | |||
@@ -0,0 +1,100 @@ | |||
1 | {-# LANGUAGE UnicodeSyntax | ||
2 | , MultiParamTypeClasses | ||
3 | , FunctionalDependencies | ||
4 | , FlexibleInstances | ||
5 | , FlexibleContexts | ||
6 | -- , OverlappingInstances | ||
7 | , UndecidableInstances #-} | ||
8 | |||
9 | import Numeric.LinearAlgebra | ||
10 | |||
11 | class Scaling a b c | a b -> c where | ||
12 | -- ^ 0x22C5 8901 DOT OPERATOR, scaling | ||
13 | infixl 7 ⋅ | ||
14 | (⋅) :: a -> b -> c | ||
15 | |||
16 | class Contraction a b c | a b -> c where | ||
17 | -- ^ 0x00D7 215 MULTIPLICATION SIGN ×, contraction | ||
18 | infixl 7 × | ||
19 | (×) :: a -> b -> c | ||
20 | |||
21 | class 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 | |||
29 | instance (Num t) => Scaling t t t where | ||
30 | (⋅) = (*) | ||
31 | |||
32 | instance Container Vector t => Scaling t (Vector t) (Vector t) where | ||
33 | (⋅) = scale | ||
34 | |||
35 | instance Container Vector t => Scaling (Vector t) t (Vector t) where | ||
36 | (⋅) = flip scale | ||
37 | |||
38 | instance Container Vector t => Scaling t (Matrix t) (Matrix t) where | ||
39 | (⋅) = scale | ||
40 | |||
41 | instance Container Vector t => Scaling (Matrix t) t (Matrix t) where | ||
42 | (⋅) = flip scale | ||
43 | |||
44 | |||
45 | instance Product t => Contraction (Vector t) (Vector t) t where | ||
46 | (×) = dot | ||
47 | |||
48 | instance Product t => Contraction (Matrix t) (Vector t) (Vector t) where | ||
49 | (×) = mXv | ||
50 | |||
51 | instance Product t => Contraction (Vector t) (Matrix t) (Vector t) where | ||
52 | (×) = vXm | ||
53 | |||
54 | instance Product t => Contraction (Matrix t) (Matrix t) (Matrix t) where | ||
55 | (×) = mXm | ||
56 | |||
57 | |||
58 | --instance Scaling a b c => Contraction a b c where | ||
59 | -- (×) = (⋅) | ||
60 | |||
61 | ----- | ||
62 | |||
63 | instance Product t => Outer (Vector t) (Vector t) (Matrix t) where | ||
64 | (⊗) = outer | ||
65 | |||
66 | instance Product t => Outer (Vector t) (Matrix t) (Matrix t) where | ||
67 | v ⊗ m = kronecker (asColumn v) m | ||
68 | |||
69 | instance Product t => Outer (Matrix t) (Vector t) (Matrix t) where | ||
70 | m ⊗ v = kronecker m (asRow v) | ||
71 | |||
72 | instance Product t => Outer (Matrix t) (Matrix t) (Matrix t) where | ||
73 | (⊗) = kronecker | ||
74 | |||
75 | ----- | ||
76 | |||
77 | |||
78 | v = 3 |> [1..] :: Vector Double | ||
79 | |||
80 | m = (3 >< 3) [1..] :: Matrix Double | ||
81 | |||
82 | s = 3 :: Double | ||
83 | |||
84 | a = s ⋅ v × m × m × v ⋅ s | ||
85 | |||
86 | b = (v ⊗ m) ⊗ (v ⊗ m) | ||
87 | |||
88 | c = v ⊗ m ⊗ v ⊗ m | ||
89 | |||
90 | d = s ⋅ (3 |> [10,20..] :: Vector Double) | ||
91 | |||
92 | main = do | ||
93 | print $ scale s v <> m <.> v | ||
94 | print $ scale s v <.> (m <> v) | ||
95 | print $ s * (v <> m <.> v) | ||
96 | print $ s ⋅ v × m × v | ||
97 | print a | ||
98 | print (b == c) | ||
99 | print d | ||
100 | |||
diff --git a/hmatrix.cabal b/hmatrix.cabal index a8dcb43..a5563aa 100644 --- a/hmatrix.cabal +++ b/hmatrix.cabal | |||
@@ -1,5 +1,5 @@ | |||
1 | Name: hmatrix | 1 | Name: hmatrix |
2 | Version: 0.11.0.5 | 2 | Version: 0.11.1.0 |
3 | License: GPL | 3 | License: GPL |
4 | License-file: LICENSE | 4 | License-file: LICENSE |
5 | Author: Alberto Ruiz | 5 | Author: Alberto Ruiz |
@@ -54,6 +54,7 @@ extra-source-files: examples/tests.hs | |||
54 | examples/vector.hs | 54 | examples/vector.hs |
55 | examples/monadic.hs | 55 | examples/monadic.hs |
56 | examples/bool.hs | 56 | examples/bool.hs |
57 | examples/multiply.hs | ||
57 | 58 | ||
58 | extra-source-files: lib/Numeric/LinearAlgebra/LAPACK/lapack-aux.h, | 59 | extra-source-files: lib/Numeric/LinearAlgebra/LAPACK/lapack-aux.h, |
59 | lib/Numeric/LinearAlgebra/LAPACK/clapack.h | 60 | lib/Numeric/LinearAlgebra/LAPACK/clapack.h |
diff --git a/lib/Data/Packed/Matrix.hs b/lib/Data/Packed/Matrix.hs index ab68618..0b23b2f 100644 --- a/lib/Data/Packed/Matrix.hs +++ b/lib/Data/Packed/Matrix.hs | |||
@@ -36,6 +36,7 @@ module Data.Packed.Matrix ( | |||
36 | subMatrix, takeRows, dropRows, takeColumns, dropColumns, | 36 | subMatrix, takeRows, dropRows, takeColumns, dropColumns, |
37 | extractRows, | 37 | extractRows, |
38 | diagRect, takeDiag, | 38 | diagRect, takeDiag, |
39 | mapMatrix, mapMatrixWithIndex, mapMatrixWithIndexM, mapMatrixWithIndexM_, | ||
39 | liftMatrix, liftMatrix2, liftMatrix2Auto,fromArray2D | 40 | liftMatrix, liftMatrix2, liftMatrix2Auto,fromArray2D |
40 | ) where | 41 | ) where |
41 | 42 | ||
@@ -44,6 +45,7 @@ import qualified Data.Packed.ST as ST | |||
44 | import Data.List(transpose,intersperse) | 45 | import Data.List(transpose,intersperse) |
45 | import Data.Array | 46 | import Data.Array |
46 | import Foreign.Storable | 47 | import Foreign.Storable |
48 | import Control.Arrow((***)) | ||
47 | 49 | ||
48 | ------------------------------------------------------------------- | 50 | ------------------------------------------------------------------- |
49 | 51 | ||
@@ -348,3 +350,56 @@ toBlocksEvery r c m = toBlocks rs cs m where | |||
348 | cs = replicate qc c ++ if rc > 0 then [rc] else [] | 350 | cs = replicate qc c ++ if rc > 0 then [rc] else [] |
349 | 351 | ||
350 | ------------------------------------------------------------------- | 352 | ------------------------------------------------------------------- |
353 | |||
354 | mk c g = \k v -> g ((fromIntegral *** fromIntegral) (divMod k c)) v | ||
355 | |||
356 | {- | | ||
357 | |||
358 | @ghci> mapMatrixWithIndexM_ (\\(i,j) v -> printf \"m[%.0f,%.0f] = %.f\\n\" i j v :: IO()) ((2><3)[1 :: Double ..]) | ||
359 | m[0,0] = 1 | ||
360 | m[0,1] = 2 | ||
361 | m[0,2] = 3 | ||
362 | m[1,0] = 4 | ||
363 | m[1,1] = 5 | ||
364 | m[1,2] = 6@ | ||
365 | -} | ||
366 | mapMatrixWithIndexM_ | ||
367 | :: (Element a, Num a, | ||
368 | Functor f, Monad f) => | ||
369 | ((a, a) -> a -> f ()) -> Matrix a -> f () | ||
370 | mapMatrixWithIndexM_ g m = mapVectorWithIndexM_ (mk c g) . flatten $ m | ||
371 | where | ||
372 | c = cols m | ||
373 | |||
374 | {- | | ||
375 | |||
376 | @ghci> mapMatrixWithIndexM (\\(i,j) v -> Just $ 100*v + 10*i + j) (ident 3:: Matrix Double) | ||
377 | Just (3><3) | ||
378 | [ 100.0, 1.0, 2.0 | ||
379 | , 10.0, 111.0, 12.0 | ||
380 | , 20.0, 21.0, 122.0 ]@ | ||
381 | -} | ||
382 | mapMatrixWithIndexM | ||
383 | :: (Foreign.Storable.Storable t, | ||
384 | Element a, Num a, | ||
385 | Functor f, Monad f) => | ||
386 | ((a, a) -> a -> f t) -> Matrix a -> f (Matrix t) | ||
387 | mapMatrixWithIndexM g m = fmap (reshape c) . mapVectorWithIndexM (mk c g) . flatten $ m | ||
388 | where | ||
389 | c = cols m | ||
390 | |||
391 | {- | | ||
392 | @ghci> mapMatrixWithIndex (\\(i,j) v -> 100*v + 10*i + j) (ident 3:: Matrix Double) | ||
393 | (3><3) | ||
394 | [ 100.0, 1.0, 2.0 | ||
395 | , 10.0, 111.0, 12.0 | ||
396 | , 20.0, 21.0, 122.0 ]@ | ||
397 | -} | ||
398 | mapMatrixWithIndex :: (Foreign.Storable.Storable t, | ||
399 | Element a, Num a) => | ||
400 | ((a, a) -> a -> t) -> Matrix a -> Matrix t | ||
401 | mapMatrixWithIndex g = head . mapMatrixWithIndexM (\a b -> [g a b]) | ||
402 | |||
403 | mapMatrix :: (Storable a, Storable b) => (a -> b) -> Matrix a -> Matrix b | ||
404 | mapMatrix f = liftMatrix (mapVector f) | ||
405 | |||
diff --git a/lib/Numeric/Container.hs b/lib/Numeric/Container.hs index 621574e..90155fe 100644 --- a/lib/Numeric/Container.hs +++ b/lib/Numeric/Container.hs | |||
@@ -36,7 +36,7 @@ module Numeric.Container ( | |||
36 | -- * Matrix product | 36 | -- * Matrix product |
37 | Product(..), | 37 | Product(..), |
38 | optimiseMult, | 38 | optimiseMult, |
39 | mXm,mXv,vXm,(<.>),(<>),(<\>), | 39 | mXm,mXv,vXm,(<.>),Mul(..),(<\>), |
40 | outer, kronecker, | 40 | outer, kronecker, |
41 | -- * Random numbers | 41 | -- * Random numbers |
42 | RandDist(..), | 42 | RandDist(..), |