summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--examples/Static.hs104
-rw-r--r--examples/latexmat.hs11
-rw-r--r--examples/parallel.hs10
-rw-r--r--examples/usaStatic.hs36
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
3module Static where
4
5import Language.Haskell.TH
6import Numeric.LinearAlgebra
7import Foreign
8import Language.Haskell.TH.Syntax
9
10instance Lift Double where
11 lift x = return (LitE (RationalL (toRational x)))
12
13--instance (Lift a, Storable a) => Lift (Vector a ) where
14
15tdim :: Int -> ExpQ
16tdim 0 = [| Z |]
17tdim n = [| S $(tdim (n-1)) |]
18
19
20data Z = Z deriving Show
21data S a = S a deriving Show
22
23class Dim a
24
25instance Dim Z
26instance Dim a => Dim (S a)
27
28class Sum a b c | a b -> c -- , a c -> b, b c -> a
29
30instance Sum Z a a
31instance Sum a Z a
32instance Sum a b c => Sum a (S b) (S c)
33
34newtype SVec d t = SVec (Vector t) deriving Show
35newtype SMat r c t = SMat (Matrix t) deriving Show
36
37createl :: d -> [Double] -> SVec d Double
38createl d l = SVec (fromList l)
39
40createv :: Storable t => d -> Vector t -> SVec d t
41createv d v = SVec v
42
43--vec'' v = [|createv ($(tdim (dim v))) v|]
44
45vec' :: [Double] -> ExpQ
46vec' d = [| createl ($(tdim (length d))) d |]
47
48
49createml :: (Dim r, Dim c) => r -> c -> Int -> Int -> [Double] -> SMat r c Double
50createml _ _ r c l = SMat ((r><c) l)
51
52mat :: Int -> Int -> [Double] -> ExpQ
53mat r c l = [| createml ($(tdim r)) ($(tdim c)) r c l |]
54
55vec :: [Double] -> ExpQ
56vec d = [|mat (length d) 1 d|]
57
58covec :: [Double] -> ExpQ
59covec d = mat 1 (length d) d
60
61scalar :: SMat (S Z) (S Z) Double -> Double
62scalar (SMat m) = flatten m @> 0
63
64v = fromList [1..5] :: Vector Double
65l = [1,1.5..5::Double]
66
67k = [11..30::Int]
68
69rawv (SVec v) = v
70raw (SMat m) = m
71
72liftStatic :: (Matrix a -> Matrix b -> Matrix c) -> SMat dr dc a -> SMat dr dc b -> SMat dr dc c
73liftStatic f a b = SMat (f (raw a) (raw b))
74
75a |+| b = liftStatic (+) a b
76
77prod :: SMat r k Double -> SMat k c Double -> SMat r c Double
78prod a b = SMat (raw a <> raw b)
79
80strans :: SMat r c Double -> SMat c r Double
81strans = SMat . trans . raw
82
83sdot a b = scalar (prod a b)
84
85jv :: (Field t, Sum r1 r2 r3) => SMat r1 c t -> SMat r2 c t -> SMat r3 c t
86jv 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
90jh a b = strans (jv (strans a) (strans b))
91
92
93homog :: (Field t) => SMat r c t -> SMat (S r) c t
94homog m = SMat (raw m <-> constant 1 (cols (raw m)))
95
96inhomog :: (Linear Vector t) => SMat (S (S r)) c t -> SMat r c t
97inhomog (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
103ht 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 @@
1import Numeric.LinearAlgebra
2import Text.Printf
3
4disp w l fmt m = unlines $ map (++l) $ lines $ format w (printf fmt) m
5
6latex fmt m = "\\begin{bmatrix}\n" ++ disp " & " " \\\\" fmt m ++ "\\end{bmatrix}"
7
8main = 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 @@
1import System(getArgs)
2import Numeric.LinearAlgebra
3import Control.Parallel.Strategies
4
5work k = vectorMax s
6 where (_,s,_) = svd (ident k :: Matrix Double)
7
8main = 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
3import Static
4import Numeric.LinearAlgebra
5
6
7x = $(vec [1,2])
8
9y = $(vec [5,7])
10
11z a = vec [a,a]
12
13w = $(vec [1,2,3])
14
15cx = $(covec [1,2,3])
16
17
18t3 = $(tdim 3)
19
20crm33 = createml t3 t3 3 3
21
22rot a = crm33 [a,0,0,0,a,0,0,0,1]
23
24--q = x |+| y |+| $(z 5)
25
26m = $(mat 2 3 [1..6])
27
28n = $(mat 3 5 [1..15])
29
30infixl 7 <*>
31(<*>) = prod
32
33r1 = m <*> n
34r2 = strans (strans n <*> strans m)
35
36--r' = prod n m