Fix a lot of things following from Jan's comments.
[matthijs/master-project/report.git] / Chapters / Future.tex
1 \chapter[chap:future]{Future work}
2 \section{Improved notation for hierarchical state}
3 The hierarchical state model requires quite some boilerplate code for unpacking
4 and distributing the input state and collecting and repacking the output
5 state.
6
7 \in{Example}[ex:NestedState] shows a simple composition of two stateful
8 functions, \hs{funca} and \hs{funcb}. The state annotation using the
9 \hs{State} newtype has been left out, for clarity and because the proposed
10 approach below cannot handle that (yet).
11
12 \startbuffer[NestedState]
13   type FooState = ( AState, BState )
14   foo :: Word -> FooState -> (FooState, Word)
15   foo in s = (s', outb)
16     where
17       (sa, sb) = s
18       (sa', outa) = funca in sa
19       (sb', outb) = funcb outa sb
20       s' = (sa', sb')
21 \stopbuffer
22 \placeexample[here][ex:NestedState]{Simple function composing two stateful
23                                     functions.}{\typebufferhs{NestedState}}
24
25 Since state handling always follows strict rules, there is really no other way
26 in which this state handling can be done (you can of course move some things
27 around from the where clause to the pattern or vice versa, but it would still
28 be effectively the same thing). This means it makes extra sense to hide this
29 boilerplate away. This would incur no flexibility cost at all, since there are
30 no other ways that would work.
31
32 One particular notation in Haskell that seems promising, is the \hs{do}
33 notation. This is meant to simplify Monad notation by hiding away some
34 details. It allows one to write a list of expressions, which are composited
35 using the monadic \emph{bind} operator, written in Haskell as \hs{>>}. For
36 example, the snippet:
37
38 \starthaskell
39 do
40   somefunc a
41   otherfunc b
42 \stophaskell
43
44 will be desugared into:
45
46 \starthaskell
47 (somefunc a) >> (otherfunc b)
48 \stophaskell
49
50 The main reason to have the monadic notation, is to be able to wrap
51 results of functions in a datatype (the \emph{monad}) that can contain
52 extra information, and hide extra behaviour in the binding operators.
53
54 The \hs{>>=} operator allows extracting the actual result of a function
55 and passing it to another function. Let's try to illustrate this from an
56 example. The following snippet:
57
58 \starthaskell
59 do
60   x <- somefunc a
61   otherfunc x
62 \stophaskell
63
64 will be desugared into:
65
66 \starthaskell
67 (somefunc a) >>= (\x -> otherfunc x)
68 \stophaskell
69
70 The \hs{\x -> ...} notation creates a lambda abstraction in Haskell,
71 that binds the \hs{x} variable. Here, the \hs{>>=} operator is supposed
72 to extract whatever result somefunc has and pass it to the lambda
73 expression created. This will probably not make the monadic notation
74 completely clear to a reader without prior experience with Haskell, but
75 it should serve to understand the following discussion.
76
77 The monadic notation could perhaps be used to compose a number of
78 stateful functions into another stateful computation. Perhaps this could
79 move all the boilerplate code into the \hs{>>} and \hs{>>=} operators.
80 Because the boilerplate is still there (it's not magically disappeared,
81 just moved into these functions), the compiler should still be able to compile
82 these descriptions without any special magic (though perhaps it should
83 always inline the binding operators to reveal the flow of values).
84
85 This highlights an important aspect of using a functional language for our
86 descriptions: We can use the language itself to provide abstractions of common
87 patterns, making our code smaller and easier to read.
88
89 \subsection{Breaking out of the Monad}
90 However, simply using the monad notation is not as easy as it sounds. The main
91 problem is that the Monad type class poses a number of limitations on the
92 bind operator \hs{>>}. Most importantly, it has the following type signature:
93
94 \starthaskell
95 (>>) :: (Monad m) => m a -> m b -> m b
96 \stophaskell
97
98 This means that any expression in our composition must use the same Monad
99 instance as its type, only the "return" value can be different between
100 expressions. 
101
102 Ideally, we would like the \hs{>>} operator to have a type like the following
103 \starthaskell
104 type Stateful s r = s -> (s, r)
105 (>>) :: Stateful s1 r1 -> Stateful s2 r2 -> Stateful (s1, s2) r2
106 \stophaskell
107
108 What we see here, is that when we compose two stateful functions (that
109 have already been applied to their inputs, leaving just the state
110 argument to be applied to), the result is again a stateful function
111 whose state is composed of the two \emph{substates}. The return value is
112 simply the return value of the second function, discarding the first (to
113 preserve that result, the \hs{>>=} operator can be used).
114
115 There is a trick we can apply to change the signature of the \hs{>>} operator.
116 \small{GHC} does not require the bind operators to be part of the \hs{Monad}
117 type class, as long as it can use them to translate the do notation. This
118 means we can define our own \hs{>>} and \hs{>>=} operators, outside of the
119 \hs{Monad} typeclass. This does conflict with the existing methods of the
120 \hs{Monad} typeclass, so we should prevent \small{GHC} from loading those (and
121 all of the Prelude) by passing \type{-XNoImplicitPrelude} to \type{ghc}. This
122 is slightly inconvenient, but since we hardly using anything from the prelude,
123 this is not a big problem. We might even be able to replace some of the
124 Prelude with hardware-translateable versions by doing this.
125
126 The binding operators can now be defined exactly as they are needed. For
127 completeness, the \hs{return} function is also defined. It is not called
128 by \small{GHC} implicitely, but can be called explicitely by a hardware
129 description. \in{Example}[ex:StateMonad] shows these definitions.
130
131 \startbuffer[StateMonad]
132 (>>) :: Stateful s1 r1 -> Stateful s2 r2 -> Stateful (s1, s2) r2
133 f1 >> f2 = f1 >>= \_ -> f2
134
135 (>>=) :: Stateful s1 r1 -> (r1 -> Stateful s2 r2) -> Stateful (s1, s2) r2
136 f1 >>= f2 = \(s1, s2) -> let (s1', r1) = f1 s1
137                              (s2', r2) = f2 r1 s2
138                          in ((s1', s2'), r2)
139                
140 return :: r -> Stateful () r
141 return r = \s -> (s, r)
142 \stopbuffer
143 \placeexample[here][ex:StateMonad]{Binding operators to compose stateful computations}
144   {\typebufferhs{StateMonad}}
145
146 These definitions closely resemble the boilerplate of unpacking state,
147 passing it to two functions and repacking the new state. With these
148 definitions, we could have writting \in{example}[ex:NestedState] a lot
149 shorter, see \in{example}[ex:DoState]. In this example the type signature of
150 foo is the same (though it is now written using the \hs{Stateful} type
151 synonym, it is still completely equivalent to the original: \hs{foo :: Word ->
152 FooState -> (FooState, Word)}.
153
154 Note that the \hs{FooState} type has changed (so indirectly the type of
155 \hs{foo} as well). Since the state composition by the \hs{>>} works on two
156 stateful functions at a time, the final state consists of nested two-tuples.
157 The final \hs{()} in the state originates from the fact that the \hs{return}
158 function has no real state, but is part of the composition. We could have left
159 out the return expression (and the \hs{outb <-} part) to make \hs{foo}'s return
160 value equal to \hs{funcb}'s, but this approach makes it clearer what is
161 happening.
162
163 \startbuffer[DoState]
164   type FooState = ( AState, (BState, ()) )
165   foo :: Word -> Stateful FooState Word
166   foo in = do
167       outa <- funca in
168       outb <- funcb outa
169       return outb
170 \stopbuffer
171 \placeexample[][ex:DoState]{Simple function composing two stateful
172                                 functions, using do notation.}
173                                {\typebufferhs{DoState}}
174
175 An important implication of this approach is that the order of writing
176 function applications affects the state type. Fortunately, this problem can be
177 localized by consistently using type synonyms for state types, which should
178 prevent changes in other function's source when a function changes.
179
180 A less obvous implications of this approach is that the scope of variables
181 produced by each of these expressions (using the \hs{<-} syntax) is limited to
182 the expressions that come after it. This prevents values from flowing between
183 two functions (components) in two directions. For most Monad instances, this
184 is a requirement, but here it could have been different.
185
186 \todo{Add examples or reference for state synonyms}
187
188 \subsection{Alternative syntax}
189 Because of these typing issues, misusing Haskell's do notation is probably not
190 the best solution here. However, it does show that using fairly simple
191 abstractions, we could hide a lot of the boilerplate code. Extending
192 \small{GHC} with some new syntax sugar similar to the do notation might be a
193 feasible.
194
195 \subsection{Arrows}
196 Another abstraction mechanism offered by Haskell are arrows. Arrows are
197 a generalisation of monads \cite[hughes98], for which \GHC also supports
198 some syntax sugar \cite[paterson01]. Their use for hiding away state
199 boilerplate is not directly evident, but since arrows are a complex
200 concept further investigation is appropriate.
201
202 \section[sec:future:pipelining]{Improved notation or abstraction for pipelining}
203 Since pipelining is a very common optimization for hardware systems, it should
204 be easy to specify a pipelined system. Since it introduces quite some registers
205 into an otherwise regular combinatoric system, we might look for some way to
206 abstract away some of the boilerplate for pipelining.
207
208 Something similar to the state boilerplate removal above might be appropriate:
209 Abstract away some of the boilerplate code using combinators, then hide away
210 the combinators in special syntax. The combinators will be slightly different,
211 since there is a (typing) distinction between a pipeline stage and a pipeline
212 consisting of multiple stages. Also, it seems necessary to treat either the
213 first or the last pipeline stage differently, to prevent an off-by-one error
214 in the amount of registers (which is similar to the extra \hs{()} state type
215 in \in{example}[ex:DoState], which is harmless there, but would be a problem
216 if it introduced an extra, useless, pipeline stage).
217
218 This problem is slightly more complex than the problem we've seen before. One
219 significant difference is that each variable that crosses a stage boundary
220 needs a register. However, when a variable crosses multiple stage boundaries,
221 it must be stored for a longer period and should receive multiple registers.
222 Since we can't find out from the combinator code where the result of the
223 combined values is used (at least not without using Template Haskell to
224 inspect the \small{AST}), there seems to be no easy way to find how much
225 registers are needed.
226
227 There seem to be two obvious ways of handling this problem:
228
229 \startitemize
230   \item Limit the scoping of each variable produced by a stage to the next
231   stage only. This means that any variables that are to be used in subsequent
232   stages should be passed on explicitely, which should allocate the required
233   number of registers.
234
235   This produces cumbersome code, where there is still a lot of explicitness
236   (though this could be hidden in syntax sugar).
237   \todo{The next sentence is unclear}
238   \item Scope each variable over every subsequent pipeline stage and allocate
239   the maximum amount of registers that \emph{could} be needed. This means we
240   will allocate registers that are never used, but those could be optimized
241   away later. This does mean we need some way to introduce a variable number
242   of variables (depending on the total number of stages), assign the output of
243   a different register to each (\eg., a different part of the state) and scope
244   a different one of them over each the subsequent stages.
245
246   This also means that when adding a stage to an existing pipeline will change
247   the state type of each of the subsequent pipeline stages, and the state type
248   ofthe added stage depends on the number of subsequent stages.
249
250   Properly describing this will probably also require quite explicit syntax,
251   meaning this is not feasible without some special syntax.
252 \stopitemize
253
254 Some other interesting issues include pipeline stages which are already
255 stateful, mixing pipelined with normal computation, etc.
256
257 \section{Recursion}
258 The main problems of recursion have been described in
259 \in{section}[sec:recursion]. In the current implementation, recursion is
260 therefore not possible, instead we rely on a number of implicitly list-recursive
261 builtin functions.
262
263 Since recursion is a very important and central concept in functional
264 programming, it would very much improve the flexibility and elegance of our
265 hardware descriptions if we could support (full) recursion.
266
267 For this, there are two main problems to solve:
268
269 \startitemize
270 \item For list recursion, how to make a description type check? It is quite
271 possible that improvements in the \small{GHC} typechecker will make this
272 possible, though it will still stay a challenge. Further advances in
273 dependent typing support for Haskell will probably help here as well.
274
275 \todo{Reference Christiaan and other type-level work
276 (http://personal.cis.strath.ac.uk/conor/pub/she/)}
277 \item For all recursion, there is the obvious challenge of deciding when
278 recursion is finished. For list recursion, this might be easier (Since the
279 base case of the recursion influences the type signatures). For general
280 recursion, this requires a complete set of simplification and evaluation
281 transformations to prevent infinite expansion. The main challenge here is how
282 to make this set complete, or at least define the constraints on possible
283 recursion that guarantee it will work.
284
285 \todo{Reference Christian for loop unrolling?}
286 \stopitemize
287
288 \section{Multiple clock domains and asynchronicity}
289 Cλash currently only supports synchronous systems with a single clock domain.
290 In a lot of real-world systems, both of these limitations pose problems.
291
292 There might be asynchronous events to which a system wants to respond. The
293 most obvious asynchronous event is of course a reset signal. Though a reset
294 signal can be synchronous, that is less flexible (and a hassle to describe in
295 Cλash, currently). Since every function in Cλash describes the behaviour on
296 each cycle boundary, we really can't fit in asynchronous behaviour easily.
297
298 Due to the same reason, multiple clock domains cannot be easily supported. There is
299 currently no way for the compiler to know in which clock domain a function
300 should operate and since the clock signal is never explicit, there is also no
301 way to express circuits that synchronize various clock domains.
302
303 A possible way to express more complex timing behaviour would be to make
304 functions more generic event handlers, where the system generates a stream of
305 events (Like \quote{clock up}, \quote{clock down}, \quote{input A changed},
306 \quote{reset}, etc.). When working with multiple clock domains, each domain
307 could get its own clock events.
308
309 \startbuffer[AsyncDesc]
310 data Event = ClockUp | Reset | ...
311
312 type MainState = State Word
313
314 -- Initial state
315 initstate :: MainState
316 initstate = State 0
317
318 main :: Word -> Event -> MainState -> (MainState, Word)
319 main inp event (State acc) = (State acc', acc')
320   where
321     acc' = case event of
322       -- On a reset signal, reset the accumulator and output
323       Reset -> initstate
324       -- On a normal clock cycle, accumulate the result of func
325       ClockUp -> acc + (func inp event)
326       -- On any other event, leave state and output unchanged
327       _ -> acc
328
329 -- func is some combinatoric expression
330 func :: Word -> Event -> Word
331 func inp _ = inp * 2 + 3
332 \stopbuffer
333
334 \placeexample[][ex:AsyncDesc]{Hardware description using asynchronous events.}
335   {\typebufferhs{AsyncDesc}}
336
337 \todo{Picture}
338
339 \in{Example}[ex:AsyncDesc] shows a simple example of this event-based
340 approach. In this example we see that every function takes an input of
341 type \hs{Event}. The function \hs{main} that takes the output of
342 \hs{func} and accumulates it on every clock cycle. On a reset signal,
343 the accumulator is reset. The function \hs{func} is just a combinatoric
344 function, with no synchronous elements.  We can see this because there
345 is no state and the event input is completely ignored. If the compiler
346 is smart enough, we could even leave the event input out for functions
347 that don't use it, either because they are completely combinatoric (like
348 in this example), or because they rely on the the caller to select the
349 clock signal.
350
351 This structure is similar to the event handling structure used to perform I/O
352 in languages like Amanda. \todo{ref} There is a top level case expression that
353 decides what to do depending on the current input event.
354
355 A slightly more complex example is show in
356 \in{example}[ex:MulticlockDesc]. It shows a system with two clock
357 domains. There is no real integration between the clock domains in this
358 example (there is one input and one output for each clock domain), but
359 it does show how multiple clocks can be distinguished.
360
361 \startbuffer[MulticlockDesc]
362 data Event = ClockUpA | ClockUpB | ...
363
364 type MainState = State (SubAState, SubBState)
365
366 -- Initial state
367 initstate :: MainState
368 initstate = State (initsubastate, initsubbstate)
369
370 main :: Word -> Word -> Event -> MainState -> (MainState, Word, Word)
371 main inpa inpb event (State (sa, sb)) = (State (sa', sb'), outa, outb)
372   where
373     -- Only update the substates if the corresponding clock has an up
374     -- transition.
375     sa' = case event of
376       ClockUpA -> sa''
377       _ -> sa
378     sb' = case event of
379       ClockUpB -> sb''
380       _ -> sb
381     -- Always call suba and subb, so we can always have a value for our output
382     -- ports.
383     (sa'', outa) = suba inpa sa
384     (sb'', outb) = subb inpb sb
385
386 type SubAState = State ...
387 suba :: Word -> SubAState -> (SubAState, Word)
388 suba = ...
389
390 type SubBState = State ...
391 subb :: Word -> SubAState -> (SubAState, Word)
392 subb = ...
393 \stopbuffer
394
395 \placeexample[][ex:MulticlockDesc]{Hardware description with multiple clock domains through events.}
396   {\typebufferhs{MulticlockDesc}}
397
398 Note that in \in{example}[ex:MulticlockDesc] the \hs{suba} and \hs{subb}
399 functions are \emph{always} called, to get at their combinatoric
400 outputs. The new state is calculated as well, but only saved when the
401 right clock has an up transition.
402
403 As you can see, there is some code duplication in the case expression that
404 selects the right clock. One of the advantages of an explicit approach like
405 this, is that some of this duplication can be extracted away into helper
406 functions. For example, we could imagine a \hs{select_clock} function, which
407 takes a stateful function that is not aware of events, and changes it into a
408 function that only updates its state on a specific (clock) event. Such a
409 function is shown in \in{example}[ex:SelectClock].
410
411 \startbuffer[SelectClock]
412 select_clock :: Event
413                 -> (input -> State s -> (State s, output))
414                 -> (input -> State s -> Event -> (State s, output))
415 select_clock clock func inp state event = (state', out)
416   where
417     state' = if clock == event then state'' else state
418     (state'', out) = func inp state
419
420 main :: Word -> Word -> Event -> MainState -> (MainState, Word, Word)
421 main inpa inpb event (State (sa, sb)) = (State (sa', sb'), outa, outb)
422   where
423     (sa'', outa) = (select_clock ClockUpA suba) inpa sa event
424     (sb'', outb) = (select_clock ClockUpB subb) inpb sb event
425 \stopbuffer
426 \placeexample[][ex:SelectClock]{A function to filter clock events.}
427   {\typebufferhs{SelectClock}}
428
429 As you can see, this can greatly reduce the length of the main function, while
430 increasing the readability. As you might also have noted, the select\_clock
431 function takes any stateful function from the current Cλash prototype and
432 turns it into an event-aware function!
433
434 Going along this route for more complex timing behaviour seems promising,
435 espicially since it seems possible to express very advanced timing behaviours,
436 while still allowing simple functions without any extra overhead when complex
437 behaviour is not needed.
438
439 The main cost of this approach will probably be extra complexity in the
440 compiler: The paths (state) data can take become very non-trivial, and it
441 is probably hard to properly analyze these paths and produce the
442 intended \VHDL description.
443
444 \section{Multiple cycle descriptions}
445 In the current Cλash prototype, every description is a single-cycle
446 description. In other words, every function describes behaviour for each
447 separate cycle and any recursion (or folds, maps, etc.) is expanded in space.
448
449 Sometimes, you might want to have a complex description that could possibly
450 take multiple cycles. Some examples include:
451
452 \startitemize
453   \item Some kind of map or fold over a list that could be expanded in time
454   instead of space. This would result in a function that describes n cycles
455   instead of just one, where n is the lenght of the list.
456   \item A large combinatoric expressions that would introduce a very long
457   combinatoric path and thus limit clock frequency. Such an expression could
458   be broken up into multiple stages, which effectively results in a pipelined
459   system (see also \in{section}[sec:future:pipelining]) with a known delay.
460   There should probably be some way for the developer to specify the cycle
461   division of the expression, since automatically deciding on such a division
462   is too complex and contains too many tradeoffs, at least initially.
463   \item Unbounded recursion. It is not possible to expand unbounded (or even
464   recursion with a depth that is not known at compile time) in space, since
465   there is no way to tell how much hardware to create (it might even be
466   infinite).
467
468   When expanding infinite recursion over time, each step of the recursion can
469   simply become a single clockcycle. When expanding bounded but unknown
470   recursion, we probably need to add an extra data valid output bit or
471   something similar.
472 \stopitemize
473
474 Apart from translating each of these multiple cycle descriptions into a per-cycle
475 description, we also need to somehow match the type signature of the multiple
476 cycle description to the type signature of the single cycle description that
477 the rest of the system expects (assuming that the rest of the system is
478 described in the \quote{normal} per-cycle manner). For example, an infinitely
479 recursive expression typically has the return type \lam{[a]}, while the rest
480 of the system would expect just \lam{a} (since the recursive expression
481 generates just a single element each cycle).
482
483 Naively, this matching could be done using a (builtin) function with a
484 signature like \lam{[a] -> a}, which also serves as an indicator to the
485 compiler that some expanding over time is required. However, this poses a
486 problem for simulation: How will our Haskell implementation of this magical
487 builtin function know which element of the input list to return. This
488 obviously depends on the current cycle number, but there is no way for this
489 function to know the current cycle without breaking all kinds of safety and
490 purity properties. Making this function have some state input and output could
491 help, though this state is not present in the actual hardware (or perhaps
492 there is some state, if there are value passed from one recursion step to the
493 next, but how can the type of that state be determined by the typechecker?).
494
495 It seems that this is the most pressing problem for multicycle descriptions:
496 How to interface with the rest of the system, without sacrificing safety and
497 simulation capabilities?
498
499 \section{Higher order values in state}
500 Another interesting idea is putting a higher order value inside a function's
501 state value. Since we can use higher order values anywhere, why not in the
502 state?
503
504 \startbuffer[HigherAccum]
505 -- The accumulator function that takes a word and returns a new accumulator
506 -- and the result so far. This is the function we want to put inside the
507 -- state.
508 type Acc = Word -> (Acc, Word)
509 acc = \a -> (\b -> acc ( a + b ), a )
510
511 main :: Word -> State Acc -> (State Acc, Word)
512 main a s = (State s', out)
513   where (s', out) = s a
514 \stopbuffer
515 \placeexample[][ex:HigherAccum]{An accumulator using a higher order state.}
516   {\typebufferhs{HigherAccum}}
517
518 As a (contrived) example, consider the accumulator in
519 \in{example}[ex:HigherAccum]. This code uses a function as its state,
520 which implicitely contains the value accumulated so far. This is a
521 fairly trivial example, that is more easy to write with a simple
522 \hs{Word} state value, but for more complex descriptions this style
523 might pay off. Note that in a way we are using the \emph{continuation
524 passing style} of writing functions, where we pass a sort of
525 \emph{continuation} from one cycle to the next.
526
527 Our normalization process completely removes higher order values inside a
528 function by moving applications and higher order values around so that every
529 higher order value will eventually be full applied. However, if we would put a
530 higher order value inside our state, the path from the higher order value
531 definition to its application runs through the state, which is external to the
532 function. A higher order value defined in one cycle is not applied until a
533 later cycle. Our normalization process only works within the function, so it
534 cannot remove this use of a higher order value.
535
536 However, we cannot leave a higher order value in our state value, since it is
537 impossible to generate a register containing a higher order value, we simply
538 can't translate a function type to a hardware type. To solve this, we must
539 replace the higher order value inside our state with some other value
540 representing these higher order values.
541
542 On obvious approach here is to use an algebraic datatype where each
543 constructor represents one possible higher order value that can end up in the
544 state and each constructor has an argument for each free variable of the
545 higher order value replaced. This allows us to completely reconstruct the
546 higher order value at the spot where it is applied, and thus the higher order
547 value disappears.
548
549 This approach is commonly known as the \quote{Reynolds approach to
550 defuntionalization}, first described by J.C. Reynolds and seems to apply well
551 to this situation. One note here is that Reynolds' approach puts all the
552 higher order values in a single datatype. For a typed language, we will at
553 least have to have a single datatype for each function type, since we can't
554 mix them. It would be even better to split these datatypes a bit further, so
555 that such a datatype will never hold a constructor that is never used for a
556 particular state variable. This separation is probably a non-trivial problem,
557 though.
558
559 \todo{Reference "Definitional interpreters for higher-order programming
560 languages":
561 http://portal.acm.org/citation.cfm?id=805852\&dl=GUIDE\&coll=GUIDE\&CFID=58835435\&CFTOKEN=81856623}
562
563 \section{New language}
564 During the development of the prototype, it has become clear that Haskell is
565 not the perfect language for this work. There are two main problems:
566 \startitemize
567 \item Haskell is not expressive enough. Haskell is still quite new in the area
568 of dependent typing, something we use extensively. Also, Haskell has some
569 special syntax to write monadic composition and arrow composition, which is
570 well suited to normal Haskell programs. However, for our hardware
571 descriptions, we could use some similar, but other, syntactic sugar (as we
572 have seen above).
573 \item Haskell is too expressive. There are some things that Haskell can
574 express, but we can never properly translate. There are certain types (both
575 primitive types and certain type constructions like recursive types) we can
576 never translate, as well as certain forms of recursion.
577 \stopitemize
578
579 It might be good to reevaluate the choice of language for Cλash, perhaps there
580 are other languages which are better suited to describe hardware, now that
581 we've learned a lot about it.
582
583 Perhaps Haskell (or some other language) can be extended by using a
584 preprocessor. There has been some (point of proof) work on a the Strathclyde
585 Haskell Enhancement (\small{SHE}) preprocessor for type-level programming,
586 perhaps we can extend that, or create something similar for hardware-specific
587 notation.
588
589 It is not unlikely that the most flexible way
590 forward would be to define a completely new language with exactly the needed
591 features. This is of course an enormous effort, which should not be taken
592 lightly.
593
594 \section{Don't care values}
595   A powerful value in \VHDL is the \emph{don't care} value, given as
596   \type{'-'}. This value tells the compiler that you don't really care about
597   which value is assigned to a signal, allowing the compiler to make some
598   optimizations. Since hardware choice in hardware is often implemented using
599   a collection of logic gates instead of multiplexers only, synthesizers can
600   often reduce the amount of hardware needed by smartly choosing values for
601   these don't care cases.
602
603   There is not really anything comparable with don't care values in normal
604   programming languages. The closest thing is an undefined or uninitialized
605   value, though those are usually associated with error conditions.
606
607   It would be useful if Cλash also has some way to specify don't care values.
608   When looking at the Haskell typing system, there are really two ways to do
609   this:
610
611   \startitemize
612     \item Add a special don't care value to every datatype. This includes the
613     obvious \hs{Bit} type, but will also need to include every user defined
614     type. An exception can be made for vectors and product types, since those
615     can simply use the don't care values of the types they contain.
616
617     This would also require some kind of \quote{Dont careable} type class
618     that allows each type to specify what its don't care value is. The
619     compiler must then recognize this constant and replace it with don't care
620     values in the final \VHDL code.
621
622     This is of course a very intrusive solution. Every type must become member
623     of this typeclass, and there is now some member in every type that is a
624     special don't care value. Guaranteeing the obvious don't care semantics
625     also becomes harder, since every pattern match or case expressions must now
626     also take care of the don't care value (this might actually be an
627     advantage, since it forces designers to specify how to handle don't care
628     for different operations).
629
630     \item Use the special \hs{undefined}, or \emph{bottom} value present in
631     Haskell. This is a type that is member of all types automatically, without
632     any explicit declarations.
633
634     Any expression that requires evaluation of an undefined value
635     automatically becomes undefined itself (or rather, there is some exception
636     mechanism). Since Haskell is lazy, this means that whenever it tries to
637     evaluate undefined, it is apparently required for determining the output
638     of the system. This property is useful, since typically a don't care
639     output is used when some output is not valid and should not be read. If
640     it is in fact not read, it should never be evaluated and simulation should
641     be fine.
642
643     In practice, this works less ideal. In particular, pattern matching is not
644     always smart enough to deal with undefined. Consider the following
645     definition of an \hs{and} operator:
646
647     \starthaskell
648     or :: Bit -> Bit -> Bit
649     and Low _ = Low
650     and _ Low = Low
651     and High High = High
652     \stophaskell
653
654     When using the \hs{and} operation on an undefined (don't care) and a Low
655     value should always return a Low value. Its value does not depend on the
656     value chosen for the don't care value. However, though when applying the
657     above and function to \hs{Low} and \hs{undefined} results in exactly that
658     behviour, the result is \hs{undefined} when the arguments are swapped.
659     This is because the first pattern forces the first argument to be
660     evaluated. If it is \hs{undefined}, evaluation is halted and an exception
661     is show, which is not what is intended.
662   \stopitemize
663
664   These options should be explored further to see if they provide feasible
665   methods for describing don't care conditions. Possibly there are completely
666   other methods which work better.
667
668 \section{Correctness proofs of the normalization system}
669 As stated in \in{section}[sec:normalization:properties], there are a
670 number of properties we would like to see verified about the
671 normalization system.  In particular, the \emph{termination} and
672 \emph{completeness} of the system would be a good candidate for future
673 research. Specifying formal semantics for the Core language in
674 order to verify the \emph{soundness} of the system would be an even more
675 challenging task.
676 % vim: set sw=2 sts=2 expandtab: