summaryrefslogtreecommitdiff
path: root/packages/base
diff options
context:
space:
mode:
Diffstat (limited to 'packages/base')
-rw-r--r--packages/base/hmatrix.cabal3
-rw-r--r--packages/base/src/Internal/Matrix.hs1
-rw-r--r--packages/base/src/Internal/Static.hs25
3 files changed, 23 insertions, 6 deletions
diff --git a/packages/base/hmatrix.cabal b/packages/base/hmatrix.cabal
index 9fa3c4e..5524d2b 100644
--- a/packages/base/hmatrix.cabal
+++ b/packages/base/hmatrix.cabal
@@ -79,8 +79,7 @@ library
79 src/Internal/C/vector-aux.c 79 src/Internal/C/vector-aux.c
80 80
81 81
82 extensions: ForeignFunctionInterface, 82 extensions: ForeignFunctionInterface
83 CPP
84 83
85 ghc-options: -Wall 84 ghc-options: -Wall
86 -fno-warn-missing-signatures 85 -fno-warn-missing-signatures
diff --git a/packages/base/src/Internal/Matrix.hs b/packages/base/src/Internal/Matrix.hs
index 3082e8d..f9b02ca 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 9
9 10
10 11
diff --git a/packages/base/src/Internal/Static.hs b/packages/base/src/Internal/Static.hs
index 419ff07..0ad2cad 100644
--- a/packages/base/src/Internal/Static.hs
+++ b/packages/base/src/Internal/Static.hs
@@ -1,3 +1,4 @@
1{-# LANGUAGE CPP #-}
1#if __GLASGOW_HASKELL__ >= 708 2#if __GLASGOW_HASKELL__ >= 708
2 3
3{-# LANGUAGE DataKinds #-} 4{-# LANGUAGE DataKinds #-}
@@ -12,6 +13,7 @@
12{-# LANGUAGE TypeOperators #-} 13{-# LANGUAGE TypeOperators #-}
13{-# LANGUAGE ViewPatterns #-} 14{-# LANGUAGE ViewPatterns #-}
14{-# LANGUAGE BangPatterns #-} 15{-# LANGUAGE BangPatterns #-}
16{-# LANGUAGE DeriveGeneric #-}
15 17
16{- | 18{- |
17Module : Internal.Static 19Module : Internal.Static
@@ -33,6 +35,8 @@ import Control.DeepSeq
33import Data.Proxy(Proxy) 35import Data.Proxy(Proxy)
34import Foreign.Storable(Storable) 36import Foreign.Storable(Storable)
35import Text.Printf 37import Text.Printf
38import Data.Binary
39import GHC.Generics (Generic)
36 40
37-------------------------------------------------------------------------------- 41--------------------------------------------------------------------------------
38 42
@@ -40,7 +44,14 @@ type ℝ = Double
40type ℂ = Complex Double 44type ℂ = Complex Double
41 45
42newtype Dim (n :: Nat) t = Dim t 46newtype Dim (n :: Nat) t = Dim t
43 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)
44 55
45lift1F 56lift1F
46 :: (c t -> c t) 57 :: (c t -> c t)
@@ -58,15 +69,21 @@ instance NFData t => NFData (Dim n t) where
58-------------------------------------------------------------------------------- 69--------------------------------------------------------------------------------
59 70
60newtype R n = R (Dim n (Vector ℝ)) 71newtype R n = R (Dim n (Vector ℝ))
61 deriving (Num,Fractional,Floating) 72 deriving (Num,Fractional,Floating,Generic)
62 73
63newtype C n = C (Dim n (Vector ℂ)) 74newtype C n = C (Dim n (Vector ℂ))
64 deriving (Num,Fractional,Floating) 75 deriving (Num,Fractional,Floating,Generic)
65 76
66newtype L m n = L (Dim m (Dim n (Matrix ℝ))) 77newtype L m n = L (Dim m (Dim n (Matrix ℝ)))
78 deriving (Generic)
67 79
68newtype M m n = M (Dim m (Dim n (Matrix ℂ))) 80newtype M m n = M (Dim m (Dim n (Matrix ℂ)))
81 deriving (Generic)
69 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)
70 87
71mkR :: Vector ℝ -> R n 88mkR :: Vector ℝ -> R n
72mkR = R . Dim 89mkR = R . Dim