www

Unnamed repository; edit this file 'description' to name the repository.
Log | Files | Refs | README

state-of-the-art.scrbl (30902B)


      1 #lang scribble/manual
      2 
      3 @require["util.rkt"
      4          scribble/core
      5          scribble/latex-properties
      6          scriblib/render-cond]
      7 @(use-mathjax)
      8 
      9 @title[#:style (with-html5 manual-doc-style)
     10        #:version (version-text)]{State of the art}
     11 
     12 @htodo{sablecc, treecc, pipelines}
     13 
     14 @asection{
     15  @atitle[#:tag "related-type-expander"]{Extending the type system via macros}
     16 
     17  Our work explores one interesting use of macros: their use to extend a
     18  programming language's type system.
     19 
     20  Chang, Knauth and Greenman@~cite["chang2017type-systems-as-macros"] took
     21  the decision to depart from @|typedracket|, and implemented a new approach,
     22  which allows type systems to be implemented as macros. Typing information
     23  about identifiers is threaded across the program at compile-time, and macros
     24  can decide whether a term is well-typed or not.
     25 
     26  Another related project is Cur@note{@url{https://github.com/wilbowma/cur}}, a
     27  dependent type system implemented using Racket macros.
     28 
     29  Bracha suggests that pluggable type systems should be
     30  used@~cite["bracha2004pluggable-types"]. Such a system, JavaCOP is presented by
     31  Andreae, Noble, Markstrum and
     32  Shane@~cite["pluggable-types-andreae2006framework"] as a tool which ``enforces
     33  user-defined typing constraints written in a declarative and expressive rule
     34  language''.
     35 
     36  In contrast, @|typedracket|@~cite["tobin-hochstadt_design_2008"] was
     37  implemented using macros on top of ``untyped'' Racket, but was not
     38  designed as an extensible system: new rules in the type system must be
     39  added to the core implementation, a system which is complex to approach.
     40 
     41  Following work by Asumu
     42  Takikawa@note{@url{https://github.com/racket/racket/pull/604}}, we
     43  extended @|typedracket| with support for macros in the type declarations and
     44  annotations. We call this sort of macro ``type expanders'', following the
     45  commonly-used naming convention (e.g. ``match expanders'' are macros which
     46  operate within patterns in pattern-matching forms). These type expanders
     47  allow users to easily extend the type system with new kinds of types, as
     48  long as these can be translated back to the types offered natively by
     49  @|typedracket|.
     50 
     51  While the Type Systems as Macros by Chang, Knauth and
     52  Greenman@~cite["chang2017type-systems-as-macros"] allows greater flexibility
     53  by not relying on a fixed set of core types, it also places on the
     54  programmer the burden of ensuring that the type checking macros are
     55  sound. In contrast, our type expanders rely on @|typedracket|'s type
     56  checker, which will still catch type errors in the fully-expanded
     57  types. In other words, writing type expanders is safe, because they do not
     58  require any specific trust, and translate down to plain @|typedracket|
     59  types, where any type error would be caught at that level.
     60 
     61  An interesting aspect of our work is that the support for type expanders
     62  was implemented without any change to the core of @|typedracket|. Instead,
     63  the support for type expanders itself is available as a library, which
     64  overrides special forms like @tt{define}, @tt{lambda} or
     65  @tt{cast}, enhancing them by pre-processing type expanders, and
     66  translating back to the ``official'' forms from @|typedracket|. It is worth
     67  noting that @|typedracket| itself is implemented in a similar way: special
     68  forms like @tt{define} and @tt{lambda} support plain type
     69  annotations, and translate back to the ``official'' forms from so-called
     70  ``untyped'' Racket. In both cases, this approach goes with the Racket
     71  spirit of implementing languages as
     72  libraries@~cite["tobin-hochstadt_languages_as_libraries_2011"]}
     73 
     74 @asection{ @atitle[#:tag "related-adt"]{Algebraic datatypes for compilers}
     75  @epigraph["Personal communication from a friend"]{I used polymorphic variants
     76   @htodo{this winter} to solve the @tt{assert false} problems in my @htodo{put
     77    the language name here if I'm allowed to quote} lexical analyser, along with
     78   some subtyping. You have to write the typecasts explicitly, but that aside it
     79   is very powerful (a constructor can “belong” to several types etc.).}
     80   
     81  The @tt{phc-adt} library implements algebraic datatypes (variants and
     82  structures) which are adapted to compiler-writing.
     83 
     84  There is an existing ``simple'' datatype library for @|typedracket| (source
     85  code available at @url{https://github.com/pnwamk/datatype}). It differs
     86  from our library on several points:
     87  @itemlist[
     88  @item{``datatype'' uses nominal typing, while we use structural typing
     89    (i.e. two identical type declarations in distinct modules yield the same
     90    type in our case). This avoids the need to centralize the type
     91    definition of ASTs.}
     92  @item{``datatype'' uses closed variants, where a constructor can only
     93    belong to one variant. We simply define variants as a union of
     94    constructors, where a constructor can belong to several variants. This
     95    allows later passes in the compiler to add or remove cases of variants,
     96    without the need to duplicate all the constructors under slightly
     97    different names.}
     98  @item{``datatype'' does not support row polymorphism, or similarly the
     99    update and extension of its product types with values for existing and
    100    new fields, regardless of optional fields. We implement the
    101    latter.@htodo{ Probably the former too.}}]
    102 
    103  @todo{Cite the variations on variants paper (for Haskell)}
    104 
    105  @asection{
    106   @atitle{The case for bounded row polymorphism}
    107   @todo{Explain the ``expression problem''.}
    108   @todo{Talk about the various ways in which it can be ``solved'', and which
    109    tradeoffs we aim for. Mention @cond-element[
    110  [html @elem{
    111       @seclink["top"
    112                #:doc
    113                '(lib
    114                  "extensible-functions/documentation/extensible-functions.scrbl"
    115                  )]{extensible-functions}}]
    116  [else @elem{extensible-functions@note{@url{
    117     http://docs.racket-lang.org/extensible-functions}}}]], another solution
    118    to the expression problem in Racket, but with rather different
    119    tradeoffs.}
    120 
    121   We strive to implement compilers using many passes. A pass should be
    122   able to accept a real-world AST, and produce accordingly a real-world
    123   transformed AST as its output. It should also be possible to use
    124   lightweight ``mock'' ASTs, containing only the values relevant to the
    125   passes under test (possibly only the pass being called, or multiple
    126   passes tested from end to end). The pass should then return a
    127   corresponding simplified output AST, omitting the fields which are
    128   irrelevant to this pass (and were not part of the input). Since the
    129   results of the pass on a real input and on a test input are equivalent
    130   modulo the irrelevant fields, this allows testing the pass in isolation
    131   with simple data, without having to fill in each irrelevant field with
    132   @tt{null} (and hope that they are indeed irrelevant, without a
    133   comforting guarantee that this is the case), as is commonly done when
    134   creating ``mocks'' to test object-oriented programs.
    135 
    136   This can be identified as a problem similar to the ``expression
    137   problem''. In our context, we do not strive to build a compiler which
    138   can be extended in an ``open world'', by adding new node types to the
    139   AST, or new operations handling these nodes. Rather, the desired outcome
    140   is to allow passes to support multiple known subsets of the same AST
    141   type, from the start.
    142 
    143   We succinctly list below some of the different sorts of polymorphism,
    144   and argue that row polymorphism is well-suited for our purpose. More
    145   specifically, bounded row polymorphism gives the flexibility needed when
    146   defining passes which keep some fields intact (without reading their
    147   value), but the boundedness ensures that changes in the input type of a
    148   pass do not go unnoticed, so that the pass can be amended to handle the
    149   new information, or its type can be updated to ignore this new
    150   information.
    151 
    152   @subsubsub*section{Subtyping, polymorphism and alternatives}
    153   @|~|@(linebreak)
    154   @~cite["ducournau-cours-lots"].  @htodo{The course includes a couple of
    155    other kinds of polymorphism and subtyping (or makes finer distinctions
    156    than in the list below). Refine and augment the list below using
    157    Roland's classification.} @htodo{Probably also cite:}
    158   @~cite["cardelli1985understanding"] @htodo{(apparently does not cover
    159    ``Higher-Kinded Polymorphism'', ``Structural Polymorphism'' and ``Row
    160    Polymorphism'')}
    161   @itemlist[
    162  @item{Subtyping (also called inclusion polymorphism, subtype
    163     polymorphism, or nominal subtyping ?): Subclasses and interfaces in
    164     @csharp and Java, sub-structs and union types in @|typedracket|,
    165     polymorphic variants in @CAML
    166     @~cite[#:precision @list{chap. 6, sec. Polymorphic Variants}
    167            "minsky2013real"]}
    168  @; https://realworldocaml.org/v1/en/html/variants.html
    169         
    170  @; See also: use of exceptions as dynamically extensible sum types:
    171  @; http://caml-list.inria.narkive.com/VJcoGfvp/dynamically-extensible-sum-types
    172  @; 
    173  @; quote: I need a dynamically extensible sum type. I can think of three approaches:
    174  @; quote: 
    175  @; quote: (1) Use polymorphic variants: `Foo of a * b, `Bar of c * d * e, etc
    176  @; quote: 
    177  @; quote: (2) Use exceptions: exception Foo of a * b, exception Bar of c * d * e, etc
    178  @; quote: 
    179  @; quote: (3) Use thunks: (fun () -> foo a b), (fun () -> bar c d e), etc
    180  @; quote: 
    181  @; quote: Using exceptions seems somewhat sneaky to me. Does it have any advantages over
    182  @; quote: polymorphic variants? The polymorphic variants seem like they might be better
    183  @; quote: since you could actually limit the domain of certain functions... thus, one
    184  @; quote: part of your program could be constrained to a subrange of the sum type, while
    185  @; quote: other parts could be opened up fully.
    186  @; quote: 
    187  @; quote: Until now I have been using the thunking approach in an event-based
    188  @; quote: architecture (each event on the queue is a unit->unit thunk). This seems to
    189  @; quote: work pretty well. But now I'm thinking that the other approaches would allow
    190  @; quote: arbitrary filters to be applied to events; i.e., the thunk approach imposes a
    191  @; quote: "read once" discipline on elements of the sum type, and in some applications
    192  @; quote: you might want "read multiple".
    193  @; quote: 
    194  @; quote: I'm not asking the question solely in terms of event-based architectures,
    195  @; quote: though, and I'm interested in others experience with the different approaches
    196  @; quote: to dynamically extensible sum types, and what led you to choose one approach
    197  @; quote: over the others. Thanks!
    198  @item{Multiple inheritance. @NIT, @CLOS, @CPP, @csharp interfaces, Java
    199     interfaces. As an extension in ``untyped'' Racket with Alexis King's
    200     safe multimethods@note{@url{https://lexi-lambda.github.io/blog/2016/02/18/simple-safe-multimethods-in-racket/}}.
    201         
    202     This in principle could help in our case: AST nodes would have
    203     @tt{.withField(value)} methods returning a copy of the node with
    204     the field's value updated, or a node of a different type with that
    205     new field, if it is not present in the initial node type. This would
    206     however require the declaration of many such methods in advance, so
    207     that they can be used when needed (or with a recording mechanism
    208     like the one we use, so that between compilations the methods called
    209     are remembered and generated on the fly by a macro). Furthermore,
    210     @typedracket lacks support for multiple inheritance on structs. It
    211     supports multiple inheritance for classes @todo{?}, but classes
    212     currently lack the ability to declare immutable fields, which in
    213     turn causes problems with occurrence typing (see the note in the
    214     ``row polymorphism'' point below).}
    215  @item{Parametric polymorphism: Generics in @csharp and Java,
    216     polymorphic types in @CAML and @typedracket}
    217  @item{F-bounded polymorphism: Java, @csharp, @CPP, Eiffel. Possible
    218     to mimic to some extent in @typedracket with (unbounded) parametric
    219     polymorphism and intersection types.
    220     @todo{Discuss how it would work/not work in our case.}}
    221  @item{Operator overloading (also called overloading polymorphism?) and
    222     multiple dispatch:
    223     @itemlist[
    224  @item{Operator overloading in @csharp}
    225  @item{Nothing in Java aside from the built-in cases for arithmetic and string concatenation, but those are not extensible}
    226  @item{@CPP}
    227  @item{typeclasses in Haskell? @todo{I'm not proficient enough in Haskell to
    228        be sure or give a detailed description, I have to ask around to double-check.}}
    229  @item{LISP (CLOS): has multiple dispatch}
    230  @item{nothing built-in in @|typedracket|.}
    231  @item{@|CAML|?}]}
    232  @item{Coercion polymorphism (automatic casts to a given type). This
    233     includes Scala's implicits, @csharp implicit coercion operators
    234     (user-extensible, but at most one coercion operator is applied
    235     automatically, so if there is a coercion operator @${A → B},
    236     and a coercion operator @${B → C}, it is still impossible to
    237     supply an @${A} where a @${C} is expected without manually coercing the
    238     value), and @CPP's implicit conversions, where single-argument
    239     constructors are treated as implicit conversion operators, unless
    240     annotated with the @tt{explicit} keyword.  Similarly to @csharp,
    241     @CPP allows only one implicit conversion, not two or more in a chain.
    242 
    243     Struct type properties in untyped Racket can somewhat be used to that
    244     effect, although they are closer to Java's interfaces than to coercion
    245     polymorphism. Struct type properties are unsound in @typedracket and are
    246     not represented within the type system, so their use is subject to caution
    247     anyway.}
    248  @item{Coercion (downcasts). Present in most typed languages. This
    249     would not help in our case, as the different AST types are
    250     incomparable (especially since @typedracket lacks multiple inheritance)}
    251 
    252         
    253  @item{Higher-kinded polymorphism: Type which is parameterized by a
    254     @${\mathit{Type} → \mathit{Type}} function. Scala, Haskell. Maybe
    255     @|CAML|?
    256 
    257     The type expander library which we developed for @typedracket
    258     supports @${Λ}, used to describe anonymous type-level
    259     macros. They enable some limited form of
    260     @${\mathit{Type} → \mathit{Type}} functions, but are
    261     actually applied at macro-expansion time, before typechecking is
    262     performed, which diminishes their use in some cases. For example,
    263     they cannot cooperate with type inference. Also, any recursive use
    264     of type-level macros must terminate, unless the type ``function''
    265     manually falls back to using @${\mathit{Rec}} to create a regular
    266     recursive type. This means that a declaration like
    267     @${F(X) := X × F(F(X))} is not possible using anonymous type-level
    268     macros only.
    269     @; See https://en.wikipedia.org/wiki/Recursive_data_type#Isorecursive_types
    270     @; Is this a matter of isorecursive vs equirecursive ?
    271 
    272     As an example of this use of the type expander library, our
    273     cycle-handling code uses internally a ``type traversal'' macro. In
    274     the type of a node, it performs a substitution on some subparts of
    275     the type. It is more or less a limited form of application of a
    276     whole family of type functions @${aᵢ → bᵢ}, which have the same inputs
    277     @${aᵢ …}, part of the initial type, but different outputs @${bᵢ …} which
    278     are substituted in place of the @${aᵢ …} in the resulting type. The
    279     ``type traversal'' macro expands the initial type into a standard
    280     polymorphic type, which accepts the desired outputs @${bᵢ …} as type
    281     arguments.}
    282  @item{Lenses. Can be in a way compared to explicit coercions, where
    283     the coercion is reversible and the accessible parts can be altered.}
    284  @item{Structural polymorphism (also sometimes called static duck-typing): Scala,
    285     TypeScript. It is also possible in @typedracket, using the algebraic
    286     datatypes library which we implemented. Possible to mimic in Java
    287     and @csharp with interfaces ``selecting'' the desired fields, but
    288     the interface has to be explicitly implemented by the class (i.e. at
    289     the definition site, not at the use-site).
    290 
    291     Palmer et al. present TinyBang@~cite["types-for-flexible-objects"], a
    292     typed language in which flexible manipulation of objects is possible,
    293     including adding and removing fields, as well as changing the type of
    294     a field. They implement in this way a sound, decidable form of static
    295     duck typing, with functional updates which can add new fields and
    296     replace the value of existing fields. Their approach is based on two
    297     main aspects:
    298     @itemlist[
    299  @item{@emph{Type-indexed records supporting asymmetric concatenation}:
    300       by concatenating two records @${r₁ \& r₂}, a new record is obtained
    301       containing all the fields from @${r₁} (associated to their value in
    302       @${r₁}), as well as the fields from @${r₂} which do not appear in @${r₁}
    303       (associated to their value in @${r₂}). Primitive types are eliminated
    304       by allowing the use of type names as keys in the records: integers
    305       then become simply records with a @${int} key, for example.}
    306  @item{@emph{Dependently-typed first-class cases}: pattern-matching
    307       functions are expressed as
    308       @${pattern \mathbin{\texttt{->}} expression}, and can be concatenated
    309       with the @${\&} operator, to obtain functions matching against
    310       different cases, possibly with a different result type for each
    311       case. The leftmost cases can shadow existing cases (i.e. the case
    312       which is used is the leftmost case for which the pattern matches
    313       successfully).}]
    314 
    315     TinyBang uses an approach which is very different from the one we
    316     followed in our Algebraic Data Types library, but contains the
    317     adequate primitives to build algebraic data types which would
    318     fulfill our requirements (aside from the ability to bound the set of
    319     extra ``row'' fields). We note that our flexible structs, which are
    320     used within the body of node-to-node functions in passes, do support
    321     an extension operation, which is similar to TinyBang's @${\&}, with
    322     the left-hand side containing a constant and fixed set of
    323     fields.@htodo{we probably can have / will have the ability to merge
    324      non-constant left-hand side values too.}}
    325  @item{Row polymorphism: Apparently, quoting a post on
    326     Quora@note{@hyperlink["https://www.quora.com/Object-Oriented-Programming-What-is-a-concise-definition-of-polymorphism"]{https://www.quora.com/Object-Oriented-Programming-What-is-a-concise-definition@|?-|-of-polymorphism}\label{quora-url-footnote}}:
    327     @aquote{
    328      Mostly only concatenative and functional languages (like Elm and PureScript) support this.
    329     }
    330 
    331     Classes in @typedracket can have a row type argument (but classes in
    332     @typedracket cannot have immutable fields (yet), and therefore
    333     occurrence typing does not work on class fields. Occurrence typing
    334     is an important idiom in @typedracket, used to achieve safe but
    335     concise pattern-matching, which is a feature frequently used when
    336     writing compilers).
    337 
    338     Our Algebraic Data Types library implements a bounded form of row
    339     polymorphism, and a separate implementation (used within the
    340     body of node-to-node functions in passes) allows unbounded row
    341     polymorphism.}
    342  @item{@todo{Virtual types}}
    343  @item{So-called ``untyped'' or ``uni-typed'' languages: naturally
    344     support most of the above, but without static checks.
    345 
    346     @htodo{
    347      @; phc/reading/CITE/Object-Oriented Programming_ What is a concise definition of polymorphism_ - Quora.html
    348      @; TODO: fix the footnote here!
    349      See also post on Quora@superscript{\ref{quora-url-footnote}},
    350      which links to @~cite["cardelli1985understanding"], and to a blog post by Sam
    351      Tobin-Hochstadt@note{@url["https://medium.com/@samth/on-typed-untyped-and-uni-typed-languages-8a3b4bedf68c"]}
    352      The blog post by Sam Tobin-Hochstadt explains how @typedracket tries to
    353      explore and understand how programmers think about programs written in
    354      so-called ``untyped'' languages (namely that the programmers still
    355      conceptually understand the arguments, variables etc as having a type (or a
    356      union of several types)). @todo{Try to find a better citation for that.}}
    357 
    358     Operator overloading can be present in ``untyped'' languages, but is
    359     really an incarnation of single or multiple dispatch, based on the
    360     run-time, dynamic type (as there is no static type based on which the
    361     operation could be chosen). However it is not possible in ``untyped''
    362     languages and languages compiled with type erasure to dispatch on
    363     ``types'' with a non-empty intersection: it is impossible to
    364     distinguish the values, and they are not annotated statically with a
    365     type.
    366 
    367     As mentioned above, @typedracket does not have operator overloading,
    368     and since the inferred types cannot be accessed reflectively at
    369     compile-time, it is not really possible to construct it as a
    370     compile-time feature via macros. @typedracket also uses type erasure,
    371     so the same limitation as for untyped languages applies when
    372     implementing some form of single or multiple dispatch at run-time ---
    373     namely the intersection of the types must be empty. @todo{Here,
    374      mention (and explain in more detail later) our compile-time
    375      ``empty-intersection check'' feature (does not work with polymorphic
    376      variables).}}]
    377 
    378   @todo{Overview of the existing ``solutions'' to the expression problems, make
    379    a summary table of their tradeoffs (verbosity, weaknesses, strengths).}
    380 
    381   @todo{Compare the various sorts of subtyping and polymorphism in that light
    382    (possibly in the same table), even those which do not directly pose as a
    383    solution to the expression problem.}
    384 
    385       
    386   ``Nominal types'': our tagged structures and node types are not nominal types.
    387 
    388   The ``trivial'' Racket library tracks static information about the types in
    389   simple cases. The ``turnstile'' Racket language @todo{is a follow-up} work,
    390   and allows to define new typed Racket languages. It tracks the types of
    391   values, as they are assigned to variables or passed as arguments to functions
    392   or macros. These libraries could be used to implement operator overloads which
    393   are based on the static type of the arguments. It could also be used to
    394   implement unbounded row polymorphism in a way that does not cause a
    395   combinatorial explosion of the size of the expanded code.@todo{Have a look at
    396    the implementation of row polymorphism in @typedracket classes, cite their
    397    work if there is something already published about it.}
    398 
    399   From the literate program (tagged-structure-low-level):
    400 
    401   @quotation{
    402    Row polymorphism, also known as "static duck typing" is a type system
    403    feature which allows a single type variable to be used as a place
    404    holder for several omitted fields, along with their types. The
    405    @tt{phc-adt} library supports a limited form of row polymorphism:
    406    for most operations, a set of tuples of omitted field names must be
    407    specified, thereby indicating a bound on the row type variable.
    408 
    409    This is both a limitation of our implementation (to reduce the
    410    combinatorial explosion of possible input and output types), as well as a
    411    desirable feature.  Indeed, this library is intended to be used to write
    412    compilers, and a compiler pass should have precise knowledge of the
    413    intermediate representation it manipulates. It is possible that a compiler
    414    pass may operate on several similar intermediate representations (for
    415    example a full-blown representation for actual compilation and a minimal
    416    representation for testing purposes), which makes row polymorphism
    417    desirable. It is however risky to allow as an input to a compiler pass any
    418    data structure containing at least the minimum set of required fields:
    419    changes in the intermediate representation may add new fields which should,
    420    semantically, be handled by the compiler pass. A catch-all row type variable
    421    would simply ignore the extra fields, without raising an error. Thanks to
    422    the bound which specifies the possible tuples of omitted field names,
    423    changes to the the input type will raise a type error, bringing the
    424    programmer's attention to the issue. If the new type is legit, and does not
    425    warrant a modification of the pass, the fix is easy to implement: simply
    426    adding a new tuple of possibly omitted fields to the bound (or replacing an
    427    existing tuple) will allow the pass to work with the new type.  If, on the
    428    other hand, the pass needs to be modified, the type system will have
    429    successfully caught a potential issue.
    430   }
    431  }
    432  }@;{Algrbraic datatypes for compilers (phc-adt)}
    433 
    434 @asection{
    435  @atitle[
    436  #:style (style #f
    437                 (list
    438                  (short-title "Writing compilers using many small passes")))
    439  #:tag "related-nanopass"
    440  ]{Writing compilers using many small passes @elem[
    441  #:style (style #f '(aux))]{(a.k.a following the Nanopass Compiler
    442    Framework philosophy)}}
    443 }
    444 
    445 @asection{
    446  @atitle[#:tag "related-cycles"]{Cycles in intermediate representations of
    447   programs}
    448 
    449  @todo{There already were a few references in my proposal for JFLA.}
    450  @todo{Look for articles about graph rewriting systems.}
    451 
    452  The following sections present the many ways in which cycles within the
    453  AST, CFG and other intermediate representations can be represented.
    454 
    455  @asection{
    456   @atitle{Mutable data structures}
    457 
    458   @itemlist[
    459  @item{Hard to debug}
    460  @item{When e.g. using lazy-loading, it is easy to mistakenly load a
    461     class or method after the Intermediate Representation was
    462     frozen. Furthermore, unless a @tt{.freeze()} method actually
    463     enforces this conceptual change from a mutable to an immutable
    464     representation, it can be unclear at which point the IR (or parts of
    465     it) is guaranteed to be complete and its state frozen. This is another
    466     factor making maintenance of such code difficult.}]
    467   Quote from@~cite["ramsey_applicative_2006"]:
    468 
    469   @quotation{
    470    We are using ML to build a compiler that does low-level optimization. To
    471    support optimizations in classic imperative style, we built a control-flow
    472    graph using mutable pointers and other mutable state in the nodes. This
    473    decision proved unfortunate: the mutable flow graph was big and complex,
    474    and it led to many bugs. We have replaced it by a smaller, simpler,
    475    applicative flow graph based on Huet’s (1997) zipper. The new flow graph
    476    is a success; this paper presents its design and shows how it leads to a
    477    gratifyingly simple implementation of the dataflow framework developed by
    478    Lerner, Grove, and Chambers (2002).}
    479  }
    480 
    481  @asection{
    482   @atitle{Unique identifiers used as a replacement for pointers}
    483 
    484   @htodo{Check that the multi-reference worked correctly here}
    485   Mono uses that@~cite["mono-cecil-website" "mono-cecil-source"], it is very
    486   easy to use an identifier which is supposed to reference a missing
    487   object, or an object from another version of the AST. It is also very
    488   easy to get things wrong when duplicating nodes (e.g. while specializing
    489   methods based on their caller), or when merging or removing nodes.
    490 
    491  }
    492 
    493  @asection{
    494   @atitle{Explicit use of other common graph representations}
    495 
    496   Adjacency lists, @DeBruijn indices.
    497 
    498   @itemlist[
    499  @item{ Error prone when updating the graph (moving nodes around, adding,
    500     duplicating or removing nodes).}
    501  @item{Needs manual @htodo{caretaking}}]
    502 
    503  }
    504 
    505  @asection{
    506   @atitle{Using lazy programming languages}
    507 
    508   @itemlist[
    509  @item{Lazy programming is harder to debug.
    510     @(linebreak)
    511     Quote@~cite["nilsson1993lazy"]:
    512     @aquote{
    513      Traditional debugging techniques are, however, not suited for lazy
    514      functional languages since computations generally do not take place in the
    515      order one might expect.
    516     }
    517 
    518     Quote@~cite["nilsson1993lazy"]:
    519     @aquote{
    520      Within the field of lazy functional programming, the lack of suitable
    521      debugging tools has been apparent for quite some time. We feel that
    522      traditional debugging techniques (e.g. breakpoints, tracing, variable
    523      watching etc.) are not particularly well suited for the class of lazy
    524      languages since computations in a program generally do not take place in
    525      the order one might expect from reading the source code.
    526     }
    527 
    528     Quote@~cite["wadler1998functional"]:
    529     @aquote{
    530      To be usable, a language system must be accompanied by a debugger and a
    531      profiler. Just as with interlanguage working, designing such tools is
    532      straightforward for strict languages, but trickier for lazy languages.
    533     }
    534 
    535     Quote@~cite["wadler1998functional"]:
    536     @aquote{
    537      Constructing debuggers and profilers for lazy languages is recognized as
    538      difficult. Fortunately, there have been great strides in profiler research,
    539      and most implementations of Haskell are now accompanied by usable time and
    540      space profiling tools. But the slow rate of progress on debuggers for lazy
    541      languages makes us researchers look, well, lazy.
    542     }
    543 
    544     Quote@~cite["morris1982real"]:
    545     @aquote{
    546      How does one debug a program with a surprising evaluation order? Our
    547      attempts to debug programs submitted to the lazy implementation have been
    548      quite entertaining. The only thing in our experience to resemble it was
    549      debugging a multi-programming system, but in this case virtually every
    550      parameter to a procedure represents a new process. It was difficult to
    551      predict when something was going to happen; the best strategy seems to be
    552      to print out well-defined intermediate results, clearly labelled.
    553    }}
    554  @item{So-called ``infinite'' data structures constructed lazily have
    555     problems with equality and serialization. The latter is especially
    556     important for serializing and de-serializing Intermediate
    557     Representations for the purpose of testing, and is also very important
    558     for code generation: the backend effectively needs to turn the
    559     infinite data structure into a finite one. The Revised$^6$ Report on
    560     Scheme requires the @racket{equal?} predicate to correctly handle
    561     cyclic data structures, but efficient algorithms implementing this
    562     requirement are nontrivial@~cite["adams2008efficient"]. Although any
    563     representation of cyclic data structures will have at some point to
    564     deal with equality and serialization, it is best if these concerns are
    565     abstracted away as much as possible.}]
    566  }
    567 
    568  @asection{
    569   @atitle{True graph representations using immutable data structures}
    570   @itemlist[
    571  @item{Roslyn@~cite["overbey2013immutable"] : immutable trees with ``up''
    572     pointers}
    573  @item{The huet zipper@~cite["huet1997zipper"]. Implementation in untyped
    574     Racket, but not @|typedracket|@note{
    575      See @cond-element[
    576  [html @elem{
    577          @seclink["top" #:doc '(lib "zippers/scribblings/zippers.scrbl")]{
    578           zippers}}]
    579  [else @elem{@url{http://docs.racket-lang.org/zippers/}}]], and
    580      @url{https://github.com/david-christiansen/racket-zippers}}}]
    581  }
    582 }