Add a section on simulation.
[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 backend 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     typcheckers 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 interchangedly 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 behavioural
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}{\useMPgraphic{ghc-pipeline}}
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       typechecker.
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       subexpression 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, typechecking
221     and other frontend 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 datastructure. 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 datastructure
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     However, we will use the normal core representation, not the simplified
243     core. Reasons for this are detailed below. \todo{Ref}
244     
245     The final prototype roughly consists of three steps:
246     
247     \startuseMPgraphic{clash-pipeline}
248       % Create objects
249       save inp, front, norm, vhdl, out;
250       newEmptyBox.inp(0,0);
251       newBox.front(btex \small{GHC} frontend etex);
252       newBox.norm(btex Normalization etex);
253       newBox.vhdl(btex \small{VHDL} generation etex);
254       newEmptyBox.out(0,0);
255
256       % Space the boxes evenly
257       inp.c - front.c = front.c - norm.c = norm.c - vhdl.c 
258         = vhdl.c - out.c = (0, 1.5cm);
259       out.c = origin;
260
261       % Draw lines between the boxes. We make these lines "deferred" and give
262       % them a name, so we can use ObjLabel to draw a label beside them.
263       ncline.inp(inp)(front) "name(haskell)";
264       ncline.front(front)(norm) "name(core)";
265       ncline.norm(norm)(vhdl) "name(normal)";
266       ncline.vhdl(vhdl)(out) "name(vhdl)";
267       ObjLabel.inp(btex Haskell source etex) "labpathname(haskell)", "labdir(rt)";
268       ObjLabel.front(btex Core etex) "labpathname(core)", "labdir(rt)";
269       ObjLabel.norm(btex Normalized core etex) "labpathname(normal)", "labdir(rt)";
270       ObjLabel.vhdl(btex \small{VHDL} description etex) "labpathname(vhdl)", "labdir(rt)";
271
272       % Draw the objects (and deferred labels)
273       drawObj (inp, front, norm, vhdl, out);
274     \stopuseMPgraphic
275     \placefigure[right]{Cλash compiler pipeline}{\useMPgraphic{clash-pipeline}}
276
277     \startdesc{Frontend}
278       This is exactly the frontend from the \small{GHC} pipeline, that
279       translates Haskell sources to a typed Core representation.
280     \stopdesc
281     \startdesc{Normalization}
282       This is a step that transforms the core representation into a normal
283       form. This normal form is still expressed in the core language, but has
284       to adhere to an additional set of constraints. This normal form is less
285       expressive than the full core language (e.g., it can have limited 
286       higher-order expressions, has a specific structure, etc.), but is
287       also very close to directly describing hardware.
288     \stopdesc
289     \startdesc{\small{VHDL} generation}
290       The last step takes the normal formed core representation and generates
291       \small{VHDL} for it. Since the normal form has a specific, hardware-like
292       structure, this final step is very straightforward.
293     \stopdesc
294     
295     The most interesting step in this process is the normalization step. That
296     is where more complicated functional constructs, which have no direct
297     hardware interpretation, are removed and translated into hardware
298     constructs. This step is described in a lot of detail at
299     \in{chapter}[chap:normalization].
300
301     
302     \defref{entry function}Translation of a hardware description always
303     starts at a single function, which is referred to as the \emph{entry
304     function}. \VHDL is generated for this function first, followed by
305     any functions used by the entry functions (recursively).
306     
307   \section[sec:prototype:core]{The Core language}
308     \defreftxt{core}{the Core language}
309     Most of the prototype deals with handling the program in the Core
310     language. In this section we will show what this language looks like and
311     how it works.
312
313     The Core language is a functional language that describes
314     \emph{expressions}. Every identifier used in Core is called a
315     \emph{binder}, since it is bound to a value somewhere. On the highest
316     level, a Core program is a collection of functions, each of which bind a
317     binder (the function name) to an expression (the function value, which has
318     a function type).
319
320     The Core language itself does not prescribe any program structure
321     (like modules, declarations, imports, etc.), only expression
322     structure. In the \small{GHC} compiler, the Haskell module structure
323     is used for the resulting Core code as well. Since this is not so
324     relevant for understanding the Core language or the Normalization
325     process, we will only look at the Core expression language here.
326
327     Each Core expression consists of one of these possible expressions.
328
329     \startdesc{Variable reference}
330       \defref{variable reference}
331       \startlambda
332       bndr :: T
333       \stoplambda
334       This is a reference to a binder. It is written down as the
335       name of the binder that is being referred to along with its type. The
336       binder name should of course be bound in a containing scope
337       (including top level scope, so a reference to a top level function
338       is also a variable reference). Additionally, constructors from
339       algebraic datatypes also become variable references.
340
341       In our examples, binders will commonly consist of a single
342       characters, but they can have any length.
343
344       The value of this expression is the value bound to the given
345       binder.
346
347       Each binder also carries around its type (explicitly shown above), but
348       this is usually not shown in the Core expressions. Only when the type is
349       relevant (when a new binder is introduced, for example) will it be
350       shown. In other cases, the binder is either not relevant, or easily
351       derived from the context of the expression. \todo{Ref sidenote on type
352       annotations}
353     \stopdesc
354
355     \startdesc{Literal}
356       \defref{literal}
357       \startlambda
358       10
359       \stoplambda
360       This is a literal. Only primitive types are supported, like
361       chars, strings, ints and doubles. The types of these literals are the
362       \quote{primitive}, unboxed versions, like \lam{Char\#} and \lam{Word\#}, not the
363       normal Haskell versions (but there are built-in conversion
364       functions). Without going into detail about these types, note that
365       a few conversion functions exist to convert these to the normal
366       (boxed) Haskell equivalents.
367     \stopdesc
368
369     \startdesc{Application}
370       \defref{application}
371       \startlambda
372       func arg
373       \stoplambda
374       This is function application. Each application consists of two
375       parts: The function part and the argument part. Applications are used
376       for normal function \quote{calls}, but also for applying type
377       abstractions and data constructors.
378
379       In core, there is no distinction between an operator and a
380       function. This means that, for example the addition of two numbers
381       looks like the following in Core:
382       
383       \startlambda
384       (+) 1 2
385       \stoplambda
386
387       Where the function \quote{\lam{(+)}} is applied to the numbers 1
388       and 2. However, to increase readability, an application of an
389       operator like \lam{(+)} is sometimes written infix. In this case,
390       the parenthesis are also left out, just like in Haskell. In other
391       words, the following means exactly the same as the addition above:
392
393       \startlambda
394       1 + 2
395       \stoplambda
396
397       The value of an application is the value of the function part, with the
398       first argument binder bound to the argument part.
399     \stopdesc
400
401     \startdesc{Lambda abstraction}
402       \defref{lambda abstraction}
403       \startlambda
404       λbndr.body
405       \stoplambda
406       This is the basic lambda abstraction, as it occurs in lambda calculus.
407       It consists of a binder part and a body part.  A lambda abstraction
408       creates a function, that can be applied to an argument. The binder is
409       usually a value binder, but it can also be a \emph{type binder} (or
410       \emph{type variable}). The latter case introduces a new polymorphic
411       variable, which can be used in types later on. See
412       \in{section}[sec:prototype:coretypes] for details.
413      
414       The body of a lambda abstraction extends all the way to the end of
415       the expression, or the closing bracket surrounding the lambda. In
416       other words, the lambda abstraction \quote{operator} has the
417       lowest priority of all.
418
419       The value of an application is the value of the body part, with the
420       binder bound to the value the entire lambda abstraction is applied to.
421     \stopdesc
422
423     \startdesc{Non-recursive let expression}
424       \defref{let expression}
425       \startlambda
426       let bndr = value in body
427       \stoplambda
428       A let expression allows you to bind a binder to some value, while
429       evaluating to some other value (for which that binder is in scope). This
430       allows for sharing of subexpressions (you can use a binder twice) and
431       explicit \quote{naming} of arbitrary expressions. A binder is not
432       in scope in the value bound it is bound to, so it is not possible
433       to make recursive definitions with a non-recursive let expression
434       (see the recursive form below).
435
436       Even though this let expression is an extension on the basic lambda
437       calculus, it is easily translated to a lambda abstraction. The let
438       expression above would then become:
439
440       \startlambda
441       (λbndr.body) value
442       \stoplambda
443
444       This notion might be useful for verifying certain properties on
445       transformations, since a lot of verification work has been done on
446       lambda calculus already.
447
448       The value of a let expression is the value of the body part, with the
449       binder bound to the value. 
450     \stopdesc
451
452     \startdesc{Recursive let expression}
453       \startlambda
454       letrec
455         bndr1 = value1
456         \vdots
457         bndrn = valuen
458       in 
459         body
460       \stoplambda
461       This is the recursive version of the let expression. In \small{GHC}'s
462       Core implementation, non-recursive and recursive lets are not so
463       distinct as we present them here, but this provides a clearer overview.
464       
465       The main difference with the normal let expression is that it can
466       contain multiple bindings (or even none) and each of the binders
467       is in scope in each of the values, in addition to the body. This
468       allows for self-recursive or mutually recursive definitions.
469
470       It is also possible to express a recursive let expression using
471       normal lambda calculus, if we use the \emph{least fixed-point
472       operator}, \lam{Y} (but the details are too complicated to help
473       clarify the let expression, so this will not be explored further).
474     \stopdesc
475
476     \placeintermezzo{}{
477       \startframedtext[width=8cm,background=box,frame=no]
478       \startalignment[center]
479         {\tfa Weak head normal form (\small{WHNF})}
480       \stopalignment
481       \blank[medium]
482         An expression is in weak head normal form if it is either an
483         constructor application or lambda abstraction. \todo{How about
484         atoms?}
485
486         Without going into detail about the differences with head
487         normal form and normal form, note that evaluating the scrutinee
488         of a case expression to normal form (evaluating any function
489         applications, variable references and case expressions) is
490         sufficient to decide which case alternatives should be chosen.
491         \todo{ref?}
492       \stopframedtext
493
494     }
495
496     \startdesc{Case expression}
497       \defref{case expression}
498       \startlambda
499         case scrutinee of bndr
500           DEFAULT -> defaultbody
501           C0 bndr0,0 ... bndr0,m -> body0
502           \vdots
503           Cn bndrn,0 ... bndrn,m -> bodyn
504       \stoplambda
505
506       A case expression is the only way in Core to choose between values. All
507       \hs{if} expressions and pattern matchings from the original Haskell
508       PRogram have been translated to case expressions by the desugarer. 
509       
510       A case expression evaluates its scrutinee, which should have an
511       algebraic datatype, into weak head normal form (\small{WHNF}) and
512       (optionally) binds it to \lam{bndr}. Every alternative lists a
513       single constructor (\lam{C0 ... Cn}). Based on the actual
514       constructor of the scrutinee, the corresponding alternative is
515       chosen. The binders in the chosen alternative (\lam{bndr0,0 ....
516       bndr0,m} are bound to the actual arguments to the constructor in
517       the scrutinee.
518
519       This is best illustrated with an example. Assume
520       there is an algebraic datatype declared as follows\footnote{This
521       datatype is not suported by the current Cλash implementation, but
522       serves well to illustrate the case expression}:
523
524       \starthaskell
525       data D = A Word | B Bit
526       \stophaskell
527
528       This is an algebraic datatype with two constructors, each getting
529       a single argument. A case expression scrutinizing this datatype
530       could look like the following:
531
532       \startlambda
533         case s of
534           A word -> High
535           B bit -> bit
536       \stoplambda
537
538       What this expression does is check the constructor of the
539       scrutinee \lam{s}. If it is \lam{A}, it always evaluates to
540       \lam{High}. If the constructor is \lam{B}, the binder \lam{bit} is
541       bound to the argument passed to \lam{B} and the case expression
542       evaluates to this bit.
543       
544       If none of the alternatives match, the \lam{DEFAULT} alternative
545       is chosen. A case expression must always be exhaustive, \ie it
546       must cover all possible constructors that the scrutinee can have
547       (if all of them are covered explicitly, the \lam{DEFAULT}
548       alternative can be left out).
549       
550       Since we can only match the top level constructor, there can be no overlap
551       in the alternatives and thus order of alternatives is not relevant (though
552       the \lam{DEFAULT} alternative must appear first for implementation
553       efficiency).
554       
555       To support strictness, the scrutinee is always evaluated into
556       \small{WHNF}, even when there is only a \lam{DEFAULT} alternative. This
557       allows aplication of the strict function \lam{f} to the argument \lam{a}
558       to be written like:
559
560       \startlambda
561       f (case a of arg DEFAULT -> arg)
562       \stoplambda
563
564       According to the \GHC documentation, this is the only use for the extra
565       binder to which the scrutinee is bound.  When not using strictness
566       annotations (which is rather pointless in hardware descriptions),
567       \small{GHC} seems to never generate any code making use of this binder.
568       In fact, \GHC has never been observed to generate code using this
569       binder, even when strictness was involved.  Nonetheless, the prototype
570       handles this binder as expected.
571
572       Note that these case expressions are less powerful than the full Haskell
573       case expressions. In particular, they do not support complex patterns like
574       in Haskell. Only the constructor of an expression can be matched,
575       complex patterns are implemented using multiple nested case expressions.
576
577       Case expressions are also used for unpacking of algebraic datatypes, even
578       when there is only a single constructor. For examples, to add the elements
579       of a tuple, the following Core is generated:
580
581       \startlambda
582       sum = λtuple.case tuple of
583         (,) a b -> a + b
584       \stoplambda
585     
586       Here, there is only a single alternative (but no \lam{DEFAULT}
587       alternative, since the single alternative is already exhaustive). When
588       its body is evaluated, the arguments to the tuple constructor \lam{(,)}
589       (\eg, the elements of the tuple) are bound to \lam{a} and \lam{b}.
590     \stopdesc
591
592     \startdesc{Cast expression}
593       \defref{cast expression}
594       \startlambda
595       body ▶ targettype
596       \stoplambda
597       A cast expression allows you to change the type of an expression to an
598       equivalent type. Note that this is not meant to do any actual work, like
599       conversion of data from one format to another, or force a complete type
600       change. Instead, it is meant to change between different representations
601       of the same type, \eg switch between types that are provably equal (but
602       look different).
603       
604       In our hardware descriptions, we typically see casts to change between a
605       Haskell newtype and its contained type, since those are effectively
606       different types (so a cast is needed) with the same representation (but
607       no work is done by the cast).
608
609       More complex are types that are proven to be equal by the typechecker,
610       but look different at first glance. To ensure that, once the typechecker
611       has proven equality, this information sticks around, explicit casts are
612       added. In our notation we only write the target type, but in reality a
613       cast expressions carries around a \emph{coercion}, which can be seen as a
614       proof of equality. \todo{Example}
615
616       The value of a cast is the value of its body, unchanged. The type of this
617       value is equal to the target type, not the type of its body.
618
619       \todo{Move and update this paragraph}
620       Note that this syntax is also used sometimes to indicate that a particular
621       expression has a particular type, even when no cast expression is
622       involved. This is then purely informational, since the only elements that
623       are explicitly typed in the Core language are the binder references and
624       cast expressions, the types of all other elements are determined at
625       runtime.
626     \stopdesc
627
628     \startdesc{Note}
629       The Core language in \small{GHC} allows adding \emph{notes}, which serve
630       as hints to the inliner or add custom (string) annotations to a core
631       expression. These should not be generated normally, so these are not
632       handled in any way in the prototype.
633     \stopdesc
634
635     \startdesc{Type}
636       \defref{type expression}
637       \startlambda
638       @T
639       \stoplambda
640       It is possibly to use a Core type as a Core expression. To prevent
641       confusion between types and values, the \lam{@} sign is used to
642       explicitly mark a type that is used in a Core expression.
643       
644       For the actual types supported by Core, see
645       \in{section}[sec:prototype:coretypes]. This \quote{lifting} of a
646       type into the value domain is done to allow for type abstractions
647       and applications to be handled as normal lambda abstractions and
648       applications above. This means that a type expression in Core can
649       only ever occur in the argument position of an application, and
650       only if the type of the function that is applied to expects a type
651       as the first argument. This happens in applications of all
652       polymorphic functions. Consider the \lam{fst} function:
653
654       \startlambda
655       fst :: \forall t1. \forall t2. (t1, t2) ->t1 
656       fst = λt1.λt2.λ(tup :: (t1, t2)). case tup of (,) a b -> a
657
658       fstint :: (Int, Int) -> Int
659       fstint = λa.λb.fst @Int @Int a b
660       \stoplambda
661           
662       The type of \lam{fst} has two universally quantified type variables. When
663       \lam{fst} is applied in \lam{fstint}, it is first applied to two types.
664       (which are substitued for \lam{t1} and \lam{t2} in the type of \lam{fst}, so
665       the actual type of arguments and result of \lam{fst} can be found:
666       \lam{fst @Int @Int :: (Int, Int) -> Int}).
667     \stopdesc
668
669     \subsection[sec:prototype:coretypes]{Core type system}
670       Whereas the expression syntax of Core is very simple, its type system is
671       a bit more complicated. It turns out it is harder to \quote{desugar}
672       Haskell's complex type system into something more simple. Most of the
673       type system is thus very similar to that of Haskell.
674
675       We will slightly limit our view on Core's type system, since the more
676       complicated parts of it are only meant to support Haskell's (or rather,
677       \GHC's) type extensions, such as existential types, \small{GADT}s, type
678       families and other non-standard Haskell stuff which we do not (plan to)
679       support.
680
681       In Core, every expression is typed. The translation to Core happens
682       after the typechecker, so types in Core are always correct as well
683       (though you could of course construct invalidly typed expressions
684       through the \GHC API).
685
686       Any type in core is one of the following:
687
688       \startdesc{A type variable}
689         \startlambda
690         t
691         \stoplambda
692
693         This is a reference to a type defined elsewhere. This can either be a
694         polymorphic type (like the latter two \lam{t}'s in \lam{id :: \forall t.
695         t -> t}), or a type constructor (like \lam{Bool} in \lam{not :: Bool ->
696         Bool}). Like in Haskell, polymorphic type variables always
697         start with a lowercase letter, while type constructors always start
698         with an uppercase letter.
699
700         \todo{How to define (new) type constructors?}
701
702         A special case of a type constructor is the \emph{function type
703         constructor}, \lam{->}. This is a type constructor taking two arguments
704         (using application below). The function type constructor is commonly
705         written inline, so we write \lam{a -> b} when we really mean \lam{-> a
706         b}, the function type constructor applied to \lam{a} and \lam{b}.
707
708         Polymorphic type variables can only be defined by a lambda
709         abstraction, see the forall type below.
710       \stopdesc
711
712       \startdesc{A type application}
713         \startlambda
714           Maybe Int
715         \stoplambda
716
717         This applies some type to another type. This is particularly used to
718         apply type variables (type constructors) to their arguments.
719
720         As mentioned above, applications of some type constructors have
721         special notation. In particular, these are applications of the
722         \emph{function type constructor} and \emph{tuple type constructors}:
723         \startlambda
724           foo :: t1 -> t2 
725           foo' :: -> t1 t2 
726           bar :: (t1, t2, t3)
727           bar' :: (,,) t1 t2 t3
728         \stoplambda
729       \stopdesc
730
731       \startdesc{The forall type}
732         \startlambda
733           id :: \forall t. t -> t
734         \stoplambda
735         The forall type introduces polymorphism. It is the only way to
736         introduce new type variables, which are completely unconstrained (Any
737         possible type can be assigned to it). Constraints can be added later
738         using predicate types, see below.
739
740         A forall type is always (and only) introduced by a type lambda
741         expression. For example, the Core translation of the
742         id function is:
743         \startlambda
744           id = λt.λ(x :: t).x
745         \stoplambda
746
747         Here, the type of the binder \lam{x} is \lam{t}, referring to the
748         binder in the topmost lambda.
749
750         When using a value with a forall type, the actual type
751         used must be applied first. For example Haskell expression \hs{id
752         True} (the function \hs{id} appleid to the dataconstructor \hs{True})
753         translates to the following Core:
754
755         \startlambda
756         id @Bool True
757         \stoplambda
758
759         Here, id is first applied to the type to work with. Note that the type
760         then changes from \lam{id :: \forall t. t -> t} to \lam{id @Bool ::
761         Bool -> Bool}. Note that the type variable \lam{a} has been
762         substituted with the actual type.
763
764         In Haskell, forall types are usually not explicitly specified (The use
765         of a lowercase type variable implicitly introduces a forall type for
766         that variable). In fact, in standard Haskell there is no way to
767         explicitly specify forall types. Through a language extension, the
768         \hs{forall} keyword is available, but still optional for normal forall
769         types (it is needed for \emph{existentially quantified types}, which
770         Cλash does not support).
771       \stopdesc
772
773       \startdesc{Predicate type}
774         \startlambda
775           show :: \forall t. Show t ⇒ t → String
776         \stoplambda
777        
778         \todo{Sidenote: type classes?}
779
780         A predicate type introduces a constraint on a type variable introduced
781         by a forall type (or type lambda). In the example above, the type
782         variable \lam{t} can only contain types that are an \emph{instance} of
783         the \emph{type class} \lam{Show}. \refdef{type class}
784
785         There are other sorts of predicate types, used for the type families
786         extension, which we will not discuss here.
787
788         A predicate type is introduced by a lambda abstraction. Unlike with
789         the forall type, this is a value lambda abstraction, that must be
790         applied to a value. We call this value a \emph{dictionary}.
791
792         Without going into the implementation details, a dictionary can be
793         seen as a lookup table all the methods for a given (single) type class
794         instance. This means that all the dictionaries for the same type class
795         look the same (\eg contain methods with the same names). However,
796         dictionaries for different instances of the same class contain
797         different methods, of course.
798
799         A dictionary is introduced by \small{GHC} whenever it encounters an
800         instance declaration. This dictionary, as well as the binder
801         introduced by a lambda that introduces a dictionary, have the
802         predicate type as their type. These binders are usually named starting
803         with a \lam{\$}. Usually the name of the type concerned is not
804         reflected in the name of the dictionary, but the name of the type
805         class is. The Haskell expression \hs{show True} thus becomes:
806
807         \startlambda
808         show @Bool \$dShow True
809         \stoplambda
810       \stopdesc
811
812       Using this set of types, all types in basic Haskell can be represented.
813       
814       \todo{Overview of polymorphism with more examples (or move examples
815       here)}.
816         
817   \section[sec:prototype:statetype]{State annotations in Haskell}
818     As noted in \in{section}[sec:description:stateann], Cλash needs some
819     way to let the programmer explicitly specify which of a function's
820     arguments and which part of a function's result represent the
821     function's state.
822
823     Using the Haskell type systems, there are a few ways we can tackle this.
824
825     \subsection{Type synonyms}
826       Haskell provides type synonyms as a way to declare a new type that is
827       equal to an existing type (or rather, a new name for an existing type).
828       This allows both the original type and the synonym to be used
829       interchangedly in a Haskell program. This means no explicit conversion
830       is needed either. For example, a simple accumulator would become:
831
832       \starthaskell
833       type State s = s
834       acc :: Word -> State Word -> (State Word, Word)
835       acc i s = let sum = s + i in (sum, sum)
836       \stophaskell
837
838       This looks nice in Haskell, but turns out to be hard to implement. There
839       are no explicit conversion in Haskell, but not in Core either. This
840       means the type of a value might be show as \hs{AccState} in some places,
841       but \hs{Word} in others (and this can even change due to
842       transformations). Since every binder has an explicit type associated
843       with it, the type of every function type will be properly preserved and
844       could be used to track down the statefulness of each value by the
845       compiler. However, this makes the implementation a lot more complicated
846       than it currently is using \hs{newtypes}.
847
848     % Use \type instead of \hs here, since the latter breaks inside
849     % section headings.
850     \subsection{Type renaming (\type{newtype})}
851       Haskell also supports type renamings as a way to declare a new type that
852       has the same (runtime) representation as an existing type (but is in
853       fact a different type to the typechecker). With type renaming, an
854       explicit conversion between values of the two types is needed. The
855       accumulator would then become:
856
857       \starthaskell
858       newtype State s = State s
859       acc :: Word -> State Word -> (State Word, Word)
860       acc i (State s) = let sum = s + i in (State sum, sum)
861       \stophaskell
862
863       The \hs{newtype} line declares a new type \hs{State} that has one type
864       argument, \hs{s}. This type contains one \quote{constructor} \hs{State}
865       with a single argument of type \hs{s}. It is customary to name the
866       constructor the same as the type, which is allowed (since types can
867       never cause name collisions with values). The difference with the type
868       synonym example is in the explicit conversion between the \hs{State
869       Word} and \hs{Word} types by pattern matching and by using the explicit
870       the \hs{State constructor}.
871
872       This explicit conversion makes the \VHDL generation easier: Whenever we
873       remove (unpack) the \hs{State} type, this means we are accessing the
874       current state (\eg, accessing the register output). Whenever we are a
875       adding (packing) the \hs{State} type, we are producing a new value for
876       the state (\eg, providing the register input).
877
878       When dealing with nested states (a stateful function that calls stateful
879       functions, which might call stateful functions, etc.) the state type
880       could quickly grow complex because of all the \hs{State} type constructors
881       needed. For example, consider the following state type (this is just the
882       state type, not the entire function type):
883
884       \starttyping
885       State (State Bit, State (State Word, Bit), Word)
886       \stoptyping
887
888       We cannot leave all these \hs{State} type constructors out, since that
889       would change the type (unlike when using type synonyms). However, when
890       using type synonyms to hide away substates (see
891       \in{section}[sec:prototype:substatesynonyms] below), this
892       disadvantage should be limited.
893
894       \subsubsection{Different input and output types}
895         An alternative could be to use different types for input and output
896         state (\ie current and updated state). The accumulator example would
897         then become something like:
898
899         \starthaskell
900         newtype StateIn s = StateIn s
901         newtype StateOut s = StateOut s
902         acc :: Word -> StateIn Word -> (StateIn Word, Word)
903         acc i (StateIn s) = let sum = s + i in (StateIn sum, sum)
904         \stophaskell
905         
906         This could make the implementation easier and the hardware
907         descriptions less errorprone (you can no longer \quote{forget} to
908         unpack and repack a state variable and just return it directly, which
909         can be a problem in the current prototype). However, it also means we
910         need twice as many type synonyms to hide away substates, making this
911         approach a bit cumbersome. It also makes it harder to copmare input
912         and output state types, possible reducing the type safety of the
913         descriptions.
914
915     \subsection[sec:prototype:substatesynonyms]{Type synonyms for substates}
916       As noted above, when using nested (hierarchical) states, the state types
917       of the \quote{upper} functions (those that call other functions, which
918       call other functions, etc.) quickly becomes complicated. Also, when the
919       state type of one of the \quote{lower} functions changes, the state
920       types of all the upper functions changes as well. If the state type for
921       each function is explicitly and completely specified, this means that a
922       lot of code needs updating whenever a state type changes.
923
924       To prevent this, it is recommended (but not enforced) to use a type
925       synonym for the state type of every function. Every function calling
926       other functions will then use the state type synonym of the called
927       functions in its own type, requiring no code changes when the state type
928       of a called function changes. This approach is used in
929       \in{example}[ex:AvgState] below. The \hs{AccState} and \hs{AvgState}
930       are examples of such state type synonyms.
931
932     \subsection{Chosen approach}
933       To keep implementation simple, the current prototype uses the type
934       renaming approach, with a single type for both input and output
935       states. In the future, it might be worthwhile to revisit this
936       approach if more complicated flow analysis is implemented for
937       state variables. This analysis is needed to add proper error
938       checking anyway and might allow the use of type synonyms without
939       losing any expressivity.
940
941       \subsubsection{Example}
942         As an example of the used approach, there is a simple averaging circuit in
943         \in{example}[ex:AvgState]. This circuit lets the accumulation of the
944         inputs be done by a subcomponent, \hs{acc}, but keeps a count of value
945         accumulated in its own state.\footnote{Currently, the prototype
946         is not able to compile this example, since the built-in function
947         for division has not been added.}
948         
949         \startbuffer[AvgState]
950           -- The state type annotation
951           newtype State s = State s
952
953           -- The accumulator state type
954           type AccState = State Word
955           -- The accumulator
956           acc :: Word -> AccState -> (AccState, Word)
957           acc i (State s) = let sum = s + i in (State sum, sum)
958
959           -- The averaging circuit state type
960           type AvgState = State (AccState, Word)
961           -- The averaging circuit
962           avg :: Word -> AvgState -> (AvgState, Word)
963           avg i (State s) = (State s', o)
964             where
965               (accs, count) = s
966               -- Pass our input through the accumulator, which outputs a sum
967               (accs', sum) = acc i accs
968               -- Increment the count (which will be our new state)
969               count' = count + 1
970               -- Compute the average
971               o = sum / count'
972               s' = (accs', count')
973         \stopbuffer
974
975         \placeexample[here][ex:AvgState]{Simple stateful averaging circuit.}
976           %\startcombination[2*1]
977             {\typebufferhs{AvgState}}%{Haskell description using function applications.}
978           %  {\boxedgraphic{AvgState}}{The architecture described by the Haskell description.}
979           %\stopcombination
980         \todo{Picture}
981
982   \section{Implementing state}  
983     Now its clear how to put state annotations in the Haskell source,
984     there is the question of how to implement this state translation. As
985     we have seen in \in{section}[sec:prototype:design], the translation to
986     \VHDL happens as a simple, final step in the compilation process.
987     This step works on a core expression in normal form. The specifics
988     of normal form will be explained in
989     \in{chapter}[chap:normalization], but the examples given should be
990     easy to understand using the definitin of Core given above.
991
992         \startbuffer[AvgStateNormal]
993           acc = λi.λspacked.
994             let
995               -- Remove the State newtype
996               s = spacked ▶ Word
997               s' = s + i
998               o = s + i
999               -- Add the State newtype again
1000               spacked' = s' ▶ State Word
1001               res = (spacked', o)
1002             in
1003               res
1004
1005           avg = λi.λspacked.
1006             let
1007               s = spacked ▶ (AccState, Word)
1008               accs = case s of (accs, _) -> accs
1009               count = case s of (_, count) -> count
1010               accres = acc i accs
1011               accs' = case accres of (accs', _) -> accs'
1012               sum = case accres of (_, sum) -> sum
1013               count' = count + 1
1014               o = sum / count'
1015               s' = (accs', count')
1016               spacked' = s' ▶ State (AccState, Word)
1017               res = (spacked', o)
1018             in
1019               res
1020         \stopbuffer
1021
1022         \placeexample[here][ex:AvgStateNormal]{Normalized version of \in{example}[ex:AvgState]}
1023             {\typebufferlam{AvgStateNormal}}
1024
1025     \subsection[sec:prototype:statelimits]{State in normal form}
1026       Before describing how to translate state from normal form to
1027       \VHDL, we will first see how state handling looks in normal form.
1028       What limitations are there on their use to guarantee that proper
1029       \VHDL can be generated?
1030
1031       We will try to formulate a number of rules about what operations are
1032       allowed with state variables. These rules apply to the normalized Core
1033       representation, but will in practice apply to the original Haskell
1034       hardware description as well. Ideally, these rules would become part
1035       of the intended normal form definition \refdef{intended normal form
1036       definition}, but this is not the case right now. This can cause some
1037       problems, which are detailed in
1038       \in{section}[sec:normalization:stateproblems].
1039
1040       In these rules we use the terms \emph{state variable} to refer to any
1041       variable that has a \lam{State} type. A \emph{state-containing
1042       variable} is any variable whose type contains a \lam{State} type,
1043       but is not one itself (like \lam{(AccState, Word)} in the example,
1044       which is a tuple type, but contains \lam{AccState}, which is again
1045       equal to \lam{State Word}).
1046
1047       We also use a distinction between \emph{input} and \emph{output
1048       (state) variables} and \emph{substate variables}, which will be
1049       defined in the rules themselves.
1050
1051       \startdesc{State variables can appear as an argument.}
1052         \startlambda
1053           avg = λi.λspacked. ...
1054         \stoplambda
1055
1056         Any lambda that binds a variable with a state type, creates a new
1057         input state variable.
1058       \stopdesc
1059
1060       \startdesc{Input state variables can be unpacked.}
1061         \startlambda
1062           s = spacked ▶ (AccState, Word)
1063         \stoplambda
1064
1065         An input state variable may be unpacked using a cast operation. This
1066         removes the \lam{State} type renaming and the result has no longer a
1067         \lam{State} type.
1068
1069         If the result of this unpacking does not have a state type and does
1070         not contain state variables, there are no limitations on its use.
1071         Otherwise if it does not have a state type but does contain
1072         substates, we refer to it as a \emph{state-containing input
1073         variable} and the limitations below apply. If it has a state type
1074         itself, we refer to it as an \emph{input substate variable} and the
1075         below limitations apply as well.
1076
1077         It may seem strange to consider a variable that still has a state
1078         type directly after unpacking, but consider the case where a
1079         function does not have any state of its own, but does call a single
1080         stateful function. This means it must have a state argument that
1081         contains just a substate. The function signature of such a function
1082         could look like:
1083
1084         \starthaskell
1085           type FooState = State AccState
1086         \stophaskell
1087
1088         Which is of course equivalent to \lam{State (State Word)}.
1089       \stopdesc
1090
1091       \startdesc{Variables can be extracted from state-containing input variables.}
1092         \startlambda
1093           accs = case s of (accs, _) -> accs
1094         \stoplambda
1095
1096         A state-containing input variable is typically a tuple containing
1097         multiple elements (like the current function's state, substates or
1098         more tuples containing substates). All of these can be extracted
1099         from an input variable using an extractor case (or possibly
1100         multiple, when the input variable is nested).
1101
1102         If the result has no state type and does not contain any state
1103         variables either, there are no further limitations on its use. If
1104         the result has no state type but does contain state variables we
1105         refer to it as a \emph{state-containing input variable} and this
1106         limitation keeps applying. If the variable has a state type itself,
1107         we refer to it as an \emph{input substate variable} and below
1108         limitations apply.
1109
1110       \startdesc{Input substate variables can be passed to functions.} 
1111         \startlambda
1112           accres = acc i accs
1113           accs' = case accres of (accs', _) -> accs'
1114         \stoplambda
1115         
1116         An input substate variable can (only) be passed to a function.
1117         Additionally, every input substate variable must be used in exactly
1118         \emph{one} application, no more and no less.
1119
1120         The function result should contain exactly one state variable, which
1121         can be extracted using (multiple) case expressions. The extracted
1122         state variable is referred to the \emph{output substate}
1123
1124         The type of this output substate must be identical to the type of
1125         the input substate passed to the function.
1126       \stopdesc
1127
1128       \startdesc{Variables can be inserted into a state-containing output variable.}
1129         \startlambda
1130           s' = (accs', count')
1131         \stoplambda
1132         
1133         A function's output state is usually a tuple containing its own
1134         updated state variables and all output substates. This result is
1135         built up using any single-constructor algebraic datatype.
1136
1137         The result of these expressions is referred to as a
1138         \emph{state-containing output variable}, which are subject to these
1139         limitations.
1140       \stopdesc
1141
1142       \startdesc{State containing output variables can be packed.}
1143         \startlambda
1144           spacked' = s' ▶ State (AccState, Word)
1145         \stoplambda
1146
1147         As soon as all a functions own update state and output substate
1148         variables have been joined together, the resulting
1149         state-containing output variable can be packed into an output
1150         state variable. Packing is done by casting into a state type.
1151       \stopdesc
1152
1153       \startdesc{Output state variables can appear as (part of) a function result.}
1154         \startlambda
1155           avg = λi.λspacked.
1156             let
1157             \vdots
1158             res = (spacked', o)
1159           in
1160             res
1161         \stoplambda
1162         When the output state is packed, it can be returned as a part
1163         of the function result. Nothing else can be done with this
1164         value (or any value that contains it).
1165       \stopdesc
1166
1167       There is one final limitation that is hard to express in the above
1168       itemization. Whenever substates are extracted from the input state
1169       to be passed to functions, the corresponding output substates
1170       should be inserted into the output state in the same way. In other
1171       words, each pair of corresponding substates in the input and
1172       output states should be passed / returned from the same called
1173       function.
1174
1175       The prototype currently does not check much of the above
1176       conditions. This means that if the conditions are violated,
1177       sometimes a compile error is generated, but in other cases output
1178       can be generated that is not valid \VHDL or at the very least does
1179       not correspond to the input.
1180
1181     \subsection{Translating to \VHDL}
1182       As noted above, the basic approach when generating \VHDL for stateful
1183       functions is to generate a single register for every stateful function.
1184       We look around the normal form to find the let binding that removes the
1185       \lam{State} newtype (using a cast). We also find the let binding that
1186       adds a \lam{State} type. These are connected to the output and the input
1187       of the generated let binding respectively. This means that there can
1188       only be one let binding that adds and one that removes the \lam{State}
1189       type. It is easy to violate this constraint. This problem is detailed in
1190       \in{section}[sec:normalization:stateproblems].
1191
1192       This approach seems simple enough, but will this also work for more
1193       complex stateful functions involving substates?  Observe that any
1194       component of a function's state that is a substate, \ie passed on as
1195       the state of another function, should have no influence on the
1196       hardware generated for the calling function. Any state-specific
1197       \small{VHDL} for this component can be generated entirely within the
1198       called function.  So, we can completely ignore substates when
1199       generating \VHDL for a function.
1200       
1201       From this observation it might seem logical to remove the
1202       substates from a function's states altogether and leave only the
1203       state components which are actual states of the current function.
1204       While doing this would not remove any information needed to
1205       generate \small{VHDL} from the function, it would cause the
1206       function definition to become invalid (since we will not have any
1207       substate to pass to the functions anymore).  We could solve the
1208       syntactic problems by passing \type{undefined} for state
1209       variables, but that would still break the code on the semantic
1210       level (\ie, the function would no longer be semantically
1211       equivalent to the original input).
1212
1213       To keep the function definition correct until the very end of the
1214       process, we will not deal with (sub)states until we get to the
1215       \small{VHDL} generation.  Then, we are translating from Core to
1216       \small{VHDL}, and we can simply ignore substates, effectively removing
1217       the substate components altogether.
1218
1219       But, how will we know what exactly is a substate? Since any state
1220       argument or return value that represents state must be of the
1221       \type{State} type, we can look at the type of a value. However, we
1222       must be careful to ignore only \emph{substates}, and not a
1223       function's own state.
1224
1225       In \in{example}[ex:AvgStateNorm] above, we should generate a register
1226       connected with its output connected to \lam{s} and its input connected
1227       to \lam{s'}. However, \lam{s'} is build up from both \lam{accs'} and
1228       \lam{count'}, while only \lam{count'} should end up in the register.
1229       \lam{accs'} is a substate for the \lam{acc} function, for which a
1230       register will be created when generating \VHDL for the \lam{acc}
1231       function.
1232
1233       Fortunately, the \lam{accs'} variable (and any other substate) has a
1234       property that we can easily check: It has a \lam{State} type
1235       annotation. This means that whenever \VHDL is generated for a tuple
1236       (or other algebraic type), we can simply leave out all elements that
1237       have a \lam{State} type. This will leave just the parts of the state
1238       that do not have a \lam{State} type themselves, like \lam{count'},
1239       which is exactly a function's own state. This approach also means that
1240       the state part of the result is automatically excluded when generating
1241       the output port, which is also required.
1242
1243       We can formalize this translation a bit, using the following
1244       rules.
1245
1246       \startitemize
1247         \item A state unpack operation should not generate any \small{VHDL}.
1248         The binder to which the unpacked state is bound should still be
1249         declared, this signal will become the register and will hold the
1250         current state.
1251         \item A state pack operation should not generate any \small{VHDL}.
1252         The binder to which the packed state is bound should not be
1253         declared. The binder that is packed is the signal that will hold the
1254         new state.
1255         \item Any values of a State type should not be translated to
1256         \small{VHDL}. In particular, State elements should be removed from
1257         tuples (and other datatypes) and arguments with a state type should
1258         not generate ports.
1259         \item To make the state actually work, a simple \small{VHDL}
1260         (sequential) process should be generated. This process updates
1261         the state at every clockcycle, by assigning the new state to the
1262         current state. This will be recognized by synthesis tools as a
1263         register specification.
1264       \stopitemize
1265
1266       When applying these rules to the description in
1267       \in{example}[ex:AvgStateNormal], we be left with the description
1268       in \in{example}[ex:AvgStateRemoved]. All the parts that do not
1269       generate any \VHDL directly are crossed out, leaving just the
1270       actual flow of values in the final hardware.
1271       
1272       \startlambda
1273         avg = iλ.λ--spacked.--
1274           let 
1275             s = --spacked ▶ (AccState, Word)--
1276             --accs = case s of (accs, _) -> accs--
1277             count = case s of (--_,-- count) -> count
1278             accres = acc i --accs--
1279             --accs' = case accres of (accs', _) -> accs'--
1280             sum = case accres of (--_,-- sum) -> sum
1281             count' = count + 1
1282             o = sum / count'
1283             s' = (--accs',-- count')
1284             --spacked' = s' ▶ State (AccState, Word)--
1285             res = (--spacked',-- o)
1286           in
1287             res
1288       \stoplambda
1289               
1290       When we would really leave out the crossed out parts, we get a slightly
1291       weird program: There is a variable \lam{s} which has no value, and there
1292       is a variable \lam{s'} that is never used. Together, these two will form
1293       the state process of the function. \lam{s} contains the "current" state,
1294       \lam{s'} is assigned the "next" state. So, at the end of each clock
1295       cycle, \lam{s'} should be assigned to \lam{s}.
1296
1297       In the example the definition of \lam{s'} is still present, since
1298       it does not have a state type. The \lam{accums'} substate has been
1299       removed, leaving us just with the state of \lam{avg} itself.
1300
1301       As an illustration of the result of this function,
1302       \in{example}[ex:AccStateVHDL] and \in{example}[ex:AvgStateVHDL] show the the \VHDL that is
1303       generated from the examples is this section.
1304
1305       \startbuffer[AvgStateVHDL]
1306         entity avgComponent_0 is
1307              port (\izAlE2\ : in \unsigned_31\;
1308                    \foozAo1zAo12\ : out \(,)unsigned_31\;
1309                    clock : in std_logic;
1310                    resetn : in std_logic);
1311         end entity avgComponent_0;
1312
1313
1314         architecture structural of avgComponent_0 is
1315              signal \szAlG2\ : \(,)unsigned_31\;
1316              signal \countzAlW2\ : \unsigned_31\;
1317              signal \dszAm62\ : \(,)unsigned_31\;
1318              signal \sumzAmk3\ : \unsigned_31\;
1319              signal \reszAnCzAnM2\ : \unsigned_31\;
1320              signal \foozAnZzAnZ2\ : \unsigned_31\;
1321              signal \reszAnfzAnj3\ : \unsigned_31\;
1322              signal \s'zAmC2\ : \(,)unsigned_31\;
1323         begin
1324              \countzAlW2\ <= \szAlG2\.A;
1325
1326              \comp_ins_dszAm62\ : entity accComponent_1
1327                                        port map (\izAob3\ => \izAlE2\,
1328                                                  \foozAoBzAoB2\ => \dszAm62\,
1329                                                  clock => clock,
1330                                                  resetn => resetn);
1331
1332              \sumzAmk3\ <= \dszAm62\.A;
1333
1334              \reszAnCzAnM2\ <= to_unsigned(1, 32);
1335
1336              \foozAnZzAnZ2\ <= \countzAlW2\ + \reszAnCzAnM2\;
1337
1338              \reszAnfzAnj3\ <= \sumzAmk3\ * \foozAnZzAnZ2\;
1339
1340              \s'zAmC2\.A <= \foozAnZzAnZ2\;
1341
1342              \foozAo1zAo12\.A <= \reszAnfzAnj3\;
1343
1344              state : process (clock, resetn)
1345              begin
1346                   if resetn = '0' then
1347                   elseif rising_edge(clock) then
1348                        \szAlG2\ <= \s'zAmC2\;
1349                   end if;
1350              end process state;
1351         end architecture structural;
1352       \stopbuffer
1353       \startbuffer[AccStateVHDL]
1354         entity accComponent_1 is
1355              port (\izAob3\ : in \unsigned_31\;
1356                    \foozAoBzAoB2\ : out \(,)unsigned_31\;
1357                    clock : in std_logic;
1358                    resetn : in std_logic);
1359         end entity accComponent_1;
1360
1361
1362         architecture structural of accComponent_1 is
1363              signal \szAod3\ : \unsigned_31\;
1364              signal \reszAonzAor3\ : \unsigned_31\;
1365         begin
1366              \reszAonzAor3\ <= \szAod3\ + \izAob3\;
1367              
1368              \foozAoBzAoB2\.A <= \reszAonzAor3\;
1369              
1370              state : process (clock, resetn)
1371              begin
1372                   if resetn = '0' then
1373                   elseif rising_edge(clock) then
1374                        \szAod3\ <= \reszAonzAor3\;
1375                   end if;
1376              end process state;
1377         end architecture structural;
1378       \stopbuffer 
1379     
1380       \placeexample[][ex:AccStateVHDL]{\VHDL generated for acc from \in{example}[ex:AvgState]}
1381           {\typebuffer[AccStateVHDL]}
1382       \placeexample[][ex:AvgStateVHDL]{\VHDL generated for avg from \in{example}[ex:AvgState]}
1383           {\typebuffer[AvgStateVHDL]}
1384 %    \subsection{Initial state}
1385 %      How to specify the initial state? Cannot be done inside a hardware
1386 %      function, since the initial state is its own state argument for the first
1387 %      call (unless you add an explicit, synchronous reset port).
1388 %
1389 %      External init state is natural for simulation.
1390 %
1391 %      External init state works for hardware generation as well.
1392 %
1393 %      Implementation issues: state splitting, linking input to output state,
1394 %      checking usage constraints on state variables.
1395 %
1396 %      \todo{Implementation issues: Separate compilation, simplified core.}
1397 %
1398 % vim: set sw=2 sts=2 expandtab: