Really revert all of the recent rotating changes.
[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 {-# NOINLINE register_bank #-}
34 register_bank :: 
35   RegAddr -- ^ Address
36   -> Bit -- ^ Write Enable
37   -> Word -- ^ Data
38   -> RegisterBankState -> -- State
39   (RegisterBankState, Word) -- (State', Output)
40
41 register_bank addr we d (State s) = (State s', o)
42   where
43     s' = case we of
44       Low -> s -- Read
45       High -> -- Write
46         let
47           (r0, r1) = s
48           r0' = case addr of Low -> d; High -> r0
49           r1' = case addr of High -> d; Low -> r1
50         in (r0', r1')
51     o = case we of
52       -- Read
53       Low -> case addr of Low -> fst s; High -> snd s
54       -- Write
55       High -> 0 -- Don't output anything useful
56
57 -- ALU
58
59 type AluOp = Bit
60
61 alu :: AluOp -> Word -> Word -> Word
62 {-# NOINLINE alu #-}
63 --alu High a b = a `hwand` b
64 --alu Low a b = a `hwor` b
65 alu High a b = a + b
66 alu Low a b = a - b
67
68 type ExecState = State (RegisterBankState, Word, Word)
69 exec :: (RegAddr, Bit, AluOp) -> ExecState -> (ExecState, Word)
70
71 {-# ANN exec TopEntity #-}
72 -- Read & Exec
73 exec (addr, we, op) (State s) =
74   (State s', z')
75   where
76     (reg_s, t, z) = s
77     (reg_s', t') = register_bank addr we z reg_s
78     z' = alu op t' t
79     s' = (reg_s', t', z')
80
81 -- vim: set ts=8 sw=2 sts=2 expandtab: