diff options
Diffstat (limited to 'examples')
-rw-r--r-- | examples/pru.hs | 27 | ||||
-rw-r--r-- | examples/tests.hs | 20 |
2 files changed, 11 insertions, 36 deletions
diff --git a/examples/pru.hs b/examples/pru.hs index 10789d2..a90aa6f 100644 --- a/examples/pru.hs +++ b/examples/pru.hs | |||
@@ -1,9 +1,11 @@ | |||
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.Vector | 5 | import Data.Packed.Internal.Vector |
5 | import Data.Packed.Internal.Matrix | 6 | import Data.Packed.Internal.Matrix |
6 | import Data.Packed.Internal.Tensor | 7 | import Data.Packed.Internal.Tensor |
8 | import Data.Packed.Matrix | ||
7 | import LAPACK | 9 | import LAPACK |
8 | 10 | ||
9 | import Complex | 11 | import Complex |
@@ -11,17 +13,6 @@ import Numeric(showGFloat) | |||
11 | import Data.List(transpose,intersperse,sort) | 13 | import Data.List(transpose,intersperse,sort) |
12 | import Foreign.Storable | 14 | import Foreign.Storable |
13 | 15 | ||
14 | r >< c = f where | ||
15 | f l | dim v == r*c = matrixFromVector RowMajor c v | ||
16 | | otherwise = error $ "inconsistent list size = " | ||
17 | ++show (dim v) ++"in ("++show r++"><"++show c++")" | ||
18 | where v = fromList l | ||
19 | |||
20 | r >|< c = f where | ||
21 | f l | dim v == r*c = matrixFromVector ColumnMajor c v | ||
22 | | otherwise = error $ "inconsistent list size = " | ||
23 | ++show (dim v) ++"in ("++show r++"><"++show c++")" | ||
24 | where v = fromList l | ||
25 | 16 | ||
26 | vr = fromList [1..15::Double] | 17 | vr = fromList [1..15::Double] |
27 | vc = fromList (map (\x->x :+ (x+1)) [1..15::Double]) | 18 | vc = fromList (map (\x->x :+ (x+1)) [1..15::Double]) |
@@ -49,8 +40,10 @@ cf = mulF af bc | |||
49 | r = mulC cc (trans cf) | 40 | r = mulC cc (trans cf) |
50 | 41 | ||
51 | rd = (2><2) | 42 | rd = (2><2) |
52 | [ 43492.0, 50572.0 | 43 | [ 27736.0, 65356.0 |
53 | , 102550.0, 119242.0 ] | 44 | , 65356.0, 154006.0 ] |
45 | |||
46 | |||
54 | 47 | ||
55 | main = do | 48 | main = do |
56 | print $ r |=| rd | 49 | print $ r |=| rd |
@@ -77,7 +70,6 @@ e i n = fromList [ delta k i | k <- [1..n]] | |||
77 | 70 | ||
78 | diagl = diag.fromList | 71 | diagl = diag.fromList |
79 | 72 | ||
80 | ident n = diag (constant n 1) | ||
81 | 73 | ||
82 | tensorFromVector idx v = T {dims = [(dim v,idx)], ten = v} | 74 | tensorFromVector idx v = T {dims = [(dim v,idx)], ten = v} |
83 | tensorFromMatrix idxr idxc m = T {dims = [(rows m,idxr),(cols m,idxc)], ten = cdat m} | 75 | tensorFromMatrix idxr idxc m = T {dims = [(rows m,idxr),(cols m,idxc)], ten = cdat m} |
@@ -107,10 +99,3 @@ pru = do | |||
107 | print $ normal t2 | 99 | print $ normal t2 |
108 | print $ foldl part t2 [("j'",0),("p",1),("r",1)] | 100 | print $ foldl part t2 [("j'",0),("p",1),("r",1)] |
109 | 101 | ||
110 | |||
111 | names t = sort $ map (snd.snd) (dims t) | ||
112 | |||
113 | normal t = tridx (names t) t | ||
114 | |||
115 | contractions t1 t2 = [ contraction t1 n1 t2 n2 | n1 <- names t1, n2 <- names t2, compatIdx t1 n1 t2 n2 ] | ||
116 | |||
diff --git a/examples/tests.hs b/examples/tests.hs index b075704..9f0ae2a 100644 --- a/examples/tests.hs +++ b/examples/tests.hs | |||
@@ -4,7 +4,9 @@ | |||
4 | 4 | ||
5 | ----------------------------------------------------------------------------- | 5 | ----------------------------------------------------------------------------- |
6 | 6 | ||
7 | import Data.Packed.Internal.Vector | 7 | import Data.Packed.Internal |
8 | import Data.Packed.Vector | ||
9 | import Data.Packed.Matrix | ||
8 | import Data.Packed.Internal.Matrix | 10 | import Data.Packed.Internal.Matrix |
9 | import LAPACK | 11 | import LAPACK |
10 | import Test.QuickCheck | 12 | import Test.QuickCheck |
@@ -31,18 +33,6 @@ nullspaceProp tol m = cr > 0 ==> m <> nt ~~ zeros | |||
31 | 33 | ||
32 | -} | 34 | -} |
33 | 35 | ||
34 | r >< c = f where | ||
35 | f l | dim v == r*c = matrixFromVector RowMajor c v | ||
36 | | otherwise = error $ "inconsistent list size = " | ||
37 | ++show (dim v) ++"in ("++show r++"><"++show c++")" | ||
38 | where v = fromList l | ||
39 | |||
40 | r >|< c = f where | ||
41 | f l | dim v == r*c = matrixFromVector ColumnMajor c v | ||
42 | | otherwise = error $ "inconsistent list size = " | ||
43 | ++show (dim v) ++"in ("++show r++"><"++show c++")" | ||
44 | where v = fromList l | ||
45 | |||
46 | ac = (2><3) [1 .. 6::Double] | 36 | ac = (2><3) [1 .. 6::Double] |
47 | bc = (3><4) [7 .. 18::Double] | 37 | bc = (3><4) [7 .. 18::Double] |
48 | 38 | ||
@@ -82,8 +72,8 @@ cf = mulF af bc | |||
82 | r = mulC cc (trans cf) | 72 | r = mulC cc (trans cf) |
83 | 73 | ||
84 | rd = (2><2) | 74 | rd = (2><2) |
85 | [ 43492.0, 50572.0 | 75 | [ 27736.0, 65356.0 |
86 | , 102550.0, 119242.0 :: Double] | 76 | , 65356.0, 154006.0 ::Double] |
87 | 77 | ||
88 | instance (Arbitrary a, RealFloat a) => Arbitrary (Complex a) where | 78 | instance (Arbitrary a, RealFloat a) => Arbitrary (Complex a) where |
89 | arbitrary = do | 79 | arbitrary = do |