diff options
-rw-r--r-- | examples/oldtests.hs | 2 | ||||
-rw-r--r-- | examples/pru.hs | 159 | ||||
-rw-r--r-- | examples/tests.hs | 2 | ||||
-rw-r--r-- | lib/Data/Packed/Internal/Tensor.hs | 32 | ||||
-rw-r--r-- | lib/Data/Packed/Matrix.hs | 4 | ||||
-rw-r--r-- | lib/Data/Packed/Tensor.hs | 82 | ||||
-rw-r--r-- | lib/GSL/Vector.hs | 4 |
7 files changed, 146 insertions, 139 deletions
diff --git a/examples/oldtests.hs b/examples/oldtests.hs index 987ef98..1f1ca25 100644 --- a/examples/oldtests.hs +++ b/examples/oldtests.hs | |||
@@ -10,7 +10,7 @@ realVector = fromList :: [Double] -> Vector Double | |||
10 | toComplexM = uncurry $ liftMatrix2 (curry toComplex) | 10 | toComplexM = uncurry $ liftMatrix2 (curry toComplex) |
11 | 11 | ||
12 | infixl 2 =~= | 12 | infixl 2 =~= |
13 | a =~= b = pnorm PNorm1 (flatten (a - b)) < 1E-6 | 13 | a =~= b = pnorm 1 (flatten (a - b)) < 1E-6 |
14 | 14 | ||
15 | randomMatrix seed (n,m) = reshape m $ realVector $ take (n*m) $ randomRs (-100,100) $ mkStdGen seed | 15 | randomMatrix seed (n,m) = reshape m $ realVector $ take (n*m) $ randomRs (-100,100) $ mkStdGen seed |
16 | 16 | ||
diff --git a/examples/pru.hs b/examples/pru.hs index f855bce..71f33bf 100644 --- a/examples/pru.hs +++ b/examples/pru.hs | |||
@@ -1,56 +1,33 @@ | |||
1 | --{-# OPTIONS_GHC #-} | 1 | --{-# OPTIONS_GHC #-} |
2 | --module Main where | 2 | --module Main where |
3 | 3 | {- | |
4 | import Data.Packed.Internal | 4 | import Data.Packed.Internal |
5 | import Data.Packed.Internal.Vector | 5 | import Data.Packed.Internal.Vector |
6 | import Data.Packed.Internal.Matrix | 6 | import Data.Packed.Internal.Matrix |
7 | import Data.Packed.Internal.Tensor | 7 | import Data.Packed.Tensor |
8 | import Data.Packed.Matrix | 8 | import Data.Packed.Matrix |
9 | import GSL.Vector | 9 | import GSL.Vector |
10 | import LAPACK | 10 | import LAPACK |
11 | import Data.List(foldl') | ||
11 | 12 | ||
12 | import Complex | 13 | import Complex |
13 | import Numeric(showGFloat) | 14 | import Numeric(showGFloat) |
14 | import Data.List(transpose,intersperse,sort,elemIndex,nub,foldl',foldl1') | ||
15 | import Foreign.Storable | ||
16 | |||
17 | |||
18 | vr = fromList [1..15::Double] | ||
19 | vc = fromList (map (\x->x :+ (x+1)) [1..15::Double]) | ||
20 | |||
21 | mi = (2 >< 3) [1 .. 6::Int] | ||
22 | mz = (2 >< 3) [1,2,3,4,5,6:+(1::Double)] | ||
23 | |||
24 | ac = (2><3) [1 .. 6::Double] | ||
25 | bc = (3><4) [7 .. 18::Double] | ||
26 | |||
27 | af = (2>|<3) [1,4,2,5,3,6::Double] | ||
28 | bf = (3>|<4) [7,11,15,8,12,16,9,13,17,10,14,18::Double] | ||
29 | |||
30 | |||
31 | a |=| b = rows a == rows b && | ||
32 | cols a == cols b && | ||
33 | toList (cdat a) == toList (cdat b) | ||
34 | |||
35 | mulC a b = multiply RowMajor a b | ||
36 | mulF a b = multiply ColumnMajor a b | ||
37 | |||
38 | cc = mulC ac bf | ||
39 | cf = mulF af bc | ||
40 | 15 | ||
41 | r = mulC cc (trans cf) | 16 | import Foreign.Storable |
42 | 17 | -} | |
43 | rd = (2><2) | ||
44 | [ 27736.0, 65356.0 | ||
45 | , 65356.0, 154006.0 ] | ||
46 | 18 | ||
19 | import GSL | ||
20 | import Data.List(foldl', foldl1') | ||
21 | import Data.Packed.Internal.Tensor | ||
22 | import Data.Packed.Tensor | ||
23 | import Complex | ||
47 | 24 | ||
48 | 25 | ||
49 | main = do | 26 | main = do |
50 | print $ r |=| rd | ||
51 | print $ foldl part t [("p",1),("q",0),("r",2)] | 27 | print $ foldl part t [("p",1),("q",0),("r",2)] |
52 | print $ foldl part t [("p",1),("r",2),("q",0)] | 28 | print $ foldl part t [("p",1),("r",2),("q",0)] |
53 | print $ foldl part t $ reverse [("p",1),("r",2),("q",0)] | 29 | print $ foldl part t $ reverse [("p",1),("r",2),("q",0)] |
30 | pru | ||
54 | 31 | ||
55 | t = T [IdxDesc 4 Covariant "p",IdxDesc 2 Covariant "q" ,IdxDesc 3 Contravariant "r"] | 32 | t = T [IdxDesc 4 Covariant "p",IdxDesc 2 Covariant "q" ,IdxDesc 3 Contravariant "r"] |
56 | $ fromList [1..24::Double] | 33 | $ fromList [1..24::Double] |
@@ -61,10 +38,17 @@ t1 = T [IdxDesc 4 Covariant "p",IdxDesc 4 Contravariant "q" ,IdxDesc 2 Covariant | |||
61 | t2 = T [IdxDesc 4 Covariant "p",IdxDesc 4 Contravariant "q"] | 38 | t2 = T [IdxDesc 4 Covariant "p",IdxDesc 4 Contravariant "q"] |
62 | $ fromList [1..16::Double] | 39 | $ fromList [1..16::Double] |
63 | 40 | ||
41 | vector n v = tvector n (fromList v) :: Tensor Double | ||
42 | |||
43 | kron n = tensorFromMatrix (Contravariant,"k1") (Covariant,"k2") (ident n) | ||
64 | 44 | ||
45 | tensorFromTrans m = tensorFromMatrix (Contravariant,"1") (Covariant,"2") m | ||
65 | 46 | ||
66 | addT ts = T (dims (head ts)) (fromList $ sumT ts) | 47 | tam = (3><3) [1..9] |
48 | tbm = (3><3) [11..19] | ||
67 | 49 | ||
50 | ta = tensorFromMatrix (Contravariant,"a1") (Covariant,"a2") tam :: Tensor Double | ||
51 | tb = tensorFromMatrix (Contravariant,"b1") (Covariant,"b2") tbm :: Tensor Double | ||
68 | 52 | ||
69 | delta i j | i==j = 1 | 53 | delta i j | i==j = 1 |
70 | | otherwise = 0 | 54 | | otherwise = 0 |
@@ -73,12 +57,6 @@ e i n = fromList [ delta k i | k <- [1..n]] | |||
73 | 57 | ||
74 | diagl = diag.fromList | 58 | diagl = diag.fromList |
75 | 59 | ||
76 | scalar x = T [] (fromList [x]) | ||
77 | tensorFromVector (tp,nm) v = T {dims = [IdxDesc (dim v) tp nm] | ||
78 | , ten = v} | ||
79 | tensorFromMatrix (tpr,nmr) (tpc,nmc) m = T {dims = [IdxDesc (rows m) tpr nmr,IdxDesc (cols m) tpc nmc] | ||
80 | , ten = cdat m} | ||
81 | |||
82 | td = tensorFromMatrix (Contravariant,"i") (Covariant,"j") $ diagl [1..4] :: Tensor Double | 60 | td = tensorFromMatrix (Contravariant,"i") (Covariant,"j") $ diagl [1..4] :: Tensor Double |
83 | 61 | ||
84 | tn = tensorFromMatrix (Contravariant,"i") (Covariant,"j") $ (2><3) [1..6] :: Tensor Double | 62 | tn = tensorFromMatrix (Contravariant,"i") (Covariant,"j") $ (2><3) [1..6] :: Tensor Double |
@@ -91,7 +69,7 @@ r1 = contraction tt "j" tq "p" | |||
91 | r1' = contraction' tt "j" tq "p" | 69 | r1' = contraction' tt "j" tq "p" |
92 | 70 | ||
93 | pru = do | 71 | pru = do |
94 | mapM_ (putStrLn.shdims.dims.normal) (contractions t1 t2) | 72 | mapM_ (putStrLn.shdims.dims.normal) (possibleContractions t1 t2) |
95 | let t1 = contraction tt "i" tq "q" | 73 | let t1 = contraction tt "i" tq "q" |
96 | print $ normal t1 | 74 | print $ normal t1 |
97 | print $ foldl part t1 [("j",0),("p'",1),("r'",1)] | 75 | print $ foldl part t1 [("j",0),("p'",1),("r'",1)] |
@@ -104,43 +82,24 @@ pru = do | |||
104 | let t2 = contraction' tq "q" tt "i" | 82 | let t2 = contraction' tq "q" tt "i" |
105 | print $ normal t2 | 83 | print $ normal t2 |
106 | print $ foldl part t2 [("j'",0),("p",1),("r",1)] | 84 | print $ foldl part t2 [("j'",0),("p",1),("r",1)] |
107 | 85 | putStrLn "--------------------------------------------" | |
108 | scsig t = scalar (signature (nms t)) `prod` t | 86 | print $ flatten $ tam <> tbm |
109 | where nms = map idxName . dims | 87 | print $ contractions (ta <*> tb <*> kron 3) [("a2","k1'"),("b1'","k2'")] |
110 | 88 | print $ contraction ta "a2" tb "b1" | |
111 | antisym' t = addT $ map (scsig . flip tridx t) (perms (names t)) | 89 | print $ normal $ contractions (ta <*> tb) [("a2","b1'")] |
112 | 90 | print $ normal $ contraction' ta "a2" tb "b1" | |
113 | {- | 91 | putStrLn "--------------------------------------------" |
114 | where T d v = t | 92 | print $ raise $ dualMV $ raise $ dualMV (x1/\x2) /\ dualV [x3,x4] |
115 | t' = T d' v | 93 | putStrLn "--------------------------------------------" |
116 | fixdim (T _ v) = T d v | 94 | print $ foldl' contractionF (leviCivita 4) [y1,y2] |
117 | d' = [(n,(c,show (pos q))) | (n,(c,q)) <- d] | 95 | print $ contractions (leviCivita 4 <*> (y1/\y2)) [("1","p'"),("2'","q''")] <*> (scalar (recip $ fact 2)) |
118 | pos n = i where Just i = elemIndex n nms | 96 | print $ foldl' contractionF (leviCivita 4) [y1,y2,y3,y5] |
119 | nms = map (snd.snd) d | 97 | print $ contractions (leviCivita 4 <*> (y1/\y2/\y3/\y5)) [("1","p'"),("2'","q''"),("3'","r''"),("4'","t''")] <*> (scalar (recip $ fact 4)) |
120 | -} | 98 | print $ dim $ ten $ leviCivita 4 <*> (y1/\y2/\y3/\y5) |
121 | 99 | print $ innerAT (leviCivita 4) (y1/\y2/\y3/\y5) | |
122 | auxrename (T d v) = T d' v | 100 | |
123 | where d' = [IdxDesc n c (show (pos q)) | IdxDesc n c q <- d] | 101 | |
124 | pos n = i where Just i = elemIndex n nms | 102 | y5 = vector "t" [0,1,-2,0] |
125 | nms = map idxName d | ||
126 | |||
127 | antisym t = T (dims t) (ten (antisym' (auxrename t))) | ||
128 | |||
129 | |||
130 | norper t = prod t (scalar (recip $ fromIntegral $ product [1 .. length (dims t)])) | ||
131 | antinorper t = prod t (scalar (fromIntegral $ product [1 .. length (dims t)])) | ||
132 | |||
133 | |||
134 | tvector n v = tensorFromVector (Contravariant,n) v | ||
135 | tcovector n v = tensorFromVector (Covariant,n) v | ||
136 | |||
137 | vector n v = tvector n (fromList v) :: Tensor Double | ||
138 | |||
139 | wedge a b = antisym (prod (norper a) (norper b)) | ||
140 | |||
141 | a /\ b = wedge a b | ||
142 | |||
143 | a <*> b = normal $ prod a b | ||
144 | 103 | ||
145 | u = vector "p" [1,1,0] | 104 | u = vector "p" [1,1,0] |
146 | v = vector "q" [0,1,1] | 105 | v = vector "q" [0,1,1] |
@@ -149,35 +108,15 @@ w = vector "r" [1,0,1] | |||
149 | uv = u /\ v | 108 | uv = u /\ v |
150 | uw = u /\ w | 109 | uw = u /\ w |
151 | 110 | ||
152 | normAT t = sqrt $ innerAT t t | ||
153 | |||
154 | innerAT t1 t2 = dot (ten t1) (ten t2) / fromIntegral (fact $ length $ dims t1) | ||
155 | |||
156 | det m = product $ toList s where (_,s,_) = svdR' m | ||
157 | |||
158 | fact n = product [1..n] | ||
159 | 111 | ||
160 | l1 = vector "p" [0,0,0,1] | 112 | l1 = vector "p" [0,0,0,1] |
161 | l2 = vector "q" [1,0,0,1] | 113 | l2 = vector "q" [1,0,0,1] |
162 | l3 = vector "r" [0,1,0,1] | 114 | l3 = vector "r" [0,1,0,1] |
163 | 115 | ||
164 | leviCivita n = antisym $ foldl1 prod $ zipWith tcovector (map show [1,2..]) (toRows (ident n)) | ||
165 | |||
166 | contractionF t1 t2 = contraction t1 n1 t2 n2 | ||
167 | where n1 = fn t1 | ||
168 | n2 = fn t2 | ||
169 | fn = idxName . head . dims | ||
170 | |||
171 | |||
172 | dualV vs = foldl' contractionF (leviCivita n) vs | ||
173 | where n = idxDim . head . dims . head $ vs | ||
174 | |||
175 | |||
176 | dual1 = foldl' contractionF (leviCivita 3) [u,v] | 116 | dual1 = foldl' contractionF (leviCivita 3) [u,v] |
177 | dual2 = foldl' contractionF (leviCivita 3) [u,v,w] | 117 | dual2 = foldl' contractionF (leviCivita 3) [u,v,w] |
178 | 118 | ||
179 | 119 | ||
180 | contract1b t (n1,n2) = contract1 t n1 n2 | ||
181 | 120 | ||
182 | dual1' = prod (foldl' contract1b ((leviCivita 3) <*> (u /\ v)) [("1","p'"),("2'","q''")]) (scalar (recip $ fact 2)) | 121 | dual1' = prod (foldl' contract1b ((leviCivita 3) <*> (u /\ v)) [("1","p'"),("2'","q''")]) (scalar (recip $ fact 2)) |
183 | dual2' = prod (foldl' contract1b ((leviCivita 3) <*> (u /\ v /\ w)) [("1","p'"),("2'","q''"),("3'","r''")]) (scalar (recip $ fact 3)) | 122 | dual2' = prod (foldl' contract1b ((leviCivita 3) <*> (u /\ v /\ w)) [("1","p'"),("2'","q''"),("3'","r''")]) (scalar (recip $ fact 3)) |
@@ -188,17 +127,6 @@ x2 = vector "q" [2,2,2] | |||
188 | x3 = vector "r" [-3,-1,-1] | 127 | x3 = vector "r" [-3,-1,-1] |
189 | x4 = vector "s" [12,0,3] | 128 | x4 = vector "s" [12,0,3] |
190 | 129 | ||
191 | raise (T d v) = T (map raise' d) v | ||
192 | where raise' idx@IdxDesc {idxType = Covariant } = idx {idxType = Contravariant} | ||
193 | raise' idx@IdxDesc {idxType = Contravariant } = idx {idxType = Covariant} | ||
194 | |||
195 | dualMV t = prod (foldl' contract1b (lc <*> t) ds) (scalar (recip $ fromIntegral $ fact (length ds))) | ||
196 | where | ||
197 | lc = leviCivita n | ||
198 | nms1 = map idxName (dims lc) | ||
199 | nms2 = map ((++"'").idxName) (dims t) | ||
200 | ds = zip nms1 nms2 | ||
201 | n = idxDim . head . dims $ t | ||
202 | 130 | ||
203 | -- intersection of two lines :-) | 131 | -- intersection of two lines :-) |
204 | -- > raise $ dualMV $ raise $ dualMV (x1/\x2) /\ dualV [x3,x4] | 132 | -- > raise $ dualMV $ raise $ dualMV (x1/\x2) /\ dualV [x3,x4] |
@@ -214,17 +142,6 @@ y4 = vector "s" [12,0,0,3] | |||
214 | -- scalar 0.0 | 142 | -- scalar 0.0 |
215 | -- it seems that the sum of ranks must be greater than n :( | 143 | -- it seems that the sum of ranks must be greater than n :( |
216 | 144 | ||
217 | asBase r n = filter (\x-> (x==nub x && x==sort x)) $ sequence $ replicate r [1..n] | ||
218 | |||
219 | partF t i = part t (name,i) where name = idxName . head . dims $ t | ||
220 | |||
221 | --partL = foldl' partF | ||
222 | |||
223 | niceAS t = filter ((/=0.0).fst) $ zip vals base | ||
224 | where vals = map ((`at` 0).ten.foldl' partF t) (map (map pred) base) | ||
225 | base = asBase r n | ||
226 | r = length (dims t) | ||
227 | n = idxDim . head . dims $ t | ||
228 | 145 | ||
229 | z1 = vector "p" [0,0,0,1] | 146 | z1 = vector "p" [0,0,0,1] |
230 | z2 = vector "q" [1,0,0,1] | 147 | z2 = vector "q" [1,0,0,1] |
diff --git a/examples/tests.hs b/examples/tests.hs index 5acfa9d..eb8f50d 100644 --- a/examples/tests.hs +++ b/examples/tests.hs | |||
@@ -20,7 +20,7 @@ import Test.HUnit hiding ((~:)) | |||
20 | import Complex | 20 | import Complex |
21 | import LinearAlgebra.Algorithms | 21 | import LinearAlgebra.Algorithms |
22 | import GSL.Matrix | 22 | import GSL.Matrix |
23 | import GSL.Compat hiding ((<>)) | 23 | import GSL.Compat hiding ((<>),constant) |
24 | 24 | ||
25 | dist :: (Normed t, Num t) => t -> t -> Double | 25 | dist :: (Normed t, Num t) => t -> t -> Double |
26 | dist a b = norm (a-b) | 26 | dist a b = norm (a-b) |
diff --git a/lib/Data/Packed/Internal/Tensor.hs b/lib/Data/Packed/Internal/Tensor.hs index c4faf49..8296935 100644 --- a/lib/Data/Packed/Internal/Tensor.hs +++ b/lib/Data/Packed/Internal/Tensor.hs | |||
@@ -18,7 +18,8 @@ import Data.Packed.Internal.Common | |||
18 | import Data.Packed.Internal.Vector | 18 | import Data.Packed.Internal.Vector |
19 | import Data.Packed.Internal.Matrix | 19 | import Data.Packed.Internal.Matrix |
20 | import Foreign.Storable | 20 | import Foreign.Storable |
21 | import Data.List(sort,elemIndex,nub) | 21 | import Data.List(sort,elemIndex,nub,foldl1') |
22 | import GSL.Vector | ||
22 | 23 | ||
23 | data IdxType = Covariant | Contravariant deriving (Show,Eq) | 24 | data IdxType = Covariant | Contravariant deriving (Show,Eq) |
24 | 25 | ||
@@ -79,10 +80,10 @@ concatRename l1 l2 = l1 ++ map ren l2 where | |||
79 | ren idx = if {- s `elem` fs -} True then idx {idxName = idxName idx ++ "'"} else idx | 80 | ren idx = if {- s `elem` fs -} True then idx {idxName = idxName idx ++ "'"} else idx |
80 | fs = map idxName l1 | 81 | fs = map idxName l1 |
81 | 82 | ||
82 | prod :: (Field t, Num t) => Tensor t -> Tensor t -> Tensor t | 83 | --prod :: (Field t, Num t) => Tensor t -> Tensor t -> Tensor t |
83 | prod (T d1 v1) (T d2 v2) = T (concatRename d1 d2) (outer' v1 v2) | 84 | prod (T d1 v1) (T d2 v2) = T (concatRename d1 d2) (outer' v1 v2) |
84 | 85 | ||
85 | contraction :: (Field t, Num t) => Tensor t -> IdxName -> Tensor t -> IdxName -> Tensor t | 86 | --contraction :: (Field t, Num t) => Tensor t -> IdxName -> Tensor t -> IdxName -> Tensor t |
86 | contraction t1 n1 t2 n2 = | 87 | contraction t1 n1 t2 n2 = |
87 | if compatIdx t1 n1 t2 n2 | 88 | if compatIdx t1 n1 t2 n2 |
88 | then T (concatRename (tail d1) (tail d2)) (cdat m) | 89 | then T (concatRename (tail d1) (tail d2)) (cdat m) |
@@ -91,16 +92,27 @@ contraction t1 n1 t2 n2 = | |||
91 | (d2,m2) = putFirstIdx n2 t2 | 92 | (d2,m2) = putFirstIdx n2 t2 |
92 | m = multiply RowMajor (trans m1) m2 | 93 | m = multiply RowMajor (trans m1) m2 |
93 | 94 | ||
94 | sumT :: (Storable t, Enum t, Num t) => [Tensor t] -> [t] | 95 | --sumT :: (Storable t, Enum t, Num t) => [Tensor t] -> [t] |
95 | sumT ls = foldl (zipWith (+)) [0,0..] (map (toList.ten) ls) | 96 | --sumT ls = foldl (zipWith (+)) [0,0..] (map (toList.ten) ls) |
97 | --addT ts = T (dims (head ts)) (fromList $ sumT ts) | ||
96 | 98 | ||
97 | contract1 :: (Num t, Enum t, Field t) => Tensor t -> IdxName -> IdxName -> Tensor t | 99 | liftTensor f (T d v) = T d (f v) |
98 | contract1 t name1 name2 = T d $ fromList $ sumT y | 100 | |
101 | liftTensor2 f (T d1 v1) (T d2 v2) | compat d1 d2 = T d1 (f v1 v2) | ||
102 | | otherwise = error "liftTensor2 with incompatible tensors" | ||
103 | where compat a b = length a == length b | ||
104 | |||
105 | |||
106 | a |+| b = liftTensor2 add a b | ||
107 | addT l = foldl1' (|+|) l | ||
108 | |||
109 | --contract1 :: (Num t, Field t) => Tensor t -> IdxName -> IdxName -> Tensor t | ||
110 | contract1 t name1 name2 = addT y | ||
99 | where d = dims (head y) | 111 | where d = dims (head y) |
100 | x = (map (flip parts name2) (parts t name1)) | 112 | x = (map (flip parts name2) (parts t name1)) |
101 | y = map head $ zipWith drop [0..] x | 113 | y = map head $ zipWith drop [0..] x |
102 | 114 | ||
103 | contraction' :: (Field t, Enum t, Num t) => Tensor t -> IdxName -> Tensor t -> IdxName -> Tensor t | 115 | --contraction' :: (Field t, Enum t, Num t) => Tensor t -> IdxName -> Tensor t -> IdxName -> Tensor t |
104 | contraction' t1 n1 t2 n2 = | 116 | contraction' t1 n1 t2 n2 = |
105 | if compatIdx t1 n1 t2 n2 | 117 | if compatIdx t1 n1 t2 n2 |
106 | then contract1 (prod t1 t2) n1 (n2++"'") | 118 | then contract1 (prod t1 t2) n1 (n2++"'") |
@@ -130,8 +142,8 @@ names t = sort $ map idxName (dims t) | |||
130 | normal :: (Field t) => Tensor t -> Tensor t | 142 | normal :: (Field t) => Tensor t -> Tensor t |
131 | normal t = tridx (names t) t | 143 | normal t = tridx (names t) t |
132 | 144 | ||
133 | contractions :: (Num t, Field t) => Tensor t -> Tensor t -> [Tensor t] | 145 | possibleContractions :: (Num t, Field t) => Tensor t -> Tensor t -> [Tensor t] |
134 | contractions t1 t2 = [ contraction t1 n1 t2 n2 | n1 <- names t1, n2 <- names t2, compatIdx t1 n1 t2 n2 ] | 146 | possibleContractions t1 t2 = [ contraction t1 n1 t2 n2 | n1 <- names t1, n2 <- names t2, compatIdx t1 n1 t2 n2 ] |
135 | 147 | ||
136 | -- sent to Haskell-Cafe by Sebastian Sylvan | 148 | -- sent to Haskell-Cafe by Sebastian Sylvan |
137 | perms :: [t] -> [[t]] | 149 | perms :: [t] -> [[t]] |
diff --git a/lib/Data/Packed/Matrix.hs b/lib/Data/Packed/Matrix.hs index 36bf32e..2033dc7 100644 --- a/lib/Data/Packed/Matrix.hs +++ b/lib/Data/Packed/Matrix.hs | |||
@@ -87,14 +87,14 @@ ident n = diag (constant 1 n) | |||
87 | r >< c = f where | 87 | r >< c = f where |
88 | f l | dim v == r*c = matrixFromVector RowMajor c v | 88 | f l | dim v == r*c = matrixFromVector RowMajor c v |
89 | | otherwise = error $ "inconsistent list size = " | 89 | | otherwise = error $ "inconsistent list size = " |
90 | ++show (dim v) ++"in ("++show r++"><"++show c++")" | 90 | ++show (dim v) ++" in ("++show r++"><"++show c++")" |
91 | where v = fromList l | 91 | where v = fromList l |
92 | 92 | ||
93 | (>|<) :: (Field a) => Int -> Int -> [a] -> Matrix a | 93 | (>|<) :: (Field a) => Int -> Int -> [a] -> Matrix a |
94 | r >|< c = f where | 94 | r >|< c = f where |
95 | f l | dim v == r*c = matrixFromVector ColumnMajor c v | 95 | f l | dim v == r*c = matrixFromVector ColumnMajor c v |
96 | | otherwise = error $ "inconsistent list size = " | 96 | | otherwise = error $ "inconsistent list size = " |
97 | ++show (dim v) ++"in ("++show r++"><"++show c++")" | 97 | ++show (dim v) ++" in ("++show r++"><"++show c++")" |
98 | where v = fromList l | 98 | where v = fromList l |
99 | 99 | ||
100 | ---------------------------------------------------------------- | 100 | ---------------------------------------------------------------- |
diff --git a/lib/Data/Packed/Tensor.hs b/lib/Data/Packed/Tensor.hs index 75a9288..68ce9a5 100644 --- a/lib/Data/Packed/Tensor.hs +++ b/lib/Data/Packed/Tensor.hs | |||
@@ -12,9 +12,85 @@ | |||
12 | -- | 12 | -- |
13 | ----------------------------------------------------------------------------- | 13 | ----------------------------------------------------------------------------- |
14 | 14 | ||
15 | module Data.Packed.Tensor ( | 15 | module Data.Packed.Tensor where |
16 | |||
17 | ) where | ||
18 | 16 | ||
17 | import Data.Packed.Matrix | ||
19 | import Data.Packed.Internal | 18 | import Data.Packed.Internal |
20 | import Complex | 19 | import Complex |
20 | import Data.List(transpose,intersperse,sort,elemIndex,nub,foldl',foldl1') | ||
21 | |||
22 | scalar x = T [] (fromList [x]) | ||
23 | tensorFromVector (tp,nm) v = T {dims = [IdxDesc (dim v) tp nm] | ||
24 | , ten = v} | ||
25 | tensorFromMatrix (tpr,nmr) (tpc,nmc) m = T {dims = [IdxDesc (rows m) tpr nmr,IdxDesc (cols m) tpc nmc] | ||
26 | , ten = cdat m} | ||
27 | |||
28 | scsig t = scalar (signature (nms t)) `prod` t | ||
29 | where nms = map idxName . dims | ||
30 | |||
31 | antisym' t = addT $ map (scsig . flip tridx t) (perms (names t)) | ||
32 | |||
33 | |||
34 | auxrename (T d v) = T d' v | ||
35 | where d' = [IdxDesc n c (show (pos q)) | IdxDesc n c q <- d] | ||
36 | pos n = i where Just i = elemIndex n nms | ||
37 | nms = map idxName d | ||
38 | |||
39 | antisym t = T (dims t) (ten (antisym' (auxrename t))) | ||
40 | |||
41 | |||
42 | norper t = prod t (scalar (recip $ fromIntegral $ product [1 .. length (dims t)])) | ||
43 | antinorper t = prod t (scalar (fromIntegral $ product [1 .. length (dims t)])) | ||
44 | |||
45 | |||
46 | tvector n v = tensorFromVector (Contravariant,n) v | ||
47 | tcovector n v = tensorFromVector (Covariant,n) v | ||
48 | |||
49 | wedge a b = antisym (prod (norper a) (norper b)) | ||
50 | |||
51 | a /\ b = wedge a b | ||
52 | |||
53 | a <*> b = normal $ prod a b | ||
54 | |||
55 | normAT t = sqrt $ innerAT t t | ||
56 | |||
57 | innerAT t1 t2 = dot (ten t1) (ten t2) / fromIntegral (fact $ length $ dims t1) | ||
58 | |||
59 | fact n = product [1..n] | ||
60 | |||
61 | leviCivita n = antisym $ foldl1 prod $ zipWith tcovector (map show [1,2..]) (toRows (ident n)) | ||
62 | |||
63 | contractionF t1 t2 = contraction t1 n1 t2 n2 | ||
64 | where n1 = fn t1 | ||
65 | n2 = fn t2 | ||
66 | fn = idxName . head . dims | ||
67 | |||
68 | |||
69 | dualV vs = foldl' contractionF (leviCivita n) vs | ||
70 | where n = idxDim . head . dims . head $ vs | ||
71 | |||
72 | raise (T d v) = T (map raise' d) v | ||
73 | where raise' idx@IdxDesc {idxType = Covariant } = idx {idxType = Contravariant} | ||
74 | raise' idx@IdxDesc {idxType = Contravariant } = idx {idxType = Covariant} | ||
75 | |||
76 | dualMV t = prod (foldl' contract1b (lc <*> t) ds) (scalar (recip $ fromIntegral $ fact (length ds))) | ||
77 | where | ||
78 | lc = leviCivita n | ||
79 | nms1 = map idxName (dims lc) | ||
80 | nms2 = map ((++"'").idxName) (dims t) | ||
81 | ds = zip nms1 nms2 | ||
82 | n = idxDim . head . dims $ t | ||
83 | |||
84 | contract1b t (n1,n2) = contract1 t n1 n2 | ||
85 | |||
86 | contractions t pairs = foldl' contract1b t pairs | ||
87 | |||
88 | asBase r n = filter (\x-> (x==nub x && x==sort x)) $ sequence $ replicate r [1..n] | ||
89 | |||
90 | partF t i = part t (name,i) where name = idxName . head . dims $ t | ||
91 | |||
92 | niceAS t = filter ((/=0.0).fst) $ zip vals base | ||
93 | where vals = map ((`at` 0).ten.foldl' partF t) (map (map pred) base) | ||
94 | base = asBase r n | ||
95 | r = length (dims t) | ||
96 | n = idxDim . head . dims $ t | ||
diff --git a/lib/GSL/Vector.hs b/lib/GSL/Vector.hs index a074254..0b3c3a9 100644 --- a/lib/GSL/Vector.hs +++ b/lib/GSL/Vector.hs | |||
@@ -21,7 +21,9 @@ module GSL.Vector ( | |||
21 | scale, addConstant, add, sub, mul, | 21 | scale, addConstant, add, sub, mul, |
22 | ) where | 22 | ) where |
23 | 23 | ||
24 | import Data.Packed.Internal | 24 | import Data.Packed.Internal.Common |
25 | import Data.Packed.Internal.Vector | ||
26 | |||
25 | import Complex | 27 | import Complex |
26 | import Foreign | 28 | import Foreign |
27 | 29 | ||