X-Git-Url: https://git.stderr.nl/gitweb?a=blobdiff_plain;f=c%CE%BBash%2FCLasH%2FHardwareTypes.hs;h=2912e50fe75bf98ab63bb4f31ba6ab421581656c;hb=e1ef152dc63f28dddce2de4950ec739c79c8d18f;hp=682cd05c46fbd2a1718216b3847d30e9b42360f2;hpb=655444253776431f0949cafce2b991d12613fe04;p=matthijs%2Fmaster-project%2Fc%CE%BBash.git diff --git "a/c\316\273ash/CLasH/HardwareTypes.hs" "b/c\316\273ash/CLasH/HardwareTypes.hs" index 682cd05..2912e50 100644 --- "a/c\316\273ash/CLasH/HardwareTypes.hs" +++ "b/c\316\273ash/CLasH/HardwareTypes.hs" @@ -1,19 +1,23 @@ -{-# LANGUAGE TemplateHaskell, DeriveDataTypeable #-} +{-# LANGUAGE TemplateHaskell, DeriveDataTypeable, FlexibleContexts, TypeFamilies, TypeOperators #-} module CLasH.HardwareTypes ( module Types - , module Data.Param.TFVec - , module Data.RangedWord - , module Data.SizedInt - , module Data.SizedWord + , module Data.Param.Vector + , module Data.Param.Index + , module Data.Param.Signed + , module Data.Param.Unsigned , module Prelude , Bit(..) , State(..) - , Vector + , resizeInt + , resizeWord , hwand , hwor , hwxor , hwnot + , RAM + , MemState + , blockRAM ) where import qualified Prelude as P @@ -21,24 +25,29 @@ import Prelude hiding ( null, length, head, tail, last, init, take, drop, (++), map, foldl, foldr, zipWith, zip, unzip, concat, reverse, iterate ) import Types -import qualified Data.Param.TFVec as TFVec -import Data.Param.TFVec hiding (TFVec) -import Data.RangedWord -import Data.SizedInt -import Data.SizedWord +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 Language.Haskell.TH.Lift import Data.Typeable newtype State s = State s deriving (P.Show) -type Vector = TFVec.TFVec +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) -$(deriveLift1 ''Bit) +deriveLift ''Bit hwand :: Bit -> Bit -> Bit hwor :: Bit -> Bit -> Bit @@ -57,4 +66,28 @@ Low `hwxor` High = High _ `hwxor` _ = Low hwnot High = Low -hwnot Low = High \ No newline at end of file +hwnot Low = High + +type RAM s a = Vector (s :+: D1) a + +type MemState s a = State (RAM s a) + +blockRAM :: + (NaturalT s + ,PositiveT (s :+: D1) + ,((s :+: D1) :>: s) ~ True ) => + (MemState s a) -> + a -> + Index s -> + Index s -> + Bool -> + ((MemState s a), a ) +blockRAM (State mem) data_in rdaddr wraddr wrenable = + ((State mem'), data_out) + where + data_out = mem!rdaddr + -- Only write data_in to memory if write is enabled + mem' = if wrenable then + replace mem wraddr data_in + else + mem