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