Implementing a Type Theory with Observational Equality, Using Normalisation by Evaluation
Abstract
We report on an experimental implementation in Haskell of a dependent type theory featuring an observational equality type, based on Pujet et al.’s . We use normalisation by evaluation to produce an efficient normalisation function, which is used to implement a bidirectional type checker. To allow for greater expressivity, we extend the core calculus with quotient types and inductive types. To make the system usable, we explore various proof-assistant features, notably a rudimentary version of a “hole” system similar to Agda’s. While rather crude, this experience should inform other, more substantial implementation efforts of observational equality.
Keywords and phrases:
Dependent type theory, Bidirectional typing, Observational equality, Normalisation by evaluationCopyright and License:
2012 ACM Subject Classification:
Software and its engineering Functional languages ; Theory of computation Type theory ; Theory of computation Denotational semanticsSupplementary Material:
archived at
swh:1:dir:a55c73294775921cf98631f7da69b9a9a3dabf82
Editors:
Rasmus Ejlers Møgelberg and Benno van den BergSeries and Publisher:
Leibniz International Proceedings in Informatics, Schloss Dagstuhl – Leibniz-Zentrum für Informatik
1 Introduction
Since the inception of logics based on (dependent) type theories, propositional equality, i.e. the one manipulated in proofs, has been a thorn in the side of users. In recent years, an alternative has been proposed by Altenkirch et al. [5, 6], and developed by Pujet and Tabareau [27, 26, 28]: observational equality. It has two main characteristics. First, it is definitionally proof-irrelevant: any two proofs of equality are identified in the type theory, drastically simplifying its behaviour. Second, rather than being defined uniformly, observational equality has a specific behaviour at each type. Equality between functions is pointwise equality (function extensionality), equality between propositions is logical equivalence (propositional extensionality), and equality at quotient types is the relation by which the quotient was taken. Together, these aspects make equality closer to what mathematicians are used to, and allow seamless support for quotient types. Lean’s mathematics library [32], a leading effort in formalized mathematics, relies on such a definitionally irrelevant equality with function extensionality and quotient, although their approach is type-theoretically somewhat ill-behaved compared to observational equality.
Pujet and Tabareau’s work comes with extensive meta-theory, but no implementation. We attack this unexplored aspect with an experimental implementation of , based on normalisation by evaluation (NbE) [1]. NbE is a modern technique to decide definitional equality, the equations that the type-checker is able to automatically enforce – in contrast with propositional equality, which require explicit proofs. To decide definitional equality, NbE follows the naïve strategy of computing normal forms for the terms/types under scrutiny. NbE shines, in that it very efficiently computes these normal forms, by instrumenting the evaluation mechanism of the host language.111We somewhat depart from this by implementing defunctionalized NbE [1], where closures are used instead of meta-level functions.
Contributions.
In our implementation, we extend standard NbE techniques, as presented by e.g. Abel [1] and in Kovács’ elaboration-zoo [19], to an extension of Pujet and Tabareau’s [26]. In addition to the constructions already handled by Abel and Kovács, our type theory features a sort of definitionally irrelevant (strict) propositions [13], an observational equality valued in that sort, and quotient types by -valued relations. We also explore inductive types, as first-class constructs equipped with a Mendler-style recursion [23].
Experimental implementations of and of NbE for strict propositions already exist [7, 9], but to the best of our knowledge we are the first to describe one in print. The latter was also theoretically studied [2], but not implemented, and we observe (in Sec. 3.3) that their approach is actually problematic. Our dependently-typed adaptation of Mendler-style induction is also novel, although it would deserve a theoretical investigation we lack.
A last contribution is in some sense a non-contribution: an experience report that, apart from subtleties around strict propositions, NbE mostly just worked. This is not our achievement, but we believe it is nonetheless important to stress. The same can also be said of other techniques, such as bidirectional typing and pattern unification, which readily adapted to our setting.
In Section 2 we present the type theory we implement. As our base NbE algorithm is very close to Abel’s [1], we refer the reader to that work for background. In Section 3, we tackle the core of our implementation, NbE and type-checking for . Section 4 presents extensions: quotient and inductive types, and a lightweight feature similar to Agda’s holes.
2 Background
Our type theory is an extension of [26, 27, 28], itself based on Martin-Löf Type Theory (MLTT) [21], the staple dependently-typed theory. In this section, we first quickly sum up the additions made by compared to MLTT. Our version of is very close to that of Pujet [26], to which we refer for an extensive discussion. We then present the main point where we depart from it: the addition of inductive type as a first-class construct in the language, featuring Mendler-style recursion.
2.1 Observational type theory
Martin-Löf Type Theory.
MLTT is a dependent type theory presented by five mutually defined judgements, characterizing well-formed context , types and terms , and asserting that two terms (resp. types) are convertible or definitionally equal (resp. ). During type-checking we need to compare (dependent) types, which can contain terms. Thus, equations between the latter can appear when comparing the former, meaning we have to decide conversion between arbitrary terms.
MLTT is a language with binders, represented with names in the text for readability. In the implementation, the front language has names, but internally we use de Bruijn indices for terms and de Bruijn levels for semantic values, as is standard for NbE [1].
We use a single universe as the type of all types, with . This is known to break termination of the system [14], making the type theory undecidable and inconsistent. Yet, as this is orthogonal to our focus, we go with the simple albeit inconsistent approach in our prototype. Apart from this, our MLTT is standard, featuring dependent function () and pair () types with their -laws, natural numbers with large elimination, and a unit type.
Proof irrelevance.
The first extension of compared to MLTT are proof-irrelevant propositions, given by a universe with the following conversion rule:
We use the symbol for an arbitrary sort, or . Propositions include the false and true propositions and , and existential quantification . A type with a propositional codomain is again a proposition, representing universal quantification if the domain is relevant, or (dependent) implication if it is not.
Observational equality.
Observational equality is a family of types, representing identifications between two inhabitants of the same type.
Equality is proven by reflexivity , and can be used in two different ways: transport lets us use the proof to turn the proof into a proof of ;222Thanks to proof irrelevance, our version of transport where the motive depends on the proof of equality is inter-derivable with one without, so we include the stronger primitive for ease of use, while Pujet has the weaker primitive to simplify meta-theory. with cast , we can use a proof to construct an inhabitant of one of . The difference is that the latter applies to relevant types, while the former proves a proposition. Thus, only needs to be endowed with computational content, as all propositions are convertible.
Beyond , we add constants for symmetry () and transitivity (). These are provable using and , but some of our computation rules need them, so it is easier and cleaner to add them as primitives. This is a benefit of strict propositions: since there is no computation in the irrelevant layer, we are free to add propositional constants without needing to endow them with computational content.
Contrarily to MLTT, where equality is a type constructor and cast computes on reflexivity, in both the equality type and cast compute on the types. Yet, we still retain the following conversion, a generalisation of reduction of in MLTT – its special case when is . This should be seen as an extensionality rule, similar to -rules.
Quotient types.
Observational equality gives us a synthetic language to talk about setoids [17, 4], types equipped with an equivalence relation. We can exploit this to integrate quotient types : observational equality at such a quotient type simply boils down to the equivalence relation . Quotients come with a projection map , and their elimination captures the idea that a function out of a quotient must respect the relation, i.e. map related inputs to equal outputs.
2.2 Inductive types
We extend with a form of first-class indexed inductive types, and explore their interaction with observational equality. Our approach is exploratory, and we do not pretend to have a fully fleshed-out design, especially since we do not carry any meta-theoretic study.
First-class indexed inductive types.
Since our system does not distinguish between local and global context, our inductive types are first-class [11, 8]: we can bind them to variables, and generally treat them as any other value. They take the following form:
The variable is bound by . represents the type of indices. We have a finite list of constructors, each with a name , an argument of type , and an index , which might depend on the argument. The at the end of each constructor is mere syntax indicating the type being constructed; it is not a free variable. In what follows, we use the following shortcut: , i.e. stands for a generic inductive.
We restrict inductive types to have exactly one index, and constructors to have exactly one argument. This loses no expressivity since we can pack arguments or indices together with types, and simplifies the implementation. For further simplification, we also do not implement a positivity checker, so the typing rule allows non-strictly positive inductive types. As for universes, this is mainly orthogonal to our main concerns.
Since inductive types are first class, parameters can be handled by -abstraction, as illustrated by the standard example of vectors:
Constructors.
Values of inductive types are created by the constructors. We use fording [22, p. 65]: we allow all constructors to build a value of type for any index if they provide a proof that , where is the index computed from the argument of the constructor. In the MLTT presentation of inductive types, this constraint is instead enforced definitionally.
Pattern-matching.
Elimination of inductive types is single-level, total pattern matching:
This rule might appear strange, as the motive does not abstract over the index. Suppose as above, and we match on , so . In the branch, we substitute into . However, the index of is , this looks ill-typed! But thanks to fording we can have , given a proof of , which we do have in this branch. Moreover, since , we can use this to witness that this branch is in fact unreachable. The rule is straightforward, but for handling of the forded equality.
Observational equality for inductive types.
Observational equality between inductive types does not equate inductive types structurally: types with propositionally equal but definitionally different index and constructor types are not deemed equal.
The goal is twofold. First, this simplifies the implementation, as it means we avoid having to compare telescopes of parameters with numerous casts. Second, a purely structural equality of inductive types would equate all “boolean” inductive types (those with two argumentless constructors), a severe case of boolean blindness [16].
When the two definitions are not convertible, observational equality is simply stuck,333 As noted by Pujet [26, 5.2.2], there is a lot of room in how much definitional equalities are imposed on observational equality, the sole constraint – coming from canonicity – being that casts between convertible closed types must compute. i.e. it does not reduce further. This covers the case of definitely different inductive types (where we could be more eager and reduce to ), but also of parameterized inductive types. Indeed, for two different variables and , is stuck, and will compute further only if and are substituted by convertible types. This equality therefore does not imply . We thus do not implement a conversion rule like the following:
Deriving these definitional equalities roughly amounts to deriving a general operation for inductive types, a non-trivial enterprise which we did not attempt. Since the design of our prototype, Pujet and Tabareau [29] have explored the question further, and proposed a solution, which we did not try to reproduce.
Equality of general inductives behaves like that of natural numbers: when comparing equal constructors, the proposition steps to equality of the contents, and when they are different, it steps to . These respectively reflect injectivity and no-confusion of constructors.
For casts on constructors, as explained above we do not need to – and indeed cannot – propagate them deep in the structure. Instead, we merely need to handle indices, which amounts to composing equality proofs. Note the use of the primitive.
Mendler induction.
Pattern matching as eliminator for inductive types does not let us handle their recursive structure. That is, we have no notion of induction, as we can look only one level at a time. To correct this, we introduce in a style extending Mendler recursion [23] to dependent induction.
To express it, we first need an operation which applies a functor to a type .
This operation is defined by the following equation:
In essence, is an inductive type which is mute in the variable , that is, non-recursive. It represents adding a single “layer” of -structure over the family .
Using this primitive, we can express the type of Mendler-style induction. As above, we abbreviate the inductive type to . The type is the one we want to inhabit by induction.
To type the body of the fixed point, Mendler induction operates by introducing a generic type family, and an inhabitant of , and demands that we construct an inhabitant of at , while having access to “recursive calls” only on inhabitants of via the function . Intuitively, we can pattern-match on , recovering values of corresponding to “subterms”, that can be used for recursive calls. Since is abstract, this is the only way to call , and so the fixed point we obtain is structurally decreasing.
The operation computes when applied to a constructor, as per the following rule. The argument must be a constructor in order to prevent infinite unfolding.
Views and paramorphisms.
Mendler induction ensures is well-founded by restricting recursive appeals to the induction hypothesis. However, in this process, we lose information: we only have access to recursive calls, but not to the current value of the inductive type. In categorical parlance, fixed-points and pattern matching implement catamorphisms: generalised folds over tree-like structures.
What we want instead are paramorphisms, which provide primitive recursion by giving access to the current value. We thus introduce an extra function to view the opaque as the inductive type it represents. Once the knot of the fixed point is tied and the variable is substituted for the inductive type, this becomes the identity.
To type the fixed point’s body we need to lift into . Hence, we need again the action of the functor on values, i.e. the associated . As explained above, we do not provide infrastructure to derive this operation. We instead allow an inductive definition to come with a user-provided functor action.444We do not check this indeed is the functor action, since generating the equalities a correct operation satisfies is basically the same as deriving that operation itself. Note that in the premise we use an inductive type without a functor.
To be able to use this definition, we introduce the term for projecting the functorial action from an inductive type and , witnessing the isomorphism between and , which is the identity function on constructors: .
With this infrastructure, we extend the typing rule for fixed-points.
The variable is now accessible in both the motive and the body of the fixed-point, facilitating primitive recursion. At the top level, is substituted by the identity function. By functoriality, this means is , which also behaves as the identity.
In summary, if the user provides a operation, we leverage that to upgrade our Mendler-style catamorphisms to paramorphisms. Of course, in a full-fledged implementation we would derive that operation automatically, and simply give access to the paramorphism.
3 Core Implementation
Let us start with the core features of : strict propositions and inductive equality. The implementation is written in Haskell, and makes extensive use of structural data types and declarative style to keep the code as close as possible to the theory. Figure 1 gives an overview of the implementation’s structure. We use for the meta-level (i.e. Haskell’s) function type, and a sans font for its types and functions.
3.1 Syntax
Syntax.
We present in Russell style [21, 25], so we have a common grammar for both terms and types, given in Figure 2. This is roughly the one given in Pujet [26], with some additions: let bindings and type annotations, which are important with bidirectional typing, and, as explained in Section 2.1, constants for symmetry and transitivity.
| Universe sorts | ||
|---|---|---|
| | Variable | |
| Universe | ||
| Dependent functions | ||
| Natural numbers | ||
| Dependent pairs | ||
| False, true and unit types | ||
| Box types | ||
| Observational equality | ||
| Transport and casting | ||
| Let binding | ||
| Type annotation |
We use a unit type , with the term-directed -conversions and . These break transitivity of a term-directed algorithmic conversion: in the context , we have but . This is a trade-off: since we impose inductive types to have exactly one index and constructors exactly one argument, this unit type is handy to pad these positions with definitionally irrelevant content. In a more mature implementation, this would not be necessary, and we could drop our ill-behaved , or adopt the more complex – and satisfactory – solution proposed by Kovács [20].
Box types turn a type into a proposition – what is alternatively called squashing, truncation, or inhabited – see Pujet [26] for details.
Application is tagged with the sort of the argument , and -terms and pairs with their domain sort. This is necessary for evaluation, but is always inferred during type-checking; users need not give these annotations in the source syntax.
This grammar inductively defines the type of pre-terms: syntactically well-formed, but untyped. We define another type of well-typed terms. Every well-typed term has a (unique) sort – or –, the type of its type. We let and be the set of terms with sort and respectively. In the code we have separate types for and , the former using named variables and the latter de Bruijn indices. We cannot enforce in Haskell that contains only well-typed terms, but maintain this as an invariant.
In what follows, we do not always cover all cases, focusing on the most interesting or illustrative ones. The code can be consulted for the complete picture.
Normal forms.
Normals and neutrals are defined mutually as predicates on . In contrast to Pujet [27], they are deep, so subterms are also required to be normal.
We only need to characterize normal forms in , i.e. relevant terms. Indeed, since proof-irrelevant terms have no notion of evaluation, they all are “normal forms”. This means that normal forms are only unique up to -equality and proof irrelevance. Luckily, thanks to typing constraints, irrelevant subterms of a relevant normal form can only appear as arguments to , to , or an application tagged with , which lets us decide which subterms (not) to compare purely syntactically, without typing information.
Normal forms, as standard, correspond to constructors – observational equality and cast are viewed as destructors, and so are not normal forms. Neutral forms are somewhat more involved. The observational equality type can be blocked in three places – the type, or either of the terms – although there are no neutral forms when the equality is at a or type, as such equalities always reduce. Similarly, casts can also block in three positions: either of the types, or the term being cast. Again, casts between universes, or types always reduce, and so cannot be blocked by the argument. To avoid quadratic blow-up in the presentation, some cases overlap, for example and both cover .
Pujet [26, 5.2.2] discusses the definitional equalities observational equality should satisfy, for instance whether should evaluate to or be stuck. He remarks we can replace the reduction of by two constants corresponding to the two projections out of the would-be reduct:
We chose to make conversion compute as much as possible as a minimal form of automation, although it is not entirely clear whether this makes using the proof assistant really easier.
3.2 Evaluation in the relevant layer
The overall picture for NbE is similar to the standard case [1]: we give a semantic interpretation into a domain of values, and a quoting function to reconstruct normal forms. The main difficulty is to account for complex reduction rules for propositions and casts, and proof-irrelevant propositions. We defer the latter to Section 3.3. Note that we implement untyped rather than type-directed NbE. Although the latter would have avoided issues around the unit type (see Sec. 3.1), we chose it to avoid an extra layer of complexity, and check that even a complex type theory like can still be implemented this way.
Semantic domain.
| (see Sec. 3.3) | |||||
First, we construct the various domains data-structures in Figure 3. The domains and represent respectively normal and neutral forms. The domain represents propositional values and is explained in Section 3.3. is the union of and , and we often omit the injections and .
These are defined mutually with closures indexed by their return sort and their arity , as not all of them await a single argument. This is a landmark of defunctionalised NbE, which replaces semantic functions by such closures, making the various domains first-order strictly positive datatypes. Abel [1] needs a single kind of closure, consisting of an environment and a term, representing a meta-level function of type . Here, we need to defunctionalise various evaluation functions, and thus have multiple forms.
Neutral terms for observational equality and casting are simplified: we do not keep track of which of the three arguments to and is blocking. This is a trade-off between a precise semantic domain and a simpler interpretation function. As the goal here is to implement the system, not prove its correctness, we choose the simpler representation.
Environments contain values from both sorts. An environment interprets a context, where each variable has a sort. It is a program invariant that the domain sort in each position in the environment matches the typing context.
Interpretation.
Inputs to relevant interpretation are well-typed terms of sort ; that is, the set . Therefore, we construct the function
The interpretation is given in Figure 4. The underlined functions and are semantic counterpart to eliminators, and are defined mutually with evaluation, see below.
We also need a function for applying a closure to values of either sort:
Applying to argument of the correct sort is a code invariant but not statically type-checked.555This could be enforced with closures indexed a type-level list of sorts. We use the shorthand notation for .
As closures are used to defunctionalise specific operations, we define those alongside the corresponding case for . To begin with, we have the primary cases of a continuation, , corresponding to substitution, and , for a constant closure ignoring its argument.
Semantic application directly uses generic closure application.
Semantic observational equality.
To complete the semantic interpretation, we need to define and , the semantic counterpart to the observational equality type and to cast, which implement their reduction behaviour. The former is given in Figure 5.
Semantic equality straightforwardly implements the computational behaviour of observational equality. Note the use of the two defunctionalising closures and : forwards the equality proof into a second closure which performs the computation. This is necessary because we have two positions requiring arity-one closures, so they cannot be combined. When the types have an irrelevant domain, we need a propositional witness of type , so we use and the freeze function for embedding relevant values into the irrelevant domain, both of which will be introduced in Section 3.3.
Semantic cast.
The final component to complete evaluation is the semantic function, given in Figure 6, again straightforwardly implementing reduction rules for casts. Note the proof manipulation implemented by propositional application and projections and , and again the embedding .
Quoting.
The mutually recursive functions and let us quote domain values back into normal and neutral forms, at de Bruijn level . We rely on a helper function to fully apply a closure to fresh variables.
Quoting is given in Figure 7, and follows the expected pattern. The cases for equality and casting do not ensure statically that they produce neutral forms. However, it is a program invariant that one position will be a blocking neutral, so the term is a neutral form in .
3.3 Semantic propositions
Proofs, i.e. inhabitants of propositions, are all equal. We should thus never evaluate such irrelevant terms, and this should be reflected in the design of the domain of semantic propositions . We explored three different approaches, the first two of which (proof erasure and syntactic propositions) we found unsatisfactory, until we reached the final design we are happy with: implementing as a semantic domain.
Proof erasure.
The simplest strategy to handle proof-irrelevance is to rather brutally erase irrelevant terms at evaluation, as suggested in Abel et al. [2]. This amounts to having a single semantic proposition, i.e. defining . This vastly simplifies the implementation, by removing intricate proof manipulations.
Although this approach is correct in terms of deciding the equational theory, it has a major drawback: normal forms cannot be quoted back to terms. Indeed, since proofs are erased, there is no information left to quote! This has nasty consequences. First, we must deal with this missing information when printing terms back to users, for instance in error messages. Quoting is also using during unification, to provide term solutions for unification variables – see Sec. 4.3.
As a mitigation, Abel et al. propose to extend the language by a constant which proves every provable proposition. In practice, this would amount to indicate in quoted terms where proofs exist, but without giving a precise witness. However, one must be careful to exclude from the source language, as it makes type-checking wildly undecidable by making it depend on inhabitation. Decidability could be recovered by instead having prove all propositions, at the cost of making the type theory inconsistent, also far from ideal. Thus, in this approach we have to maintain a careful and clumsy distinction between “user-issued” terms and “kernel-generated” ones, with annoying consequences in the interaction with users: for instance, it means they would not be able to copy code from messages. We thus chose to reject this solution and look for another one.
Syntactic propositions.
A natural alternative is to retain syntactic witnesses for proof terms during evaluation: since we never need to evaluate propositions, there seems to be no point in translating them to a domain such as , which is designed for efficient evaluation. This amounts to setting – a proof witness and an environment interpreting its free variables. Indeed, while they do not reduce, propositions still admit substitutions of their variables, which happens when evaluating relevant terms, and must be accounted for. This is the point of the stored environment, used to interpret free variables during quoting.
More challenging, though, is the proof manipulation which occurs in casting reduction rules. This requires inserting a proof-relevant value into the proof witness and shifting propositions to be well-typed in a different context. In this approach, evaluation and quoting become mutually defined, and great care must be taken to transform witnesses correctly. This entanglement of evaluation and quoting is both unsatisfying and error-prone.
Semantic propositions.
We therefore introduce a third design: using a semantic domain similar to . The idea is that values in this domain never reduce, they only admit substitution, which is handled by closures, but they use de Bruijn levels, making it unnecessary to shift or quote terms during evaluation. As relevant data might appear as subterms of propositions, also embeds relevant terms. However, these do not reduce: they are “frozen”.
The domain of semantic propositions has a structure similar to terms, except for the use of closures for bound variables, and de Bruijn levels. Even let bindings and type annotations are represented, unevaluated. Calligraphic letters represent closures, which are the same as in Section 3.2, but have values from in place of .
Next, we introduce freezing, the mapping of semantic relevant values into semantic propositions, so that they may be used in proof terms. It is defined mutually with which embeds closures. Representative cases are given as follows:
Freezing has to traverse the whole term, which is rather inefficient, especially if we repeatedly freeze the same term. In retrospect, it might be possible to replace it by a mere constructor which freely embeds into .
Semantic interpretation for propositions, , is particularly easy as there are no reductions. We give only a few cases, others are entirely similar.
Projections from the environment are like in relevant interpretation, although when the entry is relevant, we freeze it with . This handles substitution – syntactic variables are substituted by values from the environment. -expressions introduce a closure which can be entered, but this never happens due to application, only during quoting. Interpretation of application always produces a , even when the interpretation of is .
We also define a function for applying closures. This works similarly to , only no reduction occurs: compared to Figure 5, we replace each semantic operator by a constructor. For example,
Finally, we also have quoting for semantic propositions , which computes in the same way as quoting for , fully applying closures to fresh variables.
3.4 Conversion checking
Conversion checking is used to decide the conversion relation , by operating on semantic values. This relation is non-trivial because normalisation, due to being untyped, does not handle extensionality rules. Yet, we still want to check equality up to and irrelevance, so this is implemented when comparing semantic values. Conversion checking is untyped and term-directed, so -expansion is triggered when one side of the conversion equation is a constructor, and the other is neutral.666This strategy is due to Coquand [10], and implemented in Coq and in Agda for functions. For types, for instance, we get
In practice, is replaced by an integer representing its length.
Conversion checking between irrelevant terms always succeeds. In fact, we only define conversion checking between values in , and proof irrelevance is implemented by not recursively comparing irrelevant terms. Consider for instance applications:
When arguments are irrelevant, is automatic and thus not checked. This explains the annotation of applications with the sort of their argument, to decide which rule to choose.
On top of -conversion, we also implement the extra equation. Treating this rule as a reduction breaks determinism, as there are multiple paths to evaluate some cast expressions. More worrying, it makes reduction and conversion checking mutually recursive. Thus, it is easier to implement it during conversion checking, although this necessitates backtracking. The implementation uses the following rules.
When the left-hand side of the equality is a cast between and , we first try Cast-Eq-Left. If this fails, we proceed with Cast-Eq-Right, and if that fails too, Cast-Conv. Backtracking is necessary as it is impossible to know a priori which strategy succeeds. Fortunately, eagerly applying Cast-Eq-Left and Cast-Eq-Right is complete, i.e. it does not lose solutions. Indeed, if Cast-Eq-Left and Cast-Conv both apply to derive , then all four types , , and are convertible, and so Cast-Conv can be replaced by Cast-Eq-Left and Cast-Eq-Right.
3.5 Bidirectional type checking
Our approach to type-checking, based on bidirectional typing, is close to e.g. Gratzer et al. [15], or what Agda implements [24]. We mutually implement the two judgements
Besides the context , we have an environment interpreting it, which is necessary to handle let-binders, as explained below. Typing uses semantic types, . Although we do not include it on paper, type-checking actually elaborates terms: while checking a pre-term in , we generate a term in , for instance annotating applications with a sort.
In this approach, constructors are checked, and destructors are inferred, and thus only normal forms are typable. To allow for more flexibility, we add two mechanisms. Type annotations let us locally record a type in a term to get back to type-checking when necessary, as per the following rule:
Let-bindings, on the other hand, can be checked or inferred, and the current mode is forwarded to the body , while the bound term is always checked against the (evaluation of the) type .
The environment is extended with the value of the variable , so that it can be used transparently while typing . We also get sharing, because a let-bound is only evaluated once at its binding site. Compare with a -redex, where the environment is extended by a variable:
Finally, while in vanilla MLTT and the equality type are constructors, this is not true in . Since equality types reduce, it is unfeasible, given a semantic type, to guess which equality it represents. For instance, many equalities reduce to . The reasonable solution is to have reflexivity infer, in line with viewing it as a destructor on the universe:
Note the use of the semantic equality type as the inferred type. So, for example, will infer , as we immediately reduce the type . Also note that this issue could have been avoided by having an equality type which does not compute, which is in hindsight a rather compelling argument for this approach.
4 Extensions
4.1 Quotient types
The ability to easily handle quotient types is one of the landmarks of observational type theory, it is thus natural to consider them as our first extension. The adaptation of NbE is actually relatively straightforward, and follows the same patterns as the core implementation. We first extend normal and neutral forms:
Note that the proofs that the relation is an equivalence – in quotient formation – and that the quotient is respected – in the eliminator – are arbitrary, as they are propositions.
We extend the semantic domains accordingly, introducing three new closures to defunctionalise the equality type reduction between quotient types and its three binders.
|
Relevant interpretation for quotients follows the same pattern as the core NbE algorithm. Quotient types are interpreted into the constructor, with the appropriate closures. Projections are interpreted into the constructor. Elimination is defined by
where reduces quotient eliminators applied to projections.
Irrelevant interpretation, , is trivially extended: once again, there is no reduction when an eliminator is applied to a projection. Quoting also takes the same form as before.
4.2 Inductive types and Mendler-style induction
Our next extension is to add inductive types, following the theory laid down in Section 2.2. The normal forms are as follows – we omit the cases of inductive types without functor instances and fixed-points without views; they follow the same shape as those presented.
|
|
Both unapplied inductive type (families) and fixed points are new normal forms. Inductive types applied to their indices are normal forms at the universe, and similarly for fixed-points. Finally, a fixed point applied to an index is neutral when its second argument, on which the fixed point computes, is itself neutral. The and terms block when their inductive type is unknown – we cannot lift type families and functions without the definition at hand –, while blocks when applied to a neutral.
Semantic domains.
As usual, the first step is to extend the domains, driven by the structure of the normal and neutral forms. Like before, we omit values for inductive types without functor definitions (in the implementation, we have optional value for the functor definition).
|
|
The semantic value of inductive types, , contains the index type, followed by a list of pairs representing constructor types and indices. We have an optional value representing the presence or absence of an index. Fixed-points have a similar structure. The neutral form represents a fixed-point blocked by a neutral argument. Defunctionalizing closures and semantic propositions are entirely unsurprising, and we omit them here.
Interpretation.
First, we give the semantics of the newly added terms.
The implementations of , , and all branch on their argument being either a constructor, in which case the relevant branch is taken, or a neutral, which leads to a neutral. They are found in the code.
Reduction of fixed points is handled by application, and we thus extend as follows:
When a semantic inductive type or fixed-point have not been applied to their index – indicated by their final component being –, we move this index into the value. When a fixed-point with an index is applied to a constructor, we invoke the closure , i.e. the body of the fixed point. Note how we pass the semantic identity function for the view.
4.3 Pattern unification
Pattern unification [3, 18] does not extend the theory, but makes writing terms more practical. Our implementation combines the contextual metavariables of Abel and Pientka [1] and NbE. Another interesting aspect, as we already mentioned, is that unification partly motivates the structure we chose for semantic propositions in Section 3.3, as we will shortly explain. Contrarily to other work, we do not insist on computing only most general solution, which would require further modifications to the structure of neutral forms.
Storing solved metavariables.
Pattern unification relies on metavariables, written and recorded in a metavariable context , which contains metavariables already solved through unification, and yet unsolved ones, as follows.
Note that we have metavariables for sorts, too. But what should be? That is, should metavariables stand for terms or for semantic values? To answer this, we must understand what operations we want to perform on them.
Metavariables are introduced during typing. As explained in Section 3.5, typing really is an elaboration procedure, taking in a preterm and constructing a term. In the presence of metavariables, it becomes stateful, as the metavariable context can be updated. The interesting rule is that which handles a hole in the surface syntax, creating two new metavariables representing the term and its type, and adding both to the metavariable context.
As any other term, we need to be able to evaluate metavariables into the semantic domains. If a metavariable is unsolved, it behaves like a variable and blocks the term, creating a new form of neutrals. We extend the semantic domain accordingly:
If a metavariable is defined, though, evaluation should reflect it. We achieve this as follows:
|
|
Indeed, we want solved metavariables to admit a substitution operation, so that we can use them in a context different from the one they were created in. Evaluation of terms is tailored to handle an environment representing a substitution, leading to the definition above. Semantic values, on the contrary, do not easily admit substitution. This leads to the choice of taking above, and to use evaluation to handle the environment.
Solving metavariables.
Metavariables are solved during conversion checking, from equations of the form . To solve such an equation, we create a partial function which succeeds when the environment satisfies the linearity conditions necessary to invert it. Partial renamings are lists of variables (with de Bruijn levels) and undefined values, , i.e. they are given by the following datastructure
|
|
We equivalently view them as partial functions on variables when this view is more useful.
In conversion, we always compare values. However, metavariable solutions are terms. Therefore, when applying the renaming to the value , we simultaneously update free variables and quote the semantic value into a term. This gives us an operation . Like with quoting, the level representing the depth we rename at. We also have access to the metavariable for the occurs check.
|
|
The first rule ensures the variable is not escaping, by checking it is defined in . The second rule implements the occurs check by ensuring the metavariable does not appear in its own solution. This way, we isolate it from linearity, which depends only on the environment . When going under a binder, we apply the closure to a fresh variable and extend the renaming in the natural way. A similar renaming operation is defined for semantic propositions in . Since we want to obtain proper terms after renaming, we need to contain enough information, explaining why the proof erasure semantics is not well-suited.
The final step is to piece these parts together to solve metavariables in conversion checking, then update the metavariable context. Both and might (validly) fail, so we take to mean that the result is defined, and assigned to the variable on the left.
4.4 A lightweight mechanism for goals
To be able to write complex terms, it is handy to build them incrementally. For this, we need a form of interactivity, where the proof assistant informs us as to what we need to provide to complete the proof: proof goals. In full-fledged proof assistants, goals are handled by the IDE and displayed using a secondary window. Implementing this is heavy, but proof goals are very necessary to be able to design even moderately-sized examples.
Instead, we implement a lightweight mechanism, where goals are inserted into
the source code to throw an error at the specific location we want to investigate.
The error message indicates the expected type at that point, if known.
Additionally, goals optionally contain lists of terms whose types
are reported to the user. We write
?{t1, t2, ..., tn}
for a goal term and a list of terms ti.
For example, consider the following code, in which we insert a proof
goal. Running the checker on the code on the left, we get the message on the right.
Using this and pattern unification, we were able to build sizable examples. The first implements booleans as a quotient on the natural numbers by the relation which relates all numbers , leaving exactly two elements: zero and “everything else”. The second reimplements Fiore’s NbE for the simply typed lambda calculus [12]. This proof demonstrates the expressivity of the system, and makes extensive use of inductive types. We do not reproduce these examples here for lack of space, but the code is available in the repository [31] and dissertation [30].
5 Conclusion
We described an NbE implementation of a significant dependently-typed language, in particular featuring observational equality and Mendler-style induction. Despite requiring some care and new ideas in the design of the implementation, especially around the semantic representation of strict propositions, the standard concepts of NbE largely apply, witnessing the robustness and power of the technique.
More generally, guiding principles drawn from the literature around unification, normalisation by evaluation, and dependent type theory in general were reliable and very useful in the design of our system. Although still very much a prototype, critically missing a proper universe system and a positivity checker, our language is usable: we have been able to implement NbE for the simply typed -calculus in the style of Fiore [12] in it.
That we were able to build such a system without major blockers and in a relatively straightforward manner is a testament to the solidity of the state of the art in the implementation of dependent type theories. On the other hand, many of the experimental implementations we learned a lot from are relatively under-documented, and often unpublished. We are surely not the only ones who would have benefitted from a more visible literature on the subject, and we can only encourage the authors of these experimental implementations to describe their valuable work in publications or talks!
References
- [1] Andreas Abel. Normalization by Evaluation Dependent Types and Impredicativity. PhD thesis, Institut für Informatik Ludwig-Maximilians-Universität München, München, May 2013. URL: https://www.cse.chalmers.se/˜abela/habil.pdf.
- [2] Andreas Abel, Thierry Coquand, and Miguel Pagano. A modular type-checking algorithm for type theory with singleton types and proof irrelevance. In Pierre-Louis Curien, editor, Typed Lambda Calculi and Applications, pages 5–19, Berlin, Heidelberg, 2009. Springer Berlin Heidelberg. doi:10.1007/978-3-642-02273-9_3.
- [3] Andreas Abel and Brigitte Pientka. Higher-Order Dynamic Pattern Unification for Dependent Types and Records. In Luke Ong, editor, Typed Lambda Calculi and Applications, volume 6690, pages 10–26. Springer Berlin Heidelberg, Berlin, Heidelberg, 2011. doi:10.1007/978-3-642-21691-6_5.
- [4] Thorsten Altenkirch. Extensional equality in intensional type theory. In Proceedings - Symposium on Logic in Computer Science, pages 412–420, February 1999. doi:10.1109/LICS.1999.782636.
- [5] Thorsten Altenkirch and Conor McBride. Towards Observational Type Theory, 2006.
- [6] Thorsten Altenkirch, Conor McBride, and Wouter Swierstra. Observational equality, now! In Proceedings of the 2007 Workshop on Programming Languages Meets Program Verification, pages 57–68, Freiburg Germany, October 2007. ACM. doi:10.1145/1292597.1292608.
- [7] Bob Atkey. Simplified observational type theory, 2017. URL: https://github.com/bobatkey/sott.
- [8] Henning Basold and Herman Geuvers. Type Theory based on Dependent Inductive and Coinductive Types. In Proceedings of the 31st Annual ACM/IEEE Symposium on Logic in Computer Science, pages 327–336, July 2016. doi:10.1145/2933575.2934514.
- [9] Rafael Bocquet. obstt, 2023. URL: https://gitlab.com/RafaelBocquet/obstt.
- [10] Thierry Coquand. An algorithm for testing conversion in type theory. Logical frameworks, 1:255–279, 1991.
- [11] Thierry Coquand and Christine Paulin. Inductively defined types. In G. Goos, J. Hartmanis, D. Barstow, W. Brauer, P. Brinch Hansen, D. Gries, D. Luckham, C. Moler, A. Pnueli, G. Seegmüller, J. Stoer, N. Wirth, Per Martin-Löf, and Grigori Mints, editors, COLOG-88, volume 417, pages 50–66. Springer Berlin Heidelberg, Berlin, Heidelberg, 1990. doi:10.1007/3-540-52335-9_47.
- [12] Marcelo Fiore. Semantic analysis of normalisation by evaluation for typed lambda calculus. Mathematical Structures in Computer Science, 32(8):1028–1065, September 2022. doi:10.1017/S0960129522000263.
- [13] Gaëtan Gilbert, Jesper Cockx, Matthieu Sozeau, and Nicolas Tabareau. Definitional proof-irrelevance without k. Proceedings of the ACM on Programming Languages, 3(POPL):1–28, January 2019. doi:10.1145/329031610.1145/3290316.
- [14] Jean-Yves Girard. Interprétation fonctionnelle et élimination des coupures de l’arithmétique d’ordre supérieur. PhD thesis, Université Paris VII, 1972.
- [15] Daniel Gratzer, Jonathan Sterling, and Lars Birkedal. Implementing a modal dependent type theory. Proc. ACM Program. Lang., 3(ICFP), July 2019. doi:10.1145/3341711.
- [16] Robert Harper. Boolean Blindness, 2011. URL: https://existentialtype.wordpress.com/2011/03/15/boolean-blindness/.
- [17] Martin Hofmann. Extensional Concepts in Intensional Type Theory. PhD thesis, University of Edinburgh, 1995. URL: https://www.lfcs.inf.ed.ac.uk/reports/95/ECS-LFCS-95-327/.
- [18] András Kovács. Elaboration with first-class implicit function types. Proceedings of the ACM on Programming Languages, 4(ICFP):1–29, August 2020. doi:10.1145/3408983.
- [19] András Kovács. Elaboration-zoo, May 2023. URL: https://github.com/AndrasKovacs/elaboration-zoo.
- [20] András Kovács. Efficient evaluation with controlled definition unfolding. In 3rd Workshop on the Implementation of Type Systems, 2025.
- [21] Per Martin-Löf. Intuitionistic type theory. In Studies in Proof Theory, 1984.
- [22] Conor McBride. Dependently typed functional programs and their proofs. PhD thesis, University of Edinburgh, 1999.
- [23] Nax Paul Mendler. Inductive types and type constraints in the second-order lambda calculus. Annals of Pure and Applied Logic, 51(1-2):159–172, March 1991. doi:10.1016/0168-0072(91)90069-X.
- [24] Ulf Norell. Towards a practical programming language based on dependent type theory. PhD thesis, Department of Computer Science and Engineering, Chalmers University of Technology, September 2007.
- [25] Erik Palmgren. On universes in type theory, pages 191––204. Oxford University Press, 1998. doi:10.1093/oso/9780198501275.003.0012.
- [26] Loïc Pujet. Computing with Extensionality Principles in Dependent Type Theory. PhD thesis, Nantes Université, December 2022.
- [27] Loïc Pujet and Nicolas Tabareau. Observational equality: Now for good. Proceedings of the ACM on Programming Languages, 6(POPL):1–27, January 2022. doi:10.1145/3498693.
- [28] Loïc Pujet and Nicolas Tabareau. Impredicative observational equality. Proc. ACM Program. Lang., 7(POPL), January 2023. doi:10.1145/3571739.
- [29] Loïc Pujet and Nicolas Tabareau. Observational equality meets cic. In Stephanie Weirich, editor, Programming Languages and Systems, pages 275–301. Springer Nature Switzerland, 2024. doi:10.1007/978-3-031-57262-3_12.
- [30] Matthew Sirman. A normalisation by evaluation implementation of a type theory with observational equality. Bachelor’s thesis, University of Cambridge, 2023.
- [31] Matthew Sirman. observational-type-theory, May 2023. URL: https://github.com/matthew-sirman/observational-type-theory.
- [32] The mathlib Community. The lean mathematical library. In Proceedings of the 9th ACM SIGPLAN International Conference on Certified Programs and Proofs, CPP 2020, pages 367–381, New York, NY, USA, 2020. Association for Computing Machinery. doi:10.1145/3372885.3373824.
