X-Git-Url: https://git.stderr.nl/gitweb?p=matthijs%2Fmaster-project%2Fhaskell-symposium-talk.git;a=blobdiff_plain;f=PolyAlu.hs;h=b9d0da8fc0dba054fad394a4e32e548c42f9154d;hp=afe9f5deaca3e649b4fb4c3e934bc2a698393132;hb=HEAD;hpb=4872fec52469b7300aeeafd3549a3a5a27cc3139 diff --git a/PolyAlu.hs b/PolyAlu.hs index afe9f5d..b9d0da8 100644 --- a/PolyAlu.hs +++ b/PolyAlu.hs @@ -1,56 +1,70 @@ {-# LINE 4 "PolyAlu.lhs" #-} {-# LANGUAGE TypeOperators, TypeFamilies, FlexibleContexts #-} -module PolyCPU where +module Main where -import qualified Prelude as P -{-# LINE 27 "PolyAlu.lhs" #-} import CLasH.HardwareTypes import CLasH.Translator.Annotations -{-# LINE 37 "PolyAlu.lhs" #-} -type Op s a = a -> Vector s a -> a -type Opcode = Bit -{-# LINE 42 "PolyAlu.lhs" #-} -type RegBank s a = Vector (s :+: D1) a -type RegState s a = State (RegBank s a) -{-# LINE 47 "PolyAlu.lhs" #-} -type Word = SizedInt D12 -{-# LINE 55 "PolyAlu.lhs" #-} -primOp :: (a -> a -> a) -> Op s a -primOp f a b = a `f` a +import qualified Prelude as P +{-# LINE 52 "PolyAlu.lhs" #-} +type Op a = a -> a -> a +type Opcode = Bit {-# LINE 60 "PolyAlu.lhs" #-} -vectOp :: (a -> a -> a) -> Op s a -vectOp f a b = foldl f a b -{-# LINE 69 "PolyAlu.lhs" #-} +type RegBank s a = + Vector (s :+: D1) a +type RegState s a = + State (RegBank s a) +{-# LINE 68 "PolyAlu.lhs" #-} +type Word = SizedInt D12 +{-# LINE 88 "PolyAlu.lhs" #-} alu :: - Op s a -> - Op s a -> - Opcode -> a -> Vector s a -> a + Op a -> Op a -> + Opcode -> a -> a -> a alu op1 op2 Low a b = op1 a b alu op1 op2 High a b = op2 a b -{-# LINE 82 "PolyAlu.lhs" #-} -registerBank :: - ((NaturalT s ,PositiveT (s :+: D1),((s :+: D1) :>: s) ~ True )) => - (RegState s a) -> a -> RangedWord s -> - RangedWord s -> Bit -> ((RegState s a), a ) - -registerBank (State mem) data_in rdaddr wraddr wrenable = +{-# LINE 110 "PolyAlu.lhs" #-} +registers :: + ((NaturalT s ,PositiveT (s :+: D1),((s :+: D1) :>: s) ~ True )) => a -> RangedWord s -> + RangedWord s -> (RegState s a) -> (RegState s a, a ) +{-# LINE 118 "PolyAlu.lhs" #-} +registers data_in rdaddr wraddr (State mem) = ((State mem'), data_out) where - data_out = mem!rdaddr - mem' | wrenable == Low = mem - | otherwise = replace mem wraddr data_in -{-# LINE 100 "PolyAlu.lhs" #-} -{-# ANN actual_cpu TopEntity#-} -actual_cpu :: - (Opcode, Word, Vector D4 Word, - RangedWord D9, - RangedWord D9, Bit) -> - RegState D9 Word -> - (RegState D9 Word, Word) + data_out = mem!rdaddr + mem' = replace mem wraddr data_in +{-# LINE 138 "PolyAlu.lhs" #-} +type Instruction = (Opcode, Word, RangedWord D9, RangedWord D9) +{-# LINE 142 "PolyAlu.lhs" #-} +{-# ANN cpu TopEntity#-} +cpu :: + Instruction -> RegState D9 Word -> (RegState D9 Word, Word) + +cpu (opc, d, rdaddr, wraddr) ram = (ram', alu_out) + where + alu_out = alu (+) (-) opc d ram_out + (ram',ram_out) = registers alu_out rdaddr wraddr ram +{-# LINE 165 "PolyAlu.lhs" #-} +{-# ANN initstate InitState#-} +initstate :: RegState D9 Word +initstate = State (copy (0 :: Word)) + +{-# ANN program TestInput#-} +program :: [Instruction] +program = + [ (Low, 4, 0, 0) -- Write 4 to Reg0 + , (Low, 3, 0, 1) -- Write 3+4 to Reg1 + , (High,8, 1, 2) -- Write 8-7 to Reg2 + ] -actual_cpu (opc, a ,b, rdaddr, wraddr, wren) ram = (ram', alu_out) +run func state [] = [] +run func state (i:input) = o:out where - alu_out = alu simpleOp vectorOp opc ram_out b - (ram',ram_out) = registerBank ram a rdaddr wraddr wren - simpleOp = primOp (+) - vectorOp = vectOp (+) + (state', o) = func i state + out = run func state' input + +main :: IO () +main = do + let input = program + let istate = initstate + let output = run cpu istate input + mapM_ (\x -> putStr $ ("(" P.++ (show x) P.++ ")\n")) output + return ()