X-Git-Url: https://git.stderr.nl/gitweb?a=blobdiff_plain;f=clash%2FCLasH%2FHardwareTypes.hs;h=f462e3efa9064bc0da99299cc2cf622ab0c4ab42;hb=HEAD;hp=d66befeeacca9a89aa5c5b853b7fcad593bd00ee;hpb=63b8956c3d9c50a619e7a9fa674b533f7ef5f3a7;p=matthijs%2Fmaster-project%2Fc%CE%BBash.git diff --git a/clash/CLasH/HardwareTypes.hs b/clash/CLasH/HardwareTypes.hs index d66befe..f462e3e 100644 --- a/clash/CLasH/HardwareTypes.hs +++ b/clash/CLasH/HardwareTypes.hs @@ -1,16 +1,17 @@ -{-# 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 + , module Language.Haskell.TH.Lift , Bit(..) , State(..) - , resizeInt - , resizeWord , hwand , hwor , hwxor @@ -21,31 +22,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