www

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

tr.scrbl (53948B)


      1 #lang scribble/manual
      2 
      3 @require["util.rkt"
      4          (for-label (only-meta-in 0 typed/racket)
      5                     typed/racket/class)
      6          scribble/example
      7          racket/string]
      8 @(use-mathjax)
      9 
     10 @(define tr-eval (make-eval-factory '(typed/racket)))
     11 
     12 @title[#:style (with-html5 manual-doc-style)
     13        #:version (version-text)
     14        #:tag "tr-chap"]{@|Typedracket|}
     15 
     16 We start this section with some history: Lisp, @emph{the} language with lots
     17 of parentheses, shortly following Fortran as one of the first high-level
     18 programming languages, was initially designed between 1956 and 1958, and
     19 subsequently implemented@~cite["McCarthyHistoryLisp"]. Dialects of Lisp
     20 generally support a variety of programming paradigms, including (but not
     21 limited to) functional programming and object-oriented programming (e.g. via
     22 CLOS, the Common Lisp Object System). One of the the most proeminent aspects
     23 of Lisp is homoiconicity, the fact that programs and data structures look the
     24 same. This enables programs to easily manipulate other programs, and led to
     25 the extensive use of macros. Uses of macros usually look like function
     26 applications, but, instead of invoking a target function at run-time, a macro
     27 will perform some computation at compile-time, and expand to some new code,
     28 which is injected as a replacement of the macro's use.
     29 
     30 The two main dialects of Lisp are Common Lisp and Scheme. Scheme follows a
     31 minimalist philosophy, where a small core is
     32 standardised@~cite["r5rs" "r6rs" "r7rs"] and subsequently extended via macros
     33 and additional function definitions.
     34 
     35 Racket, formerly named PLT Scheme, started as a Scheme implementation. Racket
     36 evolved, and the Racket Manifesto@~cite["racketmanifesto"] presents it as a
     37 ``programming-language programming language'', a language which helps with the
     38 creation of small linguistic extensions as well as entirely new languages. The
     39 Racket ecosystem features many languages covering many paradigms:
     40 
     41 @itemlist[
     42  @item{The @racketmodname[racket/base] language is a full-featured programming
     43   language which mostly encourages functional programming.}
     44  @item{@racketmodname[racket/class] implements
     45   @seclink["classes" #:doc '(lib "scribblings/guide/guide.scrbl")]{an
     46    object-oriented system}, implemented atop @racketmodname[racket/base] using
     47   macros, and can be used along with the rest of the @racketmodname[racket/base]
     48   language.}
     49  @item{@racketmodname[racklog] is a logic programming language in the style of
     50   prolog. The Racket ecosystem also includes an implementation of
     51   @racketmodname[datalog].}
     52  @item{@seclink["top" #:doc '(lib "scribblings/scribble/scribble.scrbl")]{
     53    Scribble} can be seen as an alternative to @|LaTeX|, and is used to create
     54   the @seclink["top" #:doc '(lib "scribblings/main/start.scrbl")]{Racket
     55    documentation}. It also supports literate programming, by embedding chunks of
     56   code in the document which are then aggregated together. This thesis is
     57   in fact written using Scribble.}
     58  @item{@racketmodname[slideshow] is a @deftech{DSL} (domain-specific language)
     59   for the creation of presentations, and can be thought as an alternative to
     60   Beamer and SliTeX.}
     61  @item{@racketmodname[r5rs] and @racketmodname[r6rs] are implementations of
     62   the corresponding scheme standards.}
     63  @item{@seclink["top" #:doc '(lib "redex/redex.scrbl")]{Redex} is a
     64   @usetech{DSL} which allows the specification of reduction
     65   semantics for programming languages. It features tools to explore and test
     66   the defined semantics.}
     67  @item{@|Typedracket|@~cite["tobin-hochstadt_design_2008"
     68                             "tobin-hochstadt_typed_2010"] is a typed variant of
     69   the main @racketmodname[racket] language. It is implemented as a macro which
     70   takes over the whole body of the program. That macro fully expands all other
     71   macros in the program, and then typechecks the expanded program.}
     72  @item{@seclink["top" #:doc '(lib "turnstile/scribblings/turnstile.scrbl")]{
     73    @|Turnstile|} allows the creation of new typed languages. It takes a
     74   different approach when compared to @|typedracket|, and threads the type
     75   information through assignments and special forms, in order to be able to
     76   typecheck the program during expansion, instead of doing so afterwards.}]
     77 
     78 In the remainder of this section, we will present the features of
     79 @|typedracket|'s type system, and then present formal semantics for a subset
     80 of those, namely the part which is relevant to our work.
     81 @other-doc['(lib "typed-racket/scribblings/ts-guide.scrbl")] and
     82 @other-doc['(lib "typed-racket/scribblings/ts-reference.scrbl")] provide good
     83 documentation for programmers who desire to use @|typedracket|; we will
     84 therefore keep our overview succinct and gloss over most details.
     85 
     86 @asection{
     87  @atitle[#:tag "tr-overview"]{Overview of Typed Racket's type system}
     88 
     89  @asection{
     90   @atitle{Simple primitive types}
     91    
     92   @Typedracket has types matching Racket's baggage of primitive values:
     93   @racket[Number], @racket[Boolean], @racket[Char], @racket[String],
     94   @racket[Void]@note{The @racket[Void] type contains only a single value,
     95    @racket[#,(void)], and is equivalent to the @racketid[void] type in
     96    @|C-language|. It is the equivalent of @racketid[unit] of @CAML and
     97    @|haskell|, and is often used as the return type of functions which perform
     98    side-effects. It should not be confused with @racket[Nothing], the bottom
     99    type which is not inhabited by any value, and is similar to the type of
    100    @|haskell|'s @racketid[undefined]. @racket[Nothing] can be used for example
    101    as the type of functions which never return — in that way it is similar to
    102    @|C-language|'s @tt["__attribute__ ((__noreturn__))"].} and so on.
    103 
    104   @examples[#:label #f #:eval (tr-eval)
    105             (ann #true Boolean)
    106             243
    107             "Hello world"
    108             #\c
    109             (code:comment "The void function produces the void value")
    110             (code:comment "Void values on their own are not printed,")
    111             (code:comment "so we place it in a list to make it visible.")
    112             (list (void))]
    113   
    114   For numbers, @|typedracket| offers a ``numeric tower'' of
    115   partially-overlapping types: @racket[Positive-Integer] is a subtype of
    116   @racket[Integer], which is itself a subtype of @racket[Number]. @racket[Zero],
    117   the type containing only the number 0, is a both a subtype of
    118   @racket[Nonnegative-Integer] (numbers ≥ 0) and of @racket[Nonpositive-Integer]
    119   (numbers ≤ 0).
    120 
    121   @|Typedracket| also includes a singleton type for each primitive value of
    122   these types: we already mentioned @racket[Zero], which is an alias of the
    123   @racket[0] type. Every number, character, string and boolean value can be used
    124   as a type, which is only inhabited by the same number, character, string or
    125   boolean value. For example, @racket[243] belongs to the singleton type
    126   @racket[243], which is a subtype of @racket[Positive-Integer].
    127 
    128   @examples[#:label #f #:eval (tr-eval)
    129             0
    130             (ann 243 243)
    131             #t]}
    132 
    133  @asection{
    134   @atitle{Pairs and lists}
    135 
    136   Pairs are the central data structure of most Lisp dialects. They are used to
    137   build linked lists of pairs, terminated by @racket['()], the null element. The
    138   null element has the type @racket[Null], while the pairs which build the list
    139   have the type @racket[(Pairof _A _B)], where @racketid[_A] and @racketid[_B]
    140   are replaced by the actual types for the first and second elements of the
    141   pair. For example, the pair built using @racket[(cons 729 #true)], which
    142   contains @racket[729] as its first element, and @racket[#true] as its second
    143   element, has the type @racket[(Pairof Number Boolean)], or using the most
    144   precise singleton types, @racket[(Pairof 729 #true)].
    145 
    146   @examples[#:label #f #:eval (tr-eval)
    147             (cons 729 #true)
    148             '(729 . #true)]
    149 
    150   Heterogeneous linked lists of fixed length can be given a precise type by
    151   nesting the same number of pairs at the type level. For example, the list
    152   built with @racket[(list 81 #true 'hello)] has the type
    153   @racket[(List Number Boolean Symbol)], which is a shorthand for the type
    154   @racket[(Pairof Number (Pairof Boolean (Pairof Symbol Null)))]. Lists in
    155   @|typedracket| can thus be seen as the equivalent of a chain of nested
    156   2-tuples in languages like @|CAML| or @|haskell|. The analog in
    157   object-oriented languages with support for generics would be a class
    158   @tt["Pair<A, B>"], where the generic type argument @racketid[B] could be
    159   instantiated by another instance of @tt["Pair"], and so on.
    160 
    161   @examples[#:label #f #:eval (tr-eval)
    162             (cons 81 (cons #true (cons 'hello null)))
    163             (ann (list 81 #true 'hello)
    164                  (Pairof Number (Pairof Boolean (Pairof Symbol Null))))]
    165 
    166   The type of variable-length homogeneous linked lists can be described using
    167   the @racket[Listof] type operator. The type @racket[(Listof Integer)] is
    168   equivalent to @racket[(Rec R (U (Pairof Integer R) Null))]. The @racket[Rec]
    169   type operator describes @seclink["tr-presentation-recursive-types"]{recursive
    170    types}, and @racket[U] describes @seclink["tr-presentation-unions"]{unions}.
    171   Both of these features are described below, for now we will simply say that
    172   the previously given type is a recursive type @racket[R], which can be a
    173   @racket[(Pairof Integer R)] or @racket[Null] (to terminate the linked list).
    174 
    175   @examples[#:label #f #:eval (tr-eval)
    176             (ann (range 0 5) (Listof Number))]}
    177 
    178  @asection{
    179   @atitle{Symbols}
    180 
    181   Another of Racket's primitive datatypes is symbols. Symbols are interned
    182   strings: two occurrences of a symbol produce values which are pointer-equal if
    183   the symbols are equal (i.e. they represent the same string)@note{This is true
    184    with the exception of symbols created with @racket[gensym] and the like.
    185    @racket[gensym] produces a fresh symbol which is not interned, and therefore
    186    different from all existing symbols, and different from all symbols created
    187    in the future.}.
    188 
    189   @|Typedracket| includes the @racket[Symbol] type, to which all symbols
    190   belong. Additionally, there is a singleton type for each symbol: the type
    191   @racket['foo] is only inhabited by the symbol @racket['foo].
    192 
    193   @examples[#:label #f #:eval (tr-eval)
    194             'foo]
    195 
    196   Singleton types containing symbols can be seen as similar to constructors
    197   without arguments in @|CAML| and @|haskell|, and as globally unique enum
    198   values in object-oriented languages. The main difference resides in the scope
    199   of the declaration: two constructor declarations with identical names in two
    200   separate files will usually give distinct types and values. Similarly, when
    201   using the ``type-safe enum'' design pattern, two otherwise identical
    202   declarations of an enum will yield objects of different types. In contrast,
    203   two uses of an interned symbols in Racket and @|typedracket| will produce
    204   identical values and types. A way of seeing this is that symbols are similar
    205   to constructors (in the functional programming sense) or enums which are
    206   implicitly declared globally.
    207 
    208   @examples[#:label #f #:eval (tr-eval)
    209             (module m1 typed/racket
    210               (define sym1 'foo)
    211               (provide sym1))
    212             (module m2 typed/racket
    213               (define sym2 'foo)
    214               (provide sym2))
    215             (require 'm1 'm2)
    216             (code:comment "The tow independent uses of 'foo are identical:")
    217             (eq? sym1 sym2)]
    218  }
    219   
    220  @asection{
    221   @atitle[#:tag "tr-presentation-unions"]{Unions}
    222 
    223   These singleton types may not seem very useful on their own. They can however
    224   be combined together with union types, which are built using the @racket[U]
    225   type operator.
    226   
    227   The union type @racket[(U 0 1 2)] is inhabited by the values @racket[0],
    228   @racket[1] and @racket[2], and by no other value. The @racket[Boolean] type is
    229   actually defined as @racket[(U #true #false)], i.e. the union of the singleton
    230   types containing the @racket[#true] and @racket[#false] values, respectively.
    231   The @racket[Nothing] type, which is not inhabited by any value, is defined as
    232   the empty union @racket[(U)]. The type @racket[Any] is the top type, i.e. it
    233   is a super-type of all other types, and can be seen as a large union including
    234   all other types, including those which will be declared later or in other
    235   units of code.
    236 
    237   Unions of symbols are similar to variants which contain zero-argument
    238   constructors, in @|CAML| or @|haskell|.
    239 
    240   @examples[#:label #f #:eval (tr-eval)
    241             (define v : (U 'foo 'bar) 'foo)
    242             v
    243             (set! v 'bar)
    244             v
    245             (code:comment "This throws an error at compile-time:")
    246             (eval:error (set! v 'oops))]
    247 
    248   A union such as @racket[(U 'ca (List 'cb Number) (List 'cc String Symbol))]
    249   can be seen as roughly the equivalent of a variant with three constructors,
    250   @racketid[ca], @racket[cb] and @racketid[cc], where the first has no
    251   arguments, the second has one argument (a @racket[Number]), and the third has
    252   two arguments (a @racket[String] and a @racket[Symbol]).
    253 
    254   The main difference is that a symbol can be used as parts of several unions,
    255   e.g. @racket[(U 'a 'b)] and @racket[(U 'b 'c)], while constructors can often
    256   only be part of the variant used to declare them. Unions of symbols are in
    257   this sense closer to @|CAML|'s so-called polymorphic
    258   variants@~cite["minskyRealWorldOCaml"] than to regular variants.
    259   
    260   @examples[#:label #f #:eval (tr-eval)
    261             (define-type my-variant (U 'ca
    262                                        (List 'cb Number)
    263                                        (List 'cc String Symbol)))
    264             (define v₁ : my-variant 'ca)
    265             (define v₂ : my-variant (list 'cb 2187))
    266             (define v3 : my-variant (list 'cc "Hello" 'world))]
    267 
    268   Finally, it is possible to mix different sorts of types within the same
    269   union: the type @racket[(U 0 #true 'other)] is inhabited by the number
    270   @racket[0], the boolean @racket[#true], and the symbol @racket['other].
    271   Translating such an union to a language like @|CAML| could be done by
    272   explicitly tagging each case of the union with a distinct constructor.
    273 
    274   Implementation-wise, all values in the so-called ``untyped'' version of
    275   Racket are tagged: a few bits within the value's representation are reserved
    276   and used to encode the value's type. When considering the target of a pointer
    277   in memory, Racket is therefore able to determine if the pointed-to value is a
    278   number, boolean, string, symbol and so on. Typed Racket preserves these
    279   run-time tags. They can then be used to detect the concrete type of a value
    280   when its static type is a union. This detection is done simply by using
    281   Racket's predicates: @racket[number?], @racket[string?], @racket[symbol?]
    282   etc.}
    283 
    284  @asection{
    285   @atitle{Intersections}
    286 
    287   Intersections are the converse of unions: instead of allowing a mixture of
    288   values of different types, an intersection type, described using the
    289   @racket[∩] type operator, only allows values which belong to all types.
    290 
    291   The intersection type @racket[(∩ Nonnegative-Integer Nonpositive-Integer)] is
    292   the singleton type @racket[0]. The intersection of @racket[(U 'a 'b 'c)] and
    293   @racket[(U 'b 'c 'd)] will be @racket[(U 'b 'c)], as @racket['b] and
    294   @racket['c] belong to both unions.
    295 
    296   @examples[
    297  #:label #f #:eval (tr-eval)
    298  (code:comment ":type shows the given type, or a simplified version of it")
    299  (:type (∩ (U 'a 'b 'c) (U 'b 'c 'd)))]
    300   
    301   @|Typedracket| is able to reduce some intersections such as those given above
    302   at compile-time. However, in some cases, it is forced to keep the intersection
    303   type as-is. For example, structs (@seclink["tr-presentation-structs"]{
    304    describled below} can, using special properties, impersonate functions. This
    305   mechanism is similar to PHP's @tt["__invoke"], the ability to overload
    306   @tt["operator()"] in @|CPP|. @|Typedracket| does not handle these properties
    307   (yet), and therefore cannot determine whether a given struct type also
    308   impersonates a function or not. This means that the intersection
    309   @racket[(∩ s (→ Number String))], where @racket[s] is a struct type, cannot be
    310   reduced to @racket[Nothing], because @|typedracket| cannot determine whether
    311   the struct @racket[s] can act as a function or not.
    312 
    313   Another situation where @|typedracket| cannot reduce the intersection is when
    314   intersecting two function types (@seclink["tr-presentation-functions"]{
    315    presented below}).
    316 
    317   @racketblock[
    318  (∩ (→ Number String) (→ Number Symbol))
    319  (∩ (→ Number String) (→ Boolean String))]
    320 
    321   The first intersection seems like could be simplified to
    322   @racket[(→ Number String) (→ Number Symbol)], and the second one could be
    323   simplified to @racket[(→ (U Number Boolean) String)], however the equivalence
    324   between these types has not been implemented (yet) in @|typedracket|, so we do
    325   not rely on them. Note that this issue is not a soundness issue: it only
    326   prevents passing values  types to which they belong in principle, but it
    327   cannot be exploited to assign a value to a variable with an incompatible type.
    328 
    329   Finally, when some types are intersected with a polymorphic type variable,
    330   the intersection cannot be computed until the polymorphic type is
    331   instantiated.
    332   
    333   When @|typedracket| is able to perform a simplification, occurrences of
    334   @racket[Nothing] (the bottom type) propagate outwards in some cases, pairs and
    335   struct types which contain @racket[Nothing] as one of their elements being
    336   collapsed to @racket[Nothing]. This propagation of @racket[Nothing] starts
    337   from occurrences of @racket[Nothing] in the parts of the resulting type which
    338   are traversed by the intersection operator. It collapses the containing pairs
    339   and struct types to @racket[Nothing], moving outwards until the @racket[∩]
    340   operator itself is reached. In principle, the propagation could go on past
    341   that point, but this is not implemented yet in @|typedracket|@note{See
    342    @hyperlink["https://github.com/racket/typed-racket/issues/552"]{Issue #552}
    343    on @|typedracket|'s GitHub repository for more details on what prevents
    344    implementing a more aggressive propagation of @racket[Nothing].}.
    345 
    346   The type @racket[(∩ 'a 'b)] therefore gets simplified to @racket[Nothing],
    347   and the type @racket[(∩ (Pairof 'a 'x) (Pairof 'b 'x))] also simplifies to
    348   @racket[Nothing] (@|typedracket| initially pushes the intersection down the
    349   pairs, so that the type first becomes @racket[(Pairof (∩ 'a 'b) (∩ 'x 'x))],
    350   which is simplified to @racket[(Pairof Nothing 'x)], and the occurrence of
    351   @racket[Nothing] propagates outwards). However, if the user directly specifies
    352   the type @racket[(Pairof (∩ 'a 'b) Integer)], it is simplified to
    353   @racket[(Pairof Nothing Integer)], but the @racket[Nothing] does not propagate
    354   outwards beyond the initial use of @racket[∩].
    355 
    356   @examples[#:label #f #:eval (tr-eval)
    357             (:type (∩ 'a 'b))
    358             (:type (∩ (Pairof 'a 'x) (Pairof 'b 'x)))
    359             (:type (Pairof (∩ 'a 'b) Integer))]
    360 
    361   A simple workaround exists: the outer type, which could be collapsed to
    362   @racket[Nothing], can be intersected again with a type of the same shape. The
    363   outer intersection will traverse both types (the desired one and the
    364   ``shape''), and propagate the leftover @racket[Nothing] further out.
    365 
    366   @examples[#:label #f #:eval (tr-eval)
    367             (:type (Pairof (∩ 'a 'b) Integer))
    368             (:type (∩ (Pairof (∩ 'a 'b) Integer)
    369                       (Pairof Any Any)))]
    370 
    371   These intersections are not very interesting on their own, as in most cases
    372   it is possible to express the resulting simplified type without using the
    373   intersection operator. They become more useful when mixed with polymorphic
    374   types: intersecting a polymorphic type variable with another type can be used
    375   to restrict the actual values that may be used. The type @racket[(∩ A T)],
    376   where @racket[A] is a polymorphic type variable and @racket[T] is a type
    377   defined elsewhere, is equivalent to the use of bounded type parameters in
    378   @|java| or @|csharp|. In @|csharp|, for example, the type @racket[(∩ A T)]
    379   would be written using an @tt["where A : T"] clause.}
    380  
    381  @asection{
    382   @atitle[#:tag "tr-presentation-structs"]{Structs}
    383 
    384   Racket also supports @racket[struct]s, which are mappings from fields to
    385   values. A struct is further distinguished by its struct type: instances of two
    386   struct types with the same name and fields, declared in separate files, can be
    387   differentiated using the predicates associated with these structs. Structs in
    388   Racket can be seen as the analog of classes containing only fields (but no
    389   methods) in @csharp or @|java|. Such classes are sometimes called ``Plain Old
    390   Data (POD) Objects''. Structs belong to a single-inheritance hierarchy:
    391   instances of the descendents of a struct type are recognised by their
    392   ancestor's predicate. When a struct inherits from another, it includes its
    393   parent's fields, and can add extra fields of its own.
    394 
    395   Each struct declaration within a @|typedracket| program additionally declares
    396   corresponding type.
    397 
    398   @examples[#:label #f #:eval (tr-eval)
    399             (struct parent ([field₁ : (Pairof String Symbol)])
    400               #:transparent)
    401             (struct s parent ([field₂ : Integer]
    402                               [field₃ : Symbol])
    403               #:transparent)
    404             (s (cons "x" 'y) 123 'z)]
    405 
    406   In @|typedracket|, structs can have polymorphic type arguments, which can be
    407   used inside the types of the struct's fields.
    408 
    409   @examples[#:label #f #:eval (tr-eval)
    410             (struct (A B) poly-s ([field₁ : (Pairof A B)]
    411                                   [field₂ : Integer]
    412                                   [field₃ : B])
    413               #:transparent)
    414             (poly-s (cons "x" 'y) 123 'z)]
    415 
    416   Racket further supports
    417   @tech[#:doc '(lib "scribblings/reference/reference.scrbl")]{struct type
    418    properties}, which can be seen as a limited form of method definitions for a
    419   struct, thereby making them closer to real objects. The same struct type
    420   property can be implemented by many structs, and the declaration of a struct
    421   type property is therefore roughly equivalent to the declaration of an
    422   interface with a single method.
    423 
    424   Struct type properties are often considered a low-level mechanism in Racket.
    425   Among other things, a struct type property can only be used to define a single
    426   property at a time. When multiple ``methods'' have to be defined at once (for
    427   example, when defining the @racket[prop:equal+hash] property, which requires
    428   the definition of an equality comparison function, and two hashing functions),
    429   these can be grouped together in a list of functions, which is then used as
    430   the property's value.
    431   ``@seclink["struct-generics"
    432              #:doc '(lib "scribblings/reference/reference.scrbl")]{
    433    Generic interfaces}'' are a higher-level feature, which among other things
    434   allow the definition of multiple ``methods'' as part of a single generic
    435   interface, and offers a friendlier API for specifying the ``generic
    436   interface'' itself (i.e. what Object Oriented languages call an interfece), as
    437   and for specifying the implementation of said interface.
    438 
    439   @|Typedracket| unfortunately offers no support for struct type properties and
    440   generic interfaces for now. It is impossible to assert that a struct
    441   implements a given property at the type level, and it is also for example not
    442   possible to describe the type of a function accepting any struct implementing
    443   a given property or generic interface. Finally, no type checks are performed
    444   on the body of functions bound to such properties, and to check verifies that
    445   a function implementation with the right signature is supplied to a given
    446   property. Since struct type properties and generics cannot be used in a
    447   type-safe way for now, we refrain from using these features, and only use them
    448   to implement some very common properties@note{We built a thin macro wrapper
    449    which allows typechecking the implementation and signature of the functions
    450    bound to these two properties.}: @racket[prop:custom-write] which is the
    451   equivalent of @|java|'s @tt["void toString()"], and @racket[prop:equal+hash]
    452   which is equivalent to @|java|'s @tt["boolean equals(Object o)"] and
    453   @tt["int hashCode()"].
    454 
    455  }
    456  
    457  @asection{
    458   @atitle[#:tag "tr-presentation-functions"]{Functions}
    459    
    460   @|Typedracket| provides rich function types, to support some of the flexible
    461   use patterns allowed by Racket.
    462 
    463   The simple function type below indicates that the function expects two
    464   arguments (an integer and a string), and returns a boolean:
    465 
    466   @racketblock[(→ Integer String Boolean)]
    467 
    468   We note that unlike @|haskell| and @|CAML| functions, Racket functions are
    469   not implicitly curried. To express the corresponding curried function type,
    470   one would write:
    471 
    472   @racketblock[(→ Integer (→ String Boolean))]
    473 
    474   A function may additionally accept optional positional arguments, and keyword
    475   (i.e. named) arguments, both mandatory and optional:
    476 
    477   @racketblock[
    478  (code:comment "Mandatory string, optional integer and boolean arguments:")
    479  (->* (String) (Integer Boolean) Boolean)
    480  (code:comment "Mandatory keyword arguments:")
    481  (→ #:size Integer #:str String Boolean)
    482  (code:comment "Mandatory #:str, optional #:size and #:opt:")
    483  (->* (#:str String) (#:size Integer #:opt Boolean) Boolean)]
    484 
    485   Furthermore, functions in Racket accept a catch-all ``rest'' argument, which
    486   allows for the definition of variadic functions. Typed racket also allows
    487   expressing this at the type level, as long as the arguments covered by the
    488   ``rest'' clause all have the same type:
    489 
    490   @racketblock[
    491  (code:comment "The function accepts one integer and any number of strings:")
    492  (-> Integer String * Boolean)
    493  (code:comment "Same thing with an optional symbol inbetween: ")
    494  (->* (Integer) (Symbol) #:rest String Boolean)]
    495 
    496   One of @|typedracket|'s main goals is to be able to typecheck idiomatic
    497   Racket programs. Such programs may include functions whose return type depends
    498   on the values of the input arguments. Similarly, @racket[case-lambda] can be
    499   used to create lambda functions which dispatch to multiple behaviours based on
    500   the number of arguments passed to the function.
    501 
    502   @|Typedracket| provides the @racket[case→] type operator, which can be used to
    503   describe the type of these functions:
    504 
    505   @racketblock[
    506  (code:comment "Allows 1 or 3 arguments, with the same return type.")
    507  (case→ (→ Integer Boolean)
    508         (→ Integer String Symbol Boolean))
    509  (code:comment "A similar type based on optional arguments allows 1, 2 or 3")
    510  (code:comment " arguments in contrast:")
    511  (->* (Integer) (String Symbol) Boolean)
    512  (code:comment "The output type can depend on the input type:")
    513  (case→ (→ Integer Boolean)
    514         (→ String Symbol))
    515  (code:comment "Both features (arity and dependent output type) can be mixed")
    516  (case→ (→ Integer Boolean)
    517         (→ Integer String (Listof Boolean)))]
    518 
    519   Another important feature, which can be found in the type system of most
    520   functional programming languages, and most object-oriented languages, is
    521   parametric polymorphism. @|Typedracket| allows the definition of polymorphic
    522   structs, as detailed above, as well as polymorphic functions. For example, the
    523   function @racket[cons] can be considered as a polymorphic function with two
    524   polymorphic type arguments @racket[A] and @racket[B], which takes an argument
    525   of type @racket[A], an argument of type @racket[B], and returns a pair of
    526   @racket[A] and @racket[B].
    527 
    528   @racketblock[(∀ (A B) (→ A B (Pairof A B)))]
    529 
    530   @|Typedracket| supports polymorphic functions with multiple polymorphic type
    531   variables, as the one shown above. Furthermore, it allows one of the
    532   polymorphic variables to be followed by ellipses, indicating a variable-arity
    533   polymorphic type@~cite["tobin-hochstadt_typed_2010"]. The dotted polymorphic
    534   type variable can be instantiated with a tuple of types, and will be replaced
    535   with that tuple where it appears. For example, the type
    536 
    537   @racketblock[(∀ (A B ...) (→ (List A A B ...) Void))]
    538 
    539   can be instantiated with @racket[Number String Boolean], which would yield
    540   the type for a function accepting a list of four elements: two numbers, a
    541   string and a boolean.
    542 
    543   @racketblock[(→ (List Number Number String Boolean) Void)]
    544 
    545   Dotted polymorphic type variables can only appear in some places. A dotted
    546   type variable can be used as the tail of a @racket[List] type, so
    547   @racket[(List Number B ...)] (a @racket[String] followed by any number of
    548   @racket[B]s) is a valid type, but @racket[(List B ... String)] (any number of
    549   @racket[B]s followed by a @racket[String]) is not. A dotted type variable can
    550   also be used to describe the type of a variadic function, as long as it
    551   appears after all other arguments, so @racket[(→ String B ... Void)] (a
    552   function taking a @racket[String], any number of @racket[B]s, and returning
    553   @racket[Void]) is a valid type, but @racket[(→ String B ... Void)] (a function
    554   taking any number of @racket[B]s, and a @racket[String], and returning
    555   @racket[Void]) is not. Finally, a dotted type variable can be used to
    556   represent the last element of the tuple of returned values, for functions
    557   which return multiple values (which are described below).@htodo{multiple
    558    values is described after, not cool.}
    559 
    560   When the context makes it unclear whether an ellipsis @${…} indicates a
    561   dotted type variable, or is used to indicate a metasyntactic repetition at the
    562   level of mathematical formulas, we will write the first using @${τ₁ … τₙ},
    563   explicitly indicating the first and last elements, or using @${\overline{τ}}
    564   @todo{and we will write the second using @${\textit{tvar}\ @$ooo}}
    565 
    566   @;{
    567    @todo{and we will write the second using @${\textit{tvar}\ \textit{ooo}}}
    568 
    569    @todo{and we will write the second using @${\textit{tvar}\ \textit{ddd}}}
    570 
    571    @todo{and we will write the second using @${\textit{tvar}\ ⋯}}
    572 
    573    @todo{and we will write the second using @${\textit{tvar}\ ⋰}}
    574 
    575    @todo{and we will write the second using @${\textit{tvar}\ ⋱}}
    576 
    577    @todo{and we will write the second using @${\textit{tvar}\ ⋮}}
    578 
    579    @todo{and we will write the second using @${\textit{tvar}\ _{***}}}
    580 
    581    @todo{and we will write the second using
    582     @${\textit{tvar}\ _{\circ\circ\circ}}.}
    583   }
    584 
    585   Functions in Racket can return one or several values. When the number of
    586   values returned is different from one, the result tuple can be destructured
    587   using special functions such as @racket[(call-with-values _f _g)], which
    588   passes each value returned by @racket[_f] as a distinct argument to
    589   @racket[_g]. The special form @racket[(let-values ([(_v₁ … _vₙ) _e]) _body)]
    590   binds each value returned by @racket[_e] to the corresponding @racket[_vᵢ]
    591   (the expression @racket[_e] must produce exactly @racket[n] values). The type
    592   of a function returning multiple values can be expressed using the following
    593   notation:
    594 
    595   @racket[(→ In₁ … Inₙ (Values Out₁ … Outₘ))]
    596 
    597   @htodo{Something on which types can be inferred and which can't (for now).}
    598 
    599   Finally, predicates (functions whose results can be interpreted as booleans)
    600   can be used to gain information about the type of their argument, depending on
    601   the result. The type of a predicate can include positive and negative
    602   @deftech{filters}, indicated with @racket[#:+] and @racket[#:-], respectively.
    603   The type of the @racket[string?] predicate is:
    604 
    605   @racketblock[(→ Any Boolean : #:+ String #:- (! String))]
    606 
    607   In this notation, the positive filter @racket[#:+ String] indicates that when
    608   the predicate returns @racket[#true], the argument is known to be a
    609   @racket[String]. Conversely, when the predicate exits with @racket[#false],
    610   the negative filter @racket[#:- (! String)] indicates that the input could not
    611   (@racket[!]) possibly have been a string. The information gained this way
    612   allows regular conditionals based on arbitrary predicates to work like
    613   pattern-matching:
    614 
    615   @examples[#:label #f #:eval (tr-eval)
    616             (define (f [x : (U String Number Symbol)])
    617               (if (string? x)
    618                   (code:comment "x is known to be a String here:")
    619                   (ann x String)
    620                   (code:comment "x is known to be a Number or a Symbol here:")
    621                   (ann x (U Number Symbol))))]
    622 
    623   The propositions do not necessarily need to refer to the value as a whole,
    624   and can instead give information about a sub-part of the value. Right now, the
    625   user interface for specifying paths can only target the left and right members
    626   of @racket[cons] pairs, recursively. Internally, @|typedracket| supports
    627   richer paths, and the type inference can produce filters which give
    628   information about individual structure fields, or about the result of forced
    629   promises, for example.}
    630 
    631  @asection{
    632   @atitle{Occurrence typing}
    633 
    634   @|Typedracket| is built atop @racket[Racket], which does not natively support
    635   pattern matching. Instead, pattern matching forms are implemented as macros,
    636   and expand to nested uses of @racket[if].
    637 
    638   As a result, @|typedracket| needs to typecheck code with the following
    639   structure:
    640 
    641   @racketblock[
    642  (λ ([v : (U Number String)])
    643    (if (string? v)
    644        (string-append v ".")
    645        (+ v 1)))]
    646 
    647   In this short example, the type of @racket[v] is a union type including
    648   @racket[Number] and @racket[String]. After applying the @racket[string?]
    649   predicate, the type of @racket[v] is narrowed down to @racket[String] in the
    650   @emph{then} branch, and it is narrowed down to @racket[Number] in the @emph{
    651    else} branch. The type information gained thanks to the predicate comes from
    652   the @tech{filter} part of the predicate's type (as explained in
    653   @secref["tr-presentation-functions"]).
    654 
    655   Occurrence typing only works on immutable variables and values. Indeed, if
    656   the variable is modified with @racket[set!], or if the subpart of the value
    657   stored within which is targeted by the predicate is mutable, it is possible
    658   for that value to change between the moment the predicate is executed, and the
    659   moment when the value is actually used. This places a strong incentive to
    660   mostly use immutable variables and values in @|typedracket| programs, so that
    661   pattern-matching and other forms work well.
    662 
    663   In principle, it is always possible to copy the contents of a mutated
    664   variable to a temporary one (or copy a mutable subpart of the value to a new
    665   temporary variable), and use the predicate on that temporary copy. The code in
    666   the @emph{then} and @emph{else} branches should also use the temporary copy,
    667   to benefit from the typing information gained via the predicate. In our
    668   experience, however, it seems that most macros which perform tasks similar to
    669   pattern-matching do not provide an easy means to achieve this copy. It
    670   therefore remains more practical to avoid mutation altogether when possible.}
    671 
    672  @asection{
    673   @atitle[#:tag "tr-presentation-recursive-types"]{Recursive types}
    674    
    675   @|Typedracket| allows recursive types, both via (possibly mutually-recursive)
    676   named declarations, and via the @racket[Rec] type operator.
    677 
    678   In the following examples, the types @racket[Foo] and @racket[Bar] are
    679   mutually recursive. The type @racket[Foo] matches lists with an even number of
    680   alternating @racket[Integer] and @racket[String] elements, starting with an
    681   @racket[Integer],
    682 
    683   @racketblock[
    684  (define-type Foo (Pairof Integer Bar))
    685  (define-type Bar (Pairof String (U Foo Null)))]
    686 
    687   This same type could alternatively be defined using the @racket[Rec]
    688   operator. The notation @racket[(Rec R T)] builds the type @racket[T], where
    689   occurrences of @racket[R] are interpreted as recursive occurrences of
    690   @racket[T] itself.
    691   
    692   @racketblock[
    693  (Rec R
    694       (Pairof Integer
    695               (Pairof String
    696                       (U R Null))))]}
    697 
    698  @asection{
    699   @atitle{Classes}
    700 
    701   The @racketmodname[racket/class] module provides an object-oriented system
    702   for Racket. It supports the definition of a hierarchy of classes with single
    703   inheritance, interfaces with multiple inheritance, mixins and traits (methods
    704   and fields which may be injected at compile-time into other classes), method
    705   renaming, and other features.
    706 
    707   The @racketmodname[typed/racket/class] module makes most of the features of
    708   @racketmodname[racket/class] available to @|typedracket|. In particular, it
    709   defines the following type operators:
    710 
    711   @itemlist[
    712  @item{@racket[Class] is used to describe the features a class, including the
    713     signature of its constructor, as well as the public fields and methods
    714     exposed by the class. We will note that a type expressed with @racket[Class]
    715     does not mention the name of the class. Any concrete implementation which
    716     exposes all (and only) the required methods, fields and constructor will
    717     inhabit the type. In other words, the types built with @racket[Class] are
    718     structural, and not nominal.
    719    }
    720  @item{@racket[Object] is used to describe the methods and fields which an
    721     already-built object bears.}
    722  @item{The @racket[(Instance (Class …))] type is a shorthand for the
    723     @racket[Object] type of instances of the given class type. It can be useful
    724     to describe the type of an instance of a class without repeating all the
    725     fields and methods (which could have been declared elsewhere).}
    726  @item{In types described using @racket[Class] and @racket[Instance], it is
    727     possible to omit fields which are not relevant. These fields get grouped
    728     under a single @emph{row polymorphic} type variable. A row polymorphic
    729     function can, for example, accept a class with some existing fields, and
    730     produce a new class extending the existing one:
    731 
    732     @(let ([ev (tr-eval)])
    733        @list{
    734      @examples[#:label #f #:eval ev
    735                (: add-my-field (∀ (r #:row)
    736                                   (-> (Class (field [existing Number])
    737                                              #:row-var r)
    738                                       (Class (field [existing Number]
    739                                                     [my-field String])
    740                                              #:row-var r))))
    741                (define (add-my-field parent%)
    742                  (class parent%
    743                    (super-new)
    744                    (field [my-field : String "Hello"])))]
    745 
    746      The small snippet of code above defined a function @racket[add-my-field]
    747      which accepts a @racket[parent%] class exporting at least the
    748      @racket[existing] field (and possibly other fields and methods). It then
    749      creates an returns a subclass of the given @racket[parent%] class, extended
    750      with the @racket[my-field] field.
    751 
    752      We consider the following class, with the required @racket[existing] field,
    753      and a supplementary @racket[other] field:
    754 
    755      @examples[#:label #f #:eval ev
    756                (define a-class%
    757                  (class object%
    758                    (super-new)
    759                    (field [existing : Integer 0]
    760                           [other : Boolean #true])))]
    761 
    762      When passed to the @racket[add-my-field] function, the row type variable is
    763      implicitly instantiated with the field @racket[[other Boolean]]. The result
    764      of that function call is therefore a class with the three fields
    765      @racket[existing], @racket[my-field] and @racket[other].
    766 
    767      @examples[#:label #f #:eval ev
    768                (add-my-field a-class%)]
    769 
    770      These mechanisms can be used to perform reflective operations on classes
    771      like adding new fields and methods to dynamically-created subclasses, in a
    772      type-safe fashion.
    773 
    774      The @racket[Row] operator can be used along with @racket[row-inst] to
    775      explicitly instantiate a row type variable to a specific set of fields and
    776      methods. The following call to @racket[add-my-field] is equivalent to the
    777      preceding one, but does not rely on the automatic inference of the row type
    778      variable.
    779 
    780      @examples[#:label #f #:eval ev
    781                ({row-inst add-my-field (Row (field [other Boolean]))} a-class%)]
    782      })}]
    783 
    784   We will not further describe this object system here, as our work does not
    785   rely on this aspect of @|typedracket|'s type system. We invite the curious
    786   reader to refer to the documentation for @racketmodname[racket/class] and
    787   @racketmodname[typed/racket/class] for more details.
    788 
    789   We will simply note one feature which is so far missing from @|typedracket|'s
    790   object system: immutability. It is not possible yet to indicate in the type of
    791   a class that a field is immutable, or that a method is pure (in the sense of
    792   always returning the same value given the same input arguments). The absence
    793   of immutability means that occurrence typing does not work on fields. After
    794   testing the value of a field against a predicate, it is not possible to narrow
    795   the type of that field, because it could be mutated by a third party between
    796   the check and future uses of the field.
    797  }
    798 
    799  @asection{
    800   @atitle{Local type inference}
    801 
    802   Unlike many other statically typed functional languages, @|typedracket| does
    803   not rely on a Hindley–Milner type system@~cite["HMMilner78" "HMHindley69"].
    804   This choice was made for several reasons@~cite["tobin-hochstadt_typed_2010"]:
    805   @itemlist[
    806  @item{@|Typedracket|'s type system is rich and contains many features. Among
    807     other things, it mixes polymorphism and subtyping, which notoriously make
    808     typechecking difficult.}
    809  @item{The authors of @|typedracket| claim that global type inference often
    810     produces indecipherable error messages, with a small change having
    811     repercussions on the type of terms located in other distant parts of the
    812     program.}
    813  @item{The authors of @|typedracket| suggest that type annotations are often
    814     beneficial as documentation. Since the type annotations are checked at
    815     compile-time, they additionally will stay synchronised with the code that
    816     they describe, and will not become out of date.}]
    817 
    818   Instead of relying on global type inference, @|typedracket| uses local type
    819   inference to determine the type of local variables and expressions.
    820   @|Typedracket|'s type inference can also determine the correct instantiation
    821   for most calls to polymorphic functions. It however requires type annotations
    822   in some places. For example, it is usually necessary to indicate the type of
    823   the parameters when defining a function.}
    824  @htodo{Vectors}
    825 }
    826 
    827 @(begin
    828    (define (cat x . y)
    829      (if (null? y)
    830          @list{\mathsf{@x}}
    831          @list{\mathsf{@x}\ @y}))
    832    (define ℂ∞ @${\overline{ℂ}})
    833    (define tvarset @${V})
    834    (define u𝕋 @${𝕋_@tvarset})
    835    (define u𝕋∅ @${𝕋_∅})
    836    (define (τ x) @${τ(\textit{@x})})
    837 
    838    (define (τrule v t #:& [& #t])
    839      (if &
    840          @${@v & ∈ τ(@t)}
    841          @${@v ∈ τ(@t)})))
    842 
    843 @include-asection["../from-dissertation-tobin-hochstadt/rules.scrbl"]
    844 
    845 @;{
    846 @asection{
    847  @atitle{Formal semantics for part of Typed Racket's type system}
    848   
    849 }
    850 }
    851 
    852 @htodo{
    853  @asection{
    854   @atitle{Formal semantics for part of Typed Racket's type system}
    855 
    856   We define the universe of values that can be created manipulated with
    857   @|typedracket| as follows:
    858 
    859   @$${
    860    @cases["𝔻"
    861           @acase{@cat["num"]{c} ∈ @ℂ∞}
    862           @acase{@cat["chr"]{h} ∈ ℍ}
    863           @acase{@cat["str"]{s} ∈ 𝕊}
    864           @acase{@cat["sym"]{y} ∈ 𝕐}
    865           @acase{@cat["fun"]{f} ∈ 𝔽}
    866           @acase{@cat["pair"](d, d') @where d,d' ∈ 𝔻}
    867           @acase{@cat["vec"](d₁, …, dₙ) @where dᵢ ∈ 𝔻, n ∈ ℕ}
    868           @acase{@cat["null"]}
    869           @acase{@cat["void"]}
    870           @acase{@cat["true"] ∈ 𝟙}
    871           @acase{@cat["false"] ∈ 𝟙}
    872           @acase{@cat["struct"](f₁ = d₁, …, fₙ = dₙ)
    873               @where fᵢ ∈ ℱ, dᵢ ∈ 𝔻}]
    874   }
    875 
    876   where @ℂ∞ is the subset of complex numbers that can be represented in
    877   Racket, extended with a few values like floating-point infinities and ``not a
    878   number'' special values@note{More precisely Racket can represent complex
    879    rationals with arbitrary precision (i.e. numbers of the form
    880    @${@frac["a" "b"] + @frac["c" "d"]i} where @${a,b,c,d ∈ ℤ ∧ b,d ≠ 0} and have
    881    a small enough magnitude to be represented without running out of memory), as
    882    well as complex numbers where both components are either single-precision or
    883    double-precision IEEE floating-point numbers, including special values like
    884    positive and negative infinity (for double-precision floats: @racket[+inf.0]
    885    and @racket[-inf.0]), positive and negative zero (@racket[+0.0] and
    886    @racket[-0.0]) and positive and negative ``not a number'' values
    887    (@racket[+nan.0] and @racket[-nan.0]).}.
    888 
    889   @${ℍ} is the set of characters that can be represented in Racket@note{That
    890    is, all the Unicode code points in the ranges 0 – d7ff@subscript{16} and
    891    e000@subscript{16} – 10ffff@subscript{16}}.
    892 
    893   @${𝕊} is the set of strings based on characters present in @${ℍ}.@htodo{is
    894    this a free monoid or something?}
    895 
    896   @${𝕐} is the set of symbols that can be manipulated in Racket. It includes
    897   interned symbols (which are identified by their string representation), and
    898   @tech[#:doc '(lib "scribblings/reference/reference.scrbl")]{uninterned}
    899   symbols which are different from all other symbols, including those with the
    900   same string representation@note{We will not consider
    901    @tech[#:doc '(lib "scribblings/reference/reference.scrbl")]{unreadable
    902     symbols}, whose behaviour is inbetween@htodo{This sentence sounds weird}.}.
    903 
    904   @${𝔽} is the universe of Racket functions. A function @${f ∈ 𝔽} is a partial
    905   function from tuples of arguments to tuples of return values.
    906 
    907   @$${𝔽 = 𝔻ⁿ ↛ 𝔻ᵐ @where n,m ∈ ℕ}
    908 
    909   @${ℕ} is the set of natural integers.
    910 
    911   @${𝟙} is the universe of booleans, which only contains the values
    912   @${@cat["true"]} and @${@cat["false"]}.
    913 
    914   @${ℱ} is the universe of field names.
    915 
    916   We voluntarily omit some more exotic data types such as
    917   @tech[#:doc '(lib "scribblings/guide/guide.scrbl")]{byte strings} (indexed
    918   strings of bytes, compared to the indexed strings of unicode characters
    919   presented above),
    920   @tech[#:key "regexp" #:doc '(lib "scribblings/guide/guide.scrbl")]{regular
    921    expressions} and preexisting opaque structure types from Racket's standard
    922   library (@racket[Subprocess], for example, which represent a running
    923   subprocess on which a few actions are available). We also do not consider
    924   mutable strings and pairs, which exist in @|typedracket| for backwards
    925   compatibility, but which are seldom used in practice.
    926 
    927   @todo{Value-belongs-to-type relationship:}
    928 
    929   We define a universe of types @u𝕋 parameterized by @${@tvarset ⊆ 𝕧}, which
    930   indicates the set of free variables which may occur in the type. We note
    931   individual types as @${τ(\textit{Type})}, where @${Type} is the name of the
    932   type being considered. Unless otherwise specified, @${τ(\textit{Type}) ∈
    933    @|u𝕋|\ ∀ @tvarset}. @todo{The previous sentences are a bit fuzzy.} The
    934   universe of types with no free variables is @${@u𝕋∅ ⊆ \mathcal{P}(𝔻)}.
    935 
    936   @$${
    937    \begin{gathered}
    938    \textit{tvar} ∈ @tvarset ⇒ τ(\textit{tvar}) ∈ @u𝕋 \\
    939    @u𝕋∅ ⊆ \mathcal{P}(𝔻)
    940    \end{gathered}
    941   }
    942 
    943 
    944   Values belong to their singleton type. We define a type inhabited by a single
    945   value @${v} with the notation @${τ(@cat["cat"]{v})}, where @${@cat["cat"]{}}
    946   indicates the ``category'' of the value (whether it is a number, a string, a
    947   function, a boolean…).
    948 
    949   @$${
    950    @aligned{
    951     @τrule[@cat["num"]{c} @cat["num"]{c}] \\
    952     @τrule[@cat["chr"]{h} @cat["chr"]{h}] \\
    953     @τrule[@cat["str"]{s} @cat["str"]{s}] \\
    954     @τrule[@cat["sym"]{y} @cat["sym"]{y}] \\
    955     @τrule[@cat["true"] @cat["true"]] \\
    956     @τrule[@cat["false"] @cat["false"]] \\
    957     @τrule[@cat["null"] @${\textit{Null}}] \\
    958     @τrule[@cat["void"] @${\textit{Void}}]
    959    }
    960   }
    961 
    962   These simple values also belong to their wider type, which we note as
    963   @;
    964   @${τ(\textit{Typename})}.
    965 
    966   @$${
    967    @aligned{
    968     @τrule[@cat["num"]{c} @${\textit{Number}}] &⊂ @τ{Any} \\
    969     @τrule[@cat["chr"]{h} @${\textit{Char}}] &⊂ @τ{Any} \\
    970     @τrule[@cat["str"]{s} @${\textit{String}}] &⊂ @τ{Any} \\
    971     @τrule[@cat["sym"]{y} @${\textit{Symbol}}] &⊂ @τ{Any} \\
    972     @τrule[@cat["true"] @${\textit{Boolean}}] &⊂ @τ{Any} \\
    973     @τrule[@cat["false"] @${\textit{Boolean}}] &⊂ @τ{Any} \\
    974     @cat["null"] & &⊂ @τ{Any} \\
    975     @cat["void"] & &⊂ @τ{Any}
    976    }
    977   }
    978 
    979   We give the type of pairs and vector values below:
    980 
    981   @$${
    982    @aligned{
    983     @τrule[@${@cat["pair"](a, b)} @${\textit{Pairof A B}}]
    984     &&@textif a ∈ τ(A) ∧ b ∈ τ(B) \\
    985     @τrule[@${@cat["vec"](a₁, …, aₙ)} @${\textit{Vector A₁ … Aₙ}}]
    986     &&@textif aᵢ ∈ τ(Aᵢ)\ ∀ i
    987    }
    988   }
    989 
    990   The type @${τ(\textit{List}\ A₁\ …\ Aₙ)} is a shorthand for describing the
    991   type of linked lists of pairs of fixed length:
    992 
    993   @$${
    994    @aligned{
    995     τ(\textit{List}\ A\ \overline{B})
    996     &= τ(\textit{Pairof}\ A₁\ (List\ \overline{B})) \\
    997     @where \text{$\overline{B} is a placeholder for any number of types$}
    998     τ(\textit{List}) &= τ(Null)
    999    }
   1000   }
   1001 
   1002   More general types exist for linked lists of pairs and vectors of unknown
   1003   length:
   1004 
   1005   @$${
   1006    @aligned{
   1007     @τrule[@cat["null"] @${\textit{Listof}\ A}]\ ∀\ A \\
   1008     @τrule[@${@cat["pair"](a, b)} @${\textit{Listof}\ A}]
   1009     && @textif a ∈ τ(A) ∧ b ∈ τ(\textit{Listof}\ A) \\
   1010     @τrule[@${@cat["vec"](a₁, …, aₙ)} @${\textit{Vectorof}\ A}]
   1011     && @textif aᵢ ∈ τ(A)
   1012    }
   1013   } 
   1014 
   1015   There are a few intermediate types between singleton types for individual
   1016   numbers and
   1017   @;
   1018   @${τ(\textit{Number})}. We show a few of these below. The other types which
   1019   are part of @racket[typedracket]'s numeric tower are defined in the same way,
   1020   and are omitted here for conciseness.
   1021 
   1022   @$${
   1023    @aligned{
   1024     @τrule[@cat["num"]{c} @${\textit{Positive-Integer}}]
   1025     && @textif c ∈ ℕ ∧ c > 0 \\
   1026     @τrule[@cat["num"]{c} @${\textit{Nonnegative-Integer}}]
   1027     && @textif c ∈ ℕ ∧ c ≥ 0 \\
   1028     @τrule[@cat["num"]{c} @${\textit{Nonpositive-Integer}}]
   1029     && @textif c ∈ ℕ ∧ c ≤ 0 \\
   1030     @τrule[@cat["num"]{0} @${\textit{Zero}}] \\
   1031     @τrule[@cat["num"]{1} @${\textit{One}}] &
   1032    }
   1033   }
   1034 
   1035   Functions types are inhabited by functions which accept arguments of the
   1036   correct type, and return a tuple of values belonging to the expected result
   1037   type. We do not take into consideration the possible side effects of the
   1038   function here, partly because our compiler-writing framework seldom uses
   1039   mutation (at the run-time phase of the program).
   1040 
   1041   @$${
   1042    @aligned{
   1043     &@τrule[#:& #f @cat["fun"]{f} @${τ₁, …, τₙ → (\textit{Values} τ'₁, …, τ'ₘ)}]
   1044     \\
   1045     &@|quad|@textif
   1046     vᵢ ∈ τᵢ ∀ i ⇒ (v₁, …, vₙ) ∈ dom(f) ∧ f(v₁, …, vₙ) ∈ (τ'₁, …, τ'ₘ) \\
   1047     &@|quad|@where
   1048     (o₁, …, oₘ) ∈ (τ'₁, …, τ'ₘ) @textif oᵢ ∈ τ'ᵢ\\
   1049    }
   1050   }
   1051 
   1052   For polymorphic functions, we define a @${\operatorname{freetvars}(t)}
   1053   operator, which returns the set of bound variables accessible within a given
   1054   type @todo{This is backwards: we did not define well what it means for a bound
   1055    variable to be accessible.}
   1056  
   1057   @$${t ∈ @u𝕋 ⇒ boundvars(t) = @tvarset}
   1058 
   1059   @todo{We should not have the @${@textif τᵢ, τ'ⱼ ∈ 𝕋_{@|tvarset|⁺}} clause
   1060    below, instead we should define the notion of well-scopedness of a type.}
   1061  
   1062   @$${
   1063    @aligned{
   1064     &@cat["fun"]{f} ∈ t = τ(∀\ \textit{tvar₁}\ …\ \textit{tvarₖ}
   1065     \ (τ₁ … τₙ → (Values τ'₁ … τ'ₘ)))\\
   1066     &@|quad|@where @tvarset = \operatorname{boundtvars}(t) \\
   1067     &@|quad|@where @|tvarset|⁺ = @tvarset ∪ \{\textit{tvar₁} … \textit{tvarₖ}\}
   1068     \\
   1069     &@|quad|@textif τᵢ, τ'ⱼ ∈ 𝕋_{@|tvarset|⁺} \\
   1070     @;TODO: make @u𝕋 take an argument
   1071     &@|quad|@textif
   1072     @aligned[#:valign 'top]{
   1073      ∀ \textit{inst₁}, …, \textit{instₖ} ∈ @|u𝕋|, f
   1074      ∈ τ(σ(τ₁)\ …\ σ(τₙ) → (Values\ σ(τ'₁)\ …\ σ(τ'ₘ)))
   1075      } \\
   1076     &@|quad|@where σ(τ) = τ[\textit{tvarᵢ} ↦ \textit{instᵢ} …]
   1077    }
   1078   }
   1079 
   1080   where the notation @${τ[a₁ ↦ b₁ … aₙ ↦ bₙ]} indicates the substitution within
   1081   @${τ} of all occurrences of @${aᵢ} with the corresponding @${bᵢ}. The
   1082   substitutions are performed in parallel.
   1083 
   1084   @todo{if or iff for the function's types above?}
   1085 
   1086   @todo{other function types}
   1087 
   1088   @todo{dotted function types (variadic polymorphic types)}
   1089 
   1090   @todo{Vectorof, Listof}
   1091 
   1092   @todo{Intersections}
   1093 
   1094   @todo{is the notation for tuples of values returned by functions okay?}
   1095 
   1096   @todo{A function cannot forge a value of type @racket[A], where @racket[A] is
   1097    a polymorphic type variable. It must return an input value with the desired
   1098    type (or exit with an error, in which case the function's actual return type
   1099    is @racket[Nothing]).}
   1100 
   1101   @htodo{something else I forgot?}
   1102 
   1103   The association with types and values given above naturally yields the
   1104   subtyping relationship @tr≤: explicited below:
   1105 
   1106   @$${
   1107    @aligned{
   1108     @τ{T} & @tr≤: @τ{T}\ ∀\ T & \\
   1109     @τ{Nothing} & @tr≤: @τ{T}\ ∀\ T & \\
   1110     τ(@cat["num"]{n}) & @tr≤: @τ{Number} & \\
   1111     τ(@cat["chr"]{h}) & @tr≤: @τ{Char} & \\
   1112     τ(@cat["str"]{s}) & @tr≤: @τ{String} & \\
   1113     τ(@cat["sym"]{y}) & @tr≤: @τ{Symbol} & \\
   1114     τ(@cat["true"]) & @tr≤: @τ{Boolean} & \\
   1115     τ(@cat["false"]) & @tr≤: @τ{Boolean} & \\[1ex]
   1116     τ(A) & @tr≤: τ(U\ A\ B\ …) & \\
   1117     τ(A₁ … Aₙ → B₁ … Bₘ) & @tr≤: τ(A'₁ … A'ₙ → B'₁ … B'ₘ) & \\
   1118     & @textif A'ᵢ @tr≤: Aᵢ ∧ Bᵢ @tr≤: B'ᵢ & \\
   1119     … & @tr≤: … & \\[1ex]
   1120     @τ{T} & @tr≤: @τ{Any}\ ∀\ T &
   1121    }
   1122   }
   1123  }
   1124 }