summaryrefslogtreecommitdiff
path: root/examples/pru.hs
blob: 4a5104b42c3a10bd82940f4a587bb50024dad341 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
--{-# OPTIONS_GHC  #-}
--module Main where

import Data.Packed.Internal
import Data.Packed.Internal.Vector
import Data.Packed.Internal.Matrix
import Data.Packed.Internal.Tensor
import Data.Packed.Matrix
import GSL.Vector
import LAPACK

import Complex
import Numeric(showGFloat)
import Data.List(transpose,intersperse,sort,elemIndex,nub,foldl',foldl1')
import Foreign.Storable


vr = fromList [1..15::Double]
vc = fromList (map (\x->x :+ (x+1)) [1..15::Double])

mi = (2 >< 3) [1 .. 6::Int]
mz = (2 >< 3) [1,2,3,4,5,6:+(1::Double)]

ac = (2><3) [1 .. 6::Double]
bc = (3><4) [7 .. 18::Double]

af = (2>|<3) [1,4,2,5,3,6::Double]
bf = (3>|<4) [7,11,15,8,12,16,9,13,17,10,14,18::Double]


a |=| b = rows a == rows b &&
          cols a == cols b &&
          toList (cdat a) == toList (cdat b)

mulC a b = multiply RowMajor a b
mulF a b = multiply ColumnMajor a b

cc = mulC ac bf
cf = mulF af bc

r = mulC cc (trans cf)

rd = (2><2)
 [ 27736.0,  65356.0
 , 65356.0, 154006.0 ]



main = do
    print $ r |=| rd
    print $ foldl part t [("p",1),("q",0),("r",2)]
    print $ foldl part t [("p",1),("r",2),("q",0)]
    print $ foldl part t $ reverse [("p",1),("r",2),("q",0)]

t = T [(4,(Covariant,"p")),(2,(Covariant,"q")),(3,(Contravariant,"r"))] $ fromList [1..24::Double]



t1 = T [(4,(Covariant,"p")),(4,(Contravariant,"q")),(2,(Covariant,"r"))] $ fromList [1..32::Double]
t2 = T [(4,(Covariant,"p")),(4,(Contravariant,"q"))] $ fromList [1..16::Double]



addT ts = T (dims (head ts)) (fromList $ sumT ts)


delta i j | i==j      = 1
          | otherwise = 0

e i n = fromList [ delta k i | k <- [1..n]]

diagl = diag.fromList

scalar x = T [] (fromList [x])
tensorFromVector idx v = T {dims = [(dim v,idx)], ten = v}
tensorFromMatrix idxr idxc m = T {dims = [(rows m,idxr),(cols m,idxc)], ten = cdat m}

td = tensorFromMatrix (Contravariant,"i") (Covariant,"j") $ diagl [1..4] :: Tensor Double

tn = tensorFromMatrix (Contravariant,"i") (Covariant,"j") $ (2><3) [1..6] :: Tensor Double
tt = tensorFromMatrix (Contravariant,"i") (Covariant,"j") $ (2><3) [1..6] :: Tensor Double

tq = T [(3,(Covariant,"p")),(2,(Covariant,"q")),(2,(Covariant,"r"))] $ fromList [11 .. 22] :: Tensor Double

r1 = contraction tt "j" tq "p"
r1' = contraction' tt "j" tq "p"

pru = do
    mapM_ (putStrLn.shdims.dims.normal) (contractions t1 t2)
    let t1 = contraction tt "i" tq "q"
    print $ normal t1
    print $ foldl part t1 [("j",0),("p'",1),("r'",1)]
    let t2 = contraction' tt "i" tq "q"
    print $ normal t2
    print $ foldl part t2 [("j",0),("p'",1),("r'",1)]
    let t1 = contraction tq "q" tt "i"
    print $ normal t1
    print $ foldl part t1 [("j'",0),("p",1),("r",1)]
    let t2 = contraction' tq "q" tt "i"
    print $ normal t2
    print $ foldl part t2 [("j'",0),("p",1),("r",1)]

scsig t = scalar (signature (nms t)) `prod` t
    where nms = map (snd.snd) . dims

antisym' t = addT $ map (scsig . flip tridx t) (perms (names t))

{-
   where T d v = t
          t' = T d' v
          fixdim (T _ v) = T d v
          d' = [(n,(c,show (pos q))) | (n,(c,q)) <- d]
          pos n = i where Just i = elemIndex n nms
          nms = map (snd.snd) d
-}

auxrename (T d v) = T d' v
    where d' = [(n,(c,show (pos q))) | (n,(c,q)) <- d]
          pos n = i where Just i = elemIndex n nms
          nms = map (snd.snd) d

antisym t = T (dims t) (ten (antisym' (auxrename t)))


norper t = prod t (scalar (recip $ fromIntegral $ product [1 .. length (dims t)]))
antinorper t = prod t (scalar (fromIntegral $ product [1 .. length (dims t)]))


tvector n v = tensorFromVector (Contravariant,n) v
tcovector n v = tensorFromVector (Covariant,n) v

vector n v = tvector n (fromList v) :: Tensor Double

wedge a b = antisym (prod (norper a) (norper b))

a /\ b = wedge a b

a <*> b = normal $ prod a b

u = vector "p" [1,1,0]
v = vector "q" [0,1,1]
w = vector "r" [1,0,1]

uv = u /\ v
uw = u /\ w

normAT t = sqrt $ innerAT t t

innerAT t1 t2 = dot (ten t1) (ten t2) / fromIntegral (fact $ length $ dims t1)

det m = product $ toList s where (_,s,_) = svdR' m

fact n = product [1..n]

l1 = vector "p" [0,0,0,1]
l2 = vector "q" [1,0,0,1]
l3 = vector "r" [0,1,0,1]

leviCivita n = antisym $ foldl1 prod $ zipWith tcovector (map show [1..]) (toRows (ident n))

contractionF t1 t2 = contraction t1 n1 t2 n2
    where n1 = fn t1
          n2 = fn t2
          fn = snd . snd . head . dims


dual vs = foldl' contractionF (leviCivita n) vs
    where n = fst . head . dims . head $ vs


dual1 = foldl' contractionF (leviCivita 3) [u,v]
dual2 = foldl' contractionF (leviCivita 3) [u,v,w]


contract1b t (n1,n2) = contract1 t n1 n2

dual1' = prod (foldl' contract1b ((leviCivita 3) <*> (u /\ v)) [("1","p'"),("2'","q''")]) (scalar (recip $ fact 2))
dual2' = prod (foldl' contract1b ((leviCivita 3) <*> (u /\ v /\ w)) [("1","p'"),("2'","q''"),("3'","r''")]) (scalar (recip $ fact 3))