Use boolean as write enable signal
[matthijs/master-project/cλash.git] / cλash / CLasH / HardwareTypes.hs
index b48760a9db9a9f3720e90760278fd3b2b033a750..e6e84fd8a33a13aade58bbf5d4167552ba4afab0 100644 (file)
@@ -1,4 +1,4 @@
-{-# LANGUAGE TemplateHaskell, DeriveDataTypeable #-}
+{-# LANGUAGE TemplateHaskell, DeriveDataTypeable, FlexibleContexts, TypeFamilies, TypeOperators #-}
 
 module CLasH.HardwareTypes
   ( module Types
@@ -8,10 +8,17 @@ module CLasH.HardwareTypes
   , module Data.SizedWord
   , module Prelude
   , Bit(..)
+  , State(..)
+  , Vector
+  , resizeInt
+  , resizeWord
   , hwand
   , hwor
   , hwxor
   , hwnot
+  , RAM
+  , MemState
+  , blockRAM
   ) where
 
 import qualified Prelude as P
@@ -19,14 +26,27 @@ import Prelude hiding (
   null, length, head, tail, last, init, take, drop, (++), map, foldl, foldr,
   zipWith, zip, unzip, concat, reverse, iterate )
 import Types
-import Data.Param.TFVec
+import qualified Data.Param.TFVec as TFVec
+import Data.Param.TFVec hiding (TFVec)
 import Data.RangedWord
-import Data.SizedInt
-import Data.SizedWord 
+import qualified Data.SizedInt as SizedInt
+import Data.SizedInt hiding (resize)
+import qualified Data.SizedWord as SizedWord
+import Data.SizedWord hiding (resize) 
 
 import Language.Haskell.TH.Lift
 import Data.Typeable
 
+newtype State s = State s deriving (P.Show)
+
+type Vector = TFVec.TFVec
+
+resizeInt :: (NaturalT nT, NaturalT nT') => SizedInt nT -> SizedInt nT'
+resizeInt = SizedInt.resize
+
+resizeWord :: (NaturalT nT, NaturalT nT') => SizedWord nT -> SizedWord nT'
+resizeWord = SizedWord.resize
+
 -- The plain Bit type
 data Bit = High | Low
   deriving (P.Show, P.Eq, P.Read, Typeable)
@@ -50,4 +70,28 @@ Low `hwxor` High = High
 _ `hwxor` _      = Low
 
 hwnot High = Low
-hwnot Low  = High
\ No newline at end of file
+hwnot Low  = High
+
+type RAM s a          = Vector (s :+: D1) a
+
+type MemState s a      = State (RAM s a)
+
+blockRAM :: 
+  (NaturalT s
+  ,PositiveT (s :+: D1)
+  ,((s :+: D1) :>: s) ~ True ) =>
+  (MemState s a) -> 
+  a ->
+  RangedWord s ->
+  RangedWord s ->
+  Bool -> 
+  ((MemState s a), a )
+blockRAM (State mem) data_in rdaddr wraddr wrenable = 
+  ((State mem'), data_out)
+  where
+    data_out  = mem!rdaddr
+    -- Only write data_in to memory if write is enabled
+    mem' =  if wrenable then
+              replace mem wraddr data_in
+            else
+              mem