diff options
Diffstat (limited to 'packages/base')
-rw-r--r-- | packages/base/src/Internal/Matrix.hs | 1 | ||||
-rw-r--r-- | packages/base/src/Internal/Static.hs | 24 |
2 files changed, 21 insertions, 4 deletions
diff --git a/packages/base/src/Internal/Matrix.hs b/packages/base/src/Internal/Matrix.hs index 6efbe5f..c47c625 100644 --- a/packages/base/src/Internal/Matrix.hs +++ b/packages/base/src/Internal/Matrix.hs | |||
@@ -5,6 +5,7 @@ | |||
5 | {-# LANGUAGE TypeOperators #-} | 5 | {-# LANGUAGE TypeOperators #-} |
6 | {-# LANGUAGE TypeFamilies #-} | 6 | {-# LANGUAGE TypeFamilies #-} |
7 | {-# LANGUAGE ViewPatterns #-} | 7 | {-# LANGUAGE ViewPatterns #-} |
8 | {-# LANGUAGE DeriveGeneric #-} | ||
8 | {-# LANGUAGE ConstrainedClassMethods #-} | 9 | {-# LANGUAGE ConstrainedClassMethods #-} |
9 | 10 | ||
10 | -- | | 11 | -- | |
diff --git a/packages/base/src/Internal/Static.hs b/packages/base/src/Internal/Static.hs index 2c31097..1e9a5a3 100644 --- a/packages/base/src/Internal/Static.hs +++ b/packages/base/src/Internal/Static.hs | |||
@@ -13,6 +13,7 @@ | |||
13 | {-# LANGUAGE TypeOperators #-} | 13 | {-# LANGUAGE TypeOperators #-} |
14 | {-# LANGUAGE ViewPatterns #-} | 14 | {-# LANGUAGE ViewPatterns #-} |
15 | {-# LANGUAGE BangPatterns #-} | 15 | {-# LANGUAGE BangPatterns #-} |
16 | {-# LANGUAGE DeriveGeneric #-} | ||
16 | 17 | ||
17 | {- | | 18 | {- | |
18 | Module : Internal.Static | 19 | Module : Internal.Static |
@@ -34,6 +35,8 @@ import Control.DeepSeq | |||
34 | import Data.Proxy(Proxy) | 35 | import Data.Proxy(Proxy) |
35 | import Foreign.Storable(Storable) | 36 | import Foreign.Storable(Storable) |
36 | import Text.Printf | 37 | import Text.Printf |
38 | import Data.Binary | ||
39 | import GHC.Generics (Generic) | ||
37 | 40 | ||
38 | -------------------------------------------------------------------------------- | 41 | -------------------------------------------------------------------------------- |
39 | 42 | ||
@@ -41,7 +44,14 @@ type ℝ = Double | |||
41 | type ℂ = Complex Double | 44 | type ℂ = Complex Double |
42 | 45 | ||
43 | newtype Dim (n :: Nat) t = Dim t | 46 | newtype Dim (n :: Nat) t = Dim t |
44 | deriving Show | 47 | deriving (Show, Generic) |
48 | |||
49 | instance Binary a => Binary (Complex a) | ||
50 | where | ||
51 | put (r :+ i) = put (r, i) | ||
52 | get = (\(r,i) -> r :+ i) <$> get | ||
53 | |||
54 | instance (Binary a) => Binary (Dim n a) | ||
45 | 55 | ||
46 | lift1F | 56 | lift1F |
47 | :: (c t -> c t) | 57 | :: (c t -> c t) |
@@ -59,15 +69,21 @@ instance NFData t => NFData (Dim n t) where | |||
59 | -------------------------------------------------------------------------------- | 69 | -------------------------------------------------------------------------------- |
60 | 70 | ||
61 | newtype R n = R (Dim n (Vector ℝ)) | 71 | newtype R n = R (Dim n (Vector ℝ)) |
62 | deriving (Num,Fractional,Floating) | 72 | deriving (Num,Fractional,Floating,Generic) |
63 | 73 | ||
64 | newtype C n = C (Dim n (Vector ℂ)) | 74 | newtype C n = C (Dim n (Vector ℂ)) |
65 | deriving (Num,Fractional,Floating) | 75 | deriving (Num,Fractional,Floating,Generic) |
66 | 76 | ||
67 | newtype L m n = L (Dim m (Dim n (Matrix ℝ))) | 77 | newtype L m n = L (Dim m (Dim n (Matrix ℝ))) |
78 | deriving (Generic) | ||
68 | 79 | ||
69 | newtype M m n = M (Dim m (Dim n (Matrix ℂ))) | 80 | newtype M m n = M (Dim m (Dim n (Matrix ℂ))) |
81 | deriving (Generic) | ||
70 | 82 | ||
83 | instance (KnownNat n) => Binary (R n) | ||
84 | instance (KnownNat n) => Binary (C n) | ||
85 | instance (KnownNat m, KnownNat n) => Binary (L m n) | ||
86 | instance (KnownNat m, KnownNat n) => Binary (M m n) | ||
71 | 87 | ||
72 | mkR :: Vector ℝ -> R n | 88 | mkR :: Vector ℝ -> R n |
73 | mkR = R . Dim | 89 | mkR = R . Dim |