Add derivelift function to hardwaretypes
[matthijs/master-project/cλash.git] / clash / CLasH / HardwareTypes.hs
1 {-# LANGUAGE TemplateHaskell, DeriveDataTypeable #-}
2
3 module CLasH.HardwareTypes
4   ( module Types
5   , module Data.Param.Integer
6   , module Data.Param.Vector
7   , module Data.Param.Index
8   , module Data.Param.Signed
9   , module Data.Param.Unsigned
10   , module Prelude
11   , module Data.Bits
12   , module Language.Haskell.TH.Lift
13   , Bit(..)
14   , State(..)
15   , hwand
16   , hwor
17   , hwxor
18   , hwnot
19   , RAM
20   , MemState
21   , blockRAM
22   ) where
23
24 import qualified Prelude as P
25 import Prelude (Bool(..),Num(..),Eq(..),Ord(..),snd,fst,otherwise,(&&),(||),not)
26 import Types
27 import Data.Param.Integer (HWBits(..))
28 import Data.Param.Vector
29 import Data.Param.Index
30 import Data.Param.Signed
31 import Data.Param.Unsigned 
32 import Data.Bits hiding (shiftL,shiftR)
33
34 import Language.Haskell.TH.Lift
35 import Data.Typeable
36
37 newtype State s = State s deriving (P.Show)
38
39 -- The plain Bit type
40 data Bit = High | Low
41   deriving (P.Show, Eq, P.Read, Typeable)
42
43 deriveLift ''Bit
44
45 hwand :: Bit -> Bit -> Bit
46 hwor  :: Bit -> Bit -> Bit
47 hwxor :: Bit -> Bit -> Bit
48 hwnot :: Bit -> Bit
49
50 High `hwand` High = High
51 _ `hwand` _ = Low
52
53 High `hwor` _  = High
54 _ `hwor` High  = High
55 Low `hwor` Low = Low
56
57 High `hwxor` Low = High
58 Low `hwxor` High = High
59 _ `hwxor` _      = Low
60
61 hwnot High = Low
62 hwnot Low  = High
63
64 type RAM s a          = Vector s a
65 type MemState s a     = State (RAM s a)
66
67 blockRAM :: 
68   PositiveT s  =>
69   MemState s a -> 
70   a ->
71   Index s ->
72   Index s ->
73   Bool -> 
74   (MemState s a, a )
75 blockRAM (State mem) data_in rdaddr wraddr wrenable = 
76   ((State mem'), data_out)
77   where
78     data_out  = mem!rdaddr
79     -- Only write data_in to memory if write is enabled
80     mem' =  if wrenable then
81               replace mem wraddr data_in
82             else
83               mem