summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorAlberto Ruiz <aruiz@um.es>2007-06-21 08:39:22 +0000
committerAlberto Ruiz <aruiz@um.es>2007-06-21 08:39:22 +0000
commitaa14e6615533e7bd5e2b15acdc3ec76afbe1aac4 (patch)
tree619fc0cdb35be0d67a111dc2665981aa858ebd5e
parentb2af660f87a55dd15f4519b21e66837ec811dc25 (diff)
working with tensors
-rw-r--r--examples/pru.hs82
-rw-r--r--examples/tests.hs2
-rw-r--r--lib/Data/Packed/Internal/Common.hs4
-rw-r--r--lib/Data/Packed/Internal/Tensor.hs17
4 files changed, 98 insertions, 7 deletions
diff --git a/examples/pru.hs b/examples/pru.hs
index 31e5213..4a5104b 100644
--- a/examples/pru.hs
+++ b/examples/pru.hs
@@ -11,7 +11,7 @@ import LAPACK
11 11
12import Complex 12import Complex
13import Numeric(showGFloat) 13import Numeric(showGFloat)
14import Data.List(transpose,intersperse,sort) 14import Data.List(transpose,intersperse,sort,elemIndex,nub,foldl',foldl1')
15import Foreign.Storable 15import Foreign.Storable
16 16
17 17
@@ -61,7 +61,7 @@ t2 = T [(4,(Covariant,"p")),(4,(Contravariant,"q"))] $ fromList [1..16::Double]
61 61
62 62
63 63
64 64addT ts = T (dims (head ts)) (fromList $ sumT ts)
65 65
66 66
67delta i j | i==j = 1 67delta i j | i==j = 1
@@ -71,7 +71,7 @@ e i n = fromList [ delta k i | k <- [1..n]]
71 71
72diagl = diag.fromList 72diagl = diag.fromList
73 73
74 74scalar x = T [] (fromList [x])
75tensorFromVector idx v = T {dims = [(dim v,idx)], ten = v} 75tensorFromVector idx v = T {dims = [(dim v,idx)], ten = v}
76tensorFromMatrix idxr idxc m = T {dims = [(rows m,idxr),(cols m,idxc)], ten = cdat m} 76tensorFromMatrix idxr idxc m = T {dims = [(rows m,idxr),(cols m,idxc)], ten = cdat m}
77 77
@@ -100,3 +100,79 @@ pru = do
100 print $ normal t2 100 print $ normal t2
101 print $ foldl part t2 [("j'",0),("p",1),("r",1)] 101 print $ foldl part t2 [("j'",0),("p",1),("r",1)]
102 102
103scsig t = scalar (signature (nms t)) `prod` t
104 where nms = map (snd.snd) . dims
105
106antisym' t = addT $ map (scsig . flip tridx t) (perms (names t))
107
108{-
109 where T d v = t
110 t' = T d' v
111 fixdim (T _ v) = T d v
112 d' = [(n,(c,show (pos q))) | (n,(c,q)) <- d]
113 pos n = i where Just i = elemIndex n nms
114 nms = map (snd.snd) d
115-}
116
117auxrename (T d v) = T d' v
118 where d' = [(n,(c,show (pos q))) | (n,(c,q)) <- d]
119 pos n = i where Just i = elemIndex n nms
120 nms = map (snd.snd) d
121
122antisym t = T (dims t) (ten (antisym' (auxrename t)))
123
124
125norper t = prod t (scalar (recip $ fromIntegral $ product [1 .. length (dims t)]))
126antinorper t = prod t (scalar (fromIntegral $ product [1 .. length (dims t)]))
127
128
129tvector n v = tensorFromVector (Contravariant,n) v
130tcovector n v = tensorFromVector (Covariant,n) v
131
132vector n v = tvector n (fromList v) :: Tensor Double
133
134wedge a b = antisym (prod (norper a) (norper b))
135
136a /\ b = wedge a b
137
138a <*> b = normal $ prod a b
139
140u = vector "p" [1,1,0]
141v = vector "q" [0,1,1]
142w = vector "r" [1,0,1]
143
144uv = u /\ v
145uw = u /\ w
146
147normAT t = sqrt $ innerAT t t
148
149innerAT t1 t2 = dot (ten t1) (ten t2) / fromIntegral (fact $ length $ dims t1)
150
151det m = product $ toList s where (_,s,_) = svdR' m
152
153fact n = product [1..n]
154
155l1 = vector "p" [0,0,0,1]
156l2 = vector "q" [1,0,0,1]
157l3 = vector "r" [0,1,0,1]
158
159leviCivita n = antisym $ foldl1 prod $ zipWith tcovector (map show [1..]) (toRows (ident n))
160
161contractionF t1 t2 = contraction t1 n1 t2 n2
162 where n1 = fn t1
163 n2 = fn t2
164 fn = snd . snd . head . dims
165
166
167dual vs = foldl' contractionF (leviCivita n) vs
168 where n = fst . head . dims . head $ vs
169
170
171dual1 = foldl' contractionF (leviCivita 3) [u,v]
172dual2 = foldl' contractionF (leviCivita 3) [u,v,w]
173
174
175contract1b t (n1,n2) = contract1 t n1 n2
176
177dual1' = prod (foldl' contract1b ((leviCivita 3) <*> (u /\ v)) [("1","p'"),("2'","q''")]) (scalar (recip $ fact 2))
178dual2' = prod (foldl' contract1b ((leviCivita 3) <*> (u /\ v /\ w)) [("1","p'"),("2'","q''"),("3'","r''")]) (scalar (recip $ fact 3)) \ No newline at end of file
diff --git a/examples/tests.hs b/examples/tests.hs
index 22c4674..4adc104 100644
--- a/examples/tests.hs
+++ b/examples/tests.hs
@@ -280,7 +280,7 @@ arit2 u = (vectorMapR Cos u) `mul` (vectorMapR Tan u)
280 ~|~ vectorMapR Sin u 280 ~|~ vectorMapR Sin u
281 281
282 282
283--arit3 (PairV u v) = vectorMap Sin . VectorMap Cos 283-- arit3 (PairV u v) =
284 284
285--------------------------------------------------------------------- 285---------------------------------------------------------------------
286 286
diff --git a/lib/Data/Packed/Internal/Common.hs b/lib/Data/Packed/Internal/Common.hs
index acefe92..91985f7 100644
--- a/lib/Data/Packed/Internal/Common.hs
+++ b/lib/Data/Packed/Internal/Common.hs
@@ -74,8 +74,8 @@ check msg ls f = do
74 mapM_ (touchForeignPtr . fptr) ls 74 mapM_ (touchForeignPtr . fptr) ls
75 return () 75 return ()
76 76
77class (Storable a, Typeable a) => Field a where 77class (Storable a, Typeable a) => Field a
78instance (Storable a, Typeable a) => Field a where 78instance (Storable a, Typeable a) => Field a
79 79
80isReal w x = typeOf (undefined :: Double) == typeOf (w x) 80isReal w x = typeOf (undefined :: Double) == typeOf (w x)
81isComp w x = typeOf (undefined :: Complex Double) == typeOf (w x) 81isComp w x = typeOf (undefined :: Complex Double) == typeOf (w x)
diff --git a/lib/Data/Packed/Internal/Tensor.hs b/lib/Data/Packed/Internal/Tensor.hs
index 123270d..27fce6a 100644
--- a/lib/Data/Packed/Internal/Tensor.hs
+++ b/lib/Data/Packed/Internal/Tensor.hs
@@ -18,7 +18,7 @@ import Data.Packed.Internal
18import Data.Packed.Internal.Vector 18import Data.Packed.Internal.Vector
19import Data.Packed.Internal.Matrix 19import Data.Packed.Internal.Matrix
20import Foreign.Storable 20import Foreign.Storable
21import Data.List(sort) 21import Data.List(sort,elemIndex,nub)
22 22
23data IdxTp = Covariant | Contravariant deriving (Show,Eq) 23data IdxTp = Covariant | Contravariant deriving (Show,Eq)
24 24
@@ -107,3 +107,18 @@ normal t = tridx (names t) t
107 107
108contractions t1 t2 = [ contraction t1 n1 t2 n2 | n1 <- names t1, n2 <- names t2, compatIdx t1 n1 t2 n2 ] 108contractions t1 t2 = [ contraction t1 n1 t2 n2 | n1 <- names t1, n2 <- names t2, compatIdx t1 n1 t2 n2 ]
109 109
110-- sent to Haskell-Cafe by Sebastian Sylvan
111perms [x] = [[x]]
112perms xs = [y:ps | (y,ys) <- selections xs , ps <- perms ys]
113selections [] = []
114selections (x:xs) = (x,xs) : [(y,x:ys) | (y,ys) <- selections xs]
115
116
117interchanges ls = sum (map (count ls) ls)
118 where count l p = n
119 where Just pel = elemIndex p l
120 n = length $ filter (>p) $ take pel l
121
122signature l | length (nub l) < length l = 0
123 | even (interchanges l) = 1
124 | otherwise = -1