Add shiftL and shiftR operators for signed and unsigned. Update name of shiftl and...
[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   , Bit(..)
13   , State(..)
14   , hwand
15   , hwor
16   , hwxor
17   , hwnot
18   , RAM
19   , MemState
20   , blockRAM
21   ) where
22
23 import qualified Prelude as P
24 import Prelude (Bool(..),Num(..),Eq(..),Ord(..),snd,fst,otherwise,(&&),(||),not)
25 import Types
26 import Data.Param.Integer (HWBits(..))
27 import Data.Param.Vector
28 import Data.Param.Index
29 import Data.Param.Signed
30 import Data.Param.Unsigned 
31 import Data.Bits hiding (shiftL,shiftR)
32
33 import Language.Haskell.TH.Lift
34 import Data.Typeable
35
36 newtype State s = State s deriving (P.Show)
37
38 -- The plain Bit type
39 data Bit = High | Low
40   deriving (P.Show, Eq, P.Read, Typeable)
41
42 deriveLift ''Bit
43
44 hwand :: Bit -> Bit -> Bit
45 hwor  :: Bit -> Bit -> Bit
46 hwxor :: Bit -> Bit -> Bit
47 hwnot :: Bit -> Bit
48
49 High `hwand` High = High
50 _ `hwand` _ = Low
51
52 High `hwor` _  = High
53 _ `hwor` High  = High
54 Low `hwor` Low = Low
55
56 High `hwxor` Low = High
57 Low `hwxor` High = High
58 _ `hwxor` _      = Low
59
60 hwnot High = Low
61 hwnot Low  = High
62
63 type RAM s a          = Vector s a
64 type MemState s a     = State (RAM s a)
65
66 blockRAM :: 
67   PositiveT s  =>
68   MemState s a -> 
69   a ->
70   Index s ->
71   Index s ->
72   Bool -> 
73   (MemState s a, a )
74 blockRAM (State mem) data_in rdaddr wraddr wrenable = 
75   ((State mem'), data_out)
76   where
77     data_out  = mem!rdaddr
78     -- Only write data_in to memory if write is enabled
79     mem' =  if wrenable then
80               replace mem wraddr data_in
81             else
82               mem