4 import Language.Haskell.Syntax
6 import qualified Data.Param.FSVec as FSVec
8 mainIO f = Sim.simulateIO (Sim.stateless f) ()
10 -- This function is from Sim.hs, but we redefine it here so it can get inlined
12 stateless :: (i -> o) -> (i -> () -> ((), o))
13 stateless f = \i s -> (s, f i)
15 show_add f = do print ("Sum: " ++ (displaysigs s)); print ("Carry: " ++ (displaysig c))
17 a = [High, High, High, High]
18 b = [Low, Low, Low, High]
21 mux2 :: Bit -> (Bit, Bit) -> Bit
25 -- Not really an adder, but this is nice minimal hardware description
29 bus :: (Pos len) => BitVec len -> BitVec len
32 bus_4 :: BitVec D4 -> BitVec D4
36 inv_n :: (Pos len) => BitVec len -> BitVec len
42 inv_n_rec :: vec -> vec
44 instance (Pos len) => Inv (BitVec len) where
51 instance Inv (BitVec D0) where
54 -- Not really an adder either, but a slightly more complex example
58 -- Not really an adder either, but a slightly more complex example
60 invinv a = hwnot (hwnot a)
62 -- Not really an adder either, but a slightly more complex example
63 dup :: Bit -> (Bit, Bit)
66 -- Not really an adder either, but a simple stateful example (D-flipflop)
67 dff :: Bit -> Bit -> (Bit, Bit)
73 type ShifterState = (Bit, Bit, Bit, Bit)
74 shifter :: Bit -> ShifterState -> (ShifterState, Bit)
81 -- Combinatoric stateless no-carry adder
83 no_carry_adder :: (Bit, Bit) -> Bit
84 no_carry_adder (a, b) = a `hwxor` b
86 -- Combinatoric stateless half adder
88 half_adder :: (Bit, Bit) -> (Bit, Bit)
89 {-# NOINLINE half_adder #-}
91 ( a `hwxor` b, a `hwand` b )
93 -- Combinatoric stateless full adder
94 -- (A, B, C) -> (S, C)
95 full_adder :: (Bit, Bit, Bit) -> (Bit, Bit)
96 full_adder (a, b, cin) = (s, c)
98 (s1, c1) = half_adder(a, b)
99 (s, c2) = half_adder(s1, cin)
102 sfull_adder = stateless full_adder
106 -- [a] -> [b] -> ([s], cout)
107 exp_adder :: ([Bit], [Bit]) -> ([Bit], Bit)
109 exp_adder ([a3,a2,a1,a0], [b3,b2,b1,b0]) =
110 ([s3, s2, s1, s0], c3)
112 (s0, c0) = full_adder (a0, b0, Low)
113 (s1, c1) = full_adder (a1, b1, c0)
114 (s2, c2) = full_adder (a2, b2, c1)
115 (s3, c3) = full_adder (a3, b3, c2)
117 -- Any number of bits adder
119 -- [a] -> [b] -> ([s], cout)
120 rec_adder :: ([Bit], [Bit]) -> ([Bit], Bit)
122 rec_adder ([], []) = ([], Low)
123 rec_adder ((a:as), (b:bs)) =
126 (rest, cin) = rec_adder (as, bs)
127 (s, cout) = full_adder (a, b, cin)
129 -- Four bit adder, using the continous adder below
130 -- [a] -> [b] -> ([s], cout)
131 --con_adder_4 as bs =
132 -- ([s3, s2, s1, s0], c)
134 -- ((s0, _):(s1, _):(s2, _):(s3, c):_) = con_adder (zip ((reverse as) ++ lows) ((reverse bs) ++ lows))
136 -- Continuous sequential version
137 -- Stream a -> Stream b -> Stream (sum, cout)
138 --con_adder :: Stream (Bit, Bit) -> Stream (Bit, Bit)
140 -- Forward to con_adder_int, but supply an initial state
142 -- con_adder_int pin Low
144 -- Stream a -> Stream b -> state -> Stream (s, c)
145 --con_adder_int :: Stream (Bit, Bit) -> Bit -> Stream (Bit, Bit)
146 --con_adder_int ((a,b):rest) cin =
147 -- (s, cout) : con_adder_int rest cout
149 -- (s, cout) = full_adder a b cin
151 -- vim: set ts=8 sw=2 sts=2 expandtab: