www

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

rules.scrbl (36726B)


      1 #lang scribble/manual
      2 
      3 @; This file is not under the CC0 license, as it contains rules and definitions
      4 @; copied with permission from Sam Tobin-Hochstadt's Ph.D thesis. I obtained the
      5 @; permission to copy these rules, but did not ask for a relicensing under the
      6 @; CC0 license.
      7 
      8 @require["../scribblings/util.rkt"
      9          "../scribblings/abbreviations.rkt"
     10          "../scribblings/adt-utils.rkt"
     11          (for-label (only-meta-in 0 typed/racket)
     12                     typed/racket/class)
     13          (only-in scribble/base emph)
     14          scribble/example
     15          racket/string]
     16 @(use-mathjax)
     17 
     18 @(define tr-eval (make-eval-factory '(typed/racket)))
     19 
     20 @title[#:style (with-html5 manual-doc-style)
     21        #:version (version-text)
     22        #:tag "from-dissertation-tobin-hochstadt"]{Formal semantics for part of
     23  @|typedracket|'s type system}
     24 
     25 The following definitions and rules are copied and adjusted
     26 from@~cite["tobin-hochstadt_typed_2010"], with the author's permission. Some
     27 of the notations were changed to use those of@~cite["kent2016occurrence"].
     28 
     29 We include below the grammar, semantics and typing rules related to the
     30 minimal core of the Typed Racket language@note{The core language is defined
     31  in@~cite[#:precision "pp. 61–70" "tobin-hochstadt_typed_2010"].}, dubbed @${
     32  λ_{\mathit{TS}}}, including extensions which add pairs@note{The extensions
     33  needed to handle pairs are described
     34  in@~cite[#:precision "pp. 71–75" "tobin-hochstadt_typed_2010"].}, functions of
     35 multiple arguments, variadic functions and variadic polymorphic
     36 functions@note{The extensions needed to handle functions of multiple
     37  arguments, variadic functions, and variadic functions where the type of the
     38  “rest” arguments are not uniform are described
     39  in@~cite[#:precision "pp. 91–77" "tobin-hochstadt_typed_2010"].}, intersection
     40 types, recursive types, symbols and promises. These features have been
     41 informally described in @secref["tr-overview"].
     42 
     43 We purposefully omit extensions which allow advanced logic reasoning when
     44 propagating information gained by complex combinations of conditionals@note{
     45  The extensions which allow advanced logic reasoning are described
     46  in@~cite[#:precision "pp. 75–78" "tobin-hochstadt_typed_2010"].}, refinement
     47 types@note{The extensions which introduce refinement types are described
     48  in@~cite[#:precision "pp. 85–89" "tobin-hochstadt_typed_2010"].}, dependent
     49 refinement types@note{Dependent refinement types are presented in
     50  @~cite["kent2016occurrence"].} (which allow using theories from external
     51 solvers to reason about values and their type, e.g. using bitvector theory to
     52 ensure that a sequence of operations does not produce a result exceeding a
     53 certain machine integer size), structs and classes. These extensions are not
     54 relevant to our work@note{We informally describe a translation of our system
     55  of records into structs in section @todo{[??]}, but settle for an alternative
     56  implementation in section @todo{[??]} which does not rely on structs.}, and
     57 their inclusion in the following semantics would needlessly complicate things.
     58 
     59 @asection{
     60  @atitle{Notations}
     61 
     62  We note a sequence of elements with @repeated{y}. When there is more than one
     63  sequence involved in a rule or equation, we may use the notation
     64  @repeated[#:n "n"]{y} to indicate that there are @${n} elements in the
     65  sequence. Two sequences can be forced to have the same number of elements in
     66  that way. We represent a set of elements (an “unordered” sequence) with the
     67  notation @repeatset{y}. The use of ellipses in @polydotα{α} does not indicate
     68  the repetition of @${α}. Instead, it indicates that @${α} is a @emph{
     69   variadic} polymorphic type variable: a placeholder for zero or more types
     70  which will be substituted for occurrences of @${α} when the polymorphic type
     71  is instantiated. These ellipses appear as such in the @typedracket source
     72  code, and are the reason we use the notation @repeated{y} to indicate
     73  repetition, instead of the ellipses commonly used for that purpose. FInally,
     74  an empty sequence of repeated elements is sometimes noted @${ϵ}
     75 
     76  The judgements are written following the usual convention, where @${Γ} is the
     77  environment which associates variables to their type. The @${Δ} environment
     78  contains the type variables within scope, and is mostly used to determine the
     79  validity of types.
     80 
     81  @$${@Γ[⊢ e R]}
     82 
     83  The environments can be extended as follows:
     84 
     85  @$${@Γ[@${x : τ} Δ @${\{α\}} ⊢ e R]}
     86 
     87  The typing information @R associated with an expression contains the type of
     88  the expression, as well as aliasing information and other propositions which
     89  are known to be conditionally true depending on the value of the expression at
     90  run-time. These pieces of information are described in more detail
     91  @tech[#:key "R-typing-info"]{below}. Since the typing information @R is often
     92  inlined in the typing judgement, a typing judgement will generally have the
     93  following form:
     94 
     95  @$${@Γ[⊢ e @R[τ φ⁺ φ⁻ o]]}
     96 
     97  In this notation, the @${+} and @${-} signs in @${φ⁺} and @${φ⁻} are purely
     98  syntactical, and serve to distinguish the positive and negative filters, which
     99  are instances of the nonterminal @${φ}.
    100 
    101  The various nonterminals used throughout the language are written in italics
    102  and are defined using the notation:
    103 
    104  @cases[@textit{nonterminal} #:first-sep "⩴"
    105         @acase{@textit{first case}}
    106         @acase{@textit{second case}}
    107         @acase{@textit{and so on}}]
    108 
    109  Additionally, a symbol assigned to a nonterminal may be used as a placeholder
    110  in rules and definitions, implicitly indicating that the element used to fill
    111  in that placeholder should be an instance of the corresponding nonterminal.
    112  When multiple such placeholders are present in a rule, they will be
    113  subscripted to distinguish between the different occurrences. The subscripts
    114  @${i}, @${j}, @${k} and @${l} are often used for repeated sequences.
    115 
    116  In later chapters, we extend already-defined non-terminals using the notation:
    117  
    118  @cases[@textit{nonterminal} #:first-sep "⩴"
    119         @acase{…}
    120         @acase{@textit{new case}}
    121         @acase{@textit{other new case}}]
    122 
    123  Typing rules and other rules are described following the usual natural
    124  deduction notation.
    125 
    126  @$inferrule[@${@textit{hypothesis}\\ @textit{other hypothesis}}
    127              @${@textit{deduction}}
    128              @${@textsc{Rule-Name}}]
    129 
    130  Metafunctions (i.e. functions which operate on types as syntactical elements,
    131  or on other terms of the language) are written in a roman font. The meta-values
    132  @|metatrue| and @|metafalse| indicate logical truth and falsehood respectively.
    133 
    134  @$${\mathrm{metafunction}(x,y) = \begin{cases}
    135   @metatrue &@textif x = y + 1\\
    136   @metafalse &@otherwise
    137   \end{cases}}
    138 
    139  Language operators are written in bold face:
    140 
    141  @cases["e" #:first-sep "⩴"
    142         @acase{@num-e}
    143         @acase{…}]
    144 
    145  Values are written using a bold italic font:
    146 
    147  @cases["v" #:first-sep "⩴"
    148         @acase{@num-v}
    149         @acase{…}]
    150 
    151  Type names start with a capital letter, and are written using a bold font:
    152 
    153  @cases["τ,σ" #:first-sep "⩴"
    154         @acase{@num-τ}
    155         @acase{…}]
    156 
    157  We indicate the syntactical substitution of @${y} with @${z} in @${w} using
    158  the notation @${w@subst[y ↦ z]}. When given several elements to replace, the
    159  substitution operator performs a parallel substitution (that is,
    160  @${w@subst[x ↦ y y ↦ z]} will not replace the occurrences of @${y} introduced
    161  by the first substitution).
    162 
    163  @todo{Succinctly describe the other conventions used in the thesis, if any
    164   were omitted above.}
    165 
    166  @todo{Define the meta substitution and equality operators precisely.}
    167 
    168 }
    169 
    170 @asection{
    171  @atitle{Names and bindings}
    172 
    173  In the following sections, we assume that all type variable names which occur
    174  in binding positions are unique. This assumption could be made irrelevant by
    175  explicitly renaming in the rules below all type variables to fresh unique
    176  ones. Performing this substitution would be a way of encoding a notion of
    177  scope and the possibility for one identifier to hide another. However, the
    178  Racket language features macros which routinely produce new binding forms. The
    179  macro system in Racket is a hygienic one, and relies on a powerful model of
    180  the notion of scope@~cite["flatt2016binding"]. Extending the rules below with
    181  a simplistic model of Racket's notion of scope would not do justice to the
    182  actual system, and would needlessly complicate the rules. Furthermore,
    183  @typedracket only typechecks fully-expanded programs. In these programs, the
    184  binding of each identifier has normally been determined@note.{@Typedracket
    185   actually still determines the binding for type variables by itself, but we
    186   consider this is an implementation detail.}
    187 
    188 }
    189 
    190 @asection{
    191  @atitle{Expressions}
    192 
    193  The following expressions are available in the subset of @typedracket which we
    194  consider. These expressions include references to variables, creation of basic
    195  values (numbers, booleans, lists of pairs ending with @null-v, symbols,
    196  promises), a variety of lambda functions with different handling of @emph{
    197   rest} arguments (fixed number of arguments, polymorphic functions with a
    198  uniform list of @emph{rest} arguments and variadic polymorphic functions, as
    199  well as polymorphic abstractions), a small sample of primitive functions which
    200  are part of Racket's library and a few operations manipulating these values
    201  (function application and polymorphic instantiation, forcing promises, symbol
    202  comparison and so on).
    203 
    204  @include-equation["e.rkt"]
    205 
    206  Symbol literals are noted as @${s ∈ 𝒮} and the universe of symbols (which
    207  includes symbol literals and fresh symbols created via @gensyme[]) is noted as
    208  @${@sym* ∈ @𝒮*}.
    209 
    210  @include-equation["e.rkt" sym]
    211 
    212 }
    213 
    214 @asection{
    215  @atitle{Primitive operations (library functions)}
    216 
    217  Racket offers a large selection of library functions, which we consider as
    218  primitive operations. A few of these are listed below, and their type is given
    219  later after, once the type system has been introduced. @textit{number?},
    220  @textit{pair?} and @textit{null?} are predicates for the corresponding type.
    221  @textit{car} and @textit{cdr} are accessors for the first and second elements
    222  of a pair, which can be created using @|consp|. The @textit{identity} function
    223  returns its argument unmodified, and @textit{add1} returns its numeric
    224  argument plus 1. These last two functions are simply listed as examples.
    225 
    226  @include-equation["p.rkt"]
    227 
    228 }
    229 
    230 @asection{
    231  @atitle{Values}
    232 
    233  These expressions and primitive functions may produce or manipulate the
    234  following values:
    235 
    236  @include-equation["v.rkt"]
    237 
    238  The @listv value notation is defined as a shorthand for a @|null-v|-terminated
    239  linked list of pairs.
    240 
    241  @include-equation["v.rkt" listv]
    242 }
    243 
    244 @;{
    245  @asection{
    246   @atitle{Run-time environment}
    247 
    248   Lambda functions are closures over their execution environment. The execution
    249   environment maps to their value those variables which were within the scope of
    250   the closure. In principle, it also maps type variables and dotted type
    251   variables to the type or types used to instantiate the polymorphic functions
    252   which are part of the scope of the closure. Typed Racket uses @emph{type
    253    erasure} however, that is to say that the compile-time type of values does
    254   not persist at run-time. Primitive types are still implicitly tagged with
    255   their type (which allows for untagged unions and predicates such as
    256   @racket[number?]), but the type of a function cannot be determined at run-time
    257   for example. This means that the type-variable-to-type mapping of @${ℰ} is
    258   not effectively present at run-time with the current implementation of Typed
    259   Racket.
    260 
    261   @include-equation["envrt.rkt"]
    262  }
    263 }
    264 
    265 @asection{
    266  @atitle{Evaluation contexts}
    267 
    268  The operational semantics given below rely on the following evaluation
    269  contexts:
    270 
    271  @include-equation["Ectx.rkt"]
    272 
    273  @; TODO: are other cases needed?
    274 
    275 }
    276 
    277 @asection{
    278  @atitle{Typing judgement}
    279 
    280  @;{
    281   The type system of @typedracket relies on the following typing judgement. It
    282   indicates that the expression @${e} has type @${τ}. Additionally, if the
    283   run-time value of @${e} is @false-v then the propositions contained in @${φ⁻}
    284   are valid. If the run-time value of @${e} is not @false-v, then the
    285   propositions contained in @${φ⁺} are valid. Finally, @${e} is an alias for the
    286   @object @${o}. We use here the same terminology as
    287   @~cite["tobin-hochstadt_typed_2010"], which denotes by @object a sub-element
    288   of a variable (or a sub-element of the first argument of the function, when
    289   @R[τ @${φ⁺} @${φ⁻} @${o}] is the return type of a function).
    290  }
    291 
    292  @include-equation["GammaR.rkt" Γ]
    293 
    294  @deftech[#:key "R-typing-info"]{}
    295  @include-equation["GammaR.rkt" R]
    296 
    297  The @Γ[⊢ e R] typing judgement indicates that the expression @${e} has type
    298  @${τ}. The @${Γ} typing environment maps variables to their type (and to extra
    299  information), while the @${Δ} environment stores the polymorphic type
    300  variables, variadic polymorphic type variables and recursive type variables
    301  which are in scope.
    302 
    303  Additionally, the typing judgement indicates a set of propositions @${φ⁻}
    304  which are known to be true when the run-time value of @${e} is @|false-v|, and
    305  a set of propositions @${φ⁺} which are known to be true when the run-time
    306  value of @${e} is @|true-v|@note{Any other value is treated in the same way as
    307   @|true-v|, as values other than @|false-v| are traditionally considered as
    308   true in language of the @lisp family.}. The propositions will indicate that
    309  the value of a separate variable belongs (or does not belong) to a given type.
    310  For example, the @${φ⁻} proposition @${@|Numberτ|_y} indicates that when @${e}
    311  evaluates to @|false-v|, the variable @${y} necessarily holds an integer.
    312 
    313  Finally, the typing judgement can indicate with @${o} that the expression @${
    314   e} is an alias for a sub-element of another variable in the environment. For
    315  example, if the object @${o} is @${@carπ ∷ @cdrπ(y)}, it indicates that the
    316  expression @${e} produces the same value that @racket[(car (cdr y))] would,
    317  i.e. that it returns the second element of a (possibly improper) list stored
    318  in @racket[y].
    319 
    320  Readers familiar with abstract interpretation can compare the @${φ}
    321  propositions to the Cartesian product of the abstract domains of pairs of
    322  variables. A static analyser can track possible pairs of values contained in
    323  pairs of distinct variables, and will represent this information using an
    324  abstract domain which combinations of values may be possible, and which may
    325  not. Occurrence typing similarly exploits the fact that the type of other
    326  variables may depend on the value of @${τ}. @htodo{is this some weak form of
    327   dependent typing?}
    328 
    329 }
    330 
    331 @asection{
    332  @atitle{Types}
    333 
    334  @Typedracket handles the types listed below. Aside from the top type (@${⊤})
    335  which is the supertype of all other types, this list includes singleton types
    336  for numbers, booleans, symbols and the @null-v value. The types @Numberτ and
    337  @Symbolτ are the infinite unions of all number and symbol singletons,
    338  respectively. Also present are function types (with fixed arguments,
    339  homogeneous @emph{rest} arguments and the variadic polymorphic functions which
    340  accept heterogeneous @emph{rest} arguments, as well as polymorphic
    341  abstractions), unions of other types, intersections of other types, the type
    342  of pairs and promises. The value assigned to a variadic polymorphic function's
    343  rest argument will have a type of the form @List…τ[τ α]. Finally, @typedracket
    344  allows recursive types to be described with the @recτ* combinator.
    345 
    346  @include-equation["tausigma.rkt"]
    347 
    348  Additionally, the @Booleanτ type is defined as the union of the @true-τ and
    349  @false-τ singleton types, and the @Listτ type operator is a shorthand for
    350  describing the type of @|null-v|-terminated heterogeneous linked lists of
    351  pairs, with a fixed length. The @Listofτ type operator is a shorthand for
    352  describing the type of @|null-v|-terminated homogeneous linked lists of pairs,
    353  with an unspecified length.
    354 
    355  @include-equation["tausigma.rkt" Boolean]
    356  @include-equation["tausigma.rkt" Listτ]
    357  @include-equation["tausigma.rkt" Listofτ]
    358 
    359 }
    360 
    361 @asection{
    362  @atitle{Filters (value-dependent propositions)}
    363 
    364  The filters associated with an expression are a set of positive (resp.
    365  negative) propositions which are valid when the expression is true (resp.
    366  false).
    367 
    368  @include-equation["phi-psi-o-path.rkt" φ]
    369 
    370  These propositions indicate that a specific subelement of a location has a
    371  given type.
    372 
    373  @include-equation["phi-psi-o-path.rkt" ψ]
    374 
    375  The location can be a variable, or the special @${•} token, which denotes a
    376  function's first parameter, when the propositions are associated with that
    377  function's result. This allows us to express relations between the output of a
    378  function and its input, without referring to the actual name of the parameter,
    379  which is irrelevant. In other words, @${•} occurs in an α-normal form of a
    380  function's type.
    381 
    382  @include-equation["phi-psi-o-path.rkt" loc]
    383 
    384  @Objects, which represent aliasing information, can either indicate that the
    385  expression being considered is an alias for a sub-element of a variable, or
    386  that no aliasing information is known.
    387 
    388 }
    389 
    390 @asection{
    391  @atitle{Objects (aliasing information)}
    392 
    393  @include-equation["phi-psi-o-path.rkt" o]
    394 
    395  Sub-elements are described via a chain of path elements which are used to
    396  access the sub-element starting from the variable.
    397 
    398 }
    399 
    400 @asection{
    401  @atitle{Paths}
    402 
    403  @include-equation["phi-psi-o-path.rkt" π]
    404 
    405  The path concatenation operator @${∷} is associative. @htodo{Actually, we
    406   define it for pe∷π above, not for π∷π}. The @${@emptypath} is omitted from
    407  paths with one or more elements, so we write @${car∷cdr} instead of @${
    408   car∷cdr∷@emptypath}.
    409 
    410 }
    411 
    412 @asection{
    413  @atitle{Path elements}
    414 
    415  Path elements can be @carπ and @cdrπ, to indicate access to a pair's first or
    416  second element, and @forceπ, to indicate that the proposition or object
    417  targets the result obtained after forcing a promise. We will note here that
    418  this obviously is only sound if forcing a promise always returns the same
    419  result (otherwise the properties and object which held on a former value may
    420  hold on the new result). Racket features promises which do not cache their
    421  result. These could return a different result each time they are forced by
    422  relying on external state. However, forcing a promise is generally assumed to
    423  be an idempotent operation, and not respecting this implicit contract in
    424  production code would be bad practice. Typed Racket disallows non-cached
    425  promises altogether. We introduced a small module @racketmodname[delay-pure]
    426  which allows the safe creation of non-cached promises.
    427  @racketmodname[delay-pure] restricts the language to a small subset of
    428  functions and operators which are known to not perform any mutation, and
    429  prevents access to mutable variables. This ensures that the promises created
    430  that way always produce the same value, without the need to actually cache
    431  their result.
    432 
    433  @include-equation["phi-psi-o-path.rkt" pe]
    434 
    435 }
    436 
    437 @asection{
    438  @atitle{Subtyping}
    439  The subtyping judgement is @${@<:[τ σ]}. It indicates that @${τ} is a
    440  subtype of @${σ} (or that @${τ} and @${σ} are the same type).
    441 
    442  The @<:* relation is reflexive and transitive. When two or more types are all
    443  subtypes of each other, they form an equivalence class. They are considered
    444  different notations for the same type, and we note @=:[τ σ], whereas @≠:[τ σ]
    445  indicates that @${τ} and @${σ} are not mutually subtypes of each other (but
    446  one can be a strict subtype of the other).
    447 
    448  @$p[@include-equation["subtyping.rkt" S-Eq₁]
    449      @include-equation["subtyping.rkt" S-Eq₂]
    450      @include-equation["subtyping.rkt" S-Eq₃]
    451      @include-equation["subtyping.rkt" S-Reflexive]
    452      @include-equation["subtyping.rkt" S-Transitive]]
    453 
    454  The @${⊥} type is a shorthand for the empty union @${(∪)}. It is a subtype of
    455  every other type, and is not inhabited by any value.
    456  @refrule[@textsc{S-Bot-Sub}] can be derived from @refrule[@textsc{S-Bot}]
    457  and @refrule[@textsc{S-UnionSub}], by constructing an empty union.
    458 
    459  @$p[@include-equation["subtyping.rkt" S-Top]
    460      @include-equation["subtyping.rkt" S-Bot]
    461      @include-equation["subtyping.rkt" S-Bot-Sub]]
    462 
    463  The singleton types @num-τ and @symτ[s] which are only inhabited by their
    464  literal counterpart are subtypes of the more general @Numberτ or @Symbolτ
    465  types, respectively.
    466 
    467  @$p[@include-equation["subtyping.rkt" S-Number]
    468      @include-equation["subtyping.rkt" S-Symbol]]
    469 
    470  The following subtyping rules are concerned with function types and
    471  polymorphic types:
    472 
    473  @$p[@include-equation["subtyping.rkt" S-Fun]
    474      @include-equation["subtyping.rkt" S-R]
    475      @include-equation["subtyping.rkt" S-Fun*]
    476      @include-equation["subtyping.rkt" S-Fun*-Fixed]
    477      @include-equation["subtyping.rkt" S-Fun*-Fixed*]
    478      @include-equation["subtyping.rkt" S-DFun]
    479      @include-equation["subtyping.rkt" S-Poly-α-Equiv]
    480      @include-equation["subtyping.rkt" S-PolyD-α-Equiv]
    481      @include-equation["subtyping.rkt" S-DFun-Fun*]]
    482 
    483  @todo{@textsc{S-PolyD-α-Equiv} should use the substitution for a polydot
    484   (subst-dots?), not the usual subst.}
    485 
    486  @todo{check the @textsc{S-DFun-Fun*} rule.}
    487 
    488  @htodo{Try to detach the ∀ from the →, in case the → is nested further deep.
    489   If it works.}
    490 
    491  The following rules are concerned with recursive types built with the
    492  @racket[Rec] combinator. The @refrule[@textsc{S-RecWrap}] rule allows
    493  considering @Numberτ a subtype of @recτ[r Numberτ] for example (i.e. applying
    494  the recursive type combinator to a type which does not refer to @${r} is a
    495  no-op), but it also allows deriving
    496  @<:[@recτ[r @un[@consτ[τ r] @null-τ]] @un[@consτ[τ ⊤] @null-τ]]. The
    497  @refrule[@textsc{ S-RecElim}] rule has the opposite effect, and is mainly
    498  useful to “upcast” members of an union containing @${r}. It allows the
    499  deriving @<:[@null-τ @recτ[r @un[@consτ[τ r] @null-τ]]]. The rules
    500  @refrule[@textsc{ S-RecStep}] and @refrule[@textsc{S-RecUnStep}] allow
    501  unraveling a single step of the recursion, or assimilating an such an
    502  unraveled step as part of the recursive type.
    503 
    504  @todo{TODO: renamings}
    505 
    506  @$p[
    507  @include-equation["subtyping.rkt" S-RecWrap]
    508  @include-equation["subtyping.rkt" S-RecElim]
    509  @include-equation["subtyping.rkt" S-RecStep]
    510  @include-equation["subtyping.rkt" S-RecUnStep]]
    511 
    512  The rules below describe how union and intersection types compare.
    513 
    514  @$p[@include-equation["subtyping.rkt" S-UnionSuper]
    515      @include-equation["subtyping.rkt" S-UnionSub]
    516      @include-equation["subtyping.rkt" S-IntersectionSub]
    517      @include-equation["subtyping.rkt" S-IntersectionSuper]]
    518 
    519  Finally, promises are handled by comparing the type that they produce when
    520  forced, and pairs are compared pointwise. Dotted lists types, which usually
    521  represent the type of the value assigned to a variadic polymorphic function's
    522  “rest” argument
    523 
    524  @$p[@include-equation["subtyping.rkt" S-Promise]
    525      @include-equation["subtyping.rkt" S-Pair]
    526      @include-equation["subtyping.rkt" S-DList]]
    527 
    528 }
    529 
    530 @asection{
    531  @atitle{Operational semantics}
    532 
    533  The semantics for the simplest expressions and for primitive functions are
    534  expressed using δ-rules.
    535 
    536  @$p[@include-equation["operational-semantics.rkt" E-Delta]
    537      @include-equation["operational-semantics.rkt" E-DeltaE]]
    538 
    539  @include-equation["operational-semantics.rkt" δ-rules]
    540 
    541  @include-equation["operational-semantics.rkt" δe-rules]
    542 
    543  The @refrule[@textsc{E-Context}] rule indicates that when the expression has
    544  the shape @${E[L]}, the subpart @${L} can be evaluated and replaced by its
    545  result. The syntax @${E[L]} indicates the replacement of the only occurrence
    546  of @${[⋅]} within an evaluation context @${E}. The evaluation context can then
    547  match an expression with the same shape, thereby separating the @${L} part
    548  from its context.
    549 
    550  @include-equation["operational-semantics.rkt" E-Context]
    551 
    552  The next rules handle β-reduction for the various flavours of functions.
    553 
    554  @$p[@include-equation["operational-semantics.rkt" E-Beta]
    555      @include-equation["operational-semantics.rkt" E-Beta*]
    556      @include-equation["operational-semantics.rkt" E-BetaD]]
    557 
    558  Instantiation of polymorphic abstractions is a no-op at run-time, because
    559  @typedracket performs type erasure (no typing information subsists at
    560  run-time, aside from the implicit tags used to distinguish the various
    561  primitive data types: pairs, numbers, symbols, @null-v, @true-v, @false-v,
    562  functions and promises).
    563 
    564  @$p[@include-equation["operational-semantics.rkt" E-TBeta]
    565      @include-equation["operational-semantics.rkt" E-TDBeta]]
    566 
    567  For simplicity, we assume that promises only contain pure expressions, and
    568  therefore that the expression always produces the same value (modulo object
    569  identity, i.e. pointer equality issues). In practice, @typedracket allows
    570  expressions relying on external state, and caches the value obtained after
    571  forcing the promise for the first time. The subset of the language which we
    572  present here does not contain any mutable value, and does not allow mutation
    573  of variables either, so the expression wrapped by promises is, by definition,
    574  pure. We note here that we implemented a small library for @typedracket which
    575  allows the creation of promises encapsulating a pure expression, and whose
    576  result is not cached.
    577 
    578  @include-equation["operational-semantics.rkt" E-Force]
    579 
    580  Once the evaluation context rule has been applied to evaluate the condition of
    581  an @ifop expression, the evaluation continues with the @emph{then} branch or
    582  with the @emph{else} branch, depending on the condition's value. Following
    583  @lisp tradition, all values other than @false-v are interpreted as a true
    584  condition.
    585 
    586  @$p[@include-equation["operational-semantics.rkt" E-If-False]
    587      @include-equation["operational-semantics.rkt" E-If-True]]
    588 
    589  The @gensyme expression produces a fresh symbol @${@sym* ∈ 𝒮*}, which is
    590  guaranteed to be different from all symbol literals @${s ∈ 𝒮}, and different
    591  from all previous and future symbols returned by @|gensyme|. The @eq?op
    592  operator can then be used to compare symbol literals and symbols produced by
    593  @|gensyme|.
    594 
    595  @$p[@include-equation["operational-semantics.rkt" E-Gensym]
    596      @include-equation["operational-semantics.rkt" E-Eq?-True]
    597      @include-equation["operational-semantics.rkt" E-Eq?-False]]
    598 
    599  The semantics of @mapop are standard. We note here that @mapop can also be
    600  used as a first-class function in @typedracket, and the same can be achieved
    601  with the simplified semantics using the η-expansion
    602  @;
    603  @Λe[(α β) @λv[(@${x_f:@f→[(α) @R[β ϵ ϵ ∅]]}
    604                  @${x_l:@Listofτ[α]}) @mapop[x_f x_l]]]
    605  of the @mapop operator.
    606 
    607  @$p[@include-equation["operational-semantics.rkt" E-Map-Pair]
    608      @include-equation["operational-semantics.rkt" E-Map-Null]]
    609 
    610 }
    611 
    612 @asection{
    613  @atitle{Type validity rules}
    614 
    615  Polymorphic type variables valid types if they are bound, that is if they are
    616  present in the @${Δ} environment. Additionally variadic (i.e. dotted)
    617  polymorphic type variables may be present in the environment. When this is the
    618  case, they can be used as part of a @List…τ[τ α] type.
    619 
    620  @$p[@include-equation["te.rkt" TE-Var]
    621      @include-equation["te.rkt" TE-DList]]
    622 
    623  @htodo{There are more rules needed (one for building every type, most are
    624   trivial).}
    625 
    626  @htodo{isn't there any well-scopedness constraint for the φ?}
    627 
    628  The following rules indicate that function types are valid if their use of
    629  polymorphic type variables is well-scoped.
    630 
    631  @$p[@include-equation["te.rkt" TE-DFun]
    632      @include-equation["te.rkt" TE-All]
    633      @include-equation["te.rkt" TE-DAll]
    634      @include-equation["te.rkt" TE-DPretype]]
    635 
    636  The following rule indicates that types built using the recursive type
    637  combinator @recτ* are valid if their use of the recursive type variable @${r}
    638  is well-scoped.
    639 
    640  @include-equation["te.rkt" TE-Rec]
    641 
    642  The next rules are trivial, and state that the base types are valid, or simply
    643  examine validity pointwise for unions, intersections, pairs, promises and
    644  filters. @htodo{and objects}
    645 
    646  @$p[
    647  @include-equation["te.rkt" TE-Trivial]
    648  @include-equation["te.rkt" TE-R]
    649  @include-equation["te.rkt" TE-Phi]
    650  @include-equation["te.rkt" TE-Psi]
    651  @include-equation["te.rkt" TE-Psi-Not]
    652  @include-equation["te.rkt" TE-Psi-Bot]]
    653 
    654 }
    655 
    656 @asection{
    657  @atitle{Typing rules}
    658 
    659  The rules below relate the simple expressions to their type.
    660 
    661  @htodo{Are the hypotheses for T-Eq? necessary? After all, in Racket eq? works
    662   on Any.}
    663 
    664  @$p[@include-equation["trules.rkt" T-Symbol]
    665      @include-equation["trules.rkt" T-Gensym]
    666      @include-equation["trules.rkt" T-Promise]
    667      @include-equation["trules.rkt" T-Var]
    668      @include-equation["trules.rkt" T-Primop]
    669      @include-equation["trules.rkt" T-True]
    670      @include-equation["trules.rkt" T-False]
    671      @include-equation["trules.rkt" T-Num]
    672      @include-equation["trules.rkt" T-Null]
    673      @include-equation["trules.rkt" T-Eq?]]
    674 
    675  Below are the rules for the various flavours of lambda functions and
    676  polymorphic abstractions.
    677 
    678  @htodo{Technically, in the rules T-Abs and T-DAbs, we should keep any φ and o
    679   information concerning outer variables (those not declared within the lambda,
    680   and therefore still available after it finishes executing).}
    681 
    682  @todo{Should the φ⁺ φ⁻ o be preserved in @refrule[@textsc{T-TAbs}] and
    683   @refrule[@textsc{T-DTAbs?}]}
    684 
    685  @$p[@include-equation["trules.rkt" T-AbsPred]
    686      @include-equation["trules.rkt" T-Abs]
    687      @include-equation["trules.rkt" T-Abs*]
    688      @include-equation["trules.rkt" T-DAbs]
    689      @include-equation["trules.rkt" T-TAbs]
    690      @include-equation["trules.rkt" T-DTAbs]]
    691 
    692  The @${\vphantom{φ}@substφo[x ↦ z]} operation restricts the information
    693  contained within a @${φ} or @${o} so that the result only contains information
    694  about the variable @${x}, and renames it to @${z}. When applied to a filter
    695  @${φ}, it corresponds to the @${\operatorname{abo}} and @${\operatorname{
    696    apo}} operators from
    697  @~cite[#:precision "pp. 65,75" "tobin-hochstadt_typed_2010"].
    698 
    699  The @${⊥} cases of the @${\operatorname{apo}} operator
    700  from@~cite[#:precision "pp. 65,75" "tobin-hochstadt_typed_2010"] are covered
    701  by the corresponding cases in the @${@restrict} and @${@remove} operators
    702  defined below, and therefore should not need to be included in our @${
    703   \vphantom{φ}@substφo[x ↦ z]} operator. The subst
    704 
    705  @include-equation["trules.rkt" substφ]
    706  @include-equation["trules.rkt" substo]
    707 
    708  @htodo{The definition of Γ' does not specify what the other cases ≠ x are
    709   (they are the same as the original Γ, but this is only implicit).}
    710 
    711  The @racket[map] function can be called like any other function, but also has
    712  a specific rule allowing a more precise result type when mapping a polymorphic
    713  function over a @List…τ[τ α]. @racket[ormap], @racket[andmap] and
    714  @racket[apply] similarly have special rules for variadic polymorphic lists. We
    715  include the rule for @racket[map] below as an example. The other rules are
    716  present in @~cite[#:precision "pp. 96" "tobin-hochstadt_typed_2010"].
    717 
    718  @htodo{The original TD-Map rule (p.95) seems wrong, as it allows un-dotted
    719   references to α in the function's type. But it is impossible to construct such
    720   a function, and the meaning of α in that case is unclear. I think the rule
    721   should instead expect a polymorphic function, with occurrences of α in τ_r
    722   replaced with the new β variable, as shown below.}
    723 
    724  @include-equation["trules.rkt" T-DMap]
    725 
    726  Below are the typing rules for the various flavours of function application and
    727  instantiation of polymorphic abstractions.
    728 
    729  @todo{For the inst rules, are the φ⁺ φ⁻ o preserved?}
    730 
    731  @$p[@include-equation["trules.rkt" T-App]
    732      @include-equation["trules.rkt" T-Inst]
    733      @include-equation["trules.rkt" T-DInst]
    734      @include-equation["trules.rkt" T-DInstD]]
    735 
    736  @;=====================TODO:write something vvvvvvvvvvvv
    737 
    738  The rule for @ifop uses the information gained in the condition to narrow the
    739  type of variables in the @emph{then} and @emph{else} branches. This is the
    740  core rule of the occurrence typing aspect of @|typedracket|.
    741 
    742  @include-equation["trules.rkt" T-If]
    743 
    744  The @${Γ + φ} operator narrows the type of variables in the environment using
    745  the information contained within @${φ}.
    746 
    747  @include-equation["trules.rkt" Γ+]
    748 
    749  The @update operator propagates the information contained within a @${ψ} down
    750  to the affected part of the type.
    751 
    752  @include-equation["trules.rkt" update]
    753 
    754  The @update operator can then apply @restrict to perform the intersection of
    755  the type indicated by the @|ifop|'s condition and the currently-known type for
    756  the subpart of the considered variable.
    757 
    758  @todo{How do @restrict and @remove behave on intersections?}
    759 
    760  @include-equation["trules.rkt" restrict]
    761 
    762  The @update operator can also apply
    763  the @remove operator when the condition determined that the subpart of the
    764  considered variable is @emph{not} of a given type.
    765 
    766  @include-equation["trules.rkt" remove]
    767 
    768  @;{Shouldn't no-overlap be simplified to @${@no-overlap(τ, τ') = (@<:[σ τ]
    769    ∧ @<:[σ τ′] ⇒ σ = ⊥)}? Then @${@restrict(τ,σ)} can be simplified to returning
    770   the most general type which is a subtype of τ and σ if one exists (or maybe
    771   simply returning the intersection of τ and σ).}
    772 
    773  @todo{Δ is not available here.}
    774  @todo{The non-nested use of σ is not quite correct syntactically speaking}
    775 
    776  The @restrict operator and the @simplify* operator described later both rely
    777  on @no-overlap to determine whether two types have no intersection, aside from
    778  the @${⊥} type.
    779 
    780  @include-equation["trules.rkt" no-overlap]
    781 
    782  @htodo{Say that there are more rules in the implementation, to handle various
    783   boolean operations.}
    784 
    785  The @combinefilter operator is used to combine the @${φ} information from the
    786  two branches of the @ifop expression, based on the @${φ} information of the
    787  condition. This allows @typedracket to correctly interpret @racket[and],
    788  @racket[or] as well as other boolean operations, which are implemented as
    789  macros translating down to nested @racket[if] conditionals. @Typedracket will
    790  therefore be able to determine that in the @emph{then} branch of
    791  @racket[(if (and (string? x) (number? y)) 'then 'else)], the type of
    792  @racketid[x] is @racket[String], and the type of @racketid[y] is
    793  @racket[Number]. We only detail a few cases of combinefilter here, a more
    794  complete description of the operator can be found
    795  in@~cite[#:precision "pp. 69,75–84" "tobin-hochstadt_typed_2010"].
    796 
    797  @include-equation["trules.rkt" combinefilter]
    798 
    799  @htodo{The Γ ⊢ x : τ … does not generate a Γ(x) = τ, I suspect. There should
    800   be indicated somewhere an equivalence between these two notations (and we
    801   should fix the @${Γ,x:update(…)}, as it is a third notation).}
    802 
    803 }
    804 
    805 @asection{
    806  @atitle{Simplification of intersections}
    807 
    808  In some cases, intersections are simplified, and the eventual resulting @${⊥}
    809  types propagate outwards through pairs (and structs, which we do not model
    810  here). The @simplify* and @propagate⊥ operators show how these simplification
    811  and propagation steps are performed. The simplification step mostly consists
    812  in distributing intersections over unions and pairs, and collapsing pairs and
    813  unions which contain @${⊥}, for the traversed parts of the type.
    814 
    815  @include-equation["simplify.rkt" Simplify1]
    816 
    817  @${@simplify[τ]} is applied pointwise in other cases:
    818 
    819  @include-equation["simplify.rkt" Simplify2]
    820 
    821  @include-equation["simplify.rkt" Propagate⊥]
    822 
    823  @todo{Apply the intersections on substituted poly types after an inst (or rely
    824   on the sutyping rule for intersections to recognise that ⊥ is a subtype of the
    825   resulting type?)}.
    826 
    827 }
    828 
    829 @asection{
    830  @atitle{δ-rules}
    831 
    832  Finally, the type and semantics of primitive functions are expressed using the
    833  δ-rules given below.
    834 
    835  @include-equation["deltarules.rkt"]
    836 
    837 }
    838 
    839 @asection{
    840  @atitle{Soundness}
    841 
    842  Since @typedracket is an existing language which we use for our
    843  implementation, and not a new language, we do not provide here a full proof of
    844  correctness.
    845 
    846  We invite instead the interested reader to refer to the proof sketches given
    847  in@~cite[#:precision "pp. 68–84" "tobin-hochstadt_typed_2010"]. These proof
    848  sketches only cover a subset of the language presented here, namely a language
    849  with variables, function applictation, functions of a single argument, pairs,
    850  booleans, numbers and @ifop conditionals with support for occurrence typing.
    851  Since occurrence typing is the main focus of the proof, the other extensions
    852  aggregated here should not significantly threaten its validity.
    853 }