Add a simple four-bit shift register model.
[matthijs/master-project/cλash.git] / Adders.hs
1 module Adders where
2 import Bits
3 import qualified Sim
4 import Language.Haskell.Syntax
5
6 mainIO f = Sim.simulateIO (Sim.stateless f) ()
7
8 -- This function is from Sim.hs, but we redefine it here so it can get inlined
9 -- by default.
10 stateless :: (i -> o) -> (i -> () -> ((), o))
11 stateless f = \i s -> (s, f i)
12
13 show_add f = do print ("Sum:   " ++ (displaysigs s)); print ("Carry: " ++ (displaysig c))
14   where
15     a = [High, High, High, High]
16     b = [Low, Low, Low, High]
17     (s, c) = f (a, b)
18
19 -- Not really an adder, but this is nice minimal hardware description
20 wire :: Bit -> Bit
21 wire a = a
22
23 -- Not really an adder either, but a slightly more complex example
24 inv :: Bit -> Bit
25 inv a = hwnot a
26
27 -- Not really an adder either, but a slightly more complex example
28 invinv :: Bit -> Bit
29 invinv a = hwnot (hwnot a)
30
31 -- Not really an adder either, but a slightly more complex example
32 dup :: Bit -> (Bit, Bit)
33 dup a = (a, a)
34
35 -- Not really an adder either, but a simple stateful example (D-flipflop)
36 dff :: Bit -> Bit -> (Bit, Bit)
37 dff d s = (s', q)
38   where
39     q = s
40     s' = d
41
42 type ShifterState = (Bit, Bit, Bit, Bit)
43 shifter :: Bit -> ShifterState -> (ShifterState, Bit)
44 shifter a s =
45   (s', o)
46   where
47     s' = (a, b, c, d)
48     (b, c, d, o) = s
49
50 -- Combinatoric stateless no-carry adder
51 -- A -> B -> S
52 no_carry_adder :: (Bit, Bit) -> Bit
53 no_carry_adder (a, b) = a `hwxor` b
54
55 -- Combinatoric stateless half adder
56 -- A -> B -> (S, C)
57 half_adder :: (Bit, Bit) -> (Bit, Bit)
58 half_adder (a, b) = 
59   ( a `hwxor` b, a `hwand` b )
60
61 -- Combinatoric stateless full adder
62 -- (A, B, C) -> (S, C)
63 full_adder :: (Bit, Bit, Bit) -> (Bit, Bit)
64 full_adder (a, b, cin) = (s, c)
65   where
66     (s1, c1) = half_adder(a, b)
67     (s, c2)  = half_adder(s1, cin)
68     c        = c1 `hwor` c2
69
70 sfull_adder = stateless full_adder
71
72 -- Four bit adder
73 -- Explicit version
74 -- [a] -> [b] -> ([s], cout)
75 exp_adder :: ([Bit], [Bit]) -> ([Bit], Bit)
76
77 exp_adder ([a3,a2,a1,a0], [b3,b2,b1,b0]) =
78   ([s3, s2, s1, s0], c3)
79   where
80     (s0, c0) = full_adder (a0, b0, Low)
81     (s1, c1) = full_adder (a1, b1, c0)
82     (s2, c2) = full_adder (a2, b2, c1)
83     (s3, c3) = full_adder (a3, b3, c2)
84
85 -- Any number of bits adder
86 -- Recursive version
87 -- [a] -> [b] -> ([s], cout)
88 rec_adder :: ([Bit], [Bit]) -> ([Bit], Bit)
89
90 rec_adder ([], []) = ([], Low)
91 rec_adder ((a:as), (b:bs)) = 
92   (s : rest, cout)
93   where
94     (rest, cin) = rec_adder (as, bs)
95     (s, cout) = full_adder (a, b, cin)
96
97 -- Four bit adder, using the continous adder below
98 -- [a] -> [b] -> ([s], cout)
99 --con_adder_4 as bs = 
100 --  ([s3, s2, s1, s0], c)
101 --  where
102 --    ((s0, _):(s1, _):(s2, _):(s3, c):_) = con_adder (zip ((reverse as) ++ lows) ((reverse bs) ++ lows))
103
104 -- Continuous sequential version
105 -- Stream a -> Stream b -> Stream (sum, cout)
106 --con_adder :: Stream (Bit, Bit) -> Stream (Bit, Bit)
107
108 -- Forward to con_adder_int, but supply an initial state
109 --con_adder pin =
110 --  con_adder_int pin Low
111
112 -- Stream a -> Stream b -> state -> Stream (s, c)
113 --con_adder_int :: Stream (Bit, Bit) -> Bit -> Stream (Bit, Bit)
114 --con_adder_int ((a,b):rest) cin =
115 --  (s, cout) : con_adder_int rest cout
116 --  where
117 --    (s, cout) = full_adder a b cin
118
119 -- vim: set ts=8 sw=2 sts=2 expandtab: