Only do State packing once in register_bank.
[matthijs/master-project/cλash.git] / Alu.hs
1 module Alu where
2 import qualified Sim
3 import CLasH.HardwareTypes hiding (fst,snd)
4 import CLasH.Translator.Annotations
5 import qualified Prelude as P
6
7 fst (a, b) = a
8 snd (a, b) = b
9
10 main = Sim.simulate exec program initial_state
11 mainIO = Sim.simulateIO exec initial_state
12
13 dontcare = Low
14
15 program = [
16             -- (addr, we, op)
17             (High, Low, High), -- z = r1 and t (0) ; t = r1 (1)
18             (Low, Low, Low), -- z = r0 or t (1); t = r0 (0)
19             (Low, High, dontcare), -- r0 = z (1)
20             (High, Low, High), -- z = r1 and t (0); t = r1 (1)
21             (High, High, dontcare) -- r1 = z (0)
22           ]
23
24 --initial_state = (Regs Low High, Low, Low)
25 initial_state = State (State (0, 1), 0, 0)
26
27 type Word = SizedWord D4
28 -- Register bank
29 type RegAddr = Bit
30 type RegisterBankState = State (Word, Word)
31 --data RegisterBankState = Regs { r0, r1 :: Bit} deriving (Show)
32
33 register_bank :: 
34   RegAddr -- ^ Address
35   -> Bit -- ^ Write Enable
36   -> Word -- ^ Data
37   -> RegisterBankState -> -- State
38   (RegisterBankState, Word) -- (State', Output)
39
40 register_bank addr we d (State s) = (State s', o)
41   where
42     s' = case we of
43       Low -> s -- Read
44       High -> -- Write
45         let
46           (r0, r1) = s
47           r0' = case addr of Low -> d; High -> r0
48           r1' = case addr of High -> d; Low -> r1
49         in (r0', r1')
50     o = case we of
51       -- Read
52       Low -> case addr of Low -> fst s; High -> snd s
53       -- Write
54       High -> 0 -- Don't output anything useful
55
56 -- ALU
57
58 type AluOp = Bit
59
60 alu :: AluOp -> Word -> Word -> Word
61 {-# NOINLINE alu #-}
62 --alu High a b = a `hwand` b
63 --alu Low a b = a `hwor` b
64 alu High a b = a P.+ b
65 alu Low a b = a P.- b
66
67 type ExecState = State (RegisterBankState, Word, Word)
68 exec :: (RegAddr, Bit, AluOp) -> ExecState -> (ExecState, Word)
69
70 {-# ANN exec TopEntity #-}
71 -- Read & Exec
72 exec (addr, we, op) (State s) =
73   (State s', z')
74   where
75     (reg_s, t, z) = s
76     (reg_s', t') = register_bank addr we z reg_s
77     z' = alu op t' t
78     s' = (reg_s', t', z')
79
80 -- vim: set ts=8 sw=2 sts=2 expandtab: