• Aucun résultat trouvé

Explicit Effect Subtyping

N/A
N/A
Protected

Academic year: 2022

Partager "Explicit Effect Subtyping"

Copied!
38
0
0

Texte intégral

(1)

Amr Hany Saleh1, Georgios Karachalias1, Matija Pretnar2, and Tom Schrijvers1

1 KU Leuven, Department of Computer Science, Belgium,

2 University of Ljubljana, Faculty of Mathematics and Physics, Slovenia

Abstract. As popularity of algebraic effects and handlers increases, so does a demand for their efficient execution. Eff, an ML-like language with native support for handlers, has a subtyping-based effect system on which an effect- aware optimizing compiler could be built. Unfortunately, in our experience, implementing optimizations for Eff is overly error-prone because its core language is implicitly-typed, making code transformations very fragile.

To remedy this, we present an explicitly-typed polymorphic core calculus for algebraic effect handlers with a subtyping-based type-and-effect system. It reifies appeals to subtyping in explicit casts with coercions that witness the subtyping proof, quickly exposing typing bugs in program transformations.

Our typing-directed elaboration comes with a constraint-based inference al- gorithm that turns an implicitly-typed Eff-like language into our calculus.

Moreover, all coercions and effect information can be erased in a straight- forward way, demonstrating that coercions have no computational content.

1 Introduction

Algebraic effect handlers [17, 18] are quickly maturing from a theoretical model to a practical language feature for user-defined computational effects. Yet, in practice they still incur a significant performance overhead compared to native effects.

Our earlier efforts [22] to narrow this gap with an optimising compiler from Eff [2]

to OCaml showed promising results, in some cases reaching even the performance of hand-tuned code, but were very fragile and have been postponed until a more robust solution is found. We believe the main reason behind this fragility is the complexity of subtyping in combination with the implicit typing of Eff’s core language, further aggravated by the “garbage collection” of subtyping constraints (see Section 7).3

For efficient compilation, one must avoid the poisoning problem [26], where unification forces a pure computation to take the less precise impure type of the context (e.g. a pure and an impure branch of a conditional both receive the same impure type). Since this rules out existing (and likely simpler) effect systems for handlers based on row-polymorphism [12, 8, 14], we propose a polymorphic explicitly- typed calculus based on subtyping. More specifically, our contributions are as follows:

– First, in Section 3 we presentImpEff, a polymorphic implicitly-typed calculus for algebraic effects and handlers with a subtyping-based type-and-effect system.

3For other issues stemming from the same combination see issues #11 and #16 at https://github.com/matijapretnar/eff/issues/.

(2)

ImpEffis essentially a (desugared) source language as it appears in the compiler frontend of a language like Eff.

– Next, Section 4 presents ExEff, the core calculus, which combines explicit System F-style polymorphism with explicit coercions for subtyping in the style of Breazu-Tannen et al. [3]. This calculus comes with a type-and-effect system, a small-step operational semantics and a proof of type-safety.

– Section 5 specifies the typing-directed elaboration of ImpEffintoExEffand presents a type inference algorithm for ImpEff that produces the elaborated ExEffterm as a by-product. It also establishes that the elaboration preserves typing, and that the algorithm is sound with respect to the specification and yields principal types.

– Finally, Section 6 definesSkelEff, which is a variant of ExEffwithout effect information or coercions.SkelEffis also representative of Multicore Ocaml’s support for algebraic effects and handlers [6], which is a possible compilation target of Eff. By showing that the erasure fromExEfftoSkelEffpreserves semantics, we establish thatExEff’s coercions are computationally irrelevant and that, despite the existence of multiple proofs for the same subtyping, there is no coherence problem. To enable erasure,ExEffannotates its types with(type) skeletons, which capture the erased counterpart and are, to our knowledge, a novel contribution.

– Our paper comes with two software artefacts: an ongoing implementation4of a compiler from Eff to OCaml withExEffat its core, and an Abella mechanisa- tion5of Theorems 1, 2, 6, and 7. Remaining theorems all concern the inference algorithm, and their proofs closely follow [20].

2 Overview

This section presents an informal overview of the ExEff calculus, and the main issues with elaborating to and erasing from it.

2.1 Algebraic Effect Handlers

The main premise of algebraic effects is that impure behaviour arises from a set of operations such asGetandSetfor mutable store, ReadandPrintfor interactive input and output, or Raise for exceptions [17]. This allows generalizing exception handlers to other effects, to express backtracking, co-operative multithreading and other examples in a natural way [18, 2].

Assume operationsTick :Unit→UnitandTock:Unit →Unit that take a unit value as a parameter and yield a unit value as a result. Unlike special built-in operations, these operations have no intrinsic effectful behaviour, though we can give one through handlers. For example, the handler{Tickx k7→(Print“tick”;kunit), Tockx k7→Print“tock”}replaces all calls ofTickby printing out “tick” and sim- ilarly forTock. But there is one significant difference between the two cases. Unlike

4https://github.com/matijapretnar/eff/tree/explicit-effect-subtyping

5https://github.com/matijapretnar/proofs/tree/master/explicit-effect-subtyping

(3)

exceptions, which always abort the evaluation, operations have a continuation wait- ing for their result. It is this continuation that the handler captures in the variablek and potentially uses in the handling clause. In the clause forTick, the continuation is resumed by passing it the expected unit value, whereas in the clause forTock, the operation is discarded. Thus, if we handle a computation emitting the two opera- tions, it will print out “tick” until a first “tock” is printed, after which the evaluation stops.

2.2 Elaborating Subtyping

Consider the computation do x ← Tick unit;f x and assume that f has the function typeUnit→Unit!{Tock}, taking unit values to unit values and perhaps calling Tock operations in the process. The whole computation then has the type Unit !{Tick,Tock}as it returns the unit value and may callTick andTock.

The above typing implicitly appeals to subtyping in several places. For instance, Tick unit has type Unit ! {Tick} and f x type Unit ! {Tock}. Yet, because they are sequenced with do, the type system expects they have the same set of effects. The discrepancies are implicitly reconciled by the subtyping which admits both{Tick}6{Tick,Tock}and{Tock}6{Tick,Tock}.

We elaborate theImpEffterm into the explicitly-typed core language ExEff to make those appeals to subtyping explicit by means of casts with coercions:

dox←((Tick unit)Bγ1); (f x)Bγ2

A coercion γ is a witness for a subtyping A ! ∆ 6 A0 ! ∆0 and can be used to cast a term c of type A ! ∆ to a term c B γ of type A0 ! ∆0. In the above term, γ1 and γ2 respectively witness Unit ! {Tick} 6 Unit ! {Tick,Tock} and Unit !{Tock}6Unit!{Tick,Tock}.

2.3 Polymorphic Subtyping for Types and Effects

The above basic example only features monomorphic types and effects. Yet, our calculus also supports polymorphism, which makes it considerably more expressive.

For instance the type off inletf = (fung7→gunit)in. . . is generalised to:

∀α, α0.∀δ, δ0.α6α0 ⇒δ6δ0⇒(Unit→α!δ)→α00

This polymorphic type scheme follows the qualified types convention [9] where the type(Unit→α!δ)→α00 is subjected to several qualifiers, in this caseα6α0 andδ6δ0. The universal quantifiers on the outside bind the type variablesαand α0, and the effect set variablesδ andδ0.

The elaboration off intoExEffintroduces explicit binders for both the quan- tifiers and the qualifiers, as well as the explicit casts where subtyping is used.

Λα.Λα.Λδ.Λδ0 .Λ(ω0 :α6α0).Λ(ω0:δ6δ0).fun(g:Unit→α!δ)7→(gunit)B(ω!ω0)

(4)

Here the binders for qualifiers introduce coercion variablesωbetween pure types and ω0 between operation sets, which are then combined into a computation coercion ω !ω0 and used for casting the function applicationgunit to the expected type.

Suppose thathhas typeUnit→Unit!{Tick}andf htypeUnit!{Tick,Tock}.

In theExEffcalculus the corresponding instantiation off is made explicit through type and coercion applications

fUnit Unit{Tick} {Tick,Tock}γ1γ2h

whereγ1needs to be a witness forUnit6Unitandγ2for{Tick}6{Tick,Tock}.

2.4 Guaranteed Erasure with Skeletons

One of our main requirements forExEffis that its effect information and subtyping can be easily erased. The reason is twofold. Firstly, we want to show that neither plays a role in the runtime behaviour ofExEffprograms. Secondly and more importantly, we want to use a conventionally typed (System F-like) functional language as a backend for the Eff compiler.

At first, erasure of both effect information and subtyping seems easy: simply drop that information from types and terms. But by dropping the effect variables and subtyping constraints from the type of f, we get ∀α, α0.(Unit → α) → α0 instead of the expected type ∀α.(Unit → α) → α. In our naive erasure attempt we have carelessly discarded the connection betweenαandα0. A more appropriate approach to erasure would be to unify the types in dropped subtyping constraints.

However, unifying types may reduce the number of type variables when they become instantiated, so corresponding binders need to be dropped, greatly complicating the erasure procedure and its meta-theory.

Fortunately, there is an easier way by tagging all bound type variables with skeletons, which are barebone types without effect information. For example, the skeleton of a function typeA→B !∆isτ1→τ2, whereτ1is the skeleton ofAand τ2the skeleton ofB. InExEffevery well-formed type has an associated skeleton, and any two typesA16A2 share the same skeleton. In particular, binders for type variables are explicitly annotated with skeleton variablesς. For instance, the actual type off is:

∀ς.∀(α:ς),(α0 :ς).∀δ, δ0.α6α0⇒δ6δ0 ⇒(Unit→α!δ)→α00

The skeleton quantifications and annotations also appear at the term-level:

Λς.Λ(α:ς).Λ(α0:ς).Λδ.Λδ0.Λ(ω:α6α0).Λ(ω0:δ6δ0). . . .

Now erasure is really easy: we drop not only effect and subtyping-related term for- mers, but also type binders and application. We do retain skeleton binders and applications, which take over the role of (plain) types in the backend language. In terms, we replace types by their skeletons. For instance, forf we get:

Λς.fun(g:Unit→ς)7→gunit : ∀ς.(Unit→ς)→ς

(5)

Terms

valuev::=x|unit|funx7→c|h

handlerh::={returnx7→cr,Op1x k7→cOp1, . . . ,Opnx k7→cOpn} computationc::=returnv|Opv(y.c)|dox←c1;c2

| handlecwithv|v1 v2|letx=vinc Types & Constraints

skeletonτ ::=ς|Unit|τ1→τ212

value typeA,B ::=α|Unit|A→C|C VD qualified typeK ::=A|π⇒K

polytypeS ::=K| ∀ς.S| ∀α:τ.S| ∀δ.S computation typeC,D ::=A!∆

dirt∆::=δ| ∅ | {Op} ∪∆ simple constraintπ::=A16A2|∆16∆2

constraintρ::=π|C6D Fig. 1:ImpEffSyntax

3 The ImpEff Language

This section presentsImpEff, a basic functional calculus with support for algebraic effect handlers, which forms the core language of our optimising compiler. We de- scribe the relevant concepts, but refer the reader to Pretnar’s tutorial [21], which explains essentially the same calculus in more detail.

3.1 Syntax

Figure 1 presents the syntax of the source language. There are two main kinds of terms: (pure) valuesv and (dirty) computationsc, which may call effectful opera- tions. Handlers hare a subsidiary sort of values. We assume a given set ofopera- tions Op, such as GetandPut. We abbreviateOp1x k7→cOp1, . . . ,Opnx k7→cOpn as[Opx k7→cOp]Op∈O, and writeOto denote the set{Op1, . . . ,Opn}.

Similarly, we distinguish between two basic sorts of types: the value typesA, B and the computation typesC, D. There are four forms of value types: type variables α, function typesA →C, handler types C VD and the Unit type. Skeletons τ capture the shape of types, so, by design, their forms are identical. The computation typeA!∆ is assigned to a computation returning values of typeAand potentially calling operations from thedirtset∆. A dirt set contains zero or more operationsOp and is terminated either by an empty set or a dirt variableδ. Though we usecons-list syntax, the intended semantics of dirt sets ∆ is that the order of operationsOp is irrelevant. Similarly to all HM-based systems, we discriminate between value types (or monotypes) A, qualified types K and polytypes (or type schemes)S. (Simple) subtyping constraints πdenote inequalities between either value types or dirts. We

(6)

also present the more general form of constraintsρthat includes inequalities between computation types (as we illustrate in Section 3.2 below, this allows for a single, uniform constraint entailment relation). Finally, polytypes consist of zero or more skeleton, type or dirt abstractions followed by a qualified type.

3.2 Typing

Figure 2 presents the typing rules for values and computations, along with a typing- directed elaboration into our target languageExEff. In order to simplify the pre- sentation, in this section we focus exclusively on typing. The parts of the rules that concern elaboration are highlighted in gray and are discussed in Section 5.

Values Typing for values takes the form Γ `v v : A v0, and, given a typing environmentΓ, checks a valuev against a value typeA.

RuleTmVarhandles term variables. Given thatxhas type(∀ς.α:τ .∀δ.π⇒A), we appropriately instantiate the skeleton (ς), type (α), and dirt (δ) variables, and ensure that the instantiated wanted constraintsσ(π)are satisfied, via side condition Γ `co γ:σ(π). RuleTmCastVallows casting the type of a valuevfromAtoB, ifA is a subtype ofB (upcasting). As illustrated by RuleTmTmAbs, we omit freshness conditions by adopting the Barendregt convention [1]. Finally, RuleTmHandgives typing for handlers. It requires that the right-hand sides of the return clause and all operation clauses have the same computation type (B!∆), and that all operations mentioned are part of the top-level signature Σ.6 The result type takes the form A!∆∪ OVB!∆, capturing the intended handler semantics: given a computation of typeA!∆∪O, the handler (a) produces a result of typeB, (b) handles operations O, and (c) propagates unhandled operations ∆to the output.

Computations Typing for computations takes the form Γ `c c : C c0, and, given a typing environmentΓ, checks a computationcagainst a type C.

Rule TmCastC behaves like Rule TmCastV, but for computation types.

Rule TmLet handles polymorphic, non-recursive let-bindings. Rule TmReturn handlesreturnvcomputations. Keywordreturn effectively lifts a valuev of type A into a computation of typeA !∅. Rule TmOpchecks operation calls. First, we ensure that v has the appropriate type, as specified by the signature of Op. Then, the continuation(y.c)is checked. The side conditionOp∈∆ensures that the called operationOpis captured in the result type. RuleTmDohandles sequencing. Given thatc1has typeA!∆, the pure part of the result of typeAis bound to term variable x, which is brought in scope for checkingc2. As we mentioned in Section 2, all com- putations in a do-construct should have the same effect set,∆. RuleTmHandle eliminates handler types, just as RuleTmTmAppeliminates arrow types.

Constraint Entailment The specification of constraint entailment takes the form Γ `co γ:ρ and is presented in Figure 3. Notice that we useρ instead ofπ, which

6We capture all defined operations along with their types in a global signatureΣ.

(7)

typing environmentΓ ::=|Γ, ς|Γ, α:τ |Γ, δ|Γ, x:S|Γ, ω:π Γ `vv:A v0 Values

(x:∀¯ς.∀α:τ .∀δ.¯¯π⇒A)∈Γ σ= [τ0/ς,B/α, ∆/δ] Γ `co γ:σ(π)

Γ `vx:σ(A) x ¯τ0 B¯ ∆¯¯γ TmVar Γ `vv:A v0

Γ `co γ:A6B

Γ `vv:B v0Bγ TmCastV

Γ `vunit:Unit unit TmUnit Γ, x:A`cc:C c0 Γ `vtyA:τ T

Γ `v(funx7→c) :A→C fun(x:T)7→c0 TmTmAbs Γ, x:A`ccr:B !∆ c0r Γ `vtyA:τ T

h

(Op:AOp→BOp)∈Σ Γ, x:AOp, k:BOp→B!∆`ccOp:B !∆ c0Op

i

Op∈O

cres ={return(x:T)7→c0r,[Opx k7→c0Op]Op∈O}

Γ `v{returnx7→cr,[Opx k7→cOp]Op∈O}:A!∆∪ OVB!∆ cres TmHand Γ `cc:C c0 Computations

Γ `cc:C1 c0 Γ `co γ:C16C2

Γ `cc:C2 c0Bγ TmCastC

Γ `vv1:A→C v10 Γ `vv2:A v02

Γ `cv1 v2 :C v01 v02

TmTmApp

S=∀¯ς.α:τ .∀δ.¯¯π⇒A

Γ,ς, α¯ :τ ,¯δ, ω:π`vv:A v0 Γ, x:S`cc:C c0

Γ `cletx=vinc:C letx=Λ¯ς.Λα:τ .Λδ.Λ(ω¯ :π).v0inc0 TmLet Γ `vv:A v0

Γ `creturnv:A!∅ returnv0 TmReturn (Op:AOp→BOp)∈Σ Γ `vv:AOp v0

Γ, y:BOp`cc:A!∆ c0 Γ `vtyBOp:τ TOp Op∈∆ Γ `cOpv(y.c) :A!∆ Opv0 (y:TOp.c0) TmOp Γ `cc1:A!∆ c01 Γ, x:A`cc2:B !∆ c02

Γ `cdox←c1;c2:B !∆ dox←c01;c02

TmDo

Γ `vv:C VD v0 Γ `cc:C c0

Γ `chandlecwithv:D handlec0withv0 TmHandle

Fig. 2:ImpEffTyping & Elaboration

(8)

Γ `co γ:ρ Constraint Entailment (ω:π)∈Γ

Γ `co ω:π CoVar

Γ `vtyA:τ T

Γ `co hTi:A6A VCoRefl

Γ `

Γ `co h∆i:∆6∆DCoRefl

Γ `co γ1 :A16A2

Γ `co γ2 :A26A3

Γ `co γ1γ2:A16A3

VCoTrans

Γ `co γ1:C16C2 Γ `co γ2:C26C3

Γ `co γ1γ2:C16C3 CCoTrans

Γ `co γ1:∆16∆2

Γ `co γ2:∆26∆3

Γ `co γ1γ2:∆16∆3 DCoTrans Γ `co γ1:B6A Γ `co γ2:C 6D

Γ `co γ1→γ2:A→C 6B→D VCoArr Γ `co γ:A→C6B→D

Γ `co left(γ) :B6A VCoArrL

Γ `co γ:A→C 6B→D

Γ `co right(γ) :C 6D CCoArrR Γ `co γ1:C26C1 Γ `co γ2:D16D2

Γ `co γ12:C1VD16C2VD2 VCoHand Γ `co γ:C1VD16C2VD2

Γ `co left(γ) :C26C1 CCoHL

Γ `co γ:C1VD16C2VD2

Γ `co right(γ) :D16D2 CCoHR Γ `co γ1:A1 6A2 Γ `co γ2:∆1 6∆2

Γ `co γ12:A1!∆16A2 !∆2

CCoComp

Γ `co γ:A1 !∆16A2 !∆2

Γ `co pure(γ) :A16A2

VCoPure

Γ `co γ:A1 !∆16A2 !∆2

Γ `co impure(γ) :∆16∆2

DCoImpure

Γ `co:∅6∆DCoNil

Γ `co γ:∆16∆2 (Op:AOp→BOp)∈Σ Γ `co {Op} ∪γ:{Op} ∪∆16{Op} ∪∆2

DCoOp

Fig. 3:ImpEffConstraint Entailment

allows us to capture subtyping between two value types, computation types or dirts, within the same relation. Subtyping can be established in several ways:

RuleCoVarhandles given assumptions. RulesVCoRefl andDCoReflex- press that subtyping is reflexive, for both value types and dirts. Notice that we do not have a rule for the reflexivity of computation types since, as we illustrate below, it can be established using the reflexivity of their subparts. Rules VCo-

(9)

Trans, CCoTrans and DCoTrans express the transitivity of subtyping for value types, computation types and dirts, respectively. Rule VCoArr establishes inequality of arrow types. As usual, the arrow type constructor is contravariant in the argument type. Rules VCoArrL and CCoArrR are the inversions of Rule VCoArr, allowing us to establish the relation between the subparts of the arrow types. RulesVCoHand,CCoHL, andCCoHR work similarly, for handler types. Rule CCoCompcaptures the covariance of type constructor (!), establish- ing subtyping between two computation types if subtyping is established for their respective subparts. Rules VCoPureandDCoImpureare its inversions. Finally, RulesDCoNilandDCoOpestablish subtyping between dirts. RuleDCoNilcap- tures that the empty dirty set∅is a subdirt of any dirt∆and RuleDCoOpexpresses that dirt subtyping preserved under extension with the same operationOp.

Well-formedness of Types, Constraints, Dirts, and Skeletons The relations Γ `vtyA:τ T and Γ `cty C : τ C check the well-formedness of value and computation types respectively. Similarly, relations Γ `ct ρ ρ and Γ ` ∆ check the well-formedness of constraints and dirts, respectively. They are all defined in Appendix A.

4 The ExEff Language

4.1 Syntax

Figure 4 presents ExEff’s syntax. ExEff is an intensional type theory akin to System F [7], where every term encodes its own typing derivation. In essence, all ab- stractions and applications that are implicit inImpEff, are made explicit inExEff via new syntactic forms. Additionally,ExEffis impredicative, which is reflected in the lack of discrimination between value types, qualified types and type schemes; all non-computation types are denoted by T. While the impredicativity is not strictly required for the purpose at hand, it makes for a cleaner system.

Coercions Of particular interest is the use of explicitsubtyping coercions, denoted byγ.ExEffuses these to replace the implicit casts ofImpEff(RulesTmCastV andTmCastCin Figure 2) with explicit casts(vBγ)and(cBγ).

Essentially, coercionsγ are explicit witnesses of subtyping derivations: each co- ercion form corresponds to a subtyping rule. Subtyping forms a partial order, which is reflected in coercion formsγ1γ2,hTi, andh∆i. Coercion formγ1 γ2cap- tures transitivity, while forms hTi and h∆i capture reflexivity for value types and dirts (reflexivity for computation types can be derived from these).

Subtyping for skeleton abstraction, type abstraction, dirt abstraction, and qual- ification is witnessed by forms∀ς.γ,∀α.γ, ∀δ.γ, andπ⇒γ, respectively. Similarly, formsγ[τ],γ[T],γ[∆], andγ12witness subtyping of skeleton instantiation, type instantiation, dirt instantiation, and coercion application, respectively.

Syntactic formsγ1→γ2 and γ12 capture injection for the arrow and the handler type constructor, respectively. Similarly, inversion formsleft(γ)andright(γ) capture projection, following from the injectivity of both type constructors.

(10)

Terms

valuev::=x|unit|fun(x:T)7→c|h

| Λς.v|v τ|Λα:τ.v|vT|Λδ.v|v ∆|Λ(ω:π).v|v γ|vBγ handlerh::={return(x:T)7→cr,Op1x k7→cOp1, . . . ,Opnx k7→cOpn} computationc::=returnv|Opv(y:T.c)|dox←c1;c2

| handlecwithv|v1 v2 |letx=vinc|cBγ Types

skeletonτ ::=ς|Unit|τ1→τ212| ∀ς.τ

value typeT ::=α|Unit|T→C |C1VC2| ∀ς.T| ∀α:τ.T | ∀δ.T|π⇒T simple coercion typeπ::=T16T2|∆16∆2

coercion typeρ::=π|C1 6C2 computation typeC ::=T !∆

dirt∆::=δ| ∅ | {Op} ∪∆ Coercions

γ ::=ω|γ1γ2| hTi |γ1→γ212 |left(γ)|right(γ)| h∆i | ∅| {Op} ∪γ

| ∀ς.γ|γ[τ]| ∀α.γ|γ[T]| ∀δ.γ|γ[∆]|π⇒γ|γ1212 |pure(γ)|impure(γ) Fig. 4:ExEff Syntax

Coercion formγ1 ! γ2 witnesses subtyping for computation types, using proofs for their components. Inversely, syntactic formspure(γ)andimpure(γ)witness sub- typing between the value- and dirt-components of a computation coercion.

Finally, coercion forms∅and{Op} ∪γare concerned with dirt subtyping. Form

witnesses that the empty dirt∅ is a subdirt of any dirt∆. Lastly, coercion form {Op} ∪γ witnesses that subtyping between dirts is preserved under extension with a new operation. Note that we do not have an inversion form to extract a witness for∆16∆2 from a coercion for {Op} ∪∆16{Op} ∪∆2. The reason is that dirt sets are sets and not inductive structures. For instance, for∆1={Op}and∆2=∅ the latter subtyping holds, but the former does not.

4.2 Typing

Value & Computation Typing Typing for ExEff values and computations is presented in Figures 5 and 6 and is given by two mutually recursive relations of the formΓ `vv:T(values) andΓ `cc:C(computations).ExEfftyping environments Γ contain bindings for variables of all sorts:

Γ ::=|Γ, ς|Γ, α:τ|Γ, δ|Γ, x:T |Γ, ω:π

Typing is entirely syntax-directed. Apart from the typing rules for skeleton, type, dirt, and coercion abstraction (and, subsequently, skeleton, type, dirt, and coercion

(11)

(x:T)∈Γ

Γ `vx:T Γ `vunit:Unit

Γ, x:T `cc:C Γ `T T:τ Γ `v(funx:T 7→c) :T→C Γ `vv:T1 Γ `coγ:T16T2

Γ `vvBγ:T2

Γ, ς`vv:T Γ `vΛς.v:∀ς.T

Γ, α:τ `vv:T Γ `vΛα:τ.v:∀α:τ.T Γ, δ`vv:T

Γ `vΛδ.v:∀δ.T

Γ, ω:π`vv:T Γ `ρπ Γ `vΛ(ω:π).v:π⇒T

Γ `vv:π⇒T Γ `coγ:π Γ `vv γ:T

Γ, x:Tx`ccr:T!∆

[(Op:T1→T2)∈Σ Γ, x:T1, k:T2→T!∆`ccOp:T!∆]Op∈O Γ `v{return(x:Tx)7→cr,[Opx k7→cOp]Op∈O}:Tx !∆∪ OVT !∆ Γ `vv:∀ς.T

Γ `ττ Γ `vv τ:T[τ /ς]

Γ `vv:∀α:τ.T1

Γ `T T2:τ Γ `vvT2:T1[T2/α]

Γ `vv:∀δ.T Γ `∆ Γ `vv ∆:T[∆/δ]

Fig. 5:ExEffValue Typing

application), the main difference between typing forImpEffandExEfflies in the explicit cast forms, (v B γ) and (c B γ). Given that a value v has type T1 and thatγ is a proof thatT1 is a subtype ofT2, we can upcast v with an explicit cast operation(vBγ). Upcasting for computations works analogously.

Well-formedness of Types, Constraints, Dirts & Skeletons The definitions of the judgements that check the well-formedness ofExEffvalue types (Γ `T T:τ), computation types (Γ `C C :τ), dirts (Γ `∆), and skeletons (Γ `τ τ) are equally straightforward as those for ImpEffand can be found in Appendix B.

Coercion Typing Coercion typing formalizes the intuitive interpretation of coercions we gave in Section 4.1 and takes the form Γ `co γ:ρ, defined in Appendix B. It is essentially an extension of the constraint entailment relation of Figure 3.

4.3 Operational Semantics

Figure 7 presents selected rules of ExEff’s small-step, call-by-value operational semantics. For lack of space, we omitβ-rules and other common rules and focus only on cases of interest. The complete operational semantics can be found in Appendix B.

Firstly, one of the non-conventional features of our system lies in the stratification of results in plain results and cast results:

(12)

Γ `vv1:T →C Γ `vv2:T Γ `cv1 v2:C

Γ `vv:T Γ, x:T`cc:C Γ `cletx=vinc:C Γ `cv:T

Γ `creturnv:T !∅

Γ `cc1:T1!∆ Γ, x:T1`cc2:T2 !∆ Γ `cdox←c1;c2:T2 !∆ (Op:T1→T2)∈Σ Γ `vv:T1 Γ, y:T2`cc:T !∆ Op∈∆

Γ `cOpv(y:T2.c) :T !∆ Γ `vv:C1VC2 Γ `cc:C1

Γ `chandlecwithv:C2

Γ `cc:C1 Γ `coγ:C16C2 Γ `ccBγ:C2

Fig. 6:ExEff Computation Typing

terminal value vT ::=unit|h|funx:T7→c|Λα:τ.v|Λδ.v|λω:π.v value resultvR ::=vT |vT

computation resultcR ::=returnvT |(returnvT)Bγ|OpvR(y:T.c)

Terminal valuesvT represent conventional values, and value resultsvRcan either be plain terminal values vT or terminal values with a cast: vT Bγ. The same applies to computation resultscR.7

Although unusual, this stratification can also be found in Crary’s coercion cal- culus for inclusive subtyping [4], and, more recently, in System FC [25]. Stratifica- tion is crucial for ensuring type preservation. Consider for example the expression (return5 Bhinti!∅{Op}), of type int!{Op}. We can not reduce the expression further without losing effect information; removing the cast would result in compu- tation(return5), of typeint!∅. Even if we consider type preservation only up to subtyping, the redex may still occur as a subterm in a context that expects solely the larger type.

Secondly, we need to make sure that casts do not stand in the way of evaluation.

This is captured in the so-called “push” rules, all of which appear in Figure 7.

In relationv vv0, the first rule groups nested casts into a single cast, by means of transitivity. The next three rules capture the essence of push rules: whenever a redex is “blocked” due to a cast, we take the coercion apart and redistribute it (in a type-preserving manner) over the subterms, so that evaluation can progress.

The situation in relationc cc0is quite similar. The first rule uses transitivity to group nested casts into a single cast. The second rule is a push rule forβ-reduction.

The third rule pushes a cast out of areturn-computation. The fourth rule pushes a coercion inside an operation-computation, illustrating why the syntax forcRdoes not require casts on operation-computations. The fifth rule is a push rule for sequencing

7Observe that operation values do not feature an outermost cast operation, as the coercion can always be pushed into its continuation.

(13)

v vv0 Values

(vT1)Bγ2 vvT B(γ1 γ2) (vT Bγ)T v(vT T)Bγ[T] (vTBγ)∆ v(vT ∆)Bγ[∆] (vT12 v(vT γ2)Bγ12

c cc0 Computations

(cR1)Bγ2 ccRB(γ1γ2) (vT1 Bγ)v2 c(vT1 (v2Bleft(γ)))Bright(γ) return(vT Bγ) c(returnvT)B(γ!∅)

(OpvR (y:T.c))Bγ cOpvR (y:T.(cBγ)) dox←((returnvT)Bγ);c2 cc2[(vT Bpure(γ))/x]

dox←OpvR (y:T.c1);c2 cOpvR (y:T.dox←c1;c2) handlecwith(vT Bγ) c(handle(cBleft(γ))withvT)Bright(γ)

handle((returnvT)Bγ)withh ccr[vT Bpure(γ)/x]

handle(OpvR(y:T.c))withh ccOp[vR/x,(fun(y:T)7→handlecwithh)/k]

handle(OpvR(y:T.c))withh cOpvR (y:T.handlecwithh) Fig. 7:ExEffOperational Semantics (Selected Rules)

computations and performs two tasks at once. Since we know that the computation bound to x calls no operations, we (a) safely “drop” the impure part of γ, and (b) substitutexwithvT, cast with the pure part ofγ(so that types are preserved).

The sixth rule handles operation calls in sequencing computations. If an operation is called in a sequencing computation, evaluation is suspended and the rest of the computation is captured in the continuation.

The last four rules are concerned with effect handling. The first of them pushes a coercion on the handler “outwards”, such that the handler can be exposed and evaluation is not stuck (similarly to the push rule for term application). The second rule behaves similarly to the push/beta rule for sequencing computations. Finally, the last two rules are concerned with handling of operations. The first of the two captures cases where the called operation is handled by the handler, in which case the respective clause of the handler is called. As illustrated by the rule, like Pretnar [20],ExEfffeaturesdeep handlers: the continuation is also wrapped within awith- handle construct. The last rule captures cases where the operation is not covered by the handler and thus remains unhandled.

We have shown thatExEff is type safe:

(14)

Theorem 1 (Type Safety).

– IfΓ `vv:T then eitherv is a result value orv v v0 andΓ `vv0:T.

– IfΓ `cc:C then eithercis a result computation orc cc0 andΓ `cc0:C.

5 Type Inference & Elaboration

This section presents the typing-directed elaboration of ImpEffintoExEff. This elaboration makes all the implicit type and effect information explicit, and introduces explicit term-level coercions to witness the use of subtyping.

After covering the declarative specification of this elaboration, we present a constraint-based algorithm to infer ImpEfftypes and at the same time elaborate intoExEff. This algorithm alternates between two phases: 1) the syntax-directed generation of constraints from theImpEffterm, and 2) solving these constraints.

5.1 Elaboration of ImpEff into ExEff

The grayed parts of Figure 2 augment the typing rules forImpEffvalue and compu- tation terms with typing-directed elaboration to correspondingExEff terms. The elaboration is mostly straightforward, mapping every ImpEff construct onto its corresponding ExEff construct while adding explicit type annotations to binders in Rules TmTmAbs, TmHandlerandTmOp. Implicit appeals to subtyping are turned into explicit casts with coercions in RulesTmCastVandTmCastC. Rule TmLet introduces explicit binders for skeleton, type, and dirt variables, as well as for constraints. These last also introduce coercion variables ω that can be used in casts. The binders are eliminated in rule TmVar by means of explicit application with skeletons, types, dirts and coercions. The coercions are produced by the aux- iliary judgementΓ `co γ:π, defined in Figure 3, which provides a coercion witness for every subtyping proof.

As a sanity check, we have shown that elaboration preserves types.

Theorem 2 (Type Preservation).

– IfΓ `vv:A v0 then elabΓ(Γ)`vv0:elabS(A).

– IfΓ `cc:C c0 thenelabΓ(Γ)`cc0:elabC(C).

Here elabΓ(Γ), elabS(A) and elabC(C) convert ImpEff environments and types intoExEff environments and types; they are defined in Appendix C.

5.2 Constraint Generation & Elaboration

Constraint generation with elaboration intoExEffis presented in Figures 8 (values) and 9 (computations). Before going into the details of each, we first introduce the three auxiliary constructs they use.

(15)

Q;Γ `vv:A| Q0;σ v0 Values

(x:∀¯ς.α:τ .∀¯δ.¯π⇒A)∈Γ σ= [ς0/ς, α0/α, δ0/δ]

Q;Γ `vx:σ(A)| ω:σ(π), α0:σ(τ),Q;• xς¯0α¯0 δ¯0 ω¯ Q;Γ `vunit:Unit| Q;• unit

α:ς,Q;Γ, x:α`cc:C | Q0;σ c0

Q;Γ `v(funx7→c) :σ(α)→C| Q0;σ funx:σ(α)7→c0

αrr,Q;Γ, x:αr`ccr:Br !∆r| Q0r c0r σii·σi−1·. . .·σ1

Opi∈ O:

(Opi:Ai→Bi)∈Σ

αii,Qi−1i−1r(Γ)), x:Ai, k:Bi→αii`ccOpi:BOpi!∆Opi | Qii c0Opi

Q0inin, αoutout, ω1n(Br)6αout, ω2n(∆r)6δout, ω3in(BOpi)6αout n, ω4in(∆Opi)6δout

n, ω5i:Bi→αoutout6Bi→σnii)n, ω6innrr)), ω7inout∪ O,Qn

cres={returny:σnrr))7→σn(c0r)[yBω6/x]Bω12

,

Opix l7→σn(c0Op

i)[lBω5i/k]Bω3i4i

Opi∈O}B(hαini!ω7Vhαouti!hδouti) Q;Γ `v{returnx7→cr,[Opx k7→cOp]Op∈O}:αininoutout| Q0; (σn·σr) cres

Fig. 8:Constraint Generation with Elaboration (Values)

constraint setP,Q::=• |τ12,P |α:τ,P | ω:π,P typing environmentΓ ::=|Γ, x:S

substitutionσ::=• |σ·[τ /ς]|σ·[A/α]|σ·[∆/δ]|σ· [γ/ω]

At the heart of our algorithm are sets P, containing three different kinds of con- straints: (a) skeleton equalities of the formτ12, (b) skeleton constraints of the formα:τ, and (c) wanted subtyping constraints of the formω:π. The purpose of the first two becomes clear when we discuss constraint solving, in Section 5.3. Next, typing environments Γ only contain term variable bindings, while other variables represent unknowns of their sort and may end up being instantiated after constraint solving. Finally, during type inference we compute substitutionsσ, for refining as of yet unknown skeletons, types, dirts, and coercions. The last one is essential, since our algorithm simultaneously performs type inference and elaboration intoExEff. A substitutionσis a solution of the setP, written asσ|=P, if we get derivable judgements after applyingσto all constraints inP.

Values. Constraint generation for values takes the formQ;Γ `vv:A| Q0;σ v0. It takes as inputs a set of wanted constraints Q, a typing environment Γ, and a

(16)

ImpEffvaluev, and produces a value typeA, a new set of wanted constraintsQ0, a substitutionσ, and aExEff valuev0.

Unlike standard HM, our inference algorithm does not keep constraint generation and solving separate. Instead, the two are interleaved, as indicated by the additional arguments of our relation: (a) constraintsQare passed around in a stateful manner (i.e., they are input and output), and (b) substitutionsσgenerated from constraint solving constitute part of the relation output. We discuss the reason for this inter- leaved approach in Section 5.4; we now focus on the algorithm.

The rules are syntax-directed on the inputImpEffvalue. The first rule handles term variables x: as usual for constraint-based type inference the rule instantiates the polymorphic type(∀¯ς.α:τ .∀¯δ.¯π⇒A)ofxwith fresh variables; these are place- holders that are determined during constraint solving. Moreover, the rule extends the wanted constraintsPwithπ, appropriately instantiated. In¯ ExEff, this corresponds to explicit skeleton, type, dirt, and coercion applications.

More interesting is the third rule, for term abstractions. Like in standard Hindley- Damas-Milner [5], it generates a fresh type variableαfor the type of the abstracted term variablex. In addition, it generates a fresh skeleton variable ς, to capture the (yet unknown) shape ofα.

As explained in detail in Section 5.3, the constraint solver instantiates type vari- ables only through their skeletons annotations. Because we want to allow local con- straint solving for the body c of the term abstraction the opportunity to produce a substitution σ that instantiatesα, we have to pass in the annotation constraint α:ς.8We apply the resulting substitutionσto the result type σ(α)→C.9

Finally, the fourth rule is concerned with handlers. Since it is the most complex of the rules, we discuss each of its premises separately:

Firstly, we infer a typeBr!∆rfor the right hand side of thereturn-clause. Since αr is a fresh unification variable, just like for term abstraction we requireαr : ςr, for a fresh skeleton variableςr.

Secondly, we check every operation clause inO in order. For each clause, we generate fresh skeleton, type, and dirt variables (ςi, αi, and δi), to account for the (yet unknown) result type αii of the continuation k, while inferring type BOp

i!∆Op

i for the right-hand-sidecOp

i.

More interesting is the (final) set of wanted constraintsQ0. First, we assign to the handler the overall type

αininoutout

whereςin, αin, δin, ςout, αout, δout are fresh variables of the respective sorts. In turn, we require that (a) the type of the return clause is a subtype ofαoutout (given by the combination ofω1andω2), (b) the right-hand-side type of each operation clause is a subtype of the overall result type: σn(BOpi!∆Opi) 6αoutout (witnessed by ω3i4i), (c) the actual types of the continuationsBi→αoutout in the operation clauses should be subtypes of their assumed types Bi → σnii) (witnessed

8This hints at why we need to pass constraints in a stateful manner.

9Thoughσrefers toImpEfftypes, we abuse notation to save clutter and apply it directly toExEffentities too.

(17)

Q;Γ `cc:C | Q0;σ c0 Computations

Q;Γ `vv1 :A1 | Q11 v01 Q11(Γ)`vv2:A2| Q22 v02

Q;Γ `cv1 v2:α!δ|α:ς, ω:σ2(A1)6A2→α!δ,Q2; (σ2·σ1) (σ2(v01)Bω)v20 Q;Γ `vv:A| Q0;σ v0

Q;Γ `creturnv:A!∅ | Q0;σ returnv0 Q;Γ `vv:A| Qv1 v0

solve(•;•;Qv) = (σ10,Q0v) split(σ101(Γ)),Q0v, σ01(A)) =h¯ς, α:τ ,δ, ω¯ :π,Q1i Q1101(Γ)), x:∀¯ς.∀α:τ .∀¯δ.π⇒σ01(A)`cc:C | Q22 c0

cres =letx=σ2(Λ¯ς.Λα:τ .Λδ.Λ(ω¯ :elabρ(π)).v0)inc0 Q;Γ `cletx=vinc:C| Q2; (σ2·σ10 ·σ1) cres

Q;Γ `vv:A1| Q11 v0 Q11(Γ), y:BOp`cc:A2 !∆2| Q22 c0 (Op:AOp→BOp)∈Σ cres=Op(σ2(v0)Bω) (y:elabS(BOp).c0) Q;Γ `cOpv(y:BOp.c) :A2 !{Op} ∪∆2| ω:σ2(A1)6AOp,Q2; (σ2·σ1) cres

Q;Γ `cc1:A1!∆1| Q11 c01 Q11(Γ), x:A1`cc2:A2!∆2| Q22 c02

cres =dox←(σ2(c01)Bhσ2(A1)i!ω1); (c02 BhA2i!ω2)

Q;Γ `cdox←c1;c2:A2 !δ| ω12(∆1)6δ, ω2 :∆26δ,Q2; (σ2·σ1) cres

Q;Γ `vv:A1| Q11 v0 Q11(Γ)`cc:A2!∆2 | Q22 c0

Q011, α22, ω12(A1)6(α1122), ω2:A21, ω3:∆21,Q2

cres=handle(c0B(ω23))with(σ2(v0)Bω1) Q;Γ `chandlecwithv:α2 !∆2| Q0; (σ2·σ1) cres

Fig. 9:Constraint Generation with Elaboration (Computations)

by ω5i). (d) the overall argument type αin is a subtype of the assumed type of x:σnrr))(witnessed byω6), and (e) the input dirt setδin is a subtype of the resulting dirt set δout, extended with the handled operationsO(witnessed byω7).

All the aforementioned implicit subtyping relations become explicit in the elab- orated termcres, via explicit casts.

Computations. The judgementQ;Γ `c c : C | Q0;σ c0 generates constraints for computations.

The first rule handles term applications of the formv1v2. After inferring a type for each subterm (A1 for v1 and A2 for v2), we generate the wanted constraint σ2(A1) 6 A2 → α!δ, with fresh type and dirt variables α and δ, respectively.

Associated coercion variable ω is then used in the elaborated term to explicitly (up)castv10 to the expected typeA2→α!δ.

(18)

The third rule handles polymorphic let-bindings. First, we infer a typeAforv, as well as wanted constraintsQv. Then, we simplify wanted constraintsQv by means of function solve (which we explain in detail in Section 5.3 below), obtaining a substitutionσ01and a set ofresidual constraintsQ0v.

Generalization ofx’s type is performed by auxiliary functionsplit, given by the following clause:

¯

ς={ς|(α:ς)∈ Q,@α00∈/ α¯∧(α0 :ς)∈ Q}

¯

α=fvα(Q)∪fvα(A)\ fvα(Γ) Q1={(ω:π)|(ω:π)∈ Q,fv(π)6⊆fv(Γ)}

δ¯=fvδ(Q)∪fvδ(A)\ fvδ(Γ) Q2=Q − Q1

split(Γ,Q,A) =h¯ς, α:τ ,¯δ,Q1,Q2i

In essence,split generates the type (scheme) ofxin parts. Additionally, it computes the subset Q2 of the input constraints Q that do not depend on locally-bound variables. Such constraints can be floated “upwards”, and are passed as input when inferring a type forc. The remainder of the rule is self-explanatory.

The fourth rule handles operation calls. Observe that in the elaborated term, we upcast the inferred type to match the expected type in the signature.

The fifth rule handles sequences. The requirement that all computations in ado- construct have the same dirt set is expressed in the wanted constraintsσ2(∆1)6δ and ∆2 6 δ (where δ is a fresh dirt variable; the resulting dirt set), witnessed by coercion variables ω1 and ω2. Both coercion variables are used in the elaborated term to upcastc1 andc2, such that both draw effects from the same dirt setδ.

Finally, the sixth rule is concerned with effect handling. After inferring typeA1

for the handler v, we require that it takes the form of a handler type, witnessed by coercion variable ω1 : σ2(A1) 6 (α11 V α22), for fresh α1, α2, δ1, δ2. To ensure that the type A2!∆2 of c matches the expected type, we require that A2!∆211. Our syntax does not include coercion variables for computation subtyping; we achieve the same effect by combiningω2:A21andω3:∆21. Theorem 3 (Soundness of Inference). If •;Γ `v v : A | Q;σ v0 then for any σ0 |= Q, we have (σ0·σ)(Γ) `v v : σ0(A) σ0(v0), and analogously for computations.

Theorem 4 (Completeness of Inference). If Γ `v v : A v0 then we have

•;Γ `v v :A0 | Q;σ v00 and there exists σ0 |=Q andγ, such thatσ0(v00) =v0 andσ(Γ)`co γ:σ0(A0)6A. An analogous statement holds for computations.

5.3 Constraint Solving

The second phase of our inference-and-elaboration algorithm is the constraint solver.

It is defined by thesolve function signature:

solve(σ;P; Q) = (σ0,P0)

It takes three inputs: the substitutionσaccumulated so far, a list of already processed constraints P, and a queue of still to be processed constraints Q. There are two

(19)

outputs: the substitutionσ0 that solves the constraints and the residual constraints P0. The substitutions σ and σ0 contain four kinds of mappings:ς 7→ τ, α 7→ A, δ7→∆ andω →γ which instantiate respectively skeleton variables, type variables, dirt variables and coercion variables.

Theorem 5 (Correctness of Solving).For any setQ, the callsolve(•;•;Q)either results in a failure, in which caseQhas no solutions, or returns(σ,P)such that for anyσ0|=Q, there existsσ00|=P such that σ000·σ.

The solver is invoked with solve(•;•;Q), to process the constraints Q gen- erated in the first phase of the algorithm, i.e., with an empty substitution and no processed constraints. Thesolvefunction is defined by case analysis on the queue.

Empty Queue When the queue is empty, all constraints have been processed. What remains are the residual constraints and the solving substitution σ, which are both returned as the result of the solver.

solve(σ;P;•) = (σ,P)

Skeleton Equalities The next set of cases we consider are those where the queue is non-empty and its first element is an equality between skeletonsτ12. We consider seven possible cases based on the structure of τ1 andτ2 that together essentially implement conventional unification as used in Hindley-Milner type inference [5].

solve(σ;P;τ12,Q) = matchτ12with

|ς=ς7→solve(σ;P;Q)

|ς=τ 7→ifς /∈fvς(τ) then letσ0= [τ /ς]in solve(σ0·σ;•;σ0(Q,P))else fail

|τ=ς7→ifς /∈fvς(τ) then letσ0= [τ /ς]in solve(σ0·σ;•;σ0(Q,P))else fail

| Unit=Unit7→solve(σ;P;Q)

|(τ1→τ2) = (τ3→τ4)7→solve(σ;P;τ13, τ24,Q)

|(τ12) = (τ34)7→solve(σ;P;τ13, τ24,Q)

| otherwise7→fail

The first case applies when both skeletons are the same type variableς. Then the equality trivially holds. Hence we drop it and proceed with solving the remaining constraints. The next two cases apply when eitherτ1 orτ2is a skeleton variableς. If the occurs check fails, there is no finite solution and the algorithm signals failure.

Otherwise, the constraint is solved by instantiating theς. This additional substitution is accumulated and applied to all other constraints P,Q. Because the substitution might have modified some of the already processed constraintsP, we have to revisit them. Hence, they are all pushed back onto the queue, which is processed recursively.

(20)

The next three cases consider three different ways in which the two skeletons can have the same instantiated top-level structure. In those cases the equality is decomposed into equalities on the subterms, which are pushed onto the queue and processed recursively.

The last catch-all case deals with all ways in which the two skeletons can be instantiated to different structures. Then there is no solution.

Skeleton Annotations The next four cases consider a skeleton annotation α: τ at the head of the queue, and propagate the skeleton instantiation to the type variable. The first case, where the skeleton is a variableς, has nothing to do, moves the annotation to the processed constraints and proceeds with the remainder of the queue. In the other three cases, the skeleton is instantiated and the solver instantiates the type variable with the corresponding structure, introducing fresh variables for any subterms. The instantiating substitution is accumulated and applied to the remaining constraints, which are processed recursively.

solve(σ;P;α:τ,Q) = matchτwith

|ς7→solve(σ;P, α:τ;Q)

| Unit7→letσ0= [Unit/α]in solve(σ0·σ;•;σ0(Q,P))

1→τ27→letσ0= [(ατ11→ατ22!δ)/α]in solve(σ0·σ;•;α11, α22, σ0(Q,P))

127→letσ0= [(ατ111τ222)/α]in solve(σ0·σ;•;α11, α22, σ0(Q,P))

Value Type Subtyping Next are the cases where a subtyping constraint between two value types A16A2, with as evidence the coercion variable ω, is at the head of the queue. We consider six different situations.

solve(σ;P;ω:A16A2,Q) = matchA16A2with

|A6A7→letT=elabS(A)in solve([hTi/ω]·σ;P;Q)

τ16A7→letτ2=skeleton(A)in solve(σ;P, ω:ατ16A;τ12,Q)

|A6ατ1 7→letτ2=skeleton(A)in solve(σ;P, ω:A6ατ121,Q)

|(A1→B1!∆1)6(A2→B2!∆2)7→letσ0= [(ω1→ω23)/ω]in solve(σ0·σ;P;ω1:A26A1, ω2:B16B2, ω3:∆16∆2,Q)

|(A1!∆1VA2!∆2)6(A3!∆3VA4!∆4)7→letσ0= [(ω1234)/ω]in solve(σ0·σ;P;ω1:A36A1, ω2:∆36∆1, ω3:A26A4, ω4:∆26∆4,Q)

| otherwise7→fail

If the two types are equal, the subtyping holds trivially through reflexivity. The solver thus drops the constraint and instantiatesω with the reflexivity coercionhTi. Note that each coercion variable only appears in one constraint. So we only accumulate

Références

Documents relatifs

The following observations 6 can be made: (i) adjective in French is an unmarked form that potentially agrees with the noun; (ii) in Ewondo, we can’t indicate the class marker of

These enhanced type systems make it possible to define many useful generic functions over mutable data structures, such as the function that copies a vector.. However, these systems

Figure 1 shows the result of the algorithm for computing the conjunction of FTV, obtained in accordance with [8] for fuzzy sets with membership functions, given in

This tutorial introduces to Inductive Logic Programming (ILP), being it a major logic-based approach to rule learning, and sur- veys extensions of ILP that turn out to be suitable

5 (PCR5), proposed in Dezert-Smarandache Theory and on the T-Conorm-Norm alternative class fusion rule, connecting the combination rules for information fusion with particular

The local view of an agent A that occurs in a site graph G consists of A itself, its sites and their state as men- tioned in G, alongside information about which sites of A are bound

Type inference for HMG(X ) is reduced to constraint solving in such a way that, for programs that do not involve guarded algebraic data types, constraint generation is

Garbage collection uses this information to throw away meaningless constraints. A constraint is only useful if it ac- tually constrains the type scheme, i.e. if it can potentially