Actually add bibtex entries for added references.
[matthijs/master-project/report.git] / Chapters / Prototype.tex
1 \chapter[chap:prototype]{Prototype}
2   An important step in this research is the creation of a prototype compiler.
3   Having this prototype allows us to apply the ideas from the previous chapter
4   to actual hardware descriptions and evaluate their usefulness. Having a
5   prototype also helps to find new techniques and test possible
6   interpretations.
7
8   Obviously the prototype was not created after all research
9   ideas were formed, but its implementation has been interleaved with the
10   research itself. Also, the prototype described here is the final version, it
11   has gone through a number of design iterations which we will not completely
12   describe here.
13
14   \section[sec:prototype:input]{Input language}
15     When implementing this prototype, the first question to ask is:
16     Which (functional) language will be used to describe our hardware?
17     (Note that this does not concern the \emph{implementation language}
18     of the compiler, just the language \emph{translated by} the
19     compiler).
20
21     Initially, we have two choices:
22
23     \startitemize
24       \item Create a new functional language from scratch. This has the
25       advantage of having a language that contains exactly those elements that
26       are convenient for describing hardware and can contain special
27       constructs that allows our hardware descriptions to be more powerful or
28       concise.
29       \item Use an existing language and create a new back-end for it. This has
30       the advantage that existing tools can be reused, which will speed up
31       development.
32     \stopitemize
33
34
35     \placeintermezzo{}{
36       \startframedtext[width=8cm,background=box,frame=no]
37       \startalignment[center]
38         {\tfa No \small{EDSL} or Template Haskell}
39       \stopalignment
40       \blank[medium]
41
42       Note that in this consideration, embedded domain-specific
43       languages (\small{EDSL}) and Template Haskell (\small{TH})
44       approaches have not been included. As we have seen in
45       \in{section}[sec:context:fhdls], these approaches have all kinds
46       of limitations on the description language that we would like to
47       avoid.
48       \stopframedtext
49     }
50     Considering that we required a prototype which should be working quickly,
51     and that implementing parsers, semantic checkers and especially
52     type-checkers is not exactly the Core of this research (but it is lots and
53     lots of work!), using an existing language is the obvious choice. This
54     also has the advantage that a large set of language features is available
55     to experiment with and it is easy to find which features apply well and
56     which do not. Another import advantage of using an existing language, is
57     that simulation of the code becomes trivial. Since there are existing
58     compilers and interpreters that can run the hardware description directly,
59     it can be simulated without also having to write an interpreter for the
60     new language.
61     
62     A possible second prototype could use a custom language with just the useful
63     features (and possibly extra features that are specific to
64     the domain of hardware description as well).
65
66     The second choice to be made is which of the many existing languages to use. As
67     mentioned before, the chosen language is Haskell.  This choice has not been the
68     result of a thorough comparison of languages, for the simple reason that
69     the requirements on the language were completely unclear at the start of
70     this research. The fact that Haskell is a language with a broad spectrum
71     of features, that it is commonly used in research projects and that the
72     primary compiler, \GHC, provides a high level API to its internals, made
73     Haskell an obvious choice.
74
75   \section[sec:prototype:output]{Output format}
76     The second important question is: what will be our output format?
77     This output format should at least allow for programming the
78     hardware design into a field-programmable gate array (\small{FPGA}).
79     The choice of output format is thus limited by what hardware
80     synthesis and programming tools can process.
81
82     Looking at other tools in the industry, the Electronic Design Interchange
83     Format (\small{EDIF}) is commonly used for storing intermediate
84     \emph{netlists} (lists of components and connections between these
85     components) and is commonly the target for \small{VHDL} and Verilog
86     compilers.
87
88     However, \small{EDIF} is not completely tool-independent. It specifies a
89     meta-format, but the hardware components that can be used vary between
90     various tool and hardware vendors, as well as the interpretation of the
91     \small{EDIF} standard. \cite[li89]
92    
93     This means that when working with \small{EDIF}, our prototype would become
94     technology dependent (\eg\ only work with \small{FPGA}s of a specific
95     vendor, or even only with specific chips). This limits the applicability
96     of our prototype. Also, the tools we would like to use for verifying,
97     simulating and draw pretty pictures of our output (like Precision, or
98     QuestaSim) are designed for \small{VHDL} or Verilog input.
99
100     For these reasons, we will not use \small{EDIF}, but \small{VHDL} as our
101     output language.  We choose \VHDL\ over Verilog simply because we are
102     familiar with \small{VHDL} already. The differences between \small{VHDL}
103     and Verilog are on the higher level, while we will be using \small{VHDL}
104     mainly to write low level, netlist-like descriptions anyway.
105
106     An added advantage of using VHDL is that we can profit from existing
107     optimizations in VHDL synthesizers. A lot of optimizations are done on the
108     VHDL level by existing tools. These tools have been under
109     development for years, so it would not be reasonable to assume we
110     could achieve a similar amount of optimization in our prototype (nor
111     should it be a goal, considering this is just a prototype).
112
113     \placeintermezzo{}{
114       \startframedtext[width=8cm,background=box,frame=no]
115       \startalignment[center]
116         {\tfa Translation vs. compilation vs. synthesis}
117       \stopalignment
118       \blank[medium]
119         In this thesis the words \emph{translation}, \emph{compilation} and
120         sometimes \emph{synthesis} will be used interchangeably to refer to the
121         process of translating the hardware description from the Haskell
122         language to the \VHDL\ language.
123
124         Similarly, the prototype created is referred to as both the
125         \emph{translator} as well as the \emph{compiler}.
126
127         The final part of this process is usually referred to as \emph{\VHDL\
128         generation}.
129       \stopframedtext
130     }
131
132     Note that we will be using \small{VHDL} as our output language, but will
133     not use its full expressive power. Our output will be limited to using
134     simple, structural descriptions, without any complex behavioral
135     descriptions like arbitrary sequential statements (which might not
136     be supported by all tools). This ensures that any tool that works
137     with \VHDL\ will understand our output (most tools do not support
138     synthesis of more complex \VHDL).  This also leaves open the option
139     to switch to \small{EDIF} in the future, with minimal changes to the
140     prototype.
141
142   \section{Simulation and synthesis}
143     As mentioned above, by using the Haskell language, we get simulation of
144     our hardware descriptions almost for free. The only thing that is needed
145     is to provide a Haskell implementation of all built-in functions that can
146     be used by the Haskell interpreter to simulate them.
147
148     The main topic of this thesis is therefore the path from the Haskell
149     hardware descriptions to \small{FPGA} synthesis, focusing of course on the
150     \VHDL\ generation. Since the \VHDL\ generation process preserves the meaning
151     of the Haskell description exactly, any simulation done in Haskell
152     \emph{should} produce identical results as the synthesized hardware.
153
154   \section[sec:prototype:design]{Prototype design}
155     As suggested above, we will use the Glasgow Haskell Compiler (\small{GHC}) to
156     implement our prototype compiler. To understand the design of the
157     compiler, we will first dive into the \small{GHC} compiler a bit. Its
158     compilation consists of the following steps (slightly simplified):
159
160     \startuseMPgraphic{ghc-pipeline}
161       % Create objects
162       save inp, front, desugar, simpl, back, out;
163       newEmptyBox.inp(0,0);
164       newBox.front(btex Frontend etex);
165       newBox.desugar(btex Desugarer etex);
166       newBox.simpl(btex Simplifier etex);
167       newBox.back(btex Backend etex);
168       newEmptyBox.out(0,0);
169
170       % Space the boxes evenly
171       inp.c - front.c = front.c - desugar.c = desugar.c - simpl.c 
172         = simpl.c - back.c = back.c - out.c = (0, 1.5cm);
173       out.c = origin;
174
175       % Draw lines between the boxes. We make these lines "deferred" and give
176       % them a name, so we can use ObjLabel to draw a label beside them.
177       ncline.inp(inp)(front) "name(haskell)";
178       ncline.front(front)(desugar) "name(ast)";
179       ncline.desugar(desugar)(simpl) "name(core)";
180       ncline.simpl(simpl)(back) "name(simplcore)";
181       ncline.back(back)(out) "name(native)";
182       ObjLabel.inp(btex Haskell source etex) "labpathname(haskell)", "labdir(rt)";
183       ObjLabel.front(btex Haskell AST etex) "labpathname(ast)", "labdir(rt)";
184       ObjLabel.desugar(btex Core etex) "labpathname(core)", "labdir(rt)";
185       ObjLabel.simpl(btex Simplified core etex) "labpathname(simplcore)", "labdir(rt)";
186       ObjLabel.back(btex Native code etex) "labpathname(native)", "labdir(rt)";
187
188       % Draw the objects (and deferred labels)
189       drawObj (inp, front, desugar, simpl, back, out);
190     \stopuseMPgraphic
191     \placefigure[right]{GHC compiler pipeline}{\startboxed \useMPgraphic{ghc-pipeline}\stopboxed}
192
193     \startdesc{Frontend}
194       This step takes the Haskell source files and parses them into an
195       abstract syntax tree (\small{AST}). This \small{AST} can express the
196       complete Haskell language and is thus a very complex one (in contrast
197       with the Core \small{AST}, later on). All identifiers in this
198       \small{AST} are resolved by the renamer and all types are checked by the
199       type-checker.
200     \stopdesc
201     \startdesc{Desugaring}
202       This steps takes the full \small{AST} and translates it to the
203       \emph{Core} language. Core is a very small functional language with lazy
204       semantics, that can still express everything Haskell can express. Its
205       simpleness makes Core very suitable for further simplification and
206       translation. Core is the language we will be working with as well.
207     \stopdesc
208     \startdesc{Simplification}
209       Through a number of simplification steps (such as inlining, common
210       sub-expression elimination, etc.) the Core program is simplified to make
211       it faster or easier to process further.
212     \stopdesc
213     \startdesc{Backend}
214       This step takes the simplified Core program and generates an actual
215       runnable program for it. This is a big and complicated step we will not
216       discuss it any further, since it is not required for our prototype.
217     \stopdesc
218
219     In this process, there are a number of places where we can start our work.
220     Assuming that we do not want to deal with (or modify) parsing, type-checking
221     and other front end business and that native code is not really a useful
222     format anymore, we are left with the choice between the full Haskell
223     \small{AST}, or the smaller (simplified) Core representation.
224
225     The advantage of taking the full \small{AST} is that the exact structure
226     of the source program is preserved. We can see exactly what the hardware
227     description looks like and which syntax constructs were used. However,
228     the full \small{AST} is a very complicated data-structure. If we are to
229     handle everything it offers, we will quickly get a big compiler.
230
231     Using the Core representation gives us a much more compact data-structure
232     (a Core expression only uses 9 constructors). Note that this does not mean
233     that the Core representation itself is smaller, on the contrary.
234     Since the Core language has less constructs, most Core expressions
235     are larger than the equivalent versions in Haskell.
236
237     However, the fact that the Core language is so much smaller, means it is a
238     lot easier to analyze and translate it into something else. For the same
239     reason, \small{GHC} runs its simplifications and optimizations on the Core
240     representation as well \cite[jones96].
241
242     We will use the normal Core representation, not the simplified Core. Even
243     though the simplified Core version is an equivalent, but simpler
244     definition, some problems were encountered with it in practice. The
245     simplifier restructures some (stateful) functions in a way the normalizer
246     and the \VHDL\ generation cannot handle, leading to uncompilable programs
247     (whereas the non-simplified version more closely resembles the original
248     program, allowing the original to be written in a way that can be
249     handled). This problem is further discussed in
250     \in{section}[sec:normalization:stateproblems].
251     
252     \startuseMPgraphic{clash-pipeline}
253       % Create objects
254       save inp, front, norm, vhdl, out;
255       newEmptyBox.inp(0,0);
256       newBox.front(btex \small{GHC} front-end etex);
257       newBox.norm(btex Normalization etex);
258       newBox.vhdl(btex \small{VHDL} generation etex);
259       newEmptyBox.out(0,0);
260
261       % Space the boxes evenly
262       inp.c - front.c = front.c - norm.c = norm.c - vhdl.c 
263         = vhdl.c - out.c = (0, 1.5cm);
264       out.c = origin;
265
266       % Draw lines between the boxes. We make these lines "deferred" and give
267       % them a name, so we can use ObjLabel to draw a label beside them.
268       ncline.inp(inp)(front) "name(haskell)";
269       ncline.front(front)(norm) "name(core)";
270       ncline.norm(norm)(vhdl) "name(normal)";
271       ncline.vhdl(vhdl)(out) "name(vhdl)";
272       ObjLabel.inp(btex Haskell source etex) "labpathname(haskell)", "labdir(rt)";
273       ObjLabel.front(btex Core etex) "labpathname(core)", "labdir(rt)";
274       ObjLabel.norm(btex Normalized core etex) "labpathname(normal)", "labdir(rt)";
275       ObjLabel.vhdl(btex \small{VHDL} description etex) "labpathname(vhdl)", "labdir(rt)";
276
277       % Draw the objects (and deferred labels)
278       drawObj (inp, front, norm, vhdl, out);
279     \stopuseMPgraphic
280     \placefigure[right]{Cλash compiler pipeline}{\startboxed \useMPgraphic{clash-pipeline}\stopboxed}
281
282     The final prototype roughly consists of three steps:
283
284     \page[no] % suppress page break here.
285     \startdesc{Frontend}
286       This is exactly the front-end from the \small{GHC} pipeline, that
287       translates Haskell sources to a typed Core representation.
288     \stopdesc
289     \startdesc{Normalization}
290       This is a step that transforms the Core representation into a normal
291       form. This normal form is still expressed in the Core language, but has
292       to adhere to an additional set of constraints. This normal form is less
293       expressive than the full Core language (e.g., it can have limited 
294       higher-order expressions, has a specific structure, etc.), but is
295       also very close to directly describing hardware.
296     \stopdesc
297     \startdesc{\small{VHDL} generation}
298       The last step takes the normal formed Core representation and generates
299       \small{VHDL} for it. Since the normal form has a specific, hardware-like
300       structure, this final step is very straightforward.
301     \stopdesc
302     
303     The most interesting step in this process is the normalization step. That
304     is where more complicated functional constructs, which have no direct
305     hardware interpretation, are removed and translated into hardware
306     constructs. This step is described in a lot of detail at
307     \in{chapter}[chap:normalization].
308
309     
310     \defref{entry function}Translation of a hardware description always
311     starts at a single function, which is referred to as the \emph{entry
312     function}. \VHDL\ is generated for this function first, followed by
313     any functions used by the entry functions (recursively).
314     
315   \section[sec:prototype:core]{The Core language}
316     \defreftxt{Core}{the Core language}
317     Most of the prototype deals with handling the program in the Core
318     language. In this section we will show what this language looks like and
319     how it works.
320
321     The Core language is a functional language that describes
322     \emph{expressions}. Every identifier used in Core is called a
323     \emph{binder}, since it is bound to a value somewhere. On the highest
324     level, a Core program is a collection of functions, each of which bind a
325     binder (the function name) to an expression (the function value, which has
326     a function type).
327
328     The Core language itself does not prescribe any program structure
329     (like modules, declarations, imports, etc.), only expression
330     structure. In the \small{GHC} compiler, the Haskell module structure
331     is used for the resulting Core code as well. Since this is not so
332     relevant for understanding the Core language or the Normalization
333     process, we will only look at the Core expression language here.
334
335     Each Core expression consists of one of these possible expressions.
336
337     \startdesc{Variable reference}
338       \defref{variable reference}
339       \startlambda
340       bndr :: T
341       \stoplambda
342       This is a reference to a binder. It is written down as the
343       name of the binder that is being referred to along with its type. The
344       binder name should of course be bound in a containing scope
345       (including top level scope, so a reference to a top level function
346       is also a variable reference). Additionally, constructors from
347       algebraic data-types also become variable references.
348
349       In our examples, binders will commonly consist of a single
350       characters, but they can have any length.
351
352       The value of this expression is the value bound to the given
353       binder.
354
355       Each binder also carries around its type (explicitly shown above), but
356       this is usually not shown in the Core expressions. Only when the type is
357       relevant (when a new binder is introduced, for example) will it be
358       shown. In other cases, the binder is either not relevant, or easily
359       derived from the context of the expression. \todo{Ref sidenote on type
360       annotations}
361     \stopdesc
362
363     \startdesc{Literal}
364       \defref{literal}
365       \startlambda
366       10
367       \stoplambda
368       This is a literal. Only primitive types are supported, like
369       chars, strings, integers and doubles. The types of these literals are the
370       \quote{primitive}, unboxed versions, like \lam{Char\#} and \lam{Word\#}, not the
371       normal Haskell versions (but there are built-in conversion
372       functions). Without going into detail about these types, note that
373       a few conversion functions exist to convert these to the normal
374       (boxed) Haskell equivalents.
375     \stopdesc
376
377     \startdesc{Application}
378       \defref{application}
379       \startlambda
380       func arg
381       \stoplambda
382       This is function application. Each application consists of two
383       parts: the function part and the argument part. Applications are used
384       for normal function \quote{calls}, but also for applying type
385       abstractions and data constructors.
386
387       In Core, there is no distinction between an operator and a
388       function. This means that, for example the addition of two numbers
389       looks like the following in Core:
390       
391       \startlambda
392       (+) 1 2
393       \stoplambda
394
395       Where the function \quote{\lam{(+)}} is applied to the numbers 1
396       and 2. However, to increase readability, an application of an
397       operator like \lam{(+)} is sometimes written infix. In this case,
398       the parenthesis are also left out, just like in Haskell. In other
399       words, the following means exactly the same as the addition above:
400
401       \startlambda
402       1 + 2
403       \stoplambda
404
405       The value of an application is the value of the function part, with the
406       first argument binder bound to the argument part.
407     \stopdesc
408
409     \startdesc{Lambda abstraction}
410       \defref{lambda abstraction}
411       \startlambda
412       λbndr.body
413       \stoplambda
414       This is the basic lambda abstraction, as it occurs in lambda calculus.
415       It consists of a binder part and a body part.  A lambda abstraction
416       creates a function, that can be applied to an argument. The binder is
417       usually a value binder, but it can also be a \emph{type binder} (or
418       \emph{type variable}). The latter case introduces a new polymorphic
419       variable, which can be used in types later on. See
420       \in{section}[sec:prototype:coretypes] for details.
421      
422       The body of a lambda abstraction extends all the way to the end of
423       the expression, or the closing bracket surrounding the lambda. In
424       other words, the lambda abstraction \quote{operator} has the
425       lowest priority of all.
426
427       The value of an application is the value of the body part, with the
428       binder bound to the value the entire lambda abstraction is applied to.
429     \stopdesc
430
431     \startdesc{Non-recursive let expression}
432       \defref{let expression}
433       \startlambda
434       let bndr = value in body
435       \stoplambda
436       A let expression allows you to bind a binder to some value, while
437       evaluating to some other value (for which that binder is in scope). This
438       allows for sharing of sub-expressions (you can use a binder twice) and
439       explicit \quote{naming} of arbitrary expressions. A binder is not
440       in scope in the value bound it is bound to, so it is not possible
441       to make recursive definitions with a non-recursive let expression
442       (see the recursive form below).
443
444       Even though this let expression is an extension on the basic lambda
445       calculus, it is easily translated to a lambda abstraction. The let
446       expression above would then become:
447
448       \startlambda
449       (λbndr.body) value
450       \stoplambda
451
452       This notion might be useful for verifying certain properties on
453       transformations, since a lot of verification work has been done on
454       lambda calculus already.
455
456       The value of a let expression is the value of the body part, with the
457       binder bound to the value. 
458     \stopdesc
459
460     \startdesc{Recursive let expression}
461       \startlambda
462       letrec
463         bndr1 = value1
464         \vdots
465         bndrn = valuen
466       in 
467         body
468       \stoplambda
469       This is the recursive version of the let expression. In \small{GHC}'s
470       Core implementation, non-recursive and recursive lets are not so
471       distinct as we present them here, but this provides a clearer overview.
472       
473       The main difference with the normal let expression is that it can
474       contain multiple bindings (or even none) and each of the binders
475       is in scope in each of the values, in addition to the body. This
476       allows for self-recursive or mutually recursive definitions.
477
478       It is also possible to express a recursive let expression using
479       normal lambda calculus, if we use the \emph{least fixed-point
480       operator}, \lam{Y} (but the details are too complicated to help
481       clarify the let expression, so this will not be explored further).
482     \stopdesc
483
484     \placeintermezzo{}{
485       \startframedtext[width=8cm,background=box,frame=no]
486       \startalignment[center]
487         {\tfa Weak head normal form (\small{WHNF})}
488       \stopalignment
489       \blank[medium]
490         An expression is in weak head normal form if it is either an
491         constructor application or lambda abstraction. \cite[jones87]
492
493         Without going into detail about the differences with head
494         normal form and normal form, note that evaluating the scrutinee
495         of a case expression to normal form (evaluating any function
496         applications, variable references and case expressions) is
497         sufficient to decide which case alternatives should be chosen.
498         \todo{ref?}
499       \stopframedtext
500
501     }
502
503     \startdesc{Case expression}
504       \defref{case expression}
505       \startlambda
506         case scrutinee of bndr
507           DEFAULT -> defaultbody
508           C0 bndr0,0 ... bndr0,m -> body0
509           \vdots
510           Cn bndrn,0 ... bndrn,m -> bodyn
511       \stoplambda
512
513       A case expression is the only way in Core to choose between values. All
514       \hs{if} expressions and pattern matchings from the original Haskell
515       program have been translated to case expressions by the desugarer. 
516       
517       A case expression evaluates its scrutinee, which should have an
518       algebraic datatype, into weak head normal form (\small{WHNF}) and
519       (optionally) binds it to \lam{bndr}. If bndr is wild, \refdef{wild
520       binders} it is left out.  Every alternative lists a single constructor
521       (\lam{C0 ... Cn}). Based on the actual constructor of the scrutinee, the
522       corresponding alternative is chosen. The binders in the chosen
523       alternative (\lam{bndr0,0 ....  bndr0,m} are bound to the actual
524       arguments to the constructor in the scrutinee.
525
526       This is best illustrated with an example. Assume
527       there is an algebraic datatype declared as follows\footnote{This
528       datatype is not supported by the current Cλash implementation, but
529       serves well to illustrate the case expression}:
530
531       \starthaskell
532       data D = A Word | B Bit
533       \stophaskell
534
535       This is an algebraic datatype with two constructors, each getting
536       a single argument. A case expression scrutinizing this datatype
537       could look like the following:
538
539       \startlambda
540         case s of
541           A word -> High
542           B bit -> bit
543       \stoplambda
544
545       What this expression does is check the constructor of the
546       scrutinee \lam{s}. If it is \lam{A}, it always evaluates to
547       \lam{High}. If the constructor is \lam{B}, the binder \lam{bit} is
548       bound to the argument passed to \lam{B} and the case expression
549       evaluates to this bit.
550       
551       If none of the alternatives match, the \lam{DEFAULT} alternative
552       is chosen. A case expression must always be exhaustive, \ie\ it
553       must cover all possible constructors that the scrutinee can have
554       (if all of them are covered explicitly, the \lam{DEFAULT}
555       alternative can be left out).
556       
557       Since we can only match the top level constructor, there can be no overlap
558       in the alternatives and thus order of alternatives is not relevant (though
559       the \lam{DEFAULT} alternative must appear first for implementation
560       efficiency).
561       
562       To support strictness, the scrutinee is always evaluated into
563       \small{WHNF}, even when there is only a \lam{DEFAULT} alternative. This
564       allows application of the strict function \lam{f} to the argument \lam{a}
565       to be written like:
566
567       \startlambda
568       f (case a of arg DEFAULT -> arg)
569       \stoplambda
570
571       According to the \GHC\ documentation, this is the only use for the extra
572       binder to which the scrutinee is bound.  When not using strictness
573       annotations (which is rather pointless in hardware descriptions),
574       \small{GHC} seems to never generate any code making use of this binder.
575       In fact, \GHC\ has never been observed to generate code using this
576       binder, even when strictness was involved.  Nonetheless, the prototype
577       handles this binder as expected.
578
579       Note that these case expressions are less powerful than the full Haskell
580       case expressions. In particular, they do not support complex patterns like
581       in Haskell. Only the constructor of an expression can be matched,
582       complex patterns are implemented using multiple nested case expressions.
583
584       Case expressions are also used for unpacking of algebraic data-types, even
585       when there is only a single constructor. For examples, to add the elements
586       of a tuple, the following Core is generated:
587
588       \startlambda
589       sum = λtuple.case tuple of
590         (,) a b -> a + b
591       \stoplambda
592     
593       Here, there is only a single alternative (but no \lam{DEFAULT}
594       alternative, since the single alternative is already exhaustive). When
595       its body is evaluated, the arguments to the tuple constructor \lam{(,)}
596       (\eg, the elements of the tuple) are bound to \lam{a} and \lam{b}.
597     \stopdesc
598
599     \startdesc{Cast expression}
600       \defref{cast expression}
601       \startlambda
602       body ▶ targettype
603       \stoplambda
604       A cast expression allows you to change the type of an expression to an
605       equivalent type. Note that this is not meant to do any actual work, like
606       conversion of data from one format to another, or force a complete type
607       change. Instead, it is meant to change between different representations
608       of the same type, \eg\ switch between types that are provably equal (but
609       look different).
610       
611       In our hardware descriptions, we typically see casts to change between a
612       Haskell newtype and its contained type, since those are effectively
613       different types (so a cast is needed) with the same representation (but
614       no work is done by the cast).
615
616       More complex are types that are proven to be equal by the type-checker,
617       but look different at first glance. To ensure that, once the type-checker
618       has proven equality, this information sticks around, explicit casts are
619       added. In our notation we only write the target type, but in reality a
620       cast expressions carries around a \emph{coercion}, which can be seen as a
621       proof of equality. \todo{Example}
622
623       The value of a cast is the value of its body, unchanged. The type of this
624       value is equal to the target type, not the type of its body.
625     \stopdesc
626
627     \startdesc{Note}
628       The Core language in \small{GHC} allows adding \emph{notes}, which serve
629       as hints to the inliner or add custom (string) annotations to a Core
630       expression. These should not be generated normally, so these are not
631       handled in any way in the prototype.
632     \stopdesc
633
634     \startdesc{Type}
635       \defref{type expression}
636       \startlambda
637       @T
638       \stoplambda
639       It is possibly to use a Core type as a Core expression. To prevent
640       confusion between types and values, the \lam{@} sign is used to
641       explicitly mark a type that is used in a Core expression.
642       
643       For the actual types supported by Core, see
644       \in{section}[sec:prototype:coretypes]. This \quote{lifting} of a
645       type into the value domain is done to allow for type abstractions
646       and applications to be handled as normal lambda abstractions and
647       applications above. This means that a type expression in Core can
648       only ever occur in the argument position of an application, and
649       only if the type of the function that is applied to expects a type
650       as the first argument. This happens in applications of all
651       polymorphic functions. Consider the \lam{fst} function:
652
653       \startlambda
654       fst :: \forall t1. \forall t2. (t1, t2) ->t1 
655       fst = λt1.λt2.λ(tup :: (t1, t2)). case tup of (,) a b -> a
656
657       fstint :: (Int, Int) -> Int
658       fstint = λa.λb.fst @Int @Int a b
659       \stoplambda
660           
661       The type of \lam{fst} has two universally quantified type variables. When
662       \lam{fst} is applied in \lam{fstint}, it is first applied to two types.
663       (which are substituted for \lam{t1} and \lam{t2} in the type of \lam{fst}, so
664       the actual type of arguments and result of \lam{fst} can be found:
665       \lam{fst @Int @Int :: (Int, Int) -> Int}).
666     \stopdesc
667
668     \subsection[sec:prototype:coretypes]{Core type system}
669       Whereas the expression syntax of Core is very simple, its type system is
670       a bit more complicated. It turns out it is harder to \quote{desugar}
671       Haskell's complex type system into something more simple. Most of the
672       type system is thus very similar to that of Haskell.
673
674       We will slightly limit our view on Core's type system, since the more
675       complicated parts of it are only meant to support Haskell's (or rather,
676       \GHC's) type extensions, such as existential types, \small{GADT}s, type
677       families and other non-standard Haskell stuff which we do not (plan to)
678       support.
679
680       \placeintermezzo{}{
681         \defref{id function}
682         \startframedtext[width=8cm,background=box,frame=no]
683         \startalignment[center]
684           {\tfa The \hs{id} function}
685         \stopalignment
686         \blank[medium]
687           A function that is probably present in every functional language, is
688           the \emph{identity} function. This is the function that takes a
689           single argument and simply returns it unmodified. In Haskell this
690           function is called \hs{id} and can take an argument of any type
691           (\ie, it is polymorphic).
692
693           The \hs{id} function will be used in the examples every now and
694           then.
695         \stopframedtext
696       }
697       In Core, every expression is typed. The translation to Core happens
698       after the type-checker, so types in Core are always correct as well
699       (though you could of course construct invalidly typed expressions
700       through the \GHC\ API).
701
702       Any type in Core is one of the following:
703
704       \startdesc{A type variable}
705         \startlambda
706         t
707         \stoplambda
708
709         This is a reference to a type defined elsewhere. This can either be a
710         polymorphic type (like the latter two \lam{t}'s in \lam{id :: \forall t.
711         t -> t}), or a type constructor (like \lam{Bool} in \lam{not :: Bool ->
712         Bool}). Like in Haskell, polymorphic type variables always
713         start with a lowercase letter, while type constructors always start
714         with an uppercase letter.
715
716         \todo{How to define (new) type constructors?}
717
718         A special case of a type constructor is the \emph{function type
719         constructor}, \lam{->}. This is a type constructor taking two arguments
720         (using application below). The function type constructor is commonly
721         written inline, so we write \lam{a -> b} when we really mean \lam{-> a
722         b}, the function type constructor applied to \lam{a} and \lam{b}.
723
724         Polymorphic type variables can only be defined by a lambda
725         abstraction, see the forall type below.
726       \stopdesc
727
728       \startdesc{A type application}
729         \startlambda
730           Maybe Int
731         \stoplambda
732
733         This applies some type to another type. This is particularly used to
734         apply type variables (type constructors) to their arguments.
735
736         As mentioned above, applications of some type constructors have
737         special notation. In particular, these are applications of the
738         \emph{function type constructor} and \emph{tuple type constructors}:
739         \startlambda
740           foo :: t1 -> t2 
741           foo' :: -> t1 t2 
742           bar :: (t1, t2, t3)
743           bar' :: (,,) t1 t2 t3
744         \stoplambda
745       \stopdesc
746
747       \startdesc{The forall type}
748         \startlambda
749           id :: \forall t. t -> t
750         \stoplambda
751         The forall type introduces polymorphism. It is the only way to
752         introduce new type variables, which are completely unconstrained (Any
753         possible type can be assigned to it). Constraints can be added later
754         using predicate types, see below.
755
756         A forall type is always (and only) introduced by a type lambda
757         expression. For example, the Core translation of the
758         id function is:
759         \startlambda
760           id = λt.λ(x :: t).x
761         \stoplambda
762
763         Here, the type of the binder \lam{x} is \lam{t}, referring to the
764         binder in the topmost lambda.
765
766         When using a value with a forall type, the actual type
767         used must be applied first. For example Haskell expression \hs{id
768         True} (the function \hs{id} applied to the data-constructor \hs{True})
769         translates to the following Core:
770
771         \startlambda
772         id @Bool True
773         \stoplambda
774
775         Here, id is first applied to the type to work with. Note that the type
776         then changes from \lam{id :: \forall t. t -> t} to \lam{id @Bool ::
777         Bool -> Bool}. Note that the type variable \lam{a} has been
778         substituted with the actual type.
779
780         In Haskell, forall types are usually not explicitly specified (The use
781         of a lowercase type variable implicitly introduces a forall type for
782         that variable). In fact, in standard Haskell there is no way to
783         explicitly specify forall types. Through a language extension, the
784         \hs{forall} keyword is available, but still optional for normal forall
785         types (it is needed for \emph{existentially quantified types}, which
786         Cλash does not support).
787       \stopdesc
788
789       \startdesc{Predicate type}
790         \startlambda
791           show :: \forall t. Show t ⇒ t → String
792         \stoplambda
793        
794         \todo{Sidenote: type classes?}
795
796         A predicate type introduces a constraint on a type variable introduced
797         by a forall type (or type lambda). In the example above, the type
798         variable \lam{t} can only contain types that are an \emph{instance} of
799         the \emph{type class} \lam{Show}.
800
801         There are other sorts of predicate types, used for the type families
802         extension, which we will not discuss here.
803
804         A predicate type is introduced by a lambda abstraction. Unlike with
805         the forall type, this is a value lambda abstraction, that must be
806         applied to a value. We call this value a \emph{dictionary}.
807
808         Without going into the implementation details, a dictionary can be
809         seen as a lookup table all the methods for a given (single) type class
810         instance. This means that all the dictionaries for the same type class
811         look the same (\eg\ contain methods with the same names). However,
812         dictionaries for different instances of the same class contain
813         different methods, of course.
814
815         A dictionary is introduced by \small{GHC} whenever it encounters an
816         instance declaration. This dictionary, as well as the binder
817         introduced by a lambda that introduces a dictionary, have the
818         predicate type as their type. These binders are usually named starting
819         with a \lam{\$}. Usually the name of the type concerned is not
820         reflected in the name of the dictionary, but the name of the type
821         class is. The Haskell expression \hs{show True} thus becomes:
822
823         \startlambda
824         show @Bool \$dShow True
825         \stoplambda
826       \stopdesc
827
828       Using this set of types, all types in basic Haskell can be represented.
829       \todo{Overview of polymorphism with more examples (or move examples
830       here)}
831         
832   \section[sec:prototype:statetype]{State annotations in Haskell}
833     As noted in \in{section}[sec:description:stateann], Cλash needs some
834     way to let the programmer explicitly specify which of a function's
835     arguments and which part of a function's result represent the
836     function's state.
837
838     Using the Haskell type systems, there are a few ways we can tackle this.
839
840     \subsection{Type synonyms}
841       Haskell provides type synonyms as a way to declare a new type that is
842       equal to an existing type (or rather, a new name for an existing type).
843       This allows both the original type and the synonym to be used
844       interchangeably in a Haskell program. This means no explicit conversion
845       is needed. For example, a simple accumulator would become:
846
847       \starthaskell
848       -- This type synonym would become part of Cλash, it is shown here
849       -- just for clarity.
850       type State s = s
851
852       acc :: Word -> State Word -> (State Word, Word)
853       acc i s = let sum = s + i in (sum, sum)
854       \stophaskell
855
856       This looks nice in Haskell, but turns out to be hard to implement. There
857       is no explicit conversion in Haskell, but not in Core either. This
858       means the type of a value might be shown as \hs{State Word} in
859       some places, but \hs{Word} in others (and this can even change due
860       to transformations). Since every binder has an explicit type
861       associated with it, the type of every function type will be
862       properly preserved and could be used to track down the
863       statefulness of each value by the compiler. However, this would make
864       the implementation a lot more complicated than when using type
865       renamings as described in the next section.
866
867     % Use \type instead of \hs here, since the latter breaks inside
868     % section headings.
869     \subsection{Type renaming (\type{newtype})}
870       Haskell also supports type renamings as a way to declare a new type that
871       has the same (run-time) representation as an existing type (but is in
872       fact a different type to the type-checker). With type renaming,
873       explicit conversion between values of the two types is needed. The
874       accumulator would then become:
875
876       \starthaskell
877       -- This type renaming would become part of Cλash, it is shown here
878       -- just for clarity.
879       newtype State s = State s
880
881       acc :: Word -> State Word -> (State Word, Word)
882       acc i (State s) = let sum = s + i in (State sum, sum)
883       \stophaskell
884
885       The \hs{newtype} line declares a new type \hs{State} that has one type
886       argument, \hs{s}. This type contains one \quote{constructor} \hs{State}
887       with a single argument of type \hs{s}. It is customary to name the
888       constructor the same as the type, which is allowed (since types can
889       never cause name collisions with values). The difference with the type
890       synonym example is in the explicit conversion between the \hs{State
891       Word} and \hs{Word} types by pattern matching and by using the explicit
892       the \hs{State} constructor.
893
894       This explicit conversion makes the \VHDL\ generation easier: whenever we
895       remove (unpack) the \hs{State} type, this means we are accessing the
896       current state (\ie, accessing the register output). Whenever we are
897       adding (packing) the \hs{State} type, we are producing a new value for
898       the state (\ie, providing the register input).
899
900       When dealing with nested states (a stateful function that calls stateful
901       functions, which might call stateful functions, etc.) the state type
902       could quickly grow complex because of all the \hs{State} type constructors
903       needed. For example, consider the following state type (this is just the
904       state type, not the entire function type):
905
906       \starthaskell
907       State (State Bit, State (State Word, Bit), Word)
908       \stophaskell
909
910       We cannot leave all these \hs{State} type constructors out, since that
911       would change the type (unlike when using type synonyms). However, when
912       using type synonyms to hide away sub-states (see
913       \in{section}[sec:prototype:sub-statesynonyms] below), this
914       disadvantage should be limited.
915
916       \subsubsection{Different input and output types}
917         An alternative could be to use different types for input and output
918         state (\ie\ current and updated state). The accumulator example would
919         then become something like:
920
921         \starthaskell
922         -- These type renamings would become part of Cλash, it is shown
923         -- here just for clarity.
924         newtype StateIn s = StateIn s
925         newtype StateOut s = StateOut s
926
927         acc :: Word -> StateIn Word -> (StateIn Word, Word)
928         acc i (StateIn s) = let sum = s + i in (StateIn sum, sum)
929         \stophaskell
930         
931         This could make the implementation easier and the hardware
932         descriptions less error-prone (you can no longer \quote{forget} to
933         unpack and repack a state variable and just return it directly, which
934         can be a problem in the current prototype). However, it also means we
935         need twice as many type synonyms to hide away sub-states, making this
936         approach a bit cumbersome. It also makes it harder to compare input
937         and output state types, possible reducing the type-safety of the
938         descriptions.
939
940     \subsection[sec:prototype:sub-statesynonyms]{Type synonyms for sub-states}
941       As noted above, when using nested (hierarchical) states, the state types
942       of the \quote{upper} functions (those that call other functions, which
943       call other functions, etc.) quickly become complicated. Also, when the
944       state type of one of the \quote{lower} functions changes, the state
945       types of all the upper functions changes as well. If the state type for
946       each function is explicitly and completely specified, this means that a
947       lot of code needs updating whenever a state type changes.
948
949       To prevent this, it is recommended (but not enforced) to use a type
950       synonym for the state type of every function. Every function calling
951       other functions will then use the state type synonym of the called
952       functions in its own type, requiring no code changes when the state type
953       of a called function changes. This approach is used in
954       \in{example}[ex:AvgState] below. The \hs{AccState} and \hs{AvgState}
955       are examples of such state type synonyms.
956
957     \subsection{Chosen approach}
958       To keep implementation simple, the current prototype uses the type
959       renaming approach, with a single type for both input and output
960       states. In the future, it might be worthwhile to revisit this
961       approach if more complicated flow analysis is implemented for
962       state variables. This analysis is needed to add proper error
963       checking anyway and might allow the use of type synonyms without
964       losing any expressivity.
965
966       \subsubsection{Example}
967         As an example of the used approach, a simple averaging circuit
968         is shown in \in{example}[ex:AvgState]. This circuit lets the
969         accumulation of the inputs be done by a sub-component, \hs{acc},
970         but keeps a count of value accumulated in its own
971         state.\footnote{Currently, the prototype is not able to compile
972         this example, since there is no built-in function for division.}
973         
974         \startbuffer[AvgState]
975           -- This type renaming would become part of Cλash, it is shown
976           -- here just for clarity
977           newtype State s = State s
978
979           -- The accumulator state type
980           type AccState = State Word
981           -- The accumulator
982           acc :: Word -> AccState -> (AccState, Word)
983           acc i (State s) = let sum = s + i in (State sum, sum)
984
985           -- The averaging circuit state type
986           type AvgState = State (AccState, Word)
987           -- The averaging circuit
988           avg :: Word -> AvgState -> (AvgState, Word)
989           avg i (State s) = (State s', o)
990             where
991               (accs, count) = s
992               -- Pass our input through the accumulator, which outputs a sum
993               (accs', sum) = acc i accs
994               -- Increment the count (which will be our new state)
995               count' = count + 1
996               -- Compute the average
997               o = sum / count'
998               s' = (accs', count')
999         \stopbuffer
1000
1001         \placeexample[here][ex:AvgState]{Simple stateful averaging circuit.}
1002           %\startcombination[2*1]
1003             {\typebufferhs{AvgState}}%{Haskell description using function applications.}
1004           %  {\boxedgraphic{AvgState}}{The architecture described by the Haskell description.}
1005           %\stopcombination
1006         \todo{Picture}
1007
1008   \section{\VHDL\ generation for state}  
1009     Now its clear how to put state annotations in the Haskell source,
1010     there is the question of how to implement this state translation. As
1011     we have seen in \in{section}[sec:prototype:design], the translation to
1012     \VHDL\ happens as a simple, final step in the compilation process.
1013     This step works on a Core expression in normal form. The specifics
1014     of normal form will be explained in
1015     \in{chapter}[chap:normalization], but the examples given should be
1016     easy to understand using the definition of Core given above. The
1017     conversion to and from the \hs{State} type is done using the cast
1018     operator, \lam{▶}.
1019
1020         \startbuffer[AvgStateNormal]
1021           acc = λi.λspacked.
1022             let
1023               -- Remove the State newtype
1024               s = spacked ▶ Word
1025               sum = s + i
1026               -- Add the State newtype again
1027               spacked' = sum ▶ State Word
1028               res = (spacked', sum)
1029             in
1030               res
1031
1032           avg = λi.λspacked.
1033             let
1034               s = spacked ▶ (AccState, Word)
1035               accs = case s of (a, b) -> a
1036               count = case s of (c, d) -> d
1037               accres = acc i accs
1038               accs' = case accres of (e, f) -> e
1039               sum = case accres of (g, h) -> h
1040               count' = count + 1
1041               o = sum / count'
1042               s' = (accs', count')
1043               spacked' = s' ▶ State (AccState, Word)
1044               res = (spacked', o)
1045             in
1046               res
1047         \stopbuffer
1048
1049         \placeexample[here][ex:AvgStateNormal]{Normalized version of \in{example}[ex:AvgState]}
1050             {\typebufferlam{AvgStateNormal}}
1051
1052     \subsection[sec:prototype:statelimits]{State in normal form}
1053       Before describing how to translate state from normal form to
1054       \VHDL, we will first see how state handling looks in normal form.
1055       How must their use be limited to guarantee that proper \VHDL\ can
1056       be generated?
1057
1058       We will formulate a number of rules about what operations are
1059       allowed with state variables. These rules apply to the normalized Core
1060       representation, but will in practice apply to the original Haskell
1061       hardware description as well. Ideally, these rules would become part
1062       of the intended normal form definition \refdef{intended normal form
1063       definition}, but this is not the case right now. This can cause some
1064       problems, which are detailed in
1065       \in{section}[sec:normalization:stateproblems].
1066
1067       In these rules we use the terms \emph{state variable} to refer to any
1068       variable that has a \lam{State} type. A \emph{state-containing
1069       variable} is any variable whose type contains a \lam{State} type,
1070       but is not one itself (like \lam{(AccState, Word)} in the example,
1071       which is a tuple type, but contains \lam{AccState}, which is again
1072       equal to \lam{State Word}).
1073
1074       We also use a distinction between \emph{input} and \emph{output
1075       (state) variables} and \emph{sub-state variables}, which will be
1076       defined in the rules themselves.
1077
1078       These rules describe everything that can be done with state
1079       variables and state-containing variables. Everything else is
1080       invalid. For every rule, the corresponding part of
1081       \in{example}[ex:AvgStateNormal] is shown.
1082
1083       \startdesc{State variables can appear as an argument.}
1084         \startlambda
1085           avg = λi.λspacked. ...
1086         \stoplambda
1087
1088         Any lambda that binds a variable with a state type, creates a new
1089         input state variable.
1090       \stopdesc
1091
1092       \startdesc{Input state variables can be unpacked.}
1093         \startlambda
1094           s = spacked ▶ (AccState, Word)
1095         \stoplambda
1096
1097         An input state variable may be unpacked using a cast operation. This
1098         removes the \lam{State} type renaming and the result has no longer a
1099         \lam{State} type.
1100
1101         If the result of this unpacking does not have a state type and does
1102         not contain state variables, there are no limitations on its
1103         use (this is the function's own state).  Otherwise if it does
1104         not have a state type but does contain sub-states, we refer to it
1105         as a \emph{state-containing input variable} and the limitations
1106         below apply. If it has a state type itself, we refer to it as an
1107         \emph{input sub-state variable} and the below limitations apply
1108         as well.
1109
1110         It may seem strange to consider a variable that still has a state
1111         type directly after unpacking, but consider the case where a
1112         function does not have any state of its own, but does call a single
1113         stateful function. This means it must have a state argument that
1114         contains just a sub-state. The function signature of such a function
1115         could look like:
1116
1117         \starthaskell
1118           type FooState = State AccState
1119         \stophaskell
1120
1121         Which is of course equivalent to \lam{State (State Word)}.
1122       \stopdesc
1123
1124       \startdesc{Variables can be extracted from state-containing input variables.}
1125         \startlambda
1126           accs = case s of (a, b) -> a
1127         \stoplambda
1128
1129         A state-containing input variable is typically a tuple containing
1130         multiple elements (like the current function's state, sub-states or
1131         more tuples containing sub-states). All of these can be extracted
1132         from an input variable using an extractor case (or possibly
1133         multiple, when the input variable is nested).
1134
1135         If the result has no state type and does not contain any state
1136         variables either, there are no further limitations on its use
1137         (this is the function's own state). If the result has no state
1138         type but does contain state variables we refer to it as a
1139         \emph{state-containing input variable} and this limitation keeps
1140         applying. If the variable has a state type itself, we refer to
1141         it as an \emph{input sub-state variable} and below limitations
1142         apply.
1143
1144       \startdesc{Input sub-state variables can be passed to functions.} 
1145         \startlambda
1146           accres = acc i accs
1147           accs' = case accres of (e, f) -> e
1148         \stoplambda
1149         
1150         An input sub-state variable can (only) be passed to a function.
1151         Additionally, every input sub-state variable must be used in exactly
1152         \emph{one} application, no more and no less.
1153
1154         The function result should contain exactly one state variable, which
1155         can be extracted using (multiple) case expressions. The extracted
1156         state variable is referred to the \emph{output sub-state}
1157
1158         The type of this output sub-state must be identical to the type of
1159         the input sub-state passed to the function.
1160       \stopdesc
1161
1162       \startdesc{Variables can be inserted into a state-containing output variable.}
1163         \startlambda
1164           s' = (accs', count')
1165         \stoplambda
1166         
1167         A function's output state is usually a tuple containing its own
1168         updated state variables and all output sub-states. This result is
1169         built up using any single-constructor algebraic datatype
1170         (possibly nested).
1171
1172         The result of these expressions is referred to as a
1173         \emph{state-containing output variable}, which are subject to these
1174         limitations.
1175       \stopdesc
1176
1177       \startdesc{State containing output variables can be packed.}
1178         \startlambda
1179           spacked' = s' ▶ State (AccState, Word)
1180         \stoplambda
1181
1182         As soon as all a functions own update state and output sub-state
1183         variables have been joined together, the resulting
1184         state-containing output variable can be packed into an output
1185         state variable. Packing is done by casting to a state type.
1186       \stopdesc
1187
1188       \startdesc{Output state variables can appear as (part of) a function result.}
1189         \startlambda
1190           avg = λi.λspacked.
1191             let
1192             \vdots
1193             res = (spacked', o)
1194           in
1195             res
1196         \stoplambda
1197         When the output state is packed, it can be returned as a part
1198         of the function result. Nothing else can be done with this
1199         value (or any value that contains it).
1200       \stopdesc
1201
1202       There is one final limitation that is hard to express in the above
1203       itemization. Whenever sub-states are extracted from the input state
1204       to be passed to functions, the corresponding output sub-states
1205       should be inserted into the output state in the same way. In other
1206       words, each pair of corresponding sub-states in the input and
1207       output states should be passed to / returned from the same called
1208       function.
1209
1210       The prototype currently does not check much of the above
1211       conditions. This means that if the conditions are violated,
1212       sometimes a compile error is generated, but in other cases output
1213       can be generated that is not valid \VHDL\ or at the very least does
1214       not correspond to the input.
1215
1216     \subsection{Translating to \VHDL}
1217       As noted above, the basic approach when generating \VHDL\ for stateful
1218       functions is to generate a single register for every stateful function.
1219       We look around the normal form to find the let binding that removes the
1220       \lam{State} type renaming (using a cast). We also find the let binding that
1221       adds a \lam{State} type. These are connected to the output and the input
1222       of the generated let binding respectively. This means that there can
1223       only be one let binding that adds and one that removes the \lam{State}
1224       type. It is easy to violate this constraint. This problem is detailed in
1225       \in{section}[sec:normalization:stateproblems].
1226
1227       This approach seems simple enough, but will this also work for more
1228       complex stateful functions involving sub-states?  Observe that any
1229       component of a function's state that is a sub-state, \ie\ passed on as
1230       the state of another function, should have no influence on the
1231       hardware generated for the calling function. Any state-specific
1232       \small{VHDL} for this component can be generated entirely within the
1233       called function.  So, we can completely ignore sub-states when
1234       generating \VHDL\ for a function.
1235       
1236       From this observation it might seem logical to remove the
1237       sub-states from a function's states altogether and leave only the
1238       state components which are actual states of the current function.
1239       While doing this would not remove any information needed to
1240       generate \small{VHDL} from the function, it would cause the
1241       function definition to become invalid (since we will not have any
1242       sub-state to pass to the functions anymore).  We could solve the
1243       syntactic problems by passing \type{undefined} for state
1244       variables, but that would still break the code on the semantic
1245       level (\ie, the function would no longer be semantically
1246       equivalent to the original input).
1247
1248       To keep the function definition correct until the very end of the
1249       process, we will not deal with (sub)states until we get to the
1250       \small{VHDL} generation.  Then, we are translating from Core to
1251       \small{VHDL}, and we can simply generate no \VHDL for sub-states,
1252       effectively removing them altogether.
1253
1254       But, how will we know what exactly is a sub-state? Since any state
1255       argument or return value that represents state must be of the
1256       \type{State} type, we can look at the type of a value. However, we
1257       must be careful to ignore only \emph{sub-states}, and not a
1258       function's own state.
1259
1260       For \in{example}[ex:AvgStateNormal] above, we should generate a register
1261       with its output connected to \lam{s} and its input connected
1262       to \lam{s'}. However, \lam{s'} is build up from both \lam{accs'} and
1263       \lam{count'}, while only \lam{count'} should end up in the register.
1264       \lam{accs'} is a sub-state for the \lam{acc} function, for which a
1265       register will be created when generating \VHDL\ for the \lam{acc}
1266       function.
1267
1268       Fortunately, the \lam{accs'} variable (and any other sub-state) has a
1269       property that we can easily check: it has a \lam{State} type. This
1270       means that whenever \VHDL\ is generated for a tuple (or other
1271       algebraic type), we can simply leave out all elements that have a
1272       \lam{State} type. This will leave just the parts of the state that
1273       do not have a \lam{State} type themselves, like \lam{count'},
1274       which is exactly a function's own state. This approach also means
1275       that the state part of the result (\eg\ \lam{s'} in \lam{res}) is
1276       automatically excluded when generating the output port, which is
1277       also required.
1278
1279       We can formalize this translation a bit, using the following
1280       rules.
1281
1282       \startitemize
1283         \item A state unpack operation should not generate any \small{VHDL}.
1284         The binder to which the unpacked state is bound should still be
1285         declared, this signal will become the register and will hold the
1286         current state.
1287         \item A state pack operation should not generate any \small{VHDL}.
1288         The binder to which the packed state is bound should not be
1289         declared. The binder that is packed is the signal that will hold the
1290         new state.
1291         \item Any values of a State type should not be translated to
1292         \small{VHDL}. In particular, State elements should be removed from
1293         tuples (and other data-types) and arguments with a state type should
1294         not generate ports.
1295         \item To make the state actually work, a simple \small{VHDL}
1296         (sequential) process should be generated. This process updates
1297         the state at every clock cycle, by assigning the new state to the
1298         current state. This will be recognized by synthesis tools as a
1299         register specification.
1300       \stopitemize
1301
1302       When applying these rules to the function \lam{avg} from
1303       \in{example}[ex:AvgStateNormal], we be left with the description
1304       in \in{example}[ex:AvgStateRemoved]. All the parts that do not
1305       generate any \VHDL\ directly are crossed out, leaving just the
1306       actual flow of values in the final hardware. To illustrate the
1307       change of the types of \lam{s} and \lam{s'}, their types are also
1308       shown.
1309       
1310       \startbuffer[AvgStateRemoved]
1311         avg = iλ.λ--spacked.--
1312           let 
1313             s :: (--AccState,-- Word)
1314             s = --spacked ▶ (AccState, Word)--
1315             --accs = case s of (a, b) -> a--
1316             count = case s of (--c,-- d) -> d
1317             accres = acc i --accs--
1318             --accs' = case accres of (e, f) -> e--
1319             sum = case accres of (--g,-- h) -> h
1320             count' = count + 1
1321             o = sum / count'
1322             s' :: (--AccState,-- Word)
1323             s' = (--accs',-- count')
1324             --spacked' = s' ▶ State (AccState, Word)--
1325             res = (--spacked',-- o)
1326           in
1327             res
1328       \stopbuffer
1329       \placeexample[here][ex:AvgStateRemoved]{Normalized version of \in{example}[ex:AvgState] with ignored parts crossed out}
1330           {\typebufferlam{AvgStateRemoved}}
1331               
1332       When we actually leave out the crossed out parts, we get a slightly
1333       weird program: there is a variable \lam{s} which has no value, and there
1334       is a variable \lam{s'} that is never used. But together, these two will form
1335       the state process of the function. \lam{s} contains the "current" state,
1336       \lam{s'} is assigned the "next" state. So, at the end of each clock
1337       cycle, \lam{s'} should be assigned to \lam{s}.
1338
1339       As an illustration of the result of this function,
1340       \in{example}[ex:AccStateVHDL] and \in{example}[ex:AvgStateVHDL] show the the \VHDL\ that is
1341       generated by Cλash from the examples is this section.
1342
1343       \startbuffer[AvgStateVHDL]
1344         entity avgComponent_0 is
1345              port (\izAlE2\ : in \unsigned_31\;
1346                    \foozAo1zAo12\ : out \(,)unsigned_31\;
1347                    clock : in std_logic;
1348                    resetn : in std_logic);
1349         end entity avgComponent_0;
1350
1351
1352         architecture structural of avgComponent_0 is
1353              signal \szAlG2\ : \(,)unsigned_31\;
1354              signal \countzAlW2\ : \unsigned_31\;
1355              signal \dszAm62\ : \(,)unsigned_31\;
1356              signal \sumzAmk3\ : \unsigned_31\;
1357              signal \reszAnCzAnM2\ : \unsigned_31\;
1358              signal \foozAnZzAnZ2\ : \unsigned_31\;
1359              signal \reszAnfzAnj3\ : \unsigned_31\;
1360              signal \s'zAmC2\ : \(,)unsigned_31\;
1361         begin
1362              \countzAlW2\ <= \szAlG2\.A;
1363
1364              \comp_ins_dszAm62\ : entity accComponent_1
1365                                        port map (\izAob3\ => \izAlE2\,
1366                                                  \foozAoBzAoB2\ => \dszAm62\,
1367                                                  clock => clock,
1368                                                  resetn => resetn);
1369
1370              \sumzAmk3\ <= \dszAm62\.A;
1371
1372              \reszAnCzAnM2\ <= to_unsigned(1, 32);
1373
1374              \foozAnZzAnZ2\ <= \countzAlW2\ + \reszAnCzAnM2\;
1375
1376              \reszAnfzAnj3\ <= \sumzAmk3\ * \foozAnZzAnZ2\;
1377
1378              \s'zAmC2\.A <= \foozAnZzAnZ2\;
1379
1380              \foozAo1zAo12\.A <= \reszAnfzAnj3\;
1381
1382              state : process (clock, resetn)
1383              begin
1384                   if resetn = '0' then
1385                   elseif rising_edge(clock) then
1386                        \szAlG2\ <= \s'zAmC2\;
1387                   end if;
1388              end process state;
1389         end architecture structural;
1390       \stopbuffer
1391
1392       \startbuffer[AvgStateTypes]
1393         package types is
1394              subtype \unsigned_31\ is unsigned (0 to 31);
1395                   
1396              type \(,)unsigned_31\ is record 
1397                    A : \unsigned_31\;
1398              end record;
1399         end package types;
1400       \stopbuffer
1401
1402       \startbuffer[AccStateVHDL]
1403         entity accComponent_1 is
1404              port (\izAob3\ : in \unsigned_31\;
1405                    \foozAoBzAoB2\ : out \(,)unsigned_31\;
1406                    clock : in std_logic;
1407                    resetn : in std_logic);
1408         end entity accComponent_1;
1409
1410         architecture structural of accComponent_1 is
1411              signal \szAod3\ : \unsigned_31\;
1412              signal \reszAonzAor3\ : \unsigned_31\;
1413         begin
1414              \reszAonzAor3\ <= \szAod3\ + \izAob3\;
1415              
1416              \foozAoBzAoB2\.A <= \reszAonzAor3\;
1417              
1418              state : process (clock, resetn)
1419              begin
1420                   if resetn = '0' then
1421                   elseif rising_edge(clock) then
1422                        \szAod3\ <= \reszAonzAor3\;
1423                   end if;
1424              end process state;
1425         end architecture structural;
1426       \stopbuffer 
1427     
1428       \placeexample[][ex:AvgStateTypes]{\VHDL\ types generated for \hs{acc} and \hs{avg} from \in{example}[ex:AvgState]}
1429           {\typebuffervhdl{AvgStateTypes}}
1430       \placeexample[][ex:AccStateVHDL]{\VHDL\ generated for \hs{acc} from \in{example}[ex:AvgState]}
1431           {\typebuffervhdl{AccStateVHDL}}
1432       \placeexample[][ex:AvgStateVHDL]{\VHDL\ generated for \hs{avg} from \in{example}[ex:AvgState]}
1433           {\typebuffervhdl{AvgStateVHDL}}
1434   \section{Prototype implementation}
1435     The prototype has been implemented using Haskell as its
1436     implementation language, just like \GHC. This allows the prototype
1437     do directly use parts of \GHC\ through the \small{API} it exposes
1438     (which essentially taps directly into the internals of \GHC, making
1439     this \small{API} not really a stable interface).
1440
1441     Cλash can be run from a separate library, but has also been
1442     integrated into \type{ghci} \cite[baaij09]. The latter does requires
1443     a custom \GHC\ build, however.
1444
1445     The latest version and all history of the Cλash code can be browsed
1446     on-line or retrieved using the \type{git} program.
1447
1448     http://git.stderr.nl/gitweb?p=matthijs/projects/cλash.git
1449
1450 %    \subsection{Initial state}
1451 %      How to specify the initial state? Cannot be done inside a hardware
1452 %      function, since the initial state is its own state argument for the first
1453 %      call (unless you add an explicit, synchronous reset port).
1454 %
1455 %      External init state is natural for simulation.
1456 %
1457 %      External init state works for hardware generation as well.
1458 %
1459 %      Implementation issues: state splitting, linking input to output state,
1460 %      checking usage constraints on state variables.
1461 %
1462 %
1463 % vim: set sw=2 sts=2 expandtab: