Add a double invertor model.
[matthijs/master-project/cλash.git] / Adders.hs
1 module Adders where
2 import Bits
3 import Language.Haskell.Syntax
4
5 main = do show_add exp_adder; show_add rec_adder;
6
7 show_add f = do print ("Sum:   " ++ (displaysigs s)); print ("Carry: " ++ (displaysig c))
8   where
9     a = [High, High, High, High]
10     b = [Low, Low, Low, High]
11     (s, c) = f (a, b)
12
13 -- Not really an adder, but this is nice minimal hardware description
14 wire :: Bit -> Bit
15 wire a = a
16
17 -- Not really an adder either, but a slightly more complex example
18 inv :: Bit -> Bit
19 inv a = hwnot a
20
21 -- Not really an adder either, but a slightly more complex example
22 invinv :: Bit -> Bit
23 invinv a = hwnot (hwnot a)
24
25 -- Combinatoric stateless no-carry adder
26 -- A -> B -> S
27 no_carry_adder :: (Bit, Bit) -> Bit
28 no_carry_adder (a, b) = a `hwxor` b
29
30 -- Combinatoric stateless half adder
31 -- A -> B -> (S, C)
32 half_adder :: (Bit, Bit) -> (Bit, Bit)
33 half_adder (a, b) = 
34   ( a `hwxor` b, a `hwand` b )
35
36 -- Combinatoric stateless full adder
37 -- (A, B, C) -> (S, C)
38 full_adder :: (Bit, Bit, Bit) -> (Bit, Bit)
39 full_adder (a, b, cin) = (s, c)
40   where
41     s = a `hwxor` b `hwxor` cin
42     c = a `hwand` b `hwor` (cin `hwand` (a `hwxor` b))
43
44 -- Four bit adder
45 -- Explicit version
46 -- [a] -> [b] -> ([s], cout)
47 exp_adder :: ([Bit], [Bit]) -> ([Bit], Bit)
48
49 exp_adder ([a3,a2,a1,a0], [b3,b2,b1,b0]) =
50   ([s3, s2, s1, s0], c3)
51   where
52     (s0, c0) = full_adder (a0, b0, Low)
53     (s1, c1) = full_adder (a1, b1, c0)
54     (s2, c2) = full_adder (a2, b2, c1)
55     (s3, c3) = full_adder (a3, b3, c2)
56
57 -- Any number of bits adder
58 -- Recursive version
59 -- [a] -> [b] -> ([s], cout)
60 rec_adder :: ([Bit], [Bit]) -> ([Bit], Bit)
61
62 rec_adder ([], []) = ([], Low)
63 rec_adder ((a:as), (b:bs)) = 
64   (s : rest, cout)
65   where
66     (rest, cin) = rec_adder (as, bs)
67     (s, cout) = full_adder (a, b, cin)
68
69 -- Four bit adder, using the continous adder below
70 -- [a] -> [b] -> ([s], cout)
71 --con_adder_4 as bs = 
72 --  ([s3, s2, s1, s0], c)
73 --  where
74 --    ((s0, _):(s1, _):(s2, _):(s3, c):_) = con_adder (zip ((reverse as) ++ lows) ((reverse bs) ++ lows))
75
76 -- Continuous sequential version
77 -- Stream a -> Stream b -> Stream (sum, cout)
78 --con_adder :: Stream (Bit, Bit) -> Stream (Bit, Bit)
79
80 -- Forward to con_adder_int, but supply an initial state
81 --con_adder pin =
82 --  con_adder_int pin Low
83
84 -- Stream a -> Stream b -> state -> Stream (s, c)
85 --con_adder_int :: Stream (Bit, Bit) -> Bit -> Stream (Bit, Bit)
86 --con_adder_int ((a,b):rest) cin =
87 --  (s, cout) : con_adder_int rest cout
88 --  where
89 --    (s, cout) = full_adder a b cin
90
91 -- vim: set ts=8 sw=2 sts=2 expandtab: