Add shiftL and shiftR operators for signed and unsigned. Update name of shiftl and...
[matthijs/master-project/cλash.git] / clash / CLasH / HardwareTypes.hs
index 2912e50fe75bf98ab63bb4f31ba6ab421581656c..572a64e7f66154842d1fcb6887a71ba0f6a83a8d 100644 (file)
@@ -1,16 +1,16 @@
-{-# LANGUAGE TemplateHaskell, DeriveDataTypeable, FlexibleContexts, TypeFamilies, TypeOperators #-}
+{-# LANGUAGE TemplateHaskell, DeriveDataTypeable #-}
 
 module CLasH.HardwareTypes
   ( module Types
+  , module Data.Param.Integer
   , module Data.Param.Vector
   , module Data.Param.Index
   , module Data.Param.Signed
   , module Data.Param.Unsigned
   , module Prelude
+  , module Data.Bits
   , Bit(..)
   , State(..)
-  , resizeInt
-  , resizeWord
   , hwand
   , hwor
   , hwxor
@@ -21,31 +21,23 @@ module CLasH.HardwareTypes
   ) where
 
 import qualified Prelude as P
-import Prelude hiding (
-  null, length, head, tail, last, init, take, drop, (++), map, foldl, foldr,
-  zipWith, zip, unzip, concat, reverse, iterate )
+import Prelude (Bool(..),Num(..),Eq(..),Ord(..),snd,fst,otherwise,(&&),(||),not)
 import Types
+import Data.Param.Integer (HWBits(..))
 import Data.Param.Vector
 import Data.Param.Index
-import qualified Data.Param.Signed as Signed
-import Data.Param.Signed hiding (resize)
-import qualified Data.Param.Unsigned as Unsigned
-import Data.Param.Unsigned hiding (resize) 
+import Data.Param.Signed
+import Data.Param.Unsigned 
+import Data.Bits hiding (shiftL,shiftR)
 
 import Language.Haskell.TH.Lift
 import Data.Typeable
 
 newtype State s = State s deriving (P.Show)
 
-resizeInt :: (NaturalT nT, NaturalT nT') => Signed nT -> Signed nT'
-resizeInt = Signed.resize
-
-resizeWord :: (NaturalT nT, NaturalT nT') => Unsigned nT -> Unsigned nT'
-resizeWord = Unsigned.resize
-
 -- The plain Bit type
 data Bit = High | Low
-  deriving (P.Show, P.Eq, P.Read, Typeable)
+  deriving (P.Show, Eq, P.Read, Typeable)
 
 deriveLift ''Bit
 
@@ -68,20 +60,17 @@ _ `hwxor` _      = Low
 hwnot High = Low
 hwnot Low  = High
 
-type RAM s a          = Vector (s :+: D1) a
-
-type MemState s a      = State (RAM s a)
+type RAM s a          = Vector s a
+type MemState s a     = State (RAM s a)
 
 blockRAM :: 
-  (NaturalT s
-  ,PositiveT (s :+: D1)
-  ,((s :+: D1) :>: s) ~ True ) =>
-  (MemState s a) -> 
+  PositiveT s  =>
+  MemState s a -> 
   a ->
   Index s ->
   Index s ->
   Bool -> 
-  ((MemState s a), a )
+  (MemState s a, a )
 blockRAM (State mem) data_in rdaddr wraddr wrenable = 
   ((State mem'), data_out)
   where