X-Git-Url: https://git.stderr.nl/gitweb?p=matthijs%2Fmaster-project%2Fc%CE%BBash.git;a=blobdiff_plain;f=Alu.hs;h=7171a6549d4a216f7ffb876eacdc4d8db5e22571;hp=40f76220ade83a2116b6f0bb928e8853cff34863;hb=HEAD;hpb=dcf9dd6d86a5f256c1129146a977620ab6d8d466 diff --git a/Alu.hs b/Alu.hs index 40f7622..7171a65 100644 --- a/Alu.hs +++ b/Alu.hs @@ -1,73 +1,81 @@ -module Alu (main) where -import Bits +module Alu where import qualified Sim +import CLasH.HardwareTypes hiding (fst,snd) +import CLasH.Translator.Annotations +import qualified Prelude as P + +fst (a, b) = a +snd (a, b) = b main = Sim.simulate exec program initial_state mainIO = Sim.simulateIO exec initial_state +dontcare = Low + program = [ -- (addr, we, op) (High, Low, High), -- z = r1 and t (0) ; t = r1 (1) (Low, Low, Low), -- z = r0 or t (1); t = r0 (0) - (Low, High, DontCare), -- r0 = z (1) + (Low, High, dontcare), -- r0 = z (1) (High, Low, High), -- z = r1 and t (0); t = r1 (1) - (High, High, DontCare) -- r1 = z (0) + (High, High, dontcare) -- r1 = z (0) ] -initial_state = (Regs Low High, (), Low, Low) +--initial_state = (Regs Low High, Low, Low) +initial_state = State (State (0, 1), 0, 0) +type Word = SizedWord D4 -- Register bank - type RegAddr = Bit ---type RegisterBankState = (Bit, Bit) -data RegisterBankState = Regs { r0, r1 :: Bit} deriving (Show) +type RegisterBankState = State (Word, Word) +--data RegisterBankState = Regs { r0, r1 :: Bit} deriving (Show) +{-# NOINLINE register_bank #-} register_bank :: - (RegAddr, Bit, Bit) -> -- (addr, we, d) - RegisterBankState -> -- s - (RegisterBankState, Bit) -- (s', o) - -register_bank (Low, Low, _) s = -- Read r0 - (s, r0 s) + RegAddr -- ^ Address + -> Bit -- ^ Write Enable + -> Word -- ^ Data + -> RegisterBankState -> -- State + (RegisterBankState, Word) -- (State', Output) -register_bank (High, Low, _) s = -- Read r1 - (s, r1 s) - -register_bank (addr, High, d) s = -- Write - (s', DontCare) +register_bank addr we d (State s) = (State s', o) where - Regs r0 r1 = s - r0' = if addr == Low then d else r0 - r1' = if addr == High then d else r1 - s' = Regs r0' r1' + s' = case we of + Low -> s -- Read + High -> -- Write + let + (r0, r1) = s + r0' = case addr of Low -> d; High -> r0 + r1' = case addr of High -> d; Low -> r1 + in (r0', r1') + o = case we of + -- Read + Low -> case addr of Low -> fst s; High -> snd s + -- Write + High -> 0 -- Don't output anything useful -- ALU -type AluState = () type AluOp = Bit -alu :: (AluOp, Bit, Bit) -> AluState -> (AluState, Bit) -alu (High, a, b) s = ((), a `hwand` b) -alu (Low, a, b) s = ((), a `hwor` b) +alu :: AluOp -> Word -> Word -> Word +{-# NOINLINE alu #-} +--alu High a b = a `hwand` b +--alu Low a b = a `hwor` b +alu High a b = a + b +alu Low a b = a - b -type ExecState = (RegisterBankState, AluState, Bit, Bit) -exec :: (RegAddr, Bit, AluOp) -> ExecState -> (ExecState, ()) +type ExecState = State (RegisterBankState, Word, Word) +exec :: (RegAddr, Bit, AluOp) -> ExecState -> (ExecState, Word) +{-# ANN exec TopEntity #-} -- Read & Exec -exec (addr, Low, op) s = - (s', ()) - where - (reg_s, alu_s, t, z) = s - (reg_s', t') = register_bank (addr, Low, DontCare) reg_s - (alu_s', z') = alu (op, t', t) alu_s - s' = (reg_s', alu_s', t', z') - --- Write -exec (addr, High, op) s = - (s', ()) +exec (addr, we, op) (State s) = + (State s', z') where - (reg_s, alu_s, t, z) = s - (reg_s', _) = register_bank (addr, High, z) reg_s - s' = (reg_s', alu_s, t, z) + (reg_s, t, z) = s + (reg_s', t') = register_bank addr we z reg_s + z' = alu op t' t + s' = (reg_s', t', z') -- vim: set ts=8 sw=2 sts=2 expandtab: