Added images
[matthijs/master-project/haskell-symposium-talk.git] / PolyAlu.lhs
1 %include talk.fmt
2 %if style == newcode
3 \begin{code}
4 {-# LANGUAGE  TypeOperators, TypeFamilies, FlexibleContexts #-}
5 module Main where
6
7 import CLasH.HardwareTypes
8 import CLasH.Translator.Annotations
9 import qualified Prelude as P
10 \end{code}
11 %endif
12
13 \section{Polymorphic, Higher-Order CPU}
14 \subsection{Introduction}
15 \frame
16 {
17 \frametitle{Small Use Case}
18 \begin{columns}[l]
19 \column{0.5\textwidth}
20 \begin{figure}
21 \includegraphics[width=4.75cm]{simpleCPU}
22 \end{figure}
23 \column{0.5\textwidth}
24 \begin{itemize}
25   \item Polymorphic, Higher-Order CPU
26   \item Use of state will be simple
27 \end{itemize}
28 \end{columns}
29 }\note[itemize]{
30 \item Small "toy"-example of what can be done in \clash{}
31 \item Show what can be translated to Hardware
32 \item Put your hardware glasses on: each function will be a component
33 \item Use of state will be kept simple
34 }
35
36 \subsection{Type Definitions}
37 \frame
38 {
39 \frametitle{Type definitions}\pause
40 \begin{columns}[l]
41 \column{0.5\textwidth}
42 \begin{figure}
43 \includegraphics[width=4.75cm]{simpleCPU}
44 \end{figure}
45 \column{0.5\textwidth}
46 \vspace{2em}
47
48 First we define some ALU types:
49 \begin{beamercolorbox}[sep=-2.5ex,rounded=true,shadow=true,vmode]{codebox}
50 \begin{code}
51 type Op a         =   a -> a -> a
52 \end{code}
53 \end{beamercolorbox}\pause
54 \vspace{2.5em}
55 And some Register types:
56 \begin{beamercolorbox}[sep=-2.5ex,rounded=true,shadow=true,vmode]{codebox}
57 \begin{code}
58 type RegBank s a    =   
59   Vector (s :+: D1) a
60 type RegState s a   =   
61   State (RegBank s a)
62 \end{code}
63 \end{beamercolorbox}
64 %if style == newcode
65 \begin{code}
66 type Word = SizedInt D12
67 \end{code}
68 %endif
69 \end{columns}
70 }\note[itemize]{
71 \item The first type is already polymorphic in input / output type
72 \item State has to be of the State type to be recognized as such
73 }
74
75 \subsection{Polymorphic, Higher-Order ALU}
76 \frame
77 {
78 \frametitle{Simple ALU}
79 \begin{figure}
80 \includegraphics[width=5.25cm,trim=0mm 5.5cm 0mm 1cm, clip=true]{simpleCPU}
81 \end{figure}
82 Abstract ALU definition:
83 \begin{beamercolorbox}[sep=-2.5ex,rounded=true,shadow=true,vmode]{codebox}
84 \begin{code}
85 type Opcode         =   Bit
86 alu :: 
87   Op a -> Op a -> 
88   Opcode -> a -> a -> a
89 alu op1 op2 {-"{\color<2>[rgb]{1,0,0}"-}Low{-"}"-}    a b = op1 a b
90 alu op1 op2 {-"{\color<2>[rgb]{1,0,0}"-}High{-"}"-}   a b = op2 a b
91 \end{code}
92 \end{beamercolorbox}
93 }\note[itemize]{
94 \item Alu is both higher-order, and polymorphic
95 \item Two parameters are "compile time", others are "runtime"
96 \item We support pattern matching
97 }
98
99 \subsection{Register bank}
100 \frame
101 {
102 \frametitle{Register Bank}
103 \begin{figure}
104 \includegraphics[width=5.25cm,trim=0mm 0.4cm 0mm 6.2cm, clip=true]{simpleCPU}
105 \end{figure}
106 %if style == newcode
107 \begin{code}
108 registers :: 
109   CXT((NaturalT s ,PositiveT (s :+: D1),((s :+: D1) :>: s) ~ True )) => a -> RangedWord s ->
110   RangedWord s -> (RegState s a) -> (RegState s a, a )
111 \end{code}
112 %endif
113 A simple register bank:
114 \begin{beamercolorbox}[sep=-2.5ex,rounded=true,shadow=true,vmode]{codebox}
115 \begin{code}
116 registers data_in rdaddr wraddr (State mem) = 
117   ((State mem'), data_out)
118   where
119     data_out  = mem!rdaddr
120     mem'      = replace mem wraddr data_in
121 \end{code}
122 \end{beamercolorbox}
123 }\note[itemize]{
124 \item RangedWord runs from 0 to the upper bound
125 \item mem is statefull
126 \item We support guards
127 \item replace is a builtin function
128 }
129
130 \subsection{Simple CPU: ALU \& Register Bank}
131 \frame
132 {
133 \frametitle{Simple CPU}
134 Combining ALU and register bank:
135 \begin{beamercolorbox}[sep=-2.5ex,rounded=true,shadow=true,vmode]{codebox}
136 %if style == newcode
137 \begin{code}
138 type Instruction = (Opcode, Word, RangedWord D9, RangedWord D9)
139 \end{code}
140 %endif
141 \begin{code}
142 {-"{\color<2>[rgb]{1,0,0}"-}ANN(cpu TopEntity){-"}"-}
143 cpu :: 
144   Instruction -> RegState D9 Word -> (RegState D9 Word, Word)
145
146 cpu (opc, d, rdaddr, wraddr) ram = (ram', alu_out)
147   where
148     alu_out         = alu {-"{\color<3>[rgb]{1,0,0}"-}(+){-"}"-} {-"{\color<3>[rgb]{1,0,0}"-}(-){-"}"-} opc d ram_out
149     (ram',ram_out)  = registers alu_out rdaddr wraddr ram
150 \end{code}
151 \end{beamercolorbox}
152 \begin{itemize}
153 \uncover<2->{\item Annotation is used to indicate top-level component}
154 \uncover<3->{\item Instantiate actual operations}
155 \end{itemize}
156 }\note[itemize]{
157 \item We use the new Annotion functionality to indicate this is the top level. TopEntity is defined by us.
158 \item the primOp and vectOp frameworks are now supplied with real functionality, the plus (+) operations
159 \item No polymorphism or higher-order stuff is allowed at this level.
160 \item Functions must be specialized, and have primitives for input and output 
161 }
162
163 %if style == newcode
164 \begin{code}
165 ANN(initstate InitState)
166 initstate :: RegState D9 Word
167 initstate = State (copy (0 :: Word))  
168   
169 ANN(program TestInput)
170 program :: [Instruction]
171 program =
172   [ (Low, 4, 0, 0) -- Write 4   to Reg0
173   , (Low, 3, 0, 1) -- Write 3+4 to Reg1
174   , (High,8, 1, 2) -- Write 8-7 to Reg2
175   ]
176
177 run func state [] = []
178 run func state (i:input) = o:out
179   where
180     (state', o) = func i state
181     out         = run func state' input
182     
183 main :: IO ()
184 main = do
185   let input = program
186   let istate = initstate
187   let output = run cpu istate input
188   mapM_ (\x -> putStr $ ("(" P.++ (show x) P.++ ")\n")) output
189   return ()
190 \end{code}
191 %endif