Add stateful alu (with empty state).
[matthijs/master-project/cλash.git] / Alu.hs
1 module Alu  where
2 import Bits
3 import qualified Sim
4
5 main = Sim.simulate exec program initial_state
6 mainIO = Sim.simulateIO exec initial_state
7
8 dontcare = Low
9
10 program = [
11             -- (addr, we, op)
12             (High, Low, High), -- z = r1 and t (0) ; t = r1 (1)
13             (Low, Low, Low), -- z = r0 or t (1); t = r0 (0)
14             (Low, High, dontcare), -- r0 = z (1)
15             (High, Low, High), -- z = r1 and t (0); t = r1 (1)
16             (High, High, dontcare) -- r1 = z (0)
17           ]
18
19 initial_state = (Regs Low High, Low, Low)
20
21 -- Register bank
22
23 type RegAddr = Bit
24 --type RegisterBankState = (Bit, Bit)
25 data RegisterBankState = Regs { r0, r1 :: Bit} deriving (Show)
26
27 register_bank :: 
28   (RegAddr, Bit, Bit) -> -- (addr, we, d)
29   RegisterBankState -> -- s
30   (RegisterBankState, Bit) -- (s', o)
31
32 register_bank (Low, Low, _) s = -- Read r0
33   (s, r0 s)
34
35 register_bank (High, Low, _) s = -- Read r1
36   (s, r1 s)
37
38 register_bank (addr, High, d) s = -- Write
39   (s', dontcare)
40   where
41     Regs r0 r1 = s
42     r0' = if addr == Low then d else r0
43     r1' = if addr == High then d else r1
44     s' = Regs r0' r1'
45
46 -- ALU
47
48 type AluOp = Bit
49
50 alu :: AluOp -> Bit -> Bit -> Bit
51 alu High a b = a `hwand` b
52 alu Low a b = a `hwor` b
53
54 salu :: AluOp -> Bit -> Bit -> () -> ((), Bit)
55 salu High a b s = (s, a `hwand` b)
56 salu Low a b s = (s, a `hwor` b)
57
58 type ExecState = (RegisterBankState, Bit, Bit)
59 exec :: (RegAddr, Bit, AluOp) -> ExecState -> (ExecState, ())
60
61 -- Read & Exec
62 exec (addr, Low, op) s =
63   (s', ())
64   where
65     (reg_s, t, z) = s
66     (reg_s', t') = register_bank (addr, Low, dontcare) reg_s
67     z' = alu op t' t
68     s' = (reg_s', t', z')
69
70 -- Write
71 exec (addr, High, op) s =
72   (s', ())
73   where
74     (reg_s, t, z) = s
75     (reg_s', _) = register_bank (addr, High, z) reg_s
76     s' = (reg_s', t, z)
77
78 -- vim: set ts=8 sw=2 sts=2 expandtab: