summaryrefslogtreecommitdiff
path: root/packages/base/src/Internal
diff options
context:
space:
mode:
Diffstat (limited to 'packages/base/src/Internal')
-rw-r--r--packages/base/src/Internal/Matrix.hs1
-rw-r--r--packages/base/src/Internal/Static.hs24
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{- |
18Module : Internal.Static 19Module : Internal.Static
@@ -34,6 +35,8 @@ import Control.DeepSeq
34import Data.Proxy(Proxy) 35import Data.Proxy(Proxy)
35import Foreign.Storable(Storable) 36import Foreign.Storable(Storable)
36import Text.Printf 37import Text.Printf
38import Data.Binary
39import GHC.Generics (Generic)
37 40
38-------------------------------------------------------------------------------- 41--------------------------------------------------------------------------------
39 42
@@ -41,7 +44,14 @@ type ℝ = Double
41type ℂ = Complex Double 44type ℂ = Complex Double
42 45
43newtype Dim (n :: Nat) t = Dim t 46newtype Dim (n :: Nat) t = Dim t
44 deriving Show 47 deriving (Show, Generic)
48
49instance Binary a => Binary (Complex a)
50 where
51 put (r :+ i) = put (r, i)
52 get = (\(r,i) -> r :+ i) <$> get
53
54instance (Binary a) => Binary (Dim n a)
45 55
46lift1F 56lift1F
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
61newtype R n = R (Dim n (Vector ℝ)) 71newtype R n = R (Dim n (Vector ℝ))
62 deriving (Num,Fractional,Floating) 72 deriving (Num,Fractional,Floating,Generic)
63 73
64newtype C n = C (Dim n (Vector ℂ)) 74newtype C n = C (Dim n (Vector ℂ))
65 deriving (Num,Fractional,Floating) 75 deriving (Num,Fractional,Floating,Generic)
66 76
67newtype L m n = L (Dim m (Dim n (Matrix ℝ))) 77newtype L m n = L (Dim m (Dim n (Matrix ℝ)))
78 deriving (Generic)
68 79
69newtype M m n = M (Dim m (Dim n (Matrix ℂ))) 80newtype M m n = M (Dim m (Dim n (Matrix ℂ)))
81 deriving (Generic)
70 82
83instance (KnownNat n) => Binary (R n)
84instance (KnownNat n) => Binary (C n)
85instance (KnownNat m, KnownNat n) => Binary (L m n)
86instance (KnownNat m, KnownNat n) => Binary (M m n)
71 87
72mkR :: Vector ℝ -> R n 88mkR :: Vector ℝ -> R n
73mkR = R . Dim 89mkR = R . Dim