X-Git-Url: https://git.stderr.nl/gitweb?a=blobdiff_plain;f=clash%2FCLasH%2FHardwareTypes.hs;h=dbb0ecac94cc93a0dcd446686fb01714a4d9d894;hb=7f6a8f38eea6aec322fad713d9b8dd67ffd0a9de;hp=2912e50fe75bf98ab63bb4f31ba6ab421581656c;hpb=04f836932ad17dd557af0ba388a12d2b74c1e7d7;p=matthijs%2Fmaster-project%2Fc%CE%BBash.git diff --git a/clash/CLasH/HardwareTypes.hs b/clash/CLasH/HardwareTypes.hs index 2912e50..dbb0eca 100644 --- a/clash/CLasH/HardwareTypes.hs +++ b/clash/CLasH/HardwareTypes.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE TemplateHaskell, DeriveDataTypeable, FlexibleContexts, TypeFamilies, TypeOperators #-} +{-# LANGUAGE TemplateHaskell, DeriveDataTypeable #-} module CLasH.HardwareTypes ( module Types @@ -9,8 +9,6 @@ module CLasH.HardwareTypes , module Prelude , Bit(..) , State(..) - , resizeInt - , resizeWord , hwand , hwor , hwxor @@ -21,31 +19,21 @@ 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.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 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 +56,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