Clean up source files:
[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   , resizeInt
14   , resizeWord
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 hiding (
26   null, length, head, tail, last, init, take, drop, (++), map, foldl, foldr,
27   zipWith, zip, unzip, concat, reverse, iterate )
28 import Types
29 import qualified Data.Param.TFVec as TFVec
30 import Data.Param.TFVec hiding (TFVec)
31 import Data.RangedWord
32 import qualified Data.SizedInt as SizedInt
33 import Data.SizedInt hiding (resize)
34 import qualified Data.SizedWord as SizedWord
35 import Data.SizedWord hiding (resize) 
36
37 import Language.Haskell.TH.Lift
38 import Data.Typeable
39
40 newtype State s = State s deriving (P.Show)
41
42 type Vector = TFVec.TFVec
43
44 resizeInt :: (NaturalT nT, NaturalT nT') => SizedInt nT -> SizedInt nT'
45 resizeInt = SizedInt.resize
46
47 resizeWord :: (NaturalT nT, NaturalT nT') => SizedWord nT -> SizedWord nT'
48 resizeWord = SizedWord.resize
49
50 -- The plain Bit type
51 data Bit = High | Low
52   deriving (P.Show, P.Eq, P.Read, Typeable)
53
54 deriveLift1 ''Bit
55
56 hwand :: Bit -> Bit -> Bit
57 hwor  :: Bit -> Bit -> Bit
58 hwxor :: Bit -> Bit -> Bit
59 hwnot :: Bit -> Bit
60
61 High `hwand` High = High
62 _ `hwand` _ = Low
63
64 High `hwor` _  = High
65 _ `hwor` High  = High
66 Low `hwor` Low = Low
67
68 High `hwxor` Low = High
69 Low `hwxor` High = High
70 _ `hwxor` _      = Low
71
72 hwnot High = Low
73 hwnot Low  = High
74
75 type RAM s a          = Vector (s :+: D1) a
76
77 type MemState s a      = State (RAM s a)
78
79 blockRAM :: 
80   (NaturalT s
81   ,PositiveT (s :+: D1)
82   ,((s :+: D1) :>: s) ~ True ) =>
83   (MemState s a) -> 
84   a ->
85   RangedWord s ->
86   RangedWord s ->
87   Bool -> 
88   ((MemState s a), a )
89 blockRAM (State mem) data_in rdaddr wraddr wrenable = 
90   ((State mem'), data_out)
91   where
92     data_out  = mem!rdaddr
93     -- Only write data_in to memory if write is enabled
94     mem' =  if wrenable then
95               replace mem wraddr data_in
96             else
97               mem