summaryrefslogtreecommitdiff
path: root/src/Interpreter/Array.hs
diff options
context:
space:
mode:
Diffstat (limited to 'src/Interpreter/Array.hs')
-rw-r--r--src/Interpreter/Array.hs42
1 files changed, 42 insertions, 0 deletions
diff --git a/src/Interpreter/Array.hs b/src/Interpreter/Array.hs
new file mode 100644
index 0000000..f358225
--- /dev/null
+++ b/src/Interpreter/Array.hs
@@ -0,0 +1,42 @@
+{-# LANGUAGE KindSignatures #-}
+{-# LANGUAGE DataKinds #-}
+{-# LANGUAGE GADTs #-}
+{-# LANGUAGE TupleSections #-}
+module Interpreter.Array where
+
+import Control.Monad.Trans.State.Strict
+import Data.Foldable (traverse_)
+import Data.Vector (Vector)
+import qualified Data.Vector as V
+
+import Data
+
+
+data Shape n where
+ ShNil :: Shape Z
+ ShCons :: Shape n -> Int -> Shape (S n)
+
+data Index n where
+ IxNil :: Index Z
+ IxCons :: Index n -> Int -> Index (S n)
+
+shapeSize :: Shape n -> Int
+shapeSize ShNil = 0
+shapeSize (ShCons sh n) = shapeSize sh * n
+
+
+-- | TODO: this Vector is a boxed vector, which is horrendously inefficient.
+data Array (n :: Nat) t = Array (Shape n) (Vector t)
+
+arrayShape :: Array n t -> Shape n
+arrayShape (Array sh _) = sh
+
+arraySize :: Array n t -> Int
+arraySize (Array sh _) = shapeSize sh
+
+arrayGenerateLinM :: Monad m => Shape n -> (Int -> m t) -> m (Array n t)
+arrayGenerateLinM sh f = Array sh <$> V.generateM (shapeSize sh) f
+
+-- | The Int is the linear index of the value.
+traverseArray_ :: Monad m => (Int -> t -> m ()) -> Array n t -> m ()
+traverseArray_ f (Array _ v) = evalStateT (traverse_ (\x -> StateT (\i -> (,i+1) <$> f i x)) v) 0