diff options
Diffstat (limited to 'src/Array.hs')
-rw-r--r-- | src/Array.hs | 14 |
1 files changed, 13 insertions, 1 deletions
diff --git a/src/Array.hs b/src/Array.hs index 8507544..ef9bb8d 100644 --- a/src/Array.hs +++ b/src/Array.hs @@ -1,4 +1,5 @@ {-# LANGUAGE DataKinds #-} +{-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE DeriveTraversable #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE KindSignatures #-} @@ -6,10 +7,12 @@ {-# LANGUAGE TupleSections #-} module Array where +import Control.DeepSeq import Control.Monad.Trans.State.Strict import Data.Foldable (traverse_) import Data.Vector (Vector) import qualified Data.Vector as V +import GHC.Generics (Generic) import Data @@ -20,12 +23,20 @@ data Shape n where deriving instance Show (Shape n) deriving instance Eq (Shape n) +instance NFData (Shape n) where + rnf ShNil = () + rnf (sh `ShCons` n) = rnf n `seq` rnf sh + data Index n where IxNil :: Index Z IxCons :: Index n -> Int -> Index (S n) deriving instance Show (Index n) deriving instance Eq (Index n) +instance NFData (Index n) where + rnf IxNil = () + rnf (sh `IxCons` n) = rnf n `seq` rnf sh + shapeSize :: Shape n -> Int shapeSize ShNil = 1 shapeSize (ShCons sh n) = shapeSize sh * n @@ -51,7 +62,8 @@ enumShape sh = map (fromLinearIndex sh) [0 .. shapeSize sh - 1] -- | TODO: this Vector is a boxed vector, which is horrendously inefficient. data Array (n :: Nat) t = Array (Shape n) (Vector t) - deriving (Show, Functor, Foldable, Traversable) + deriving (Show, Functor, Foldable, Traversable, Generic) +instance NFData t => NFData (Array n t) arrayShape :: Array n t -> Shape n arrayShape (Array sh _) = sh |