Added function calls
[matthijs/master-project/cλash.git] / Adders.hs
1 module Adders where
2 import Bits
3 import qualified Sim
4
5 import qualified Prelude as P
6 import Prelude hiding (
7   null, length, head, tail, last, init, take, drop, (++), map, foldl, foldr,
8   zipWith, zip, unzip, concat, reverse, iterate )
9
10 import Language.Haskell.Syntax
11 import Types
12 import Data.Param.TFVec
13
14 -- mainIO f = Sim.simulateIO (Sim.stateless f) ()
15
16 -- This function is from Sim.hs, but we redefine it here so it can get inlined
17 -- by default.
18 -- stateless :: (i -> o) -> (i -> () -> ((), o))
19 -- stateless f = \i s -> (s, f i)
20 -- 
21 -- show_add f = do print ("Sum:   " ++ (displaysigs s)); print ("Carry: " ++ (displaysig c))
22 --   where
23 --     a = [High, High, High, High]
24 --     b = [Low, Low, Low, High]
25 --     (s, c) = f (a, b)
26 -- 
27 -- mux2 :: Bit -> (Bit, Bit) -> Bit
28 -- mux2 Low (a, b) = a
29 -- mux2 High (a, b) = b
30
31 -- Not really an adder, but this is nice minimal hardware description
32 -- wire :: Bit -> Bit
33 -- wire a = a
34
35 -- bus :: (TypeLevel.Pos len) => BitVec len -> BitVec len
36 -- bus v = v
37 -- 
38 -- bus_4 :: BitVec TypeLevel.D4 -> BitVec TypeLevel.D4
39 -- bus_4 v = v
40
41 {-
42 inv_n :: (Pos len) => BitVec len -> BitVec len
43 inv_n v =
44   --FSVec.map hwnot v
45   inv_n_rec v
46
47 class Inv vec where
48   inv_n_rec :: vec -> vec
49
50 instance (Pos len) => Inv (BitVec len) where
51   inv_n_rec v = 
52     h FSVec.+> t
53     where
54       h = FSVec.head v
55       t = FSVec.tail v
56
57 instance Inv (BitVec D0) where
58   inv_n_rec v = v
59 -}
60 -- Not really an adder either, but a slightly more complex example
61 -- inv :: Bit -> Bit
62 -- inv a = let r = hwnot a in r
63
64 -- Not really an adder either, but a slightly more complex example
65 -- invinv :: Bit -> Bit
66 -- invinv a = hwnot (hwnot a)
67
68 -- Not really an adder either, but a slightly more complex example
69 -- dup :: Bit -> (Bit, Bit)
70 -- dup a = (a, a)
71
72 -- Not really an adder either, but a simple stateful example (D-flipflop)
73 -- dff :: Bit -> Bit -> (Bit, Bit)
74 -- dff d s = (s', q)
75 --   where
76 --     q = s
77 --     s' = d
78 -- 
79 -- type ShifterState = (Bit, Bit, Bit, Bit)
80 -- shifter :: Bit -> ShifterState -> (ShifterState, Bit)
81 -- shifter i (a, b, c, d) =
82 --   (s', d)
83 --   where
84 --     s' = (i, a, b, c)
85 -- 
86 -- {-# NOINLINE shifter_en #-}
87 -- shifter_en :: Bit -> Bit-> ShifterState -> (ShifterState, Bit)
88 -- shifter_en High i (a, b, c, d) =
89 --   (s', d)
90 --   where
91 --     s' = (i, a, b, c)
92 -- 
93 -- shifter_en Low i s@(a, b, c, d) =
94 --   (s, d)
95
96 -- Two multiplexed shifters
97 -- type ShiftersState = (ShifterState, ShifterState)
98 -- shifters :: Bit -> Bit -> ShiftersState -> (ShiftersState, Bit)
99 -- shifters sel i (sa, sb) =
100 --   (s', out)
101 --   where
102 --     (sa', outa) = shifter_en sel i sa
103 --     (sb', outb) = shifter_en (hwnot sel) i sb
104 --     s' = (sa', sb')
105 --     out = if sel == High then outa else outb
106
107 -- Combinatoric stateless no-carry adder
108 -- A -> B -> S
109 -- no_carry_adder :: (Bit, Bit) -> Bit
110 -- no_carry_adder (a, b) = a `hwxor` b
111
112 -- Combinatoric stateless half adder
113 -- A -> B -> (S, C)
114 -- half_adder :: (Bit, Bit) -> (Bit, Bit)
115 -- {-# NOINLINE half_adder #-}
116 -- half_adder (a, b) = 
117 --   ( a `hwxor` b, a `hwand` b )
118
119 -- Combinatoric stateless full adder
120 -- (A, B, C) -> (S, C)
121 -- full_adder :: (Bit, Bit, Bit) -> (Bit, Bit)
122 -- full_adder (a, b, cin) = (s, c)
123 --   where
124 --     (s1, c1) = half_adder(a, b)
125 --     (s, c2)  = half_adder(s1, cin)
126 --     c        = c1 `hwor` c2
127 -- 
128 -- sfull_adder = stateless full_adder
129
130 -- Four bit adder
131 -- Explicit version
132 -- [a] -> [b] -> ([s], cout)
133 -- exp_adder :: ([Bit], [Bit]) -> ([Bit], Bit)
134 -- 
135 -- exp_adder ([a3,a2,a1,a0], [b3,b2,b1,b0]) =
136 --   ([s3, s2, s1, s0], c3)
137 --   where
138 --     (s0, c0) = full_adder (a0, b0, Low)
139 --     (s1, c1) = full_adder (a1, b1, c0)
140 --     (s2, c2) = full_adder (a2, b2, c1)
141 --     (s3, c3) = full_adder (a3, b3, c2)
142
143 -- Any number of bits adder
144 -- Recursive version
145 -- [a] -> [b] -> ([s], cout)
146 -- rec_adder :: ([Bit], [Bit]) -> ([Bit], Bit)
147 -- 
148 -- rec_adder ([], []) = ([], Low)
149 -- rec_adder ((a:as), (b:bs)) = 
150 --   (s : rest, cout)
151 --   where
152 --     (rest, cin) = rec_adder (as, bs)
153 --     (s, cout) = full_adder (a, b, cin)
154 -- 
155 -- foo = id
156 -- add, sub :: Int -> Int -> Int
157 -- add a b = a + b
158 -- sub a b = a - b
159 -- 
160 -- highordtest = \x ->
161 --   let s = foo x
162 --   in
163 --      case s of
164 --        (a, b) ->
165 --          case a of
166 --            High -> add
167 --            Low -> let
168 --              op' = case b of
169 --                 High -> sub
170 --                 Low -> \c d -> c
171 --              in
172 --                 \c d -> op' d c
173
174 functiontest :: TFVec D4 Bit -> Bit
175 functiontest = \v -> let r = head v in r
176
177 -- Four bit adder, using the continous adder below
178 -- [a] -> [b] -> ([s], cout)
179 --con_adder_4 as bs = 
180 --  ([s3, s2, s1, s0], c)
181 --  where
182 --    ((s0, _):(s1, _):(s2, _):(s3, c):_) = con_adder (zip ((reverse as) ++ lows) ((reverse bs) ++ lows))
183
184 -- Continuous sequential version
185 -- Stream a -> Stream b -> Stream (sum, cout)
186 --con_adder :: Stream (Bit, Bit) -> Stream (Bit, Bit)
187
188 -- Forward to con_adder_int, but supply an initial state
189 --con_adder pin =
190 --  con_adder_int pin Low
191
192 -- Stream a -> Stream b -> state -> Stream (s, c)
193 --con_adder_int :: Stream (Bit, Bit) -> Bit -> Stream (Bit, Bit)
194 --con_adder_int ((a,b):rest) cin =
195 --  (s, cout) : con_adder_int rest cout
196 --  where
197 --    (s, cout) = full_adder a b cin
198
199 -- vim: set ts=8 sw=2 sts=2 expandtab: