Laatste wijzigingen
[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 qualified Prelude as P
8 \end{code}
9 %endif
10
11 \section{Polymorphic, Higher-Order CPU}
12 \subsection{Introduction}
13 \frame
14 {
15 \frametitle{Small Use Case}\pause
16 \begin{itemize}
17   \item Small Polymorphic, Higher-Order CPU\pause
18   \item Each function is turned into a hardware component\pause
19   \item Use of state will be simple
20 \end{itemize}
21 }\note[itemize]{
22 \item Small "toy"-example of what can be done in \clash{}
23 \item Show what can be translated to Hardware
24 \item Put your hardware glasses on: each function will be a component
25 \item Use of state will be kept simple
26 }
27
28 \frame
29 {
30 \frametitle{Imports}\pause
31 Import all the built-in types, such as vectors and integers:
32 \begin{beamercolorbox}[sep=-2.5ex,rounded=true,shadow=true,vmode]{codebox}
33 \begin{code}
34 import CLasH.HardwareTypes
35 \end{code}
36 \end{beamercolorbox}\pause
37
38 Import annotations, helps \clash{} to find top-level component:
39 \begin{beamercolorbox}[sep=-2.5ex,rounded=true,shadow=true,vmode]{codebox}
40 \begin{code}
41 import CLasH.Translator.Annotations
42 \end{code}
43 \end{beamercolorbox}
44 }\note[itemize]{
45 \item The first input is always needed, as it contains the builtin types
46 \item The second one is only needed if you want to make use of Annotations
47 }
48
49 \subsection{Type Definitions}
50 \frame
51 {
52 \frametitle{Type definitions}\pause
53 First we define some ALU types:
54 \begin{beamercolorbox}[sep=-2.5ex,rounded=true,shadow=true,vmode]{codebox}
55 \begin{code}
56 type Op s a         =   a -> Vector s a -> a
57 type Opcode         =   Bit
58 \end{code}
59 \end{beamercolorbox}\pause
60
61 And some Register types:
62 \begin{beamercolorbox}[sep=-2.5ex,rounded=true,shadow=true,vmode]{codebox}
63 \begin{code}
64 type RegBank s a    =   Vector (s :+: D1) a
65 type RegState s a   =   State (RegBank s a)
66 \end{code}
67 \end{beamercolorbox}\pause
68
69 And a simple Word type:
70 \begin{beamercolorbox}[sep=-2.5ex,rounded=true,shadow=true,vmode]{codebox}
71 \begin{code}
72 type Word           =   SizedInt D12
73 \end{code}
74 \end{beamercolorbox}
75 }\note[itemize]{
76 \item The first type is already polymorphic, both in size, and element type
77 \item It's a small example, so Opcode is just a Bit
78 \item State has to be of the State type to be recognized as such
79 \item SizedInt D12: One concrete type for now, to make the signatures smaller
80 }
81
82 \subsection{Frameworks for Operations}
83 \frame
84 {
85 \frametitle{Operations}\pause
86 We make a primitive operation:
87 \begin{beamercolorbox}[sep=-2.5ex,rounded=true,shadow=true,vmode]{codebox}
88 \begin{code}
89 primOp :: {-"{\color<4>[rgb]{1,0,0}"-}(a -> a -> a){-"}"-} -> Op s a
90 primOp f a b = a `f` a
91 \end{code}
92 \end{beamercolorbox}\pause
93
94 We make a vector operation:
95 \begin{beamercolorbox}[sep=-2.5ex,rounded=true,shadow=true,vmode]{codebox}
96 \begin{code}
97 vectOp :: {-"{\color<4>[rgb]{1,0,0}"-}(a -> a -> a){-"}"-} -> Op s a
98 vectOp f a b = {-"{\color<4>[rgb]{1,0,0}"-}foldl{-"}"-} f a b
99 \end{code}
100 \end{beamercolorbox}
101 \begin{itemize}
102 \uncover<4->{\item We support Higher-Order Functionality}
103 \end{itemize}
104 }\note[itemize]{
105 \item These are just frameworks for 'real' operations
106 \item Notice how they are High-Order functions
107 }
108
109 \subsection{Polymorphic, Higher-Order ALU}
110 \frame
111 {
112 \frametitle{Simple ALU}
113 We define a polymorphic ALU:
114 \begin{beamercolorbox}[sep=-2.5ex,rounded=true,shadow=true,vmode]{codebox}
115 \begin{code}
116 alu :: 
117   Op s a -> 
118   Op s a -> 
119   Opcode -> a -> Vector s a -> a
120 alu op1 op2 {-"{\color<2>[rgb]{1,0,0}"-}Low{-"}"-}    a b = op1 a b
121 alu op1 op2 {-"{\color<2>[rgb]{1,0,0}"-}High{-"}"-}   a b = op2 a b
122 \end{code}
123 \end{beamercolorbox}
124 \begin{itemize}
125 \uncover<2->{\item We support Pattern Matching}
126 \end{itemize}
127 }\note[itemize]{
128 \item Alu is both higher-order, and polymorphic
129 \item We support pattern matching
130 }
131
132 \subsection{Register bank}
133 \frame
134 {
135 \frametitle{Register Bank}
136 Make a simple register bank:
137 \begin{beamercolorbox}[sep=-2.5ex,rounded=true,shadow=true,vmode]{codebox}
138 \begin{code}
139 registerBank :: 
140   CXT((NaturalT s ,PositiveT (s :+: D1),((s :+: D1) :>: s) ~ True )) => (RegState s a) -> a -> RangedWord s ->
141   RangedWord s -> Bit -> ((RegState s a), a )
142   
143 registerBank (State mem) data_in rdaddr wraddr wrenable = 
144   ((State mem'), data_out)
145   where
146     data_out  =   mem!rdaddr
147     mem'  {-"{\color<2>[rgb]{1,0,0}"-}| wrenable == Low{-"}"-}    = mem
148           {-"{\color<2>[rgb]{1,0,0}"-}| otherwise{-"}"-}          = replace mem wraddr data_in
149 \end{code}
150 \end{beamercolorbox}
151 \begin{itemize}
152 \uncover<2->{\item We support Guards}
153 \end{itemize}
154 }\note[itemize]{
155 \item RangedWord runs from 0 to the upper bound
156 \item mem is statefull
157 \item We support guards
158 }
159
160 \subsection{Simple CPU: ALU \& Register Bank}
161 \frame
162 {
163 \frametitle{Simple CPU}
164 Combining ALU and register bank:
165 \begin{beamercolorbox}[sep=-2.5ex,rounded=true,shadow=true,vmode]{codebox}
166 \begin{code}
167 {-"{\color<2>[rgb]{1,0,0}"-}ANN(actual_cpu TopEntity){-"}"-}
168 actual_cpu :: 
169   (Opcode, Word, Vector D4 Word, RangedWord D9, 
170   RangedWord D9, Bit) ->  RegState D9 Word ->
171   (RegState D9 Word, Word)
172
173 actual_cpu (opc, a ,b, rdaddr, wraddr, wren) ram = (ram', alu_out)
174   where
175     alu_out = alu ({-"{\color<3>[rgb]{1,0,0}"-}primOp (+){-"}"-}) ({-"{\color<3>[rgb]{1,0,0}"-}vectOp (+){-"}"-}) opc ram_out b
176     (ram',ram_out)  = registerBank ram a rdaddr wraddr wren
177 \end{code}
178 \end{beamercolorbox}
179 \begin{itemize}
180 \uncover<2->{\item Annotation is used to indicate top-level component}
181 \end{itemize}
182 }\note[itemize]{
183 \item We use the new Annotion functionality to indicate this is the top level
184 \item the primOp and vectOp frameworks are now supplied with real functionality, the plus (+) operations
185 \item No polymorphism or higher-order stuff is allowed at this level.
186 \item Functions must be specialized, and have primitives for input and output 
187 }
188
189 %if style == newcode
190 \begin{code}
191 ANN(initstate InitState)
192 initstate :: RegState D9 Word
193 initstate = State (copy (0 :: Word))  
194   
195 ANN(program TestInput)
196 program :: [(Opcode, Word, Vector D4 Word, RangedWord D9, RangedWord D9, Bit)]
197 program =
198   [ (Low, 4, copy (0), 0, 0, High) -- Write 4 to Reg0, out = 0
199   , (Low, 3, copy (0), 0, 1, High) -- Write 3 to Reg1, out = 8
200   , (High,0, copy (3), 1, 0, Low)  -- No Write       , out = 15
201   ]
202
203 run func state [] = []
204 run func state (i:input) = o:out
205   where
206     (state', o) = func i state
207     out         = run func state' input
208     
209 main :: IO ()
210 main = do
211   let input = program
212   let istate = initstate
213   let output = run actual_cpu istate input
214   mapM_ (\x -> putStr $ ("(" P.++ (show x) P.++ ")\n")) output
215   return ()
216 \end{code}
217 %endif