Mobility types in Coq∗ Furio Honsell Ivan Scagnetto Dipartimento di Matematica e Informatica, Universit`a degli Studi di Udine honsell,
[email protected] February 3, 2004
Abstract The need for formal methods for certifying the good behaviour of computer software is dramatically increasing with the growing complexity of the latter. Moreover, in the global computing framework one must face the additional issues of concurrency and mobility. In the recent years many new process algebras have been introduced in order to reason formally about these problems; the common pattern is to specify a type system which allows one to discriminate between “good” and “bad” processes. In this paper we focus on an incremental type system for a variation of the Ambient Calculus called M 3 , i.e., Mobility types for Mobile processes in Mobile ambients and we formally prove its soundness in the proof assistant Coq.
1
Introduction
Recently, due to the widespread use of the Internet and to the appearance of new mobile devices (PDAs, smart phones etc.), the traditional notion of computing is quickly fading away, giving birth to new paradigms. Indeed, the need of exchanging data and cooperatively working towards a common goal between entities moving from one location to another gives rise to new non-trivial problems. In order to formally describe and reason about this new computing paradigms, a plethora of calculi have been proposed. Among them, the Ambient Calculus [1] is a process algebra specifically designed in order to model mobility of agents in a dynamic hierarchy of domains (ambients) with local communications. The interest towards this calculus is witnessed by the growing number of variants recently proposed in the literature. Since the original formulation of the Ambient Calculus, many studies have been carried out in order to find satisfactory alternatives to the open primitive, i.e, the capability allowing to dissolve an ambient revealing its internal structure. ∗ Work
supported by EU project IST-2001-33477 Dart
1
Indeed, this is considered a potentially dangerous operation since an agent could maliciously destroy from the outside a domain containing processes operating on sensitive data. In this paper we focus on a variant of the Ambient Calculus (originally introduced in [3]) which allows inter-ambient communication replacing the open primitive with a “to” instruction which can move lightweight processes (i.e., lists of capabilities) without the need of enclosing them into an ambient. On top of the language there is also a type system which regulates the behaviour of processes. Indeed, type systems are essential components in many ambient calculi because they allow to discriminate between “good” processes and “bad” ones; this is extremely important when one wants to model security properties in the global computing framework. A very good feature of the type system introduced in [3] is that it allows to type components in incomplete environments, i.e., it is incremental. Moreover, there is a type inference algorithm which can be used on a “raw” term in order to derive the minimum requirements for accepting it as a good process, which provides also a notion of principal type. The ultimate result of this paper is the formally certified correctness proof of the type inference algorithm. This formal proof was carried out in the Coq system (developed at the INRIA research institute [12]) incrementally with the definition of the type inference rules introduced in [3] and in few occasions it actually suggested the correct formulation of the inference rules themselves. Completeness will be addressed in a future work. We capitalize on the Higher-Order Type Theory featured by Coq approach [2, 8, 10, 13]. In particular,we use Higher-Order Abstract Syntax (HOAS) and we represent binders by means of higher-order (i.e., functional) constants. We encode the typing and inference rules in natural deduction style. Thus, we avoid an explicit encoding of many tedious mechanisms like, e.g., alpha-conversion, schemata instantiation, side conditions about the freshness of bound variables and the treatment of typing environments by means of lists. We capitalize also on some interesting features of Coq such as the Leibniz equality and the associated Rewrite tactic in order to deal with unification. Synopsis. In Section 2 we introduce basic notions about Logical Frameworks, their implementations and the main encoding techniques. In particular we focus on the Calculus of Inductive Constructions (CIC) [4] and its implementation, namely, the proof assistant Coq and on Higher-Order Abstract Syntax (HOAS) encodings. In Section 3 we introduce the M 3 calculus, the typing system and the related type inference mechanism presented in [3]. Section 4 is devoted to the formal derivation in Coq of the soundness of the type inference algorithm. Finally, in Section 5 we draw some conclusions.
2
Logical Frameworks
In order to reason formally about an object language we must somehow “encode” it into a form which can be processed by a machine. There are two ways to carry 2
out this task; the former is to implement an ad-hoc system for the case at hand. This is the way which probably provides a perfectly tailored tool for the special case (more efficient, more reminiscent of the original syntax of the implemented system etc.). The price to pay is that we are forced to explicitly implement many complicated and tedious mechanisms (it is sufficient to consider the syntax level, where support must be provided for representing terms, formulæ, derivation rules, binding operators, and substitution), loosing the focus on the essential features of the original system. However, if a new system has to be studied or even a minor change or extension of the original system is to be considered, the approach reveals a substantial lack of flexibility, since all the encoding work must be done again from scratch. Since, such an approach is not tenable, an alternative methodology based on Logical Frameworks (LFs) has been developed during the last decades. Indeed, LFs capture the main common features of a large class of logics in such a way that a great amount of work is done once and for all. Hence, the encoding can be done using the metalanguage provided by a LF, obtaining for free many useful mechanisms. The Curry-Howard isomorphism (independently introduced in [5] and [11]) gives birth to type theory-based logical frameworks, which allow one to think of types not only as partial correctness specifications of programs (terms), but also as propositions. Whence, a given term can be interpreted as a proof of the proposition associated with its type; it follows that a proposition is true (i.e, there is a proof of it) if the corresponding type is inhabited. Moreover, since logical systems can be viewed as calculi for building proofs of a given set of basic judgments, for those type theories featuring dependent types, it is possible to use the judgments-as-types principle [8, 13], which can be regarded as the metatheoretic analogue of the Curry-Howard isomorphism, in order to fruitfully use type theories as general logic programming languages, i.e., as a logical framework. This consists in representing basic judgments with suitable types of the LF; whence proofs are represented by terms whose type represents in turn the judgment that they prove. Moreover, dependent types allow one to uniformly extend basic judgment forms to two higher-order forms introduced by Martin-L¨of, namely, the hypothetical judgment (representing consequence) and the schematic judgment (representing generality). Hence, all the relevant parts of an inference system can be faithfully represented in a logical framework: syntactic categories, terms, judgments, axiom and rule schemata etc.
2.1
Coq
The Coq system [12] is an interactive proof assistant whose underlying metalanguage is the Calculus of (Co)Inductive Constructions (CC (Co)Ind ). It is the result of over ten years of research at INRIA (Institut National de Recherche en Informatique et Automatique). In 1984, Coquand and Huet wrote the first implementation of the Calculus of Constructions in CAML (a functional language belonging to the ML family and developed at INRIA). The core of the system was a proof-checker, known as Constructive Engine, which allowed the declara3
tion of axioms and parameters, the definition of mathematical types and objects and the explicit construction of proof-objects represented as λ-terms. Then, a section mechanism, called the Mathematical Vernacular, allowing one to develop mathematical theories in a hierarchical way was added. At the same time an interactive theorem prover executing tactics written in CAML was implemented; by means of this tool proofs could be built progressively in a top-down style, generating subgoals and backtracking when needed. Moreover, the basic set of tactics could be extended by the user. With the introduction of inductive types by Paulin-Mohring, a new set of tactics allowing one to carry out proofs by induction was added. The implementation of a module for compiling programs extracted from proofs in CAML is due to Werner. Starting from version V5.10 the Coq system supports coinductive types as well, implementing a powerful tactic Cofix which allows the user to interactively build proof involving coinductive predicates in a natural way, without having to exhibit a priori a bisimulation like it is usually done using “pencil and paper”. The essential features of the system are: 1. a logic metalanguage allowing one to represent formal systems; 2. a powerful proof engine assisting the user in the task of formally reasoning about the encoded systems; 3. a program extractor yielding functional programs from constructive proofs. The calculus implemented in the Coq system extends the traditional Calculus of Constructions (CC) [4] with some special constants which represent the definition, introduction and elimination of inductive types. For instance, the following definition of natural numbers (written in Gallina, Coq’s specification language) Inductive nat : Set :=
O : nat | S : nat -> nat
allows to define terms by “case analysis”, like the following function: Definition pred := [n:nat]Cases n of
O => O
|
(S u) => u
end.
where [n:nat] is Gallina notation for abstraction λn : nat. Using these elimination schemata, Coq automatically states and proves the induction principle for each inductively defined type. For instance, the above definition yields the Peano induction principle “for free”: nat_ind : (P:nat->Prop)(P O) -> ((n:nat)(P n)->(P (S n))) -> (n:nat)(P n) Q where (n:nat) is the notation for dependent product n:nat . This feature is very useful since, in order to define an inductive predicate, we need only to specify the introduction rules, and we can prove the elimination rules from the elimination principle the system automatically provides us with.
4
However, allowing for any inductive definition in CIC would yield non-normalizing terms, thus invalidating the standard proof of consistency of the system. Hence, inductive definitions are subject to the positivity condition, which (roughly) requires that the type we are defining does not occur in a negative position in the type of any argument of any constructor. This condition ensures the soundness of the system, but it rules out also many sound inductive definitions. For instance, the following definition of λ-terms in (full) higher-order abstract syntax Inductive L : Set := lam : (L->L) -> L | app : L -> L -> L. is not well-formed, due to the negative occurrence of L in the type L->L of the argument of lam. As we mentioned earlier, Coq is an interactive proof assistant in the sense that it allows one to interactively searching for an inhabitant of a type, in a top-down fashion by applying tactics step-by-step, backtracking if needed, and for verifying correctness of typing judgments. A proof search starts by entering Lemma ident : goal. where goal is the type representing the proposition to prove. At this point, Coq waits for commands from the user, in order to build the proof term which inhabits goal (i.e., the proof). To this end, Coq offers a rich set of tactics, e.g., introduction and application of assumptions, application of rules and previously proved lemmata, elimination of inductive objects, inversion of (co)inductive hypotheses and so on. These tactics allow the user to proceed in his proof search much like he would do informally. At every step, the type checking algorithm ensures the soundness of the proof. When the proof term is completed, it can be saved (by the command Qed) for future applications.
2.2
HOAS
We saw in section 2 that the philosophy which inspired the birth of the LFs is that of delegating as many features as possible to a common metalanguage, in order to avoid reinventing the wheel at every new case study. The Higher-Order Abstract Syntax (HOAS) approach goes further into this direction for what concerns the representation of variables and binders. Indeed, one of the most difficult issues to face when encoding an object language featuring binders is to properly render the latter, in order both to avoid implementing the machinery of α-conversion and capture-avoiding substitution and to retain a sufficient degree of expressivity in order to be able to carry out the formal development of the metatheory. First order approaches, like de Bruijn indexes and first-order abstract syntax overwhelm the user with technical details about α-conversion and substitution properties, which must be derived from scratch. The HOAS approach instead encodes binders by means of functional constants; this allows to automatically delegate to the metalanguage the management of bound variables and the related machinery of α-conversion and capture-avoiding substitution.
5
To illustrate this point, let us consider the case of encoding the syntax of untyped λ-calculus: M ::= x | M1 M2 | λx.M, where x ∈ V (V is an infinite set of variables). In general, to encode a logical system in a type theory based logical framework, the user must assign types to a set of constants representing the syntax constructors and the judgments with their derivation rules. In the abovementioned case (untyped λ-calculus) a na¨ıve encoding would take an inductive set (like N) as the set representing variables and map the binding operator λ to a term constructor lam of type var → tm → tm (if tm is the type chosen to represent λ-calculus terms and var the type representing variables). This is intuitive since the term lam-constructor takes as arguments one variable (x) and one term (m) in which the variable x will be bound exactly as the original λ-operator does. However, as anticipated, there are several drawbacks; indeed so doing one must then provide an additional encoding of the notions of free and bound variable and of the mechanisms of α-conversion and capture-avoiding substitution. In contrast the HOAS encoding approach the signature encoding the λcalculus syntax is the following: tm ::= app : tm → tm → tm | lam : (tm → tm) → tm Notice the type of the higher-order lam constructor taking a meta-level function as argument. So the term lam([x:tm]x) encodes the λ-term λx : x and the notion of β-reduction can be expressed in a very natural and elegant way saying that lam(f, t) reduces to f (t) without the need to specify what are free and bound variables and capture-avoiding substitution. However, it is well known that capitalizing on the advantages of the HOASencoding approach we have a price to pay for. Indeed, in order to take advantage of the inductive features of a metalanguage like the Calculus of (Co)Inductive Constructions, it is not possible to resort to a full HOAS approach, because constructor types like (tm → tm) → tm violate the positivity condition of inductive constructors. Hence it is necessary to introduce a separate type for variables, say var, with the consequence that capture-avoiding substitution of terms for variables is no more delegated to the metalevel (weak HOAS). Therefore binders are encoded by constructors with negative occurrences of the type representing variables, i.e., (var → tm) → tm. Correspondingly, var cannot be defined as an inductive type, because this would introduce exotic terms in the framework. These are λ-terms which do not correspond to any object “on the paper”, despite their types correspond to some syntactic category. Exotic terms are generated when a type has a higher-order constructor over an inductive type. A simple example is the following fragment of first-order logic: Inductive i : Set := zero : i | one : i. Inductive o : Set := ff : o | eq : i->i->o | forall : (i->o)->o. 6
Definition weird : o := (forall [x:i](Cases x of zero => ff | one => (eq zero zero) end)). The term weird does not correspond to any proposition of first order logic: there is no formula ∀xφ such that φ{0/x} and φ{1/x} are syntactically equal to “ff ” and “0 = 0”, respectively. Exotic terms are problematic in establishing the faithfulness of the formalization; usually, they have to be ruled out by means of auxiliary “validity” judgments [6]. Another approach, which we have used in this paper, is to have the higher order constructors to range over types which are not inductive, so that there is no Cases to use as above. Ironically, the last drawback is that one looses the possibility of reasoning about the properties which are delegated to the metalanguage, e.g., substitution and α-equivalence. In the literature there are several approaches aiming at reconciling HOAS with these issues; they are based on different techniques such as modal types, functor categories, permutation models of ZF, etc. [6, 7, 14]. The approach we used in several case studies about nominal calculi is known as the Theory of Contexts [9]: it consists of a set of axiom schemata about some basic properties of names/variables and contexts (i.e., terms with “holes”) over them. The main advantage of an axiomatic approach is that it can be easily plugged in an existing LF (provided it supports the introduction of new axioms) without requiring any redesign of the systems nor great encoding efforts. However, in this work we do not need to use the axioms of the Theory of Contexts; indeed, all we have to define and use are occurrence checking predicates allowing to infer if a given name occurs free or not into a term.
3
M3
In this section we briefly recall the syntax of the M 3 calculus; for further details and application examples, the interested reader is referred to [3].
3.1
The object language and its encoding
There are four basic syntactic categories, i.e., ambient names, groups, capabilities and processes which are annotated with types (see Section 3.2). Capabilities
7
(messages) are defined by the following grammar: M, N, L ::= m, n, . . . , x, y, . . . in M out M to M M.M 0
ambient names, variables moves the containing ambient into ambient M moves the containing ambient out of ambient M goes out from its ambient into a sibling ambient M path
For what concerns processes, the reader should notice that the restriction operator on groups is polyadic, i.e., it binds several groups at once. According to the authors of [3], this is needed since groups can have mutually dependent group types. The grammar defining processes is the following: P, Q, R
::= 0 M.P hM i.P (x:W ).P P |Q M [P ] !P (νn:amb(g))P ~ (k) )P (ν{g:G}
null prefixed synchronous output typed input parallel composition ambient replication name restriction group restriction
In order to “reconcile” the inductive features of Coq with the HOAS-approach, we represent the syntactic categories of names and groups by means of two parametric types: Parameter name: Set. Parameter group: Set. Thus, there is no risk of deriving exotic terms (see Section 2.2). Specific names and groups are rendered by means of Coq metavariables of type name and group, respectively. The encoding of capabilities is straightforward: Inductive cap: Set := name2cap : name -> cap | In : cap -> cap | Out : cap -> cap | to : cap -> cap | path : cap -> cap -> cap. For what concerns processes, there is a small issue to overcome if we want to stick to the HOAS-approach. Indeed, we said that the restriction operator on 8
groups is polyadic; hence, since the λ-abstraction operator of the type theory underlying the Coq system is monadic, we have to use a mutual inductive type in order to “mimick” a simultaneous group restriction: Mutual Inductive proc: Set := nil : proc | action : cap -> proc -> proc | output : cap -> proc -> proc | input : (name -> proc) -> msgType -> proc | par : proc -> proc -> proc | ambient : cap -> proc -> proc | bang : proc -> proc | nu : group -> (name -> proc) -> proc | nuG : res -> proc with res: Set := proc2res : proc -> res | resG : groupType -> (group -> res) -> res. The rˆole of terms of type res is to encode group restrictions by grouping together several monadic abstractions. For instance, the M 3 process (νg1 : G1 , g2 : G2 )0 is encoded by (nuG (resG G1 [g1:group](resG G2 [g2:group](proc2res nil)))). Since cap and proc are inductive types, the Coq system automatically provides for free inductive and recursive principles, which are very useful in order to speed up the activity of the formal development of the metatheory. Notice how the encoding of the calculus, following the principles fro encoding syntax in LF ( [8]) and the standard specification language provided by type theory, enhance the readability of the original presentation of the calculus. It is often the case that LF encodings enhance the syntax and allow to eliminate unnecessary idiosyncrasies. In this paper we are only interested in the type inference algorithm; hence, we do not recall the notions of structural congruence and of the reduction system. The interested reader is referred to [3] for more details.
3.2
Mobility types and their encoding
In order to avoid dependent types, in [3] the authors adopt an approach based on groups; hence, there are basically three categories of types: ambient types, capability types and process types. Groups are denoted by the letters g, h, . . ., sets of groups are denoted by S, C, E, . . . and the syntax for the M 3 types is
9
defined as follows: Amb P ro
::= amb(g) ::= proc(g)
Cap
::= P ro1 → P ro2
W
::= Amb Cap
T
::= shh W
G
::= gr(S, C, E, T )
ambient type: ambients of group g process type: processes that can stay in ambients of group g capability type: capabilities that, prefixed to a process of type P ro1 turn it into a process of type P ro2 message type ambient type capability type communication type no communication communication of messages of type W group type
Following the notational remark at page 7 in [3], saying that we can simply write g both for amb(g) and for proc(g) since the distinction is always clear from the context, the encoding in Coq is straightforward: Mutual Inductive msgType : Set := amb_type : group -> msgType | cap_type : group -> group -> msgType with comType : Set := Shh : comType | msg : msgType -> comType. In order to avoid an explicit treatment of typing environments, we render them by means of two parametric judgments: Parameter type_group: group -> groupType -> Prop. Parameter type_name: name -> group -> Prop. such that (type_group g G) holds iff g has group type G and (type_name n g) holds iff the name n has type g in the current environment. For instance, the environment {g : G, n : g} is rendered in Coq by declaring the following: Parameter dg: (type_group g G). Parameter dn: (type_name n g). This choice, followed by the rephrasing of the sequent style rules of the typing system in natural deduction, completely delegates to the Coq’s metalanguage the treatment of environments. Thus the whole type system is encoded by means of the following inductive predicates (the first for capabilities and the second for processes): Inductive good_msg : cap -> msgType -> Prop := ... Inductive good_proc : proc -> group -> Prop := ... 10
The complete definitions are reported in appendixA. Intuitively, (good_msg M W) holds iff M has type W and (good_proc P g) holds iff P has type g in the current environment. Group types are encoded by the following predicate, featuring only one constructor: Inductive groupType: Set := gr: Glist -> Glist -> Glist -> comType -> groupType. We recall from [3] that the meaning of the statement g : gr(S, C, E, T ) is the following: • S is the set of ambient groups where the ambients of group g can stay; • C is the set of ambient groups that the ambients of group g can cross; • E is the set of ambient groups that lightweight g-processes can enter; • T is the communication type of g-ambients. Hence, S, C, E are sets of group names that in Coq we render by means of lists of elements of type group: Inductive Glist : Set := emptyG : Glist | consG : group -> Glist -> Glist.
3.3
Type inference algorithm
The type inference algorithm introduced in [3] starts computing a type from a “raw” process, i.e., a well formed process without type annotations and group restrictions. Thus in Coq we introduce a suitable type raw_proc representing raw processes: Inductive raw_proc: Set := raw_nil : raw_proc | raw_action : cap -> raw_proc -> raw_proc | raw_output : cap -> raw_proc -> raw_proc | raw_input : (name -> raw_proc) -> raw_proc | raw_par : raw_proc -> raw_proc -> raw_proc | raw_ambient : cap -> raw_proc -> raw_proc | raw_bang : raw_proc -> raw_proc | raw_nu : (name -> raw_proc) -> raw_proc. Each constructor corresponds directly to a constructor of type proc, if we do not consider the group restriction operator. Moreover, since during the type inference process of capabilities some occurrences of group names into the S component of group types are marked with a ∗ in order to be able to infer later the correct set of group names where an ambient can stay, we need to reflect this fact into our encoding. Hence, we introduce the type star_group which admits “starred” group names beside “normal” ones: 11
Inductive star_group : Set := simple : group -> star_group | star : group -> star_group. So, (simple g) encodes a “normal” group name g, while (star g) represents a “starred” group name g ∗ . It follows that the first component S of group types must be a list of elements of type star_group (instead of elements of type Glist): Inductive starGlist : Set := starEmptyG : starGlist | starConsG : star_group -> starGlist -> starGlist. Thus, group types are recorded by means of a new inductive judgment: Inductive starGroupType: Set := gr_star: starGlist -> Glist -> Glist -> comType -> starGroupType. where the only difference w.r.t. the previous predicate groupType is the fact that the first argument of the constructor gr_star is a term of type starGlist instead of type Glist. The type environments incrementally built by the type inference algorithm are also rendered as lists: Inductive env: Set := emptyE : env | consEgroup : group -> starGroupType -> env -> env | consEname : name -> msgType -> env -> env. There are three constructors: one for the empty environment (emptyE), another for recording statements like g : gr(S, C, E, T ) (consEgroup) and the last one for statements like n : g or x : W (consEname). The next step consists in the encoding of the operations performed on the environments during the type inference process. More precisely, we have to represent completion-unifiers, compressions and closures. For what concerns unifications, we prefer to not deal explicitly with them in order to avoid to get lost into syntactical details. Hence, we represent them in form of identity constraints between terms. These constraints are rendered by means of Leibniz equalities in higher-order schematic judgments in order to be able to use the tactic Rewrite to effectively unify the terms when needed. For instance, in the rule (I-PATH) of Figure 12 in [3] the unification φ({(W, g1 → g2 ), (W 0 , g3 → g1 )}) is rendered by requiring the validity of the Leibniz equalities W=(cap_type g1 g2) and W’=(cap_type g3 g1). Moreover, when there is the need of unifying two environments e1 and e2, we render the completion-unifier by means of (unify_env e1 e2) where unify_env is defined as follows: Definition unify_env : env -> env -> Prop := [e1:env][e2:env] ((n:name)(W1,W2:msgType)(name_in_env n W1 e1) -> (name_in_env n W2 e2) -> W1=W2) /\ 12
((g:group)(S1,S2:starGlist)(C1,C2,E1,E2:Glist)(t1,t2:comType) (group_in_env g (gr_star S1 C1 E1 t1) e1) -> (group_in_env g (gr_star S2 C2 E2 t2) e2) -> t1=t2). where (name_in_env n W e) holds iff the association between the name n and the message type W occurs in the environment e. Similarly (group_in_env g t e) holds iff the association between the group name g and the group type t occurs into e. Hence, (unify_env e1 e2) means that e1 and e2 must agree for what concerns the types of names and the communication types inside group types referred to the same element. The operation of “merging” two (unified) environments is rendered by the following predicate: Inductive union_env: env -> env -> env -> Prop := trivial_union : (e:env)(union_env emptyE e e) | group_union : (e,e’,e’’,e’’’:env)(g:group)(S,S’:starGlist) (C,C’,E,E’:Glist)(t:comType) (remove_group e’ g e’’’) -> (union_env e e’’’ e’’) -> (add_S g S e’ S’) -> (add_C g C e’ C’) -> (add_E g E e’ E’) -> (union_env (consEgroup g (gr_star S C E t) e) e’ (consEgroup g (gr_star S’ C’ E’ t) e’’)) | name_union : (e,e’,e’’:env)(n:name)(W:msgType) (union_env e e’ e’’) -> (union_env (consEname n W e) e’ (consEname n W e’’)). In order to check if (union_env e1 e2 e) holds, we proceed by structural induction on e1. The case where the e1 is empty (trivial_union) is straightforward. When the head constructor of e1 is consEname, we simply “copy” the association between the name n and the message type W in the merged environment e. The only interesting case is when the head constructor of e1 is consEgroup, since we must search through e2 the occurrence of g adding the components of the relative group type to those of the occurrence of e1 (using the predicates add_S, add_C and add_E). Then we remove g from e2 (predicate remove_group) and we continue inductively. We include the definitions of all the previous auxiliary predicates in Appendix B. Finally the closure operation which computes the correct components S of group types contained in an environment (eliminating all the occurrences of the marker ∗) is defined as follows: Inductive closure: starGlist -> Glist -> env -> Prop := elim_star : (l:starGlist)(e:env) ((g:group)(S:starGlist)(C,E:Glist)(t:comType) (starGlist_isin (star g) l) /\ (group_in_env g (gr_star S C E t) e) -> (inc_starGlist S l) 13
| add_grp
) -> (closure l (star_clear l) e) : (l,S:starGlist)(C,E,l’:Glist)(t:comType) (g:group)(e:env)(starGlist_isin (star g) l) -> (group_in_env g (gr_star S C E t) e) -> ~(inc_starGlist S l) -> (closure (append_starGlist l S) l’ e) -> (closure l l’ e).
where star_clear is the function which erases all the occurrences of the marker ∗ into the list passed as argument: Fixpoint star_clear[l:starGlist]: Glist := Cases l of starEmptyG => emptyG | (starConsG (simple g) l’) => (consG g (star_clear l’)) | (starConsG (star g) l’) => (consG g (star_clear l’)) end. The two constructors elim_star and add_grp correspond to the computation rules specified in point 1 of Definition 8 in [3]. Indeed, in order to compute the closure of an environment Γ, one has to replace S(G) with S(G) ∪ S(G0 ) for every g ∗ ∈ S(G) such that g : G0 ∈ Γ and S(G0 ) 6⊂ S(G) (constructor add_grp). Then, when there are no more g ∗ satisfying the previous condition, one can erase all the ∗ markers (constructor elim_star). Now we are ready to introduce the inductive predicates which encode the type inference rules in Figures 12 and 26 of [3]: Inductive msg_inf: cap -> msgType -> env -> Prop := ... Inductive proc_inf: raw_proc -> proc -> group -> env -> Prop := ... The complete definitions appear in Appendix C.
4
The formal development
In this section we describe the formal development carried out in Coq. The ultimate result is the certification of the correctness of the type inference algorithm; however, in order to achieve this goal, there are many subtleties to deal with. In Section 4.1, we introduce the auxiliary notions and properties we have to supply in order to prove the main goal, which we illustrate in Section 4.1.1.
4.1
Basic notions and properties
In order to prove the correctness of the type inference algorithm, we need some basic properties about environments and the related operations (see Section 3.3). The first two must be stated as axioms and allow to infer from the environment computed by the type inference algorithm the needed hypotheses in 14
the current proof context in order to be able to derive the appropriate typing judgments: Axiom TYPE_NAME: (n:name)(g:group)(e:env) (name_in_env n (amb_type g) e) -> (type_name n (amb_type g)). Axiom TYPE_GROUP: (g:group)(S:starGlist)(C,E:Glist)(t:comType) (e:env)(group_in_env g (gr_star S C E t) e) -> (S’:Glist)(closure S S’ e) -> (type_group g (gr S’ C E t)). Then we need some basic properties ensuring that if a given entity (a group name or a typing association g : gr(S, C, E, T ) occurs into an environment, then it also occurs into the result of a merge with another environment or of its closure: Axiom UNION_IN: (e1,e2,e:env)(g:group)(S:starGlist)(C,E:Glist) (t:comType)(unify_env e1 e2) -> (union_env e1 e2 e) -> (group_in_env g (gr_star S C E t) e2) -> (Ex [S’:starGlist] (Ex [C’:Glist] (Ex [E’:Glist](group_in_env g (gr_star S’ C’ E’ t) e)))). Axiom GROUP_IN_UNION: (e1,e2,e3:env)(union_env e1 e2 e3) -> (g,g’:group)(S,S’:starGlist) (C,C’,E,E’:Glist)(t:comType) (group_in_env g (gr_star S C E t) e2) -> (starGlist_isin (simple g’) S) -> (group_in_env g (gr_star S’ C’ E’ t) e3) -> (starGlist_isin (simple g’) S’). Axiom GROUP_IN_CLOSURE: (S:starGlist)(S’:Glist)(e:env)(g:group) (starGlist_isin (simple g) S) -> (closure S S’ e) -> (Glist_isin g S’). Finally, we must know that for every S-component of a typing g : gr(S, C, E, T ) occurring into an environment computed by the type inference algorithm, there exists the corresponding closure S 0 : Axiom CLOSURE_EX: (S:starGlist)(g:group)(C,E:Glist)(t:comType)(e:env) (group_in_env g (gr_star S C E t) e) -> (Ex [S’:Glist](closure S S’ e)). We stated the previous properties as axioms for simplicity, but they can indeed be proved in Coq.
15
4.1.1
Soundness of the type inference algorithm
Since the type inference rules are split in two sets: the first for capabilities and the second for raw processes, we proved two soundness lemmata: Lemma MSG_INF_SOUND
: (M:cap)(W:msgType)(e:env) (msg_inf M W e) -> (good_msg M W).
Lemma PROC_INF_SOUND : (R:raw_proc)(P:proc)(g:group)(e:env) (proc_inf R P g e) -> (good_proc P g). They are proved by structural induction on M and R, respectively. Obviously, the former result is needed in order to prove the second one, since processes are built on top of capabilities. These two lemmata are the formal equivalent of Theorem 6 of [3]. The complete Coq code is available at the URL http: //www.dimi.uniud.it/~scagnett/Coq-Sources/m3.v.
5
Conclusions
In this paper we encoded the syntax and the type system of a variant of the original Ambient Calculus which replaces the potentially dangerous open primitive with a new instruction to, moving lightweight processes without enclosing them into an ambient. Moreover, we provided a formal representation of the type inference rules introduced in [3], proving that they are sound w.r.t. the original type system. The novelty of the approach used in this paper is the treatment of unifications by means of schematic judgments involving Leibniz equalities, since this approach allows us to avoid an explicit implementation of the machinery underlying the theory of most general unifiers. Indeed, Leibniz equality corresponds to βδι-equality in Coq and this fact allows to rewrite the terms involved in the unifying constraints as needed during the proof development.
A
Typing predicates
Inductive good_msg : cap -> msgType -> Prop := good_msg_exp_n : (n:name)(g:group) (type_name n g) -> (good_msg (name2cap n) (amb_type g)) | good_exp_in : (M:cap)(g1,g2:group)(S,C,E:Glist)(T:comType) (type_group g2 (gr S C E T)) -> (good_msg M (amb_type g1)) -> (Glist_isin g1 C) -> (good_msg (In M) (cap_type g2 g2)) | good_exp_out : (M:cap)(g1,g2:group) (S1,S2,C1,C2,E1,E2:Glist)(T1,T2:comType) (type_group g1 (gr S1 C1 E1 T1)) -> 16
(type_group g2 (gr S2 C2 E2 T2)) -> (good_msg M (amb_type g1)) -> (Glist_isin g1 C2) -> (inclist S1 S2) -> (good_msg (Out M) (cap_type g2 g2)) | good_exp_to : (M:cap)(g1,g2:group)(S,C,E:Glist)(T:comType) (type_group g2 (gr S C E T)) -> (good_msg M (amb_type g1)) -> (Glist_isin g1 E) -> (good_msg (to M) (cap_type g1 g2)) | good_msg_exp_path : (M,M’:cap)(g1,g2,g3:group) (good_msg M (cap_type g3 g2)) -> (good_msg M’ (cap_type g1 g3)) -> (good_msg (path M M’) (cap_type g1 g2)). Inductive good_proc : proc -> group -> Prop := good_proc_nil : (g:group)(good_proc nil g) | good_proc_prefix : (M:cap)(g1,g2:group)(P:proc) (good_msg M (cap_type g1 g2)) -> (good_proc P g1) -> (good_proc (action M P) g2) | good_proc_input : (P:name->proc)(W:msgType)(g:group)(S,C,E:Glist) ((x:name)(type_var x W) -> (good_proc (P x) g)) -> (type_group g (gr S C E (msg W))) -> (good_proc (input P W) g) | good_proc_output : (P:proc)(M:cap)(W:msgType)(g:group)(S,C,E:Glist) (good_proc P g) -> (good_msg M W) -> (type_group g (gr S C E (msg W))) -> (good_proc (output M P) g) | good_proc_amb : (P:proc)(S,C,E:Glist)(M:cap)(g,g’:group)(T:comType) (good_proc P g) -> (good_msg M (amb_type g)) -> (type_group g (gr S C E T)) -> (Glist_isin g’ S) -> (good_proc (action M P) g’) | good_proc_par : (P,Q:proc)(g:group) (good_proc P g) -> (good_proc Q g) -> (good_proc (par P Q) g) | good_proc_repl : (P:proc)(g:group) (good_proc P g) -> (good_proc (bang P) g) | good_proc_res : (P:name->proc)(g,g’:group) ((m:name)(type_name m g’) -> (good_proc (P m) g)) -> (good_proc (nu g’ P) g) with good_res : res -> group -> Prop := good_res_proc2res : (P:proc)(g:group) 17
| good_res_Gres
B
(good_proc P g) -> (good_res (proc2res P) g) : (P:group->res)(g:group)(G:groupType) ((g’:group)~g=g’ -> (type_group g’ G) -> (good_res (P g’) g) ) -> (good_res (resG G P) g).
Auxiliary predicates
Inductive remove_group: env -> group -> env -> Prop := empty_remove : (g:group)(remove_group emptyE g emptyE) | group_remove1 : (e,e’:env)(g:group)(t:starGroupType) (remove_group e g e’) -> (remove_group (consEgroup g t e) g e’) | group_remove2 : (e,e’:env)(g,g’:group)(t:starGroupType) (remove_group e g’ e’) -> ~g=g’ -> (remove_group (consEgroup g t e) g’ (consEgroup g t e’)) | name_remove : (e,e’:env)(n:name)(W:msgType)(g:group) (remove_group e g e’) -> (remove_group (consEname n W e) g (consEname n W e’)). Inductive add_S: group -> starGlist -> env -> starGlist -> Prop := add_S_empty : (g:group)(S:starGlist)(add_S g S emptyE S) | add_S_group1 : (g:group)(S,S’,S’’:starGlist)(C,E:Glist) (t:comType)(e:env)(add_S g S e S’) -> (add_S g S (consEgroup g (gr_star S’’ C E t) e) (append_starGlist S’ S’’)) | add_S_group2 : (g,g’:group)(S,S’:starGlist)(t:starGroupType) (e:env)~g=g’ -> (add_S g S e S’) -> (add_S g S (consEgroup g’ t e) S’) | add_S_name : (n:name)(W:msgType)(g:group)(S,S’:starGlist) (e:env)(add_S g S e S’) -> (add_S g S (consEname n W e) S’). Inductive add_C: group -> Glist -> env -> Glist -> Prop := add_C_empty : (g:group)(C:Glist)(add_C g C emptyE C) | add_C_group1 : (g:group)(S:starGlist)(C,C’,C’’,E:Glist) (t:comType)(e:env)(add_C g C e C’) -> (add_C g C (consEgroup g (gr_star S C’’ E t) e) (append_Glist C’ C’’)) | add_C_group2 : (g,g’:group)(C,C’:Glist)(t:starGroupType) (e:env)~g=g’ -> (add_C g C e C’) -> (add_C g C (consEgroup g’ t e) C’) | add_C_name : (n:name)(W:msgType)(g:group)(C,C’:Glist)(e:env) 18
(add_C g C e C’) -> (add_C g C (consEname n W e) C’). Inductive add_E: group -> Glist -> env -> Glist -> Prop := add_E_empty : (g:group)(E:Glist)(add_E g E emptyE E) | add_E_group1 : (g:group)(S:starGlist)(C,E,E’,E’’:Glist) (t:comType)(e:env)(add_E g E e E’) -> (add_E g E (consEgroup g (gr_star S C E’’ t) e) (append_Glist E’ E’’)) | add_E_group2 : (g,g’:group)(E,E’:Glist)(t:starGroupType) (e:env)~g=g’ -> (add_E g E e E’) -> (add_E g E (consEgroup g’ t e) E’) | add_E_name : (n:name)(W:msgType)(g:group)(E,E’:Glist)(e:env) (add_E g E e E’) -> (add_E g E (consEname n W e) E’).
C
Type inference predicates
Inductive msg_inf: cap -> msgType -> env -> Prop := msg_inf_name : (x:name)(g:group) (msg_inf (name2cap x) (amb_type g) (consEname x (amb_type g) emptyE)) | msg_inf_to : (x:name)(g1,g2:group)(t:comType) (msg_inf (to (name2cap x)) (cap_type g1 g2) (consEname x (amb_type g1) (consEgroup g2 (gr_star starEmptyG emptyG (consG g1 emptyG) t) emptyE)) ) | msg_inf_in : (x:name)(g1,g2:group)(t:comType) (msg_inf (In (name2cap x)) (cap_type g2 g2) (consEname x (amb_type g1) (consEgroup g2 (gr_star (starConsG (simple g1) starEmptyG) (consG g1 emptyG) emptyG t) emptyE)) ) | msg_inf_out : (x:name)(g1,g2:group)(t:comType) (msg_inf (Out (name2cap x)) (cap_type g2 g2) (consEname x (amb_type g1) (consEgroup g1 (gr_star starEmptyG emptyG emptyG t) (consEgroup g2 (gr_star (starConsG (star g1) starEmptyG) (consG g1 emptyG) emptyG t) emptyE))) ) | msg_inf_path : (M,N:cap)(g1,g2,g3:group)(W,W’:msgType)(e1,e2,e3:env) (msg_inf M W e1) -> (msg_inf N W’ e2) -> W=(cap_type g1 g2) -> W’=(cap_type g3 g1) -> (unify_env e1 e2) -> (union_env e1 e2 e3) -> 19
(msg_inf (path M N) (cap_type g3 g2) e3). Inductive proc_inf: raw_proc -> proc -> group -> env -> Prop := proc_inf_null : (g:group)(t:comType) (proc_inf raw_nil nil g (consEgroup g (gr_star starEmptyG emptyG emptyG t) emptyE)) | proc_inf_prefix : (M:cap)(W:msgType)(e1,e2,e3:env) (R:raw_proc)(P:proc)(g1,g2,g3:group) (msg_inf M W e1) -> (proc_inf R P g1 e2) -> W=(cap_type g1 g2) -> (unify_env e1 e2) -> (union_env e1 e2 e3) -> (proc_inf (raw_action M R) (action M P) g2 e3) | proc_inf_input : (W:msgType)(S:starGlist)(C,E:Glist)(t:comType) (R:name->raw_proc)(P:name->proc)(e:env)(g:group) (group_in_env g (gr_star S C E t) e) -> t=(msg W) -> ((x:name)(proc_inf (R x) (P x) g (consEname x (amb_type g) e))) -> (proc_inf (raw_input R) (input P W) g e) | proc_inf_output : (R:raw_proc)(P:proc)(M:cap)(W:msgType) (g:group)(e1,e2,e3:env) (proc_inf R P g e1) -> (msg_inf M W e2) -> (unify_env e1 (consEgroup g (gr_star starEmptyG emptyG emptyG (msg W)) e2)) -> (union_env e1 (consEgroup g (gr_star starEmptyG emptyG emptyG (msg W)) e2) e3) -> (proc_inf (raw_output M R) (output M P) g e3) | proc_inf_par : (R,R’:raw_proc)(P,P’:proc)(g1,g2:group) (e1,e2,e3:env)(proc_inf R P g1 e1) -> (proc_inf R’ P’ g2 e2) -> g1=g2 -> (unify_env e1 e2) -> (union_env e1 e2 e3) -> (proc_inf (raw_par R R’) (par P P’) g2 e3) | proc_inf_amb : (x:name)(W:msgType)(R:raw_proc)(P:proc) (g,g’:group)(e,e’:env)(t:comType) (msg_inf (name2cap x) W (consEname x W emptyE)) -> (proc_inf R P g e) -> W=(amb_type g) -> (unify_env e (consEname x W (consEgroup g (gr_star (starConsG (simple g’) starEmptyG) emptyG emptyG t) emptyE))) -> (union_env e (consEname x W (consEgroup g (gr_star (starConsG (simple g’) starEmptyG) emptyG emptyG t) emptyE)) e’) -> 20
| proc_inf_res
| proc_inf_repl
(proc_inf (raw_ambient (name2cap x) R) (ambient (name2cap x) P) g’ e’) : (R:name->raw_proc)(P:name->proc)(e:env) (g,g’:group) ((x:name)(proc_inf (R x) (P x) g (consEname x (amb_type g’) e))) -> (proc_inf (raw_nu R) (nu g’ P) g e) : (R:raw_proc)(P:proc)(g:group)(e:env) (proc_inf R P g e) -> (proc_inf (raw_bang R) (bang P) g e).
References [1] L. Cardelli and A. D. Gordon. Mobile ambients. In Foundations of Software Science and Computation Structures: First International Conference, FOSSACS ’98, pages 140–155. Springer-Verlag, Berlin Germany, 1998. [2] A. Church. A formulation of the simple theory of types. Journal of Symbolic Logic, 5:56–68, 1940. [3] M. Coppo, M. Dezani-Ciancaglini, E. Giovannetti, and I. Salvo. M3: Mobility types for mobile processes in mobile ambients. In Proceedings of CATS’2003, volume 78 of ENTCS. Springer-Verlag, 2003. [4] T. Coquand and G. Huet. The calculus of constructions. Information and Control, 76:95–120, 1988. [5] N. G. de Bruijn. The mathematical language AUTOMATH, its usage and some of its extensions. In Symposium on automatic demonstration, volume 125 of Lecture Notes in Mathematics, pages 29–61, Versailles 1968, 1970. Springer. [6] J. Despeyroux, A. Felty, and A. Hirschowitz. Higher-order syntax in Coq. In Proceedings of TLCA’95, volume 905 of Lecture Notes in Computer Science, Edinburgh, 1995. Springer-Verlag. Also appears as INRIA research report RR-2556, April 1995. [7] M. J. Gabbay and A. M. Pitts. A new approach to abstract syntax with variable binding. Formal Aspects of Computing, ?:?–?, 2001. Special issue in honour of Rod Burstall. To appear. [8] R. Harper, F. Honsell, and G. Plotkin. A framework for defining logics. J. ACM, 40(1):143–184, January 1993. [9] F. Honsell, M. Miculan, and I. Scagnetto. An axiomatic approach to metareasoning on systems in higher-order abstract syntax. In Proceedings of ICALP’01, volume 2076 of Lecture Notes in Computer Science, pages 963–978. Springer-Verlag, 2001. Also available at http://www.dimi.uniud.it/~miculan/Papers/. 21
[10] F. Honsell, M. Miculan, and I. Scagnetto. π-calculus in (co)inductive type theory. Theoretical computer science, 239–285(2):239–285, 2001. First appeared as a talk at TYPES’98 annual workshop. [11] W. A. Howard. The formulæ-as-types notion of construction. Lambda Calculus and Formalism, 1980. In J. R. Hindley and J. P. Seldin, editors, To H.B. Curry: Essays on Combinatory Logic. Academic Press. [12] INRIA. The Coq Proof Assistant Reference Manual - Version 7.4. INRIA, Rocquencourt, France, February 2003. Available at ftp://ftp.inria.fr/INRIA/coq/V7.4/doc. [13] P. Martin-L¨of. On the meaning of the logical constants and the justifications of the logic laws. Technical Report 2, Dipartimento di Matematica, Universit‘a di Siena, 1985. [14] F. Pfenning and C. Sch¨ urmann. System description: Twelf — A metalogical framework for deductive systems. In H. Ganzinger, editor, Proceedings of the 16th international conference on automated deduction (CADE16), volume 1632 of LNAI, Trento, Italy, 1999. Springer-Verlag.
22