X-Git-Url: https://git.stderr.nl/gitweb?p=matthijs%2Fmaster-project%2Fhaskell-symposium-talk.git;a=blobdiff_plain;f=PolyAlu.lhs;fp=PolyAlu.lhs;h=c0d196d01d4d0137b1b71aebf824ffd50cc45560;hp=547f0951baa8e27c4f431690603e4470279b653a;hb=d514bd151f4bd5bbb5ae6828902a778222de9738;hpb=bb178ef5c75d6adf38295303902670365634319c diff --git a/PolyAlu.lhs b/PolyAlu.lhs index 547f095..c0d196d 100644 --- a/PolyAlu.lhs +++ b/PolyAlu.lhs @@ -4,6 +4,8 @@ {-# LANGUAGE TypeOperators, TypeFamilies, FlexibleContexts #-} module Main where +import CLasH.HardwareTypes +import CLasH.Translator.Annotations import qualified Prelude as P \end{code} %endif @@ -12,12 +14,18 @@ import qualified Prelude as P \subsection{Introduction} \frame { -\frametitle{Small Use Case}\pause -TODO: Plaatje +\frametitle{Small Use Case} +\begin{columns}[l] +\column{0.5\textwidth} +\begin{figure} +\includegraphics[width=4.75cm]{simpleCPU} +\end{figure} +\column{0.5\textwidth} \begin{itemize} - \item Polymorphic, Higher-Order CPU\pause + \item Polymorphic, Higher-Order CPU \item Use of state will be simple \end{itemize} +\end{columns} }\note[itemize]{ \item Small "toy"-example of what can be done in \clash{} \item Show what can be translated to Hardware @@ -29,21 +37,36 @@ TODO: Plaatje \frame { \frametitle{Type definitions}\pause -TODO: Plaatje van de ALU +\begin{columns}[l] +\column{0.5\textwidth} +\begin{figure} +\includegraphics[width=4.75cm]{simpleCPU} +\end{figure} +\column{0.5\textwidth} +\vspace{2em} + First we define some ALU types: \begin{beamercolorbox}[sep=-2.5ex,rounded=true,shadow=true,vmode]{codebox} \begin{code} type Op a = a -> a -> a \end{code} \end{beamercolorbox}\pause - +\vspace{2.5em} And some Register types: \begin{beamercolorbox}[sep=-2.5ex,rounded=true,shadow=true,vmode]{codebox} \begin{code} -type RegBank s a = Vector (s :+: D1) a -type RegState s a = State (RegBank s a) +type RegBank s a = + Vector (s :+: D1) a +type RegState s a = + State (RegBank s a) \end{code} -\end{beamercolorbox}\pause +\end{beamercolorbox} +%if style == newcode +\begin{code} +type Word = SizedInt D12 +\end{code} +%endif +\end{columns} }\note[itemize]{ \item The first type is already polymorphic in input / output type \item State has to be of the State type to be recognized as such @@ -53,6 +76,9 @@ type RegState s a = State (RegBank s a) \frame { \frametitle{Simple ALU} +\begin{figure} +\includegraphics[width=5.25cm,trim=0mm 5.5cm 0mm 1cm, clip=true]{simpleCPU} +\end{figure} Abstract ALU definition: \begin{beamercolorbox}[sep=-2.5ex,rounded=true,shadow=true,vmode]{codebox} \begin{code} @@ -64,9 +90,6 @@ alu op1 op2 {-"{\color<2>[rgb]{1,0,0}"-}Low{-"}"-} a b = op1 a b alu op1 op2 {-"{\color<2>[rgb]{1,0,0}"-}High{-"}"-} a b = op2 a b \end{code} \end{beamercolorbox} -\begin{itemize} -\uncover<2->{\item We support Pattern Matching} -\end{itemize} }\note[itemize]{ \item Alu is both higher-order, and polymorphic \item Two parameters are "compile time", others are "runtime" @@ -77,24 +100,26 @@ alu op1 op2 {-"{\color<2>[rgb]{1,0,0}"-}High{-"}"-} a b = op2 a b \frame { \frametitle{Register Bank} -Make a simple register bank: -\begin{beamercolorbox}[sep=-2.5ex,rounded=true,shadow=true,vmode]{codebox} -TODO: Hide type sig +\begin{figure} +\includegraphics[width=5.25cm,trim=0mm 0.4cm 0mm 6.2cm, clip=true]{simpleCPU} +\end{figure} +%if style == newcode \begin{code} -registerBank :: +registers :: CXT((NaturalT s ,PositiveT (s :+: D1),((s :+: D1) :>: s) ~ True )) => a -> RangedWord s -> - RangedWord s -> Bool -> (RegState s a) -> ((RegState s a), a ) - -registerBank data_in rdaddr wraddr (State mem) = + RangedWord s -> (RegState s a) -> (RegState s a, a ) +\end{code} +%endif +A simple register bank: +\begin{beamercolorbox}[sep=-2.5ex,rounded=true,shadow=true,vmode]{codebox} +\begin{code} +registers data_in rdaddr wraddr (State mem) = ((State mem'), data_out) where data_out = mem!rdaddr mem' = replace mem wraddr data_in \end{code} \end{beamercolorbox} -\begin{itemize} -\uncover<2->{\item We support Guards} -\end{itemize} }\note[itemize]{ \item RangedWord runs from 0 to the upper bound \item mem is statefull @@ -108,21 +133,25 @@ registerBank data_in rdaddr wraddr (State mem) = \frametitle{Simple CPU} Combining ALU and register bank: \begin{beamercolorbox}[sep=-2.5ex,rounded=true,shadow=true,vmode]{codebox} -TODO: Hide Instruction type? +%if style == newcode +\begin{code} +type Instruction = (Opcode, Word, RangedWord D9, RangedWord D9) +\end{code} +%endif \begin{code} -type Instruction = (Opcode, Word, RangedWord D9, RangedWord D9) -> RegState D9 Word -> -{-"{\color<2>[rgb]{1,0,0}"-}ANN(actual_cpu TopEntity){-"}"-} -actual_cpu :: +{-"{\color<2>[rgb]{1,0,0}"-}ANN(cpu TopEntity){-"}"-} +cpu :: Instruction -> RegState D9 Word -> (RegState D9 Word, Word) -actual_cpu (opc, d, rdaddr, wraddr) ram = (ram', alu_out) +cpu (opc, d, rdaddr, wraddr) ram = (ram', alu_out) where - alu_out = alu ({-"{\color<3>[rgb]{1,0,0}"-}(+){-"}"-}) ({-"{\color<3>[rgb]{1,0,0}"-}(-){-"}"-}) opc d ram_out - (ram',ram_out) = registerBank alu_out rdaddr wraddr ram + alu_out = alu {-"{\color<3>[rgb]{1,0,0}"-}(+){-"}"-} {-"{\color<3>[rgb]{1,0,0}"-}(-){-"}"-} opc d ram_out + (ram',ram_out) = registers alu_out rdaddr wraddr ram \end{code} \end{beamercolorbox} \begin{itemize} \uncover<2->{\item Annotation is used to indicate top-level component} +\uncover<3->{\item Instantiate actual operations} \end{itemize} }\note[itemize]{ \item We use the new Annotion functionality to indicate this is the top level. TopEntity is defined by us. @@ -138,11 +167,11 @@ initstate :: RegState D9 Word initstate = State (copy (0 :: Word)) ANN(program TestInput) -program :: [(Opcode, Word, Vector D4 Word, RangedWord D9, RangedWord D9, Bit)] +program :: [Instruction] program = - [ (Low, 4, copy (0), 0, 0, High) -- Write 4 to Reg0, out = 0 - , (Low, 3, copy (0), 0, 1, High) -- Write 3 to Reg1, out = 8 - , (High,0, copy (3), 1, 0, Low) -- No Write , out = 15 + [ (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 ] run func state [] = [] @@ -155,7 +184,7 @@ main :: IO () main = do let input = program let istate = initstate - let output = run actual_cpu istate input + let output = run cpu istate input mapM_ (\x -> putStr $ ("(" P.++ (show x) P.++ ")\n")) output return () \end{code}