From 7f6a8f38eea6aec322fad713d9b8dd67ffd0a9de Mon Sep 17 00:00:00 2001 From: christiaanb Date: Thu, 17 Jun 2010 10:30:57 +0200 Subject: [PATCH] Implement API change of shiftl and shiftr, limit Prelude import of HardwareTypes --- clash/CLasH/HardwareTypes.hs | 22 +++++----------------- clash/CLasH/VHDL/Constants.hs | 4 ++-- clash/Data/Param/Signed.hs | 6 +++--- clash/Data/Param/Unsigned.hs | 6 +++--- clash/Data/Param/Vector.hs | 16 ++++++++-------- clash/clash.cabal | 2 +- reducer.hs | 30 +++++++++++++++--------------- 7 files changed, 37 insertions(+), 49 deletions(-) diff --git a/clash/CLasH/HardwareTypes.hs b/clash/CLasH/HardwareTypes.hs index d66befe..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 diff --git a/clash/CLasH/VHDL/Constants.hs b/clash/CLasH/VHDL/Constants.hs index c70ca71..23ac95d 100644 --- a/clash/CLasH/VHDL/Constants.hs +++ b/clash/CLasH/VHDL/Constants.hs @@ -155,11 +155,11 @@ dropId = "drop" -- | shiftl function identifier shiftlId :: String -shiftlId = "shiftl" +shiftlId = "shiftIntoL" -- | shiftr function identifier shiftrId :: String -shiftrId = "shiftr" +shiftrId = "shiftIntoR" -- | rotl function identifier rotlId :: String diff --git a/clash/Data/Param/Signed.hs b/clash/Data/Param/Signed.hs index 26ac677..e85fe60 100644 --- a/clash/Data/Param/Signed.hs +++ b/clash/Data/Param/Signed.hs @@ -1,7 +1,7 @@ {-# LANGUAGE TypeFamilies, TypeOperators, ScopedTypeVariables, FlexibleInstances, TemplateHaskell, Rank2Types, FlexibleContexts #-} module Data.Param.Signed ( Signed - , resize + , resizeSigned ) where import Language.Haskell.TH @@ -18,8 +18,8 @@ instance NaturalT nT => Lift (Signed nT) where decSignedT :: Integer -> Q Type decSignedT n = appT (conT (''Signed)) (decLiteralT n) -resize :: (NaturalT nT, NaturalT nT') => Signed nT -> Signed nT' -resize a = fromInteger (toInteger a) +resizeSigned :: (NaturalT nT, NaturalT nT') => Signed nT -> Signed nT' +resizeSigned a = fromInteger (toInteger a) sizeT :: Signed nT -> nT diff --git a/clash/Data/Param/Unsigned.hs b/clash/Data/Param/Unsigned.hs index aae032d..6f06dbd 100644 --- a/clash/Data/Param/Unsigned.hs +++ b/clash/Data/Param/Unsigned.hs @@ -1,7 +1,7 @@ {-# LANGUAGE TypeFamilies, TypeOperators, ScopedTypeVariables, FlexibleInstances, TemplateHaskell, Rank2Types, FlexibleContexts #-} module Data.Param.Unsigned ( Unsigned - , resize + , resizeUnsigned , fromIndex ) where @@ -27,8 +27,8 @@ fromIndex :: ) => Index nT -> Unsigned nT' fromIndex index = Unsigned (toInteger index) -resize :: (NaturalT nT, NaturalT nT') => Unsigned nT -> Unsigned nT' -resize a = fromInteger (toInteger a) +resizeUnsigned :: (NaturalT nT, NaturalT nT') => Unsigned nT -> Unsigned nT' +resizeUnsigned a = fromInteger (toInteger a) sizeT :: Unsigned nT -> nT diff --git a/clash/Data/Param/Vector.hs b/clash/Data/Param/Vector.hs index 6f5b722..f726945 100644 --- a/clash/Data/Param/Vector.hs +++ b/clash/Data/Param/Vector.hs @@ -28,8 +28,8 @@ module Data.Param.Vector , foldr , zip , unzip - , shiftl - , shiftr + , shiftIntoL + , shiftIntoR , rotl , rotr , concat @@ -179,13 +179,13 @@ zip = liftV2 P.zip unzip :: Vector s (a, b) -> (Vector s a, Vector s b) unzip (Vector xs) = let (a,b) = P.unzip xs in (Vector a, Vector b) -shiftl :: (PositiveT s, NaturalT n, n ~ Pred s, s ~ Succ n) => - Vector s a -> a -> Vector s a -shiftl xs x = x +> init xs +shiftIntoL :: (PositiveT s, NaturalT n, n ~ Pred s, s ~ Succ n) => + Vector s a -> a -> Vector s a +shiftIntoL xs x = x +> init xs -shiftr :: (PositiveT s, NaturalT n, n ~ Pred s, s ~ Succ n) => - Vector s a -> a -> Vector s a -shiftr xs x = tail xs <+ x +shiftIntoR :: (PositiveT s, NaturalT n, n ~ Pred s, s ~ Succ n) => + Vector s a -> a -> Vector s a +shiftIntoR xs x = tail xs <+ x rotl :: forall s a . NaturalT s => Vector s a -> Vector s a rotl = liftV rotl' diff --git a/clash/clash.cabal b/clash/clash.cabal index 9a62eac..5f8efea 100644 --- a/clash/clash.cabal +++ b/clash/clash.cabal @@ -1,5 +1,5 @@ name: clash -version: 0.1.0.3 +version: 0.1.1.0 build-type: Simple synopsis: CAES Language for Synchronous Hardware (CLaSH) description: CLaSH is a tool-chain/language to translate subsets of diff --git a/reducer.hs b/reducer.hs index 39e136f..a4d4bbb 100644 --- a/reducer.hs +++ b/reducer.hs @@ -3,7 +3,7 @@ module Reducer where import qualified Prelude as P -import CLasH.HardwareTypes hiding ((>>)) +import CLasH.HardwareTypes import CLasH.Translator.Annotations -- ======================================= @@ -48,8 +48,8 @@ notValid = (False, (0, 0)) -- ==================== -- = Helper functions = -- ==================== -v << e = shiftr v e -e >> v = shiftl v e +v <<+ e = shiftIntoR v e +e +>> v = shiftIntoL v e -- ======================= -- = Reducer State types = @@ -133,15 +133,15 @@ rippleBuffer :: rippleBuffer (State buf) (inp, shift) = (State buf', out1, out2) where -- Write value - next_valids = (map (\(a, b) -> a) buf) << True + next_valids = (map (\(a, b) -> a) buf) <<+ True buf'' = zipWith selects buf next_valids selects cell next_valid = if (not (fst cell)) && next_valid then (True, inp) else cell -- Shift values - buf' | shift == 2 = (False, 0) >> ((False, 0) >> buf'') - | shift == 1 = (False, 0) >> buf'' + buf' | shift == 2 = (False, 0) +>> ((False, 0) +>> buf'') + | shift == 1 = (False, 0) +>> buf'' | otherwise = buf'' -- Read values out1 = last buf @@ -185,7 +185,7 @@ fpAdder (State ((buffer, pipe), adderState)) (arg1, arg2) = (State ((buffer', pi -- placeholder adder (adderState', adderOut) = fpPlaceholder adderState (a1, a2) -- Save corresponding indexes and valid bits - pipe' = (valid arg1, discr arg1) >> pipe + pipe' = (valid arg1, discr arg1) +>> pipe -- Produce output for time T and T+1 pipeEndT = last pipe pipeEndT_1 = last (init pipe) @@ -280,10 +280,10 @@ reducer (State (Reducer {..})) (data_in, index) = ( State Reducer { discrState valT_1 | discr pipeT == discr pipeT_1 = not (valid from_res_mem) | otherwise = valid from_res_mem (discrO, valT, inPipe , outPipe) = pipeline - pipeline' = ( (discrN, index, new_discr) >> discrO + pipeline' = ( (discrN, index, new_discr) +>> discrO , valT_1 - , (data_in, index) >> inPipe - , output' >> outPipe + , (data_in, index) +>> inPipe + , output' +>> outPipe ) @@ -356,13 +356,13 @@ runReducer = ( reduceroutput input = siminput istate = initstate output = run reducer istate input - reduceroutput = P.map fst (filter (\x -> (snd x)) output) + reduceroutput = P.map fst (P.filter (\x -> (snd x)) output) validoutput = [P.foldl (+) 0 - (P.map (\z -> toInteger (fst z)) - (filter (\x -> (snd x) == i) input)) | i <- [0..30]] - equal = [validoutput!!i == toInteger (fst (reduceroutput!!i)) | + (P.map (\z -> P.toInteger (fst z)) + (P.filter (\x -> (snd x) == i) input)) | i <- [0..30]] + equal = [validoutput P.!! i == P.toInteger (fst (reduceroutput P.!! i)) | i <- [0..30]] - allEqual = foldl1 (&&) equal + allEqual = P.foldl1 (&&) equal siminput :: [(DataInt, ArrayIndex)] siminput = [(1,0),(5,1),(12,1),(4,2),(9,2),(2,2),(13,2),(2,2),(6,2),(1,2),(12,2),(13,3),(6,3),(11,3),(2,3),(11,3),(5,4),(11,4),(1,4),(7,4),(3,4),(4,4),(5,5),(8,5),(8,5),(13,5),(10,5),(7,5),(9,6),(9,6),(3,6),(11,6),(14,6),(13,6),(10,6),(4,7),(15,7),(13,7),(10,7),(10,7),(6,7),(15,7),(9,7),(1,7),(7,7),(15,7),(3,7),(13,7),(7,8),(3,9),(13,9),(2,10),(9,11),(10,11),(9,11),(2,11),(14,12),(14,12),(12,13),(7,13),(9,13),(7,14),(14,15),(5,16),(6,16),(14,16),(11,16),(5,16),(5,16),(7,17),(1,17),(13,17),(10,18),(15,18),(12,18),(14,19),(13,19),(2,19),(3,19),(14,19),(9,19),(11,19),(2,19),(2,20),(3,20),(13,20),(3,20),(1,20),(9,20),(10,20),(4,20),(8,21),(4,21),(8,21),(4,21),(13,21),(3,21),(7,21),(12,21),(7,21),(13,21),(3,21),(1,22),(13,23),(9,24),(14,24),(4,24),(13,25),(6,26),(12,26),(4,26),(15,26),(3,27),(6,27),(5,27),(6,27),(12,28),(2,28),(8,28),(5,29),(4,29),(1,29),(2,29),(9,29),(10,29),(4,30),(6,30),(14,30),(11,30),(15,31),(15,31),(2,31),(14,31),(9,32),(3,32),(4,32),(6,33),(15,33),(1,33),(15,33),(4,33),(3,33),(8,34),(12,34),(14,34),(15,34),(4,35),(4,35),(12,35),(14,35),(3,36),(14,37),(3,37),(1,38),(15,39),(13,39),(13,39),(1,39),(5,40),(10,40),(14,40),(1,41),(6,42),(8,42),(11,42),(11,43),(2,43),(11,43),(8,43),(12,43),(15,44),(14,44),(6,44),(8,44),(9,45),(5,45),(12,46),(6,46),(5,46),(4,46),(2,46),(9,47),(7,48),(1,48),(3,48),(10,48),(1,48),(6,48),(6,48),(11,48),(11,48),(8,48),(14,48),(5,48),(11,49),(1,49),(3,49),(11,49),(8,49),(3,50),(8,51),(9,52),(7,52),(7,53),(8,53),(10,53),(11,53),(14,54),(11,54),(4,54),(6,55),(11,55),(5,56),(7,56),(6,56),(2,56),(4,56),(12,56),(4,57),(12,57),(2,57),(14,57),(9,57),(12,57),(5,57),(11,57),(7,58),(14,58),(2,58),(10,58),(2,58),(14,58),(7,58),(12,58),(1,58),(11,59),(8,59),(2,59),(14,59),(6,59),(6,59),(6,59),(14,59),(4,59),(1,59),(4,60),(14,60),(6,60),(4,60),(8,60),(12,60),(1,60),(8,60),(8,60),(13,60),(10,61),(11,61),(6,61),(14,61),(10,61),(3,62),(10,62),(7,62),(14,62),(10,62),(4,62),(6,62),(1,62),(3,63),(3,63),(1,63),(1,63),(15,63),(7,64),(1,65),(4,65),(11,66),(3,66),(13,66),(2,67),(2,67),(5,68),(15,68),(11,68),(8,68),(4,69),(11,69),(12,69),(8,69),(7,70),(9,70),(6,70),(9,70),(11,70),(14,70),(5,71),(7,71),(11,72),(5,72),(3,72),(2,72),(1,73),(13,73),(9,73),(14,73),(5,73),(6,73),(14,73),(13,73),(3,74),(13,74),(3,75),(14,75),(10,75),(5,75),(3,75),(8,75),(9,76),(7,76),(10,76),(10,76),(8,77),(10,77),(11,77),(8,77),(2,77),(9,77),(9,77),(12,77),(4,77),(14,77),(10,77),(7,77),(3,77),(10,78),(8,79),(14,79),(11,80),(15,81),(6,81),(4,82),(6,82),(1,82),(12,83),(6,83),(11,83),(12,83),(15,83),(13,83),(1,84),(2,84),(11,84),(5,84),(2,84),(2,84),(3,84),(4,85),(6,86),(5,86),(15,86),(8,86),(9,86),(9,87),(9,87),(12,87),(4,87),(13,88),(14,88),(10,88),(11,88),(7,88),(4,88),(9,88),(1,88),(4,88),(4,88),(12,88),(8,89),(3,89),(10,89),(10,89),(5,89),(14,89),(11,89),(10,89),(5,90),(6,90),(10,90),(9,90),(8,90),(10,90),(5,90),(11,90),(6,90),(10,90),(7,90),(3,91),(7,91),(5,91),(15,91),(4,91),(6,91),(8,91),(1,91),(8,91),(12,92),(8,93),(9,93),(12,94),(8,94),(5,94),(11,95),(13,95),(5,96),(12,96),(8,96),(4,96),(7,97),(6,97),(4,97),(1,98),(5,98),(12,98),(13,99),(7,100),(12,100),(4,100),(10,100),(2,101),(3,101),(14,101),(12,101),(5,101),(2,101),(14,101),(15,101),(7,102),(13,102),(5,102),(7,102),(4,102),(8,102),(12,103),(15,103),(2,103),(2,103),(6,103),(6,103),(1,104),(14,104),(15,105),(3,105),(13,105),(1,105),(8,105),(8,105),(15,105),(13,105),(13,105),(6,105),(9,105),(6,106),(14,107),(12,107),(7,108),(7,108),(6,109),(11,109),(14,110),(8,111),(5,111),(15,111),(14,111),(3,111),(13,112),(12,112),(5,112),(10,112),(7,112),(5,113),(3,113),(2,113),(1,113),(15,113),(8,113),(10,113),(3,114),(6,114),(15,114),(4,115),(8,115),(1,115),(12,115),(5,115),(6,116),(2,116),(13,116),(12,116),(6,116),(10,117),(8,117),(14,118),(10,118),(3,118),(15,119),(6,119),(6,120),(5,121),(8,121),(4,122),(1,122),(9,123),(12,123),(6,124),(10,124),(2,124),(11,124),(9,125),(8,126),(10,126),(11,126),(14,126),(2,126),(5,126),(7,126),(3,127),(12,127),(15,128),(4,128),(1,129),(14,129),(8,129),(9,129),(6,129),(1,130),(11,130),(2,130),(13,130),(14,131),(2,131),(15,131),(4,131),(15,131),(8,131),(3,131),(8,132),(1,132),(13,132),(8,132),(5,132),(11,132),(14,132),(14,132),(4,132),(14,132),(5,132),(11,133),(1,133),(15,133),(8,133),(12,133),(8,134),(14,135),(11,136),(9,137),(3,137),(15,138),(1,138),(1,139),(4,139),(3,140),(10,140),(8,141),(12,141),(4,141),(12,141),(13,141),(10,141),(4,142),(6,142),(15,142),(4,142),(2,143),(14,143),(5,143),(10,143),(8,143),(9,143),(3,143),(11,143),(6,144),(3,145),(9,145),(10,145),(6,145),(11,145),(4,145),(13,145),(5,145),(4,145),(1,145),(3,145),(15,145),(14,146),(11,146),(9,146),(9,146),(10,146),(9,146),(3,146),(2,146),(10,146),(6,146),(7,146),(3,147),(4,147),(15,147),(11,147),(15,147),(1,147),(15,147),(14,147),(15,147),(5,147),(15,147),(4,147),(2,148),(12,149),(12,150),(10,150),(1,150),(7,151),(4,151),(14,151),(15,151),(5,152),(11,153),(3,153),(1,153),(1,153),(12,153),(1,154),(1,155),(11,155),(8,155),(3,155),(8,155),(8,155),(2,155),(9,156),(6,156),(12,156),(1,156),(3,156),(8,156),(5,157),(9,157),(12,157),(6,157),(8,158),(15,159),(2,159),(10,160),(10,160),(2,160),(6,160),(10,160),(8,160),(13,160),(12,161),(15,161),(14,161),(10,161),(13,161),(14,161),(3,161),(2,161),(1,161),(11,161),(7,161),(8,161),(4,162),(9,163),(3,164),(5,164),(9,164),(9,165),(7,165),(1,165),(6,166),(14,166),(3,166),(14,166),(4,166),(14,167),(5,167),(13,167),(12,167),(13,168),(9,168)] -- 2.30.2