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