X-Git-Url: https://git.stderr.nl/gitweb?p=matthijs%2Fmaster-project%2Fc%CE%BBash.git;a=blobdiff_plain;f=Adders.hs;h=3afb163b69c3263b6ef861d2edf18298a0b49c85;hp=e6676e94888f3ce0bec9c9a489672da8288200e0;hb=HEAD;hpb=52d5de13a6c89e7dbc46627888210ddcda1c3e6c diff --git a/Adders.hs b/Adders.hs index e6676e9..3afb163 100644 --- a/Adders.hs +++ b/Adders.hs @@ -1,9 +1,21 @@ +{-# LANGUAGE TemplateHaskell #-} + module Adders where import Bits import qualified Sim -import Language.Haskell.Syntax -import qualified Data.TypeLevel as TypeLevel -import qualified Data.Param.FSVec as FSVec + +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 Language.Haskell.Syntax +import Types +import Types.Data.Num.Decimal.Literals +import Data.Param.TFVec +import Data.RangedWord +import Data.SizedInt +import Data.SizedWord mainIO f = Sim.simulateIO (Sim.stateless f) () @@ -12,11 +24,11 @@ mainIO f = Sim.simulateIO (Sim.stateless f) () stateless :: (i -> o) -> (i -> () -> ((), o)) stateless f = \i s -> (s, f i) -show_add f = do print ("Sum: " ++ (displaysigs s)); print ("Carry: " ++ (displaysig c)) - where - a = [High, High, High, High] - b = [Low, Low, Low, High] - (s, c) = f (a, b) +-- show_add f = do print ("Sum: " P.++ (displaysigs s)); print ("Carry: " P.++ (displaysig c)) +-- where +-- a = [High, High, High, High] +-- b = [Low, Low, Low, High] +-- (s, c) = f (a, b) mux2 :: Bit -> (Bit, Bit) -> Bit mux2 Low (a, b) = a @@ -26,10 +38,10 @@ mux2 High (a, b) = b wire :: Bit -> Bit wire a = a -bus :: (TypeLevel.Pos len) => BitVec len -> BitVec len +-- bus :: (TypeLevel.Pos len) => BitVec len -> BitVec len bus v = v -bus_4 :: BitVec TypeLevel.D4 -> BitVec TypeLevel.D4 +-- bus_4 :: BitVec TypeLevel.D4 -> BitVec TypeLevel.D4 bus_4 v = v {- @@ -53,7 +65,7 @@ instance Inv (BitVec D0) where -} -- Not really an adder either, but a slightly more complex example inv :: Bit -> Bit -inv a = hwnot a +inv a = let r = hwnot a in r -- Not really an adder either, but a slightly more complex example invinv :: Bit -> Bit @@ -146,26 +158,68 @@ rec_adder ((a:as), (b:bs)) = (rest, cin) = rec_adder (as, bs) (s, cout) = full_adder (a, b, cin) +foo = id +add, sub :: Int -> Int -> Int +add a b = a + b +sub a b = a - b + +highordtest = \x -> + let s = foo x + in + case s of + (a, b) -> + case a of + High -> add + Low -> let + op' = case b of + High -> sub + Low -> \c d -> c + in + \c d -> op' d c + +xand a b = hwand a b + +functiontest :: TFVec D12 Bit -> TFVec D6 Bit +functiontest = \v -> let r = take d6 v in r + +functiontest2 :: SizedInt D8 -> SizedInt D7 +functiontest2 = \a -> let r = Data.SizedInt.resize a in r + +xhwnot x = hwnot x + +maptest :: TFVec D4 Bit -> TFVec D4 Bit +maptest = \v -> let r = map xhwnot v in r + +highordtest2 = \a b -> + case a of + High -> \c d -> d + Low -> let + op' :: Bit -> Bit -> Bit + op' = case b of + High -> \c d -> d + Low -> \c d -> c + in + \c d -> op' d c -- Four bit adder, using the continous adder below -- [a] -> [b] -> ([s], cout) ---con_adder_4 as bs = +-- con_adder_4 as bs = -- ([s3, s2, s1, s0], c) -- where --- ((s0, _):(s1, _):(s2, _):(s3, c):_) = con_adder (zip ((reverse as) ++ lows) ((reverse bs) ++ lows)) +-- ((s0, _):(s1, _):(s2, _):(s3, c):_) = con_adder (P.zip ((P.reverse as) P.++ lows) ((P.reverse bs) P.++ lows)) -- Continuous sequential version -- Stream a -> Stream b -> Stream (sum, cout) ---con_adder :: Stream (Bit, Bit) -> Stream (Bit, Bit) +-- con_adder :: Stream (Bit, Bit) -> Stream (Bit, Bit) -- Forward to con_adder_int, but supply an initial state ---con_adder pin = +-- con_adder pin = -- con_adder_int pin Low -- Stream a -> Stream b -> state -> Stream (s, c) ---con_adder_int :: Stream (Bit, Bit) -> Bit -> Stream (Bit, Bit) ---con_adder_int ((a,b):rest) cin = +-- con_adder_int :: Stream (Bit, Bit) -> Bit -> Stream (Bit, Bit) +-- con_adder_int ((a,b):rest) cin = -- (s, cout) : con_adder_int rest cout -- where --- (s, cout) = full_adder a b cin +-- (s, cout) = full_adder (a, b, cin) -- vim: set ts=8 sw=2 sts=2 expandtab: