diff options
author | Alberto Ruiz <aruiz@um.es> | 2014-05-27 10:41:40 +0200 |
---|---|---|
committer | Alberto Ruiz <aruiz@um.es> | 2014-05-27 10:41:40 +0200 |
commit | cf3c788f0c44577ac1a5365e8154200b53a36409 (patch) | |
tree | d667ea10609e74b69b11309bb59b7e000b240a92 /packages/base/src/Numeric/LinearAlgebra/Util/Static.hs | |
parent | 365e2435e71de10ebe849acac5a107b6f43817c4 (diff) |
static dimensions, cont.
Diffstat (limited to 'packages/base/src/Numeric/LinearAlgebra/Util/Static.hs')
-rw-r--r-- | packages/base/src/Numeric/LinearAlgebra/Util/Static.hs | 70 |
1 files changed, 0 insertions, 70 deletions
diff --git a/packages/base/src/Numeric/LinearAlgebra/Util/Static.hs b/packages/base/src/Numeric/LinearAlgebra/Util/Static.hs deleted file mode 100644 index a3f8eb0..0000000 --- a/packages/base/src/Numeric/LinearAlgebra/Util/Static.hs +++ /dev/null | |||
@@ -1,70 +0,0 @@ | |||
1 | {-# LANGUAGE DataKinds #-} | ||
2 | {-# LANGUAGE KindSignatures #-} | ||
3 | {-# LANGUAGE GeneralizedNewtypeDeriving #-} | ||
4 | {-# LANGUAGE MultiParamTypeClasses #-} | ||
5 | {-# LANGUAGE FlexibleContexts #-} | ||
6 | {-# LANGUAGE ScopedTypeVariables #-} | ||
7 | {-# LANGUAGE EmptyDataDecls #-} | ||
8 | {-# LANGUAGE Rank2Types #-} | ||
9 | {-# LANGUAGE FlexibleInstances #-} | ||
10 | {-# LANGUAGE TypeOperators #-} | ||
11 | |||
12 | module Numeric.LinearAlgebra.Util.Static( | ||
13 | Static (ddata), | ||
14 | R, | ||
15 | vect0, sScalar, vect2, vect3, (&) | ||
16 | ) where | ||
17 | |||
18 | |||
19 | import GHC.TypeLits | ||
20 | import Data.Packed.Numeric | ||
21 | import Numeric.Vector() | ||
22 | import Numeric.LinearAlgebra.Util(Numeric,ℝ) | ||
23 | |||
24 | lift1F :: (Vector t -> Vector t) -> Static n (Vector t) -> Static n (Vector t) | ||
25 | lift1F f (Static v) = Static (f v) | ||
26 | |||
27 | lift2F :: (Vector t -> Vector t -> Vector t) -> Static n (Vector t) -> Static n (Vector t) -> Static n (Vector t) | ||
28 | lift2F f (Static u) (Static v) = Static (f u v) | ||
29 | |||
30 | newtype Static (n :: Nat) t = Static { ddata :: t } deriving Show | ||
31 | |||
32 | type R n = Static n (Vector ℝ) | ||
33 | |||
34 | |||
35 | infixl 4 & | ||
36 | (&) :: R n -> ℝ -> R (n+1) | ||
37 | Static v & x = Static (vjoin [v, scalar x]) | ||
38 | |||
39 | vect0 :: R 0 | ||
40 | vect0 = Static (fromList[]) | ||
41 | |||
42 | sScalar :: ℝ -> R 1 | ||
43 | sScalar = Static . scalar | ||
44 | |||
45 | |||
46 | vect2 :: ℝ -> ℝ -> R 2 | ||
47 | vect2 x1 x2 = Static (fromList [x1,x2]) | ||
48 | |||
49 | vect3 :: ℝ -> ℝ -> ℝ -> R 3 | ||
50 | vect3 x1 x2 x3 = Static (fromList [x1,x2,x3]) | ||
51 | |||
52 | |||
53 | |||
54 | |||
55 | |||
56 | |||
57 | instance forall n t . (KnownNat n, Num (Vector t), Numeric t )=> Num (Static n (Vector t)) | ||
58 | where | ||
59 | (+) = lift2F add | ||
60 | (*) = lift2F mul | ||
61 | (-) = lift2F sub | ||
62 | abs = lift1F abs | ||
63 | signum = lift1F signum | ||
64 | negate = lift1F (scale (-1)) | ||
65 | fromInteger x = Static (konst (fromInteger x) d) | ||
66 | where | ||
67 | d = fromIntegral . natVal $ (undefined :: Proxy n) | ||
68 | |||
69 | data Proxy :: Nat -> * | ||
70 | |||