diff options
author | Alberto Ruiz <aruiz@um.es> | 2014-05-08 08:48:12 +0200 |
---|---|---|
committer | Alberto Ruiz <aruiz@um.es> | 2014-05-08 08:48:12 +0200 |
commit | 1925c123d7d8184a1d2ddc0a413e0fd2776e1083 (patch) | |
tree | fad79f909d9c3be53d68e6ebd67202650536d387 /packages/hmatrix/examples/multiply.hs | |
parent | eb3f702d065a4a967bb754977233e6eec408fd1f (diff) |
empty hmatrix-base
Diffstat (limited to 'packages/hmatrix/examples/multiply.hs')
-rw-r--r-- | packages/hmatrix/examples/multiply.hs | 104 |
1 files changed, 104 insertions, 0 deletions
diff --git a/packages/hmatrix/examples/multiply.hs b/packages/hmatrix/examples/multiply.hs new file mode 100644 index 0000000..572961c --- /dev/null +++ b/packages/hmatrix/examples/multiply.hs | |||
@@ -0,0 +1,104 @@ | |||
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 | instance (Num t) => Scaling t t t where | ||
17 | (⋅) = (*) | ||
18 | |||
19 | instance Container Vector t => Scaling t (Vector t) (Vector t) where | ||
20 | (⋅) = scale | ||
21 | |||
22 | instance Container Vector t => Scaling (Vector t) t (Vector t) where | ||
23 | (⋅) = flip scale | ||
24 | |||
25 | instance Container Vector t => Scaling t (Matrix t) (Matrix t) where | ||
26 | (⋅) = scale | ||
27 | |||
28 | instance Container Vector t => Scaling (Matrix t) t (Matrix t) where | ||
29 | (⋅) = flip scale | ||
30 | |||
31 | |||
32 | class 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 | |||
42 | instance Product t => Mul (Vector t) (Vector t) t where | ||
43 | (×) = udot | ||
44 | |||
45 | instance Product t => Mul (Matrix t) (Vector t) (Vector t) where | ||
46 | (×) = mXv | ||
47 | |||
48 | instance Product t => Mul (Vector t) (Matrix t) (Vector t) where | ||
49 | (×) = vXm | ||
50 | |||
51 | instance Product t => Mul (Matrix t) (Matrix t) (Matrix t) where | ||
52 | (×) = mXm | ||
53 | |||
54 | |||
55 | --instance Scaling a b c => Contraction a b c where | ||
56 | -- (×) = (⋅) | ||
57 | |||
58 | -------------------------------------------------------------------------------- | ||
59 | |||
60 | class Outer a | ||
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 | ||
67 | |||
68 | instance Outer Vector where | ||
69 | (⊗) = outer | ||
70 | |||
71 | instance Outer Matrix where | ||
72 | (⊗) = kronecker | ||
73 | |||
74 | -------------------------------------------------------------------------------- | ||
75 | |||
76 | |||
77 | v = 3 |> [1..] :: Vector Double | ||
78 | |||
79 | m = (3 >< 3) [1..] :: Matrix Double | ||
80 | |||
81 | s = 3 :: Double | ||
82 | |||
83 | a = s ⋅ v × m × m × v ⋅ s | ||
84 | |||
85 | --b = (v ⊗ m) ⊗ (v ⊗ m) | ||
86 | |||
87 | --c = v ⊗ m ⊗ v ⊗ m | ||
88 | |||
89 | d = s ⋅ (3 |> [10,20..] :: Vector Double) | ||
90 | |||
91 | u = fromList [3,0,5] | ||
92 | w = konst 1 (2,3) :: Matrix Double | ||
93 | |||
94 | main = do | ||
95 | print $ (scale s v <> m) `udot` v | ||
96 | print $ scale s v `udot` (m <> v) | ||
97 | print $ s * ((v <> m) `udot` v) | ||
98 | print $ s ⋅ v × m × v | ||
99 | print a | ||
100 | -- print (b == c) | ||
101 | print d | ||
102 | print $ asColumn u ⊗ w | ||
103 | print $ w ⊗ asColumn u | ||
104 | |||