Fix typos
[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 \vspace{5em}
25 \begin{itemize}
26   \item Polymorphic, Higher-Order CPU
27   \item Use of state will be simple
28 \end{itemize}
29 \end{columns}
30 }\note[itemize]{
31 \item Small "toy"-example of what can be done in \clash{}
32 \item Show what can be translated to Hardware
33 \item Put your hardware glasses on: each function will be a component
34 \item Use of state will be kept simple
35 }
36
37 \subsection{Type Definitions}
38 \frame
39 {
40 \frametitle{Type definitions}\pause
41 \begin{columns}[l]
42 \column{0.5\textwidth}
43 \begin{figure}
44 \includegraphics[width=4.75cm]{simpleCPU}
45 \end{figure}
46 \column{0.5\textwidth}
47 \vspace{2em}
48
49 First we define some ALU types:
50 \begin{beamercolorbox}[sep=-2.5ex,rounded=true,shadow=true,vmode]{codebox}
51 \begin{code}
52 type Op a         =   a -> a -> a
53 type Opcode       =   Bit
54 \end{code}
55 \end{beamercolorbox}\pause
56 \vspace{1em}
57 And some Register types:
58 \begin{beamercolorbox}[sep=-2.5ex,rounded=true,shadow=true,vmode]{codebox}
59 \begin{code}
60 type RegBank s a    =   
61   Vector (s :+: D1) a
62 type RegState s a   =   
63   State (RegBank s a)
64 \end{code}
65 \end{beamercolorbox}
66 %if style == newcode
67 \begin{code}
68 type Word = SizedInt D12
69 \end{code}
70 %endif
71 \end{columns}
72 }\note[itemize]{
73 \item The ALU operation is already polymorphic in input / output type
74 \item We use a fixed size vector as the placeholder for the registers
75 \item State has to be of the State type to be recognized as such
76 }
77
78 \subsection{Polymorphic, Higher-Order ALU}
79 \frame
80 {
81 \frametitle{Simple ALU}
82 \begin{figure}
83 \includegraphics[width=5.25cm,trim=0mm 5.5cm 0mm 1cm, clip=true]{simpleCPU}
84 \end{figure}
85 Abstract ALU definition:
86 \begin{beamercolorbox}[sep=-2.5ex,rounded=true,shadow=true,vmode]{codebox}
87 \begin{code}
88 alu :: 
89   Op a -> Op a -> 
90   Opcode -> a -> a -> a
91 alu op1 op2 {-"{\color<2>[rgb]{1,0,0}"-}Low{-"}"-}    a b = op1 a b
92 alu op1 op2 {-"{\color<2>[rgb]{1,0,0}"-}High{-"}"-}   a b = op2 a b
93 \end{code}
94 \end{beamercolorbox}
95 }\note[itemize]{
96 \item Alu is both higher-order, and polymorphic
97 \item First two parameters are "compile time", other three are "runtime"
98 \item We support pattern matching
99 }
100
101 \subsection{Register bank}
102 \frame
103 {
104 \frametitle{Register Bank}
105 \begin{figure}
106 \includegraphics[width=5.25cm,trim=0mm 0.4cm 0mm 6.2cm, clip=true]{simpleCPU}
107 \end{figure}
108 %if style == newcode
109 \begin{code}
110 registers :: 
111   CXT((NaturalT s ,PositiveT (s :+: D1),((s :+: D1) :>: s) ~ True )) => a -> RangedWord s ->
112   RangedWord s -> (RegState s a) -> (RegState s a, a )
113 \end{code}
114 %endif
115 A simple register bank:
116 \begin{beamercolorbox}[sep=-2.5ex,rounded=true,shadow=true,vmode]{codebox}
117 \begin{code}
118 registers data_in rdaddr wraddr (State mem) = 
119   ((State mem'), data_out)
120   where
121     data_out  = mem!rdaddr
122     mem'      = replace mem wraddr data_in
123 \end{code}
124 \end{beamercolorbox}
125 }\note[itemize]{
126 \item mem is statefull, indicated by the 'State' type
127 \item replace and (!) are a builtin functions
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 At this stage, both operations for the ALU are defined
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