Improve presentation, based on comments.
[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 TODO: Plaatje
17 \begin{itemize}
18   \item Polymorphic, Higher-Order CPU\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 \subsection{Type Definitions}
29 \frame
30 {
31 \frametitle{Type definitions}\pause
32 TODO: Plaatje van de ALU
33 First we define some ALU types:
34 \begin{beamercolorbox}[sep=-2.5ex,rounded=true,shadow=true,vmode]{codebox}
35 \begin{code}
36 type Op a         =   a -> a -> a
37 \end{code}
38 \end{beamercolorbox}\pause
39
40 And some Register types:
41 \begin{beamercolorbox}[sep=-2.5ex,rounded=true,shadow=true,vmode]{codebox}
42 \begin{code}
43 type RegBank s a    =   Vector (s :+: D1) a
44 type RegState s a   =   State (RegBank s a)
45 \end{code}
46 \end{beamercolorbox}\pause
47 }\note[itemize]{
48 \item The first type is already polymorphic in input / output type
49 \item State has to be of the State type to be recognized as such
50 }
51
52 \subsection{Polymorphic, Higher-Order ALU}
53 \frame
54 {
55 \frametitle{Simple ALU}
56 Abstract ALU definition:
57 \begin{beamercolorbox}[sep=-2.5ex,rounded=true,shadow=true,vmode]{codebox}
58 \begin{code}
59 type Opcode         =   Bit
60 alu :: 
61   Op a -> Op a -> 
62   Opcode -> a -> a -> a
63 alu op1 op2 {-"{\color<2>[rgb]{1,0,0}"-}Low{-"}"-}    a b = op1 a b
64 alu op1 op2 {-"{\color<2>[rgb]{1,0,0}"-}High{-"}"-}   a b = op2 a b
65 \end{code}
66 \end{beamercolorbox}
67 \begin{itemize}
68 \uncover<2->{\item We support Pattern Matching}
69 \end{itemize}
70 }\note[itemize]{
71 \item Alu is both higher-order, and polymorphic
72 \item Two parameters are "compile time", others are "runtime"
73 \item We support pattern matching
74 }
75
76 \subsection{Register bank}
77 \frame
78 {
79 \frametitle{Register Bank}
80 Make a simple register bank:
81 \begin{beamercolorbox}[sep=-2.5ex,rounded=true,shadow=true,vmode]{codebox}
82 TODO: Hide type sig
83 \begin{code}
84 registerBank :: 
85   CXT((NaturalT s ,PositiveT (s :+: D1),((s :+: D1) :>: s) ~ True )) => a -> RangedWord s ->
86   RangedWord s -> Bool -> (RegState s a) -> ((RegState s a), a )
87   
88 registerBank data_in rdaddr wraddr (State mem) = 
89   ((State mem'), data_out)
90   where
91     data_out  = mem!rdaddr
92     mem'      = replace mem wraddr data_in
93 \end{code}
94 \end{beamercolorbox}
95 \begin{itemize}
96 \uncover<2->{\item We support Guards}
97 \end{itemize}
98 }\note[itemize]{
99 \item RangedWord runs from 0 to the upper bound
100 \item mem is statefull
101 \item We support guards
102 \item replace is a builtin function
103 }
104
105 \subsection{Simple CPU: ALU \& Register Bank}
106 \frame
107 {
108 \frametitle{Simple CPU}
109 Combining ALU and register bank:
110 \begin{beamercolorbox}[sep=-2.5ex,rounded=true,shadow=true,vmode]{codebox}
111 TODO: Hide Instruction type?
112 \begin{code}
113 type Instruction = (Opcode, Word, RangedWord D9, RangedWord D9) ->  RegState D9 Word ->
114 {-"{\color<2>[rgb]{1,0,0}"-}ANN(actual_cpu TopEntity){-"}"-}
115 actual_cpu :: 
116   Instruction -> RegState D9 Word -> (RegState D9 Word, Word)
117
118 actual_cpu (opc, d, rdaddr, wraddr) ram = (ram', alu_out)
119   where
120     alu_out = alu ({-"{\color<3>[rgb]{1,0,0}"-}(+){-"}"-}) ({-"{\color<3>[rgb]{1,0,0}"-}(-){-"}"-}) opc d ram_out
121     (ram',ram_out)  = registerBank alu_out rdaddr wraddr ram
122 \end{code}
123 \end{beamercolorbox}
124 \begin{itemize}
125 \uncover<2->{\item Annotation is used to indicate top-level component}
126 \end{itemize}
127 }\note[itemize]{
128 \item We use the new Annotion functionality to indicate this is the top level. TopEntity is defined by us.
129 \item the primOp and vectOp frameworks are now supplied with real functionality, the plus (+) operations
130 \item No polymorphism or higher-order stuff is allowed at this level.
131 \item Functions must be specialized, and have primitives for input and output 
132 }
133
134 %if style == newcode
135 \begin{code}
136 ANN(initstate InitState)
137 initstate :: RegState D9 Word
138 initstate = State (copy (0 :: Word))  
139   
140 ANN(program TestInput)
141 program :: [(Opcode, Word, Vector D4 Word, RangedWord D9, RangedWord D9, Bit)]
142 program =
143   [ (Low, 4, copy (0), 0, 0, High) -- Write 4 to Reg0, out = 0
144   , (Low, 3, copy (0), 0, 1, High) -- Write 3 to Reg1, out = 8
145   , (High,0, copy (3), 1, 0, Low)  -- No Write       , out = 15
146   ]
147
148 run func state [] = []
149 run func state (i:input) = o:out
150   where
151     (state', o) = func i state
152     out         = run func state' input
153     
154 main :: IO ()
155 main = do
156   let input = program
157   let istate = initstate
158   let output = run actual_cpu istate input
159   mapM_ (\x -> putStr $ ("(" P.++ (show x) P.++ ")\n")) output
160   return ()
161 \end{code}
162 %endif