Give the index type an exclusive upper-bound, and fix related types accordingly
[matthijs/master-project/cλash.git] / clash / CLasH / HardwareTypes.hs
1 {-# LANGUAGE TemplateHaskell, DeriveDataTypeable, FlexibleContexts, TypeFamilies, TypeOperators #-}
2
3 module CLasH.HardwareTypes
4   ( module Types
5   , module Data.Param.Vector
6   , module Data.Param.Index
7   , module Data.Param.Signed
8   , module Data.Param.Unsigned
9   , module Prelude
10   , Bit(..)
11   , State(..)
12   , resizeInt
13   , resizeWord
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 hiding (
25   null, length, head, tail, last, init, take, drop, (++), map, foldl, foldr,
26   zipWith, zip, unzip, concat, reverse, iterate )
27 import Types
28 import Data.Param.Vector
29 import Data.Param.Index
30 import qualified Data.Param.Signed as Signed
31 import Data.Param.Signed hiding (resize)
32 import qualified Data.Param.Unsigned as Unsigned
33 import Data.Param.Unsigned hiding (resize) 
34
35 import Language.Haskell.TH.Lift
36 import Data.Typeable
37
38 newtype State s = State s deriving (P.Show)
39
40 resizeInt :: (NaturalT nT, NaturalT nT') => Signed nT -> Signed nT'
41 resizeInt = Signed.resize
42
43 resizeWord :: (NaturalT nT, NaturalT nT') => Unsigned nT -> Unsigned nT'
44 resizeWord = Unsigned.resize
45
46 -- The plain Bit type
47 data Bit = High | Low
48   deriving (P.Show, P.Eq, P.Read, Typeable)
49
50 deriveLift ''Bit
51
52 hwand :: Bit -> Bit -> Bit
53 hwor  :: Bit -> Bit -> Bit
54 hwxor :: Bit -> Bit -> Bit
55 hwnot :: Bit -> Bit
56
57 High `hwand` High = High
58 _ `hwand` _ = Low
59
60 High `hwor` _  = High
61 _ `hwor` High  = High
62 Low `hwor` Low = Low
63
64 High `hwxor` Low = High
65 Low `hwxor` High = High
66 _ `hwxor` _      = Low
67
68 hwnot High = Low
69 hwnot Low  = High
70
71 type RAM s a          = Vector s a
72 type MemState s a     = State (RAM s a)
73
74 blockRAM :: 
75   PositiveT s  =>
76   MemState s a -> 
77   a ->
78   Index s ->
79   Index s ->
80   Bool -> 
81   (MemState s a, a )
82 blockRAM (State mem) data_in rdaddr wraddr wrenable = 
83   ((State mem'), data_out)
84   where
85     data_out  = mem!rdaddr
86     -- Only write data_in to memory if write is enabled
87     mem' =  if wrenable then
88               replace mem wraddr data_in
89             else
90               mem