Add builtin blockRAM primitive
[matthijs/master-project/cλash.git] / cλash / CLasH / HardwareTypes.hs
1 {-# LANGUAGE TemplateHaskell, DeriveDataTypeable, FlexibleContexts, TypeFamilies, TypeOperators #-}
2
3 module CLasH.HardwareTypes
4   ( module Types
5   , module Data.Param.TFVec
6   , module Data.RangedWord
7   , module Data.SizedInt
8   , module Data.SizedWord
9   , module Prelude
10   , Bit(..)
11   , State(..)
12   , Vector
13   , hwand
14   , hwor
15   , hwxor
16   , hwnot
17   , RAM
18   , MemState
19   , blockRAM
20   ) where
21
22 import qualified Prelude as P
23 import Prelude hiding (
24   null, length, head, tail, last, init, take, drop, (++), map, foldl, foldr,
25   zipWith, zip, unzip, concat, reverse, iterate )
26 import Types
27 import qualified Data.Param.TFVec as TFVec
28 import Data.Param.TFVec hiding (TFVec)
29 import Data.RangedWord
30 import Data.SizedInt
31 import Data.SizedWord 
32
33 import Language.Haskell.TH.Lift
34 import Data.Typeable
35
36 newtype State s = State s deriving (P.Show)
37
38 type Vector = TFVec.TFVec
39
40 -- The plain Bit type
41 data Bit = High | Low
42   deriving (P.Show, P.Eq, P.Read, Typeable)
43
44 $(deriveLift1 ''Bit)
45
46 hwand :: Bit -> Bit -> Bit
47 hwor  :: Bit -> Bit -> Bit
48 hwxor :: Bit -> Bit -> Bit
49 hwnot :: Bit -> Bit
50
51 High `hwand` High = High
52 _ `hwand` _ = Low
53
54 High `hwor` _  = High
55 _ `hwor` High  = High
56 Low `hwor` Low = Low
57
58 High `hwxor` Low = High
59 Low `hwxor` High = High
60 _ `hwxor` _      = Low
61
62 hwnot High = Low
63 hwnot Low  = High
64
65 type RAM s a          = Vector (s :+: D1) a
66
67 type MemState s a      = State (RAM s a)
68
69 blockRAM :: 
70   (NaturalT s
71   ,PositiveT (s :+: D1)
72   ,((s :+: D1) :>: s) ~ True ) =>
73   (MemState s a) -> 
74   a ->
75   RangedWord s ->
76   RangedWord s ->
77   Bit -> 
78   ((MemState s a), a )
79 blockRAM (State mem) data_in rdaddr wraddr wrenable = 
80   ((State mem'), data_out)
81   where
82     data_out  = mem!rdaddr
83     -- Only write data_in to memory if write is enabled
84     mem' = case wrenable of
85       Low   ->  mem
86       High  ->  replace mem wraddr data_in