diff options
-rw-r--r-- | examples/Static.hs | 104 | ||||
-rw-r--r-- | examples/latexmat.hs | 11 | ||||
-rw-r--r-- | examples/parallel.hs | 10 | ||||
-rw-r--r-- | examples/usaStatic.hs | 36 |
4 files changed, 161 insertions, 0 deletions
diff --git a/examples/Static.hs b/examples/Static.hs new file mode 100644 index 0000000..c4856f5 --- /dev/null +++ b/examples/Static.hs | |||
@@ -0,0 +1,104 @@ | |||
1 | {-# OPTIONS_GHC -fglasgow-exts -fth -fallow-overlapping-instances -fallow-undecidable-instances #-} | ||
2 | |||
3 | module Static where | ||
4 | |||
5 | import Language.Haskell.TH | ||
6 | import Numeric.LinearAlgebra | ||
7 | import Foreign | ||
8 | import Language.Haskell.TH.Syntax | ||
9 | |||
10 | instance Lift Double where | ||
11 | lift x = return (LitE (RationalL (toRational x))) | ||
12 | |||
13 | --instance (Lift a, Storable a) => Lift (Vector a ) where | ||
14 | |||
15 | tdim :: Int -> ExpQ | ||
16 | tdim 0 = [| Z |] | ||
17 | tdim n = [| S $(tdim (n-1)) |] | ||
18 | |||
19 | |||
20 | data Z = Z deriving Show | ||
21 | data S a = S a deriving Show | ||
22 | |||
23 | class Dim a | ||
24 | |||
25 | instance Dim Z | ||
26 | instance Dim a => Dim (S a) | ||
27 | |||
28 | class Sum a b c | a b -> c -- , a c -> b, b c -> a | ||
29 | |||
30 | instance Sum Z a a | ||
31 | instance Sum a Z a | ||
32 | instance Sum a b c => Sum a (S b) (S c) | ||
33 | |||
34 | newtype SVec d t = SVec (Vector t) deriving Show | ||
35 | newtype SMat r c t = SMat (Matrix t) deriving Show | ||
36 | |||
37 | createl :: d -> [Double] -> SVec d Double | ||
38 | createl d l = SVec (fromList l) | ||
39 | |||
40 | createv :: Storable t => d -> Vector t -> SVec d t | ||
41 | createv d v = SVec v | ||
42 | |||
43 | --vec'' v = [|createv ($(tdim (dim v))) v|] | ||
44 | |||
45 | vec' :: [Double] -> ExpQ | ||
46 | vec' d = [| createl ($(tdim (length d))) d |] | ||
47 | |||
48 | |||
49 | createml :: (Dim r, Dim c) => r -> c -> Int -> Int -> [Double] -> SMat r c Double | ||
50 | createml _ _ r c l = SMat ((r><c) l) | ||
51 | |||
52 | mat :: Int -> Int -> [Double] -> ExpQ | ||
53 | mat r c l = [| createml ($(tdim r)) ($(tdim c)) r c l |] | ||
54 | |||
55 | vec :: [Double] -> ExpQ | ||
56 | vec d = [|mat (length d) 1 d|] | ||
57 | |||
58 | covec :: [Double] -> ExpQ | ||
59 | covec d = mat 1 (length d) d | ||
60 | |||
61 | scalar :: SMat (S Z) (S Z) Double -> Double | ||
62 | scalar (SMat m) = flatten m @> 0 | ||
63 | |||
64 | v = fromList [1..5] :: Vector Double | ||
65 | l = [1,1.5..5::Double] | ||
66 | |||
67 | k = [11..30::Int] | ||
68 | |||
69 | rawv (SVec v) = v | ||
70 | raw (SMat m) = m | ||
71 | |||
72 | liftStatic :: (Matrix a -> Matrix b -> Matrix c) -> SMat dr dc a -> SMat dr dc b -> SMat dr dc c | ||
73 | liftStatic f a b = SMat (f (raw a) (raw b)) | ||
74 | |||
75 | a |+| b = liftStatic (+) a b | ||
76 | |||
77 | prod :: SMat r k Double -> SMat k c Double -> SMat r c Double | ||
78 | prod a b = SMat (raw a <> raw b) | ||
79 | |||
80 | strans :: SMat r c Double -> SMat c r Double | ||
81 | strans = SMat . trans . raw | ||
82 | |||
83 | sdot a b = scalar (prod a b) | ||
84 | |||
85 | jv :: (Field t, Sum r1 r2 r3) => SMat r1 c t -> SMat r2 c t -> SMat r3 c t | ||
86 | jv a b = SMat ((raw a) <-> (raw b)) | ||
87 | |||
88 | -- curiously, we cannot easily fold jv because the matrics are not of the same type. | ||
89 | |||
90 | jh a b = strans (jv (strans a) (strans b)) | ||
91 | |||
92 | |||
93 | homog :: (Field t) => SMat r c t -> SMat (S r) c t | ||
94 | homog m = SMat (raw m <-> constant 1 (cols (raw m))) | ||
95 | |||
96 | inhomog :: (Linear Vector t) => SMat (S (S r)) c t -> SMat r c t | ||
97 | inhomog (SMat m) = SMat (sm <> d) where | ||
98 | sm = takeRows r' m | ||
99 | d = diag $ 1 / (flatten $ dropRows r' m) | ||
100 | r' = rows m -1 | ||
101 | |||
102 | |||
103 | ht t vs = inhomog (t `prod` homog vs) | ||
104 | |||
diff --git a/examples/latexmat.hs b/examples/latexmat.hs new file mode 100644 index 0000000..d912a28 --- /dev/null +++ b/examples/latexmat.hs | |||
@@ -0,0 +1,11 @@ | |||
1 | import Numeric.LinearAlgebra | ||
2 | import Text.Printf | ||
3 | |||
4 | disp w l fmt m = unlines $ map (++l) $ lines $ format w (printf fmt) m | ||
5 | |||
6 | latex fmt m = "\\begin{bmatrix}\n" ++ disp " & " " \\\\" fmt m ++ "\\end{bmatrix}" | ||
7 | |||
8 | main = do | ||
9 | let m = (3><4) [1..12::Double] | ||
10 | putStrLn $ disp " | " "" "%.2f" m | ||
11 | putStrLn $ latex "%.3f" m | ||
diff --git a/examples/parallel.hs b/examples/parallel.hs new file mode 100644 index 0000000..2ad686e --- /dev/null +++ b/examples/parallel.hs | |||
@@ -0,0 +1,10 @@ | |||
1 | import System(getArgs) | ||
2 | import Numeric.LinearAlgebra | ||
3 | import Control.Parallel.Strategies | ||
4 | |||
5 | work k = vectorMax s | ||
6 | where (_,s,_) = svd (ident k :: Matrix Double) | ||
7 | |||
8 | main = do | ||
9 | args <- (read . head) `fmap` getArgs | ||
10 | print $ sum $ parMap rnf work args \ No newline at end of file | ||
diff --git a/examples/usaStatic.hs b/examples/usaStatic.hs new file mode 100644 index 0000000..619af8f --- /dev/null +++ b/examples/usaStatic.hs | |||
@@ -0,0 +1,36 @@ | |||
1 | {-# OPTIONS -fno-monomorphism-restriction #-} | ||
2 | |||
3 | import Static | ||
4 | import Numeric.LinearAlgebra | ||
5 | |||
6 | |||
7 | x = $(vec [1,2]) | ||
8 | |||
9 | y = $(vec [5,7]) | ||
10 | |||
11 | z a = vec [a,a] | ||
12 | |||
13 | w = $(vec [1,2,3]) | ||
14 | |||
15 | cx = $(covec [1,2,3]) | ||
16 | |||
17 | |||
18 | t3 = $(tdim 3) | ||
19 | |||
20 | crm33 = createml t3 t3 3 3 | ||
21 | |||
22 | rot a = crm33 [a,0,0,0,a,0,0,0,1] | ||
23 | |||
24 | --q = x |+| y |+| $(z 5) | ||
25 | |||
26 | m = $(mat 2 3 [1..6]) | ||
27 | |||
28 | n = $(mat 3 5 [1..15]) | ||
29 | |||
30 | infixl 7 <*> | ||
31 | (<*>) = prod | ||
32 | |||
33 | r1 = m <*> n | ||
34 | r2 = strans (strans n <*> strans m) | ||
35 | |||
36 | --r' = prod n m | ||