summaryrefslogtreecommitdiff
path: root/examples
diff options
context:
space:
mode:
authorAlberto Ruiz <aruiz@um.es>2011-05-02 17:31:09 +0000
committerAlberto Ruiz <aruiz@um.es>2011-05-02 17:31:09 +0000
commitb48c876b4b9ba37e45104fc7b54d8024c6bd1eb5 (patch)
tree6fcd01cf5f14332f425dbe2fda9e6de1a1f04853 /examples
parente2dde2e24f581d37eb862392aee1cb2e09cf0951 (diff)
mapMatrixWithIndex, Mul, multiply.hs
Diffstat (limited to 'examples')
-rw-r--r--examples/multiply.hs100
1 files changed, 100 insertions, 0 deletions
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
9import Numeric.LinearAlgebra
10
11class Scaling a b c | a b -> c where
12 -- ^ 0x22C5 8901 DOT OPERATOR, scaling
13 infixl 7 ⋅
14 (⋅) :: a -> b -> c
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
30 (⋅) = (*)
31
32instance Container Vector t => Scaling t (Vector t) (Vector t) where
33 (⋅) = scale
34
35instance Container Vector t => Scaling (Vector t) t (Vector t) where
36 (⋅) = flip scale
37
38instance Container Vector t => Scaling t (Matrix t) (Matrix t) where
39 (⋅) = scale
40
41instance Container Vector t => Scaling (Matrix t) t (Matrix t) where
42 (⋅) = flip scale
43
44
45instance Product t => Contraction (Vector t) (Vector t) t where
46 (×) = dot
47
48instance Product t => Contraction (Matrix t) (Vector t) (Vector t) where
49 (×) = mXv
50
51instance Product t => Contraction (Vector t) (Matrix t) (Vector t) where
52 (×) = vXm
53
54instance 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
63instance Product t => Outer (Vector t) (Vector t) (Matrix t) where
64 (⊗) = outer
65
66instance Product t => Outer (Vector t) (Matrix t) (Matrix t) where
67 v ⊗ m = kronecker (asColumn v) m
68
69instance Product t => Outer (Matrix t) (Vector t) (Matrix t) where
70 m ⊗ v = kronecker m (asRow v)
71
72instance Product t => Outer (Matrix t) (Matrix t) (Matrix t) where
73 (⊗) = kronecker
74
75-----
76
77
78v = 3 |> [1..] :: Vector Double
79
80m = (3 >< 3) [1..] :: Matrix Double
81
82s = 3 :: Double
83
84a = s ⋅ v × m × m × v ⋅ s
85
86b = (v ⊗ m) ⊗ (v ⊗ m)
87
88c = v ⊗ m ⊗ v ⊗ m
89
90d = s ⋅ (3 |> [10,20..] :: Vector Double)
91
92main = 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