• Nenhum resultado encontrado

3.5 Translating Logical Systems in Dedukti

3.5.1 First-Order Logic in Dedukti

3.5. TRANSLATING LOGICAL SYSTEMS IN DEDUKTI

type : Type.

term : type -> Type.

For each n-ary type constructor F in the signature, we declare a symbol F of type

ntimes

  

type ->. . .-> type. The translation function for types is dened by

JαK := α

JF(τ1, . . . , τn)K := F Jτ1K . . . JτnK

For each function symbolf of type schemeΠα1. . . .Παk.(τ1, . . . , τn)→τ0, we declare a symbolf of typeα1:type->. . .->αk:type->term1K->. . . ->termnK->term0K.

The translation function for terms is dened by

JxK := x

Jf(τ1, . . . , τk;t1, . . . , tn)K := f Jτ1K . . . JτkK Jt1K . . . JtnK

In order to translate formulae, we declare a new Dedukti typepropand all the connec- tives:

prop : Type. true : prop . false : prop .

eq : a : type -> term a -> term a -> prop . and : prop -> prop -> prop .

or : prop -> prop -> prop . imp : prop -> prop -> prop .

all : a : type -> ( term a -> prop ) -> prop . ex : a : type -> ( term a -> prop ) -> prop . all_type : ( type -> prop ) -> prop .

ex_type : ( type -> prop ) -> prop .

Negation and equivalence are seen as derived connectives:

def not (A : prop ) : prop := imp A false .

def eqv (A : prop ) (B : prop ) : prop := and ( imp A B) ( imp B A).

For each predicate symbol P of type scheme Πα1. . . .Παk. (τ1, . . . , τn), we declare a symbol P of typeα1: type ->. . .->αk:type ->term1K->. . . ->termnK->prop.

The translation function for formulae is dened by

3.5. TRANSLATING LOGICAL SYSTEMS IN DEDUKTI

JP(τ1, . . . , τk;t1, . . . , tn)K := P Jτ1K . . . JτkK Jt1K . . . JtnK

J⊤K := true

J⊥K := false

Jt1=τ t2K := eq JτK Jt1K Jt2K

J¬Kφ := not JφK

1∧φ2K := and Jφ1K Jφ2K Jφ1∨φ2K := or Jφ1K Jφ2K Jφ1⇒φ2K := imp Jφ1K Jφ2K Jφ1⇔φ2K := eqv Jφ1K Jφ2K

J∀x:τ. φK := all JτK(x : termJτK=>JφK) J∃x:τ. φK := ex JτK(x : termJτK=> JφK) J∀typeα. φK := all_type (α : type=>JφK) J∃typeα. φK := ex_type (α : type =>JφK)

Finally, we declare a type proof parameterized by a proposition. The type proof A is intended to represent the type of the proofs of the formula A. For each deduction rule in natural deduction, we declare a corresponding symbol in Figure 3.4

Until now, we have faithfully represented the syntax of natural deduction in Dedukti using the judgment-as-type paradigm (see Section 2.5.5). Actually, we have not yet used rewriting so this encoding uses only the pure λΠ-calculus and the only dierence com- pared to an encoding in an implementation of ELF such as Twelf [147] is purely syntactic.

We emphasize this by calling this translation a deep translation as opposed to shallow translations obtained by the proposition-as-type paradigm.

Through the Curry-Howard isomorphism, proofs can be interpreted as programs and the reduction of these programs correspond on the logical side to the process of cut elimination.

Cut elimination can be added to our Dedukti signature by adding rewrite rules that simplify elimination rules applied to introduction rules:

[p] and_elim_1 _ _ ( and_intro _ _ p _) --> p.

[q] and_elim_2 _ _ ( and_intro _ _ _ q) --> q.

[p,r] or_elim _ _ _ p _ ( or_intro_1 _ _ r) --> p r [q,s] or_elim _ _ _ _ q ( or_intro_2 _ _ s) --> q s.

[p,q] imp_elim _ _ ( imp_intro _ _ p) q --> p q.

[p,x] all_elim _ _ ( all_intro _ _ p) x --> p x.

[p,x,q] ex_elim _ _ _ p ( ex_intro _ _ x q) --> p x q.

[p,a] all_type_elim _ ( all_type_intro _ p) a --> p a.

3.5. TRANSLATING LOGICAL SYSTEMS IN DEDUKTI

proof : prop -> Type.

def true_intro : proof true .

def false_elim : A : prop -> proof false -> proof A.

def and_intro : A : prop -> B : prop ->

proof A -> proof B -> proof ( and A B).

def and_elim_1 : A : prop -> B : prop -> proof ( and A B) -> proof A.

def and_elim_2 : A : prop -> B : prop -> proof ( and A B) -> proof B.

def or_intro_1 : A : prop -> B : prop -> proof A -> proof (or A B).

def or_intro_2 : A : prop -> B : prop -> proof B -> proof (or A B).

def or_elim : A : prop -> B : prop -> C : prop ->

( proof A -> proof C) -> ( proof B -> proof C) ->

proof (or A B) -> proof C.

def imp_intro : A : prop -> B : prop ->

( proof A -> proof B) -> proof ( imp A B).

def imp_elim : A : prop -> B : prop ->

proof ( imp A B) -> proof A -> proof B.

def all_intro : a : type -> A : ( term a -> prop ) ->

(x : term a -> proof (A x)) -> proof ( all a A).

def all_elim : a : type -> A : ( term a -> prop ) ->

proof ( all a A) -> x : term a -> proof (A x).

def ex_intro : a : type -> A : ( term a -> prop ) -> x : term a ->

proof (A x) -> proof (ex a A).

def ex_elim : a : type -> A : ( term a -> prop ) -> B : prop ->

(x : term a -> proof (A x) -> proof B) ->

proof (ex a A) -> proof B.

def all_type_intro : A : ( type -> prop ) ->

(a : type -> proof (A a)) -> proof ( all_type A).

def all_type_elim : A : ( type -> prop ) ->

proof ( all_type A) -> a : type -> proof (A a).

def ex_type_intro : A : ( type -> prop ) -> a : type ->

proof (A a) -> proof ( ex_type A).

def ex_type_elim : A : ( type -> prop ) -> B : prop ->

(a : type -> proof (A a) -> proof B) ->

proof ( ex_type A) -> proof B.

def eq_intro : a : type -> x : term a -> proof (eq a x x).

def eq_elim : a : type ->

x : term a -> y : term a -> A : ( term a -> prop ) ->

proof (A x) -> proof (eq a x y) -> proof (A y).

Figure 3.4: Dedukti signature for polymorphic natural deduction

3.5. TRANSLATING LOGICAL SYSTEMS IN DEDUKTI

[p,a,q] ex_type_elim _ _ p ( ex_type_intro _ a q) --> p a q.

[p] eq_elim _ _ _ _ p ( eq_intro _ _) --> p.

In the case of implication, we can read the introduction and elimination rules as axiom- atizing a logical equivalence between the types proof (imp A B)and proof A -> proof B and the rewrite rule [p,q]imp_elim _ _ (imp_intro _ _ p) q --> p q. as stating that the functions imp_elim and imp_intro are inverses of each other. We can further identify the types proof (imp A B) and proof A -> proof B thanks to the rewrite rule [A,B]proof (imp A B) --> proof A -> proof B. and quite generally, we can encode all the connectives using impredicative encodings:

def proof : prop -> Type.

[] proof true --> A : prop -> proof A -> proof A [] proof false --> A : prop -> proof A

[A,B] proof ( imp A B) --> proof A -> proof B [A,B] proof ( and A B) -->

C : prop -> ( proof A -> proof B -> proof C) -> proof C [A,B] proof (or A B) -->

C : prop -> ( proof A -> proof C) -> ( proof B -> proof C) -> proof C [a,A] proof ( all a A) --> x : term a -> proof (A x)

[a,A] proof (ex a A) -->

B : prop -> (x : term a -> proof (A x) -> proof B) -> proof B [A] proof ( all_type A) --> a : type -> proof (A a)

[A] proof ( ex_type A) -->

B : prop -> (a : type -> proof (A a) -> proof B) -> proof B [a,x,y] proof (eq a x y) -->

A : ( term a -> prop ) -> proof (A x) -> proof (A y).

Using these rewrite rules, all the deduction rules for natural deduction can be derived (see Figure 3.5).

The cut-elimination rewrite rules are now superuous, we can remove them and ask Dedukti to check that cut-reduction still holds (see Figure 3.6) using the #CONV command for checking that two terms are convertibles.

This translation of natural deduction is more shallow in the sense that it reuses more features available in Dedukti: implication is mapped to Dedukti arrow, universal quanti- cation is mapped to Dedukti dependent product etc. . .

Proof terms in this shallow translation are lighter than the ones of the deep translation because less type annotations are needed. For example, the proof of(P(t)∧ ∀x:τ. P(x)⇒

3.5. TRANSLATING LOGICAL SYSTEMS IN DEDUKTI

def true_intro : proof true := A => p => p.

def false_elim (A : prop ) (p : proof false ) : proof A := p A.

def and_intro (A : prop ) (B : prop ) (p : proof A) (q : proof B) : proof ( and A B)

:= C : prop => r : ( proof A -> proof B -> proof C) => r p q.

def and_elim_1 (A : prop ) (B : prop ) (p : proof ( and A B)) : proof A := p A (x => y => x).

def and_elim_2 (A : prop ) (B : prop ) (p : proof ( and A B)) : proof B := p B (x => y => y).

def or_intro_1 (A : prop ) (B : prop ) (p : proof A) : proof (or A B)

:= C : prop =>

q : ( proof A -> proof C) => r : ( proof B -> proof C) => q p.

def or_intro_2 (A : prop ) (B : prop ) (p : proof B) : proof (or A B)

:= C : prop =>

q : ( proof A -> proof C) => r : ( proof B -> proof C) => r p.

def or_elim (A : prop ) (B : prop ) (C : prop )

(p : proof A -> proof C) (q : proof B -> proof C) (r : proof (or A B)) : proof C

:= r C p q.

def imp_intro (A : prop ) (B : prop ) (p : ( proof A -> proof B)) : proof ( imp A B) := p.

def imp_elim (A : prop ) (B : prop ) (p : proof ( imp A B)) : proof A -> proof B := p.

def all_intro (a : type ) (A : ( term a -> prop ))

(p : x : term a -> proof (A x)) : proof ( all a A)

:= p.

def all_elim (a : type ) (A : ( term a -> prop )) (p : proof ( all a A)) : x : term a -> proof (A x) := p.

def ex_intro (a : type ) (A : ( term a -> prop ))

(x : term a) (p : proof (A x)) : proof (ex a A)

:= B : prop => q : (x : term a -> proof (A x) -> proof B) => q x p.

def ex_elim (a : type ) (A : ( term a -> prop )) (B : prop ) (p : x : term a -> proof (A x) -> proof B) (q : proof (ex a A)) : proof B

:= q B p.

def all_type_intro (A : ( type -> prop )) (p : a : type -> proof (A a)) : proof ( all_type A) := p.

def all_type_elim (A : ( type -> prop )) (p : proof ( all_type A))

: a : type -> proof (A a) := p.

def ex_type_intro (A : ( type -> prop )) (a : type ) (p : proof (A a)) : proof ( ex_type A)

:= B : prop => q : (a : type -> proof (A a) -> proof B) => q a p.

def ex_type_elim (A : ( type -> prop )) (B : prop )

(p : a : type -> proof (A a) -> proof B)

(q : proof ( ex_type A)) : proof B := q B p.

def eq_intro (a : type ) (x : term a) : proof (eq a x x) := A : ( term a -> prop ) => p : proof (A x) => p.

def eq_elim (a : type ) (x : term a) (y : term a) (A : ( term a -> prop ))

(p : proof (A x)) (q : proof (eq a x y)) : proof (A y) := q A p.

Figure 3.5: Shallow embedding of Natural Deduction in Dedukti

3.5. TRANSLATING LOGICAL SYSTEMS IN DEDUKTI

# CONV (A : prop => B : prop => p : proof A => q : proof B =>

and_elim_1 A B ( and_intro A B p q)),

(A : prop => B : prop => p : proof A => q : proof B => p).

# CONV (A : prop => B : prop => p : proof A => q : proof B =>

and_elim_2 A B ( and_intro A B p q)),

(A : prop => B : prop => p : proof A => q : proof B => q).

# CONV (A : prop => B : prop => C : prop => p : proof A =>

q : ( proof A -> proof C) => r : ( proof B -> proof C) =>

or_elim A B C q r ( or_intro_1 A B p)),

(A : prop => B : prop => C : prop => p : proof A =>

q : ( proof A -> proof C) => r : ( proof B -> proof C) => q p).

# CONV (A : prop => B : prop => C : prop => p : proof B =>

q : ( proof A -> proof C) => r : ( proof B -> proof C) =>

or_elim A B C q r ( or_intro_2 A B p)),

(A : prop => B : prop => C : prop => p : proof B =>

q : ( proof A -> proof C) => r : ( proof B -> proof C) => r p).

# CONV (A : prop => B : prop => p : ( proof A -> proof B) =>

q : proof A => imp_elim A B ( imp_intro A B p) q),

(A : prop => B : prop => p : ( proof A -> proof B) =>

q : proof A => p q).

# CONV (a : type => A : ( term a -> prop ) =>

p : (x : term a -> proof (A x)) => x : term a =>

all_elim a A ( all_intro a A p) x),

(a : type => A : ( term a -> prop ) =>

p : (x : term a -> proof (A x)) => x : term a => p x).

# CONV (a : type => A : ( term a -> prop ) => B : prop =>

p : (x : term a -> proof (A x) -> proof B) =>

x : term a => q : proof (A x) =>

ex_elim a A B p ( ex_intro a A x q)),

(a : type => A : ( term a -> prop ) => B : prop =>

p : (x : term a -> proof (A x) -> proof B) =>

x : term a => q : proof (A x) => p x q).

# CONV (A : ( type -> prop ) => p : (a : type -> proof (A a)) =>

a : type => all_type_elim A ( all_type_intro A p) a),

(A : ( type -> prop ) => p : (a : type -> proof (A a)) =>

a : type => p a).

# CONV (A : ( type -> prop ) => B : prop =>

p : (a : type -> proof (A a) -> proof B) =>

a : type => q : proof (A a) =>

ex_type_elim A B p ( ex_type_intro A a q)), (A : ( type -> prop ) => B : prop =>

p : (a : type -> proof (A a) -> proof B) =>

a : type => q : proof (A a) => p a q).

# CONV (a : type => A : ( term a -> prop ) => x : term a =>

p : proof (A x) => eq_elim a x x A p ( eq_intro a x)),

(a : type => A : ( term a -> prop ) => x : term a =>

p : proof (A x) => p).

Figure 3.6: Checking cut elimination in the shallow embedding of natural deduction in Dedukti

3.5. TRANSLATING LOGICAL SYSTEMS IN DEDUKTI

Q(x))⇒Q(t) that we gave in 1.1.2 is written as follows in the deep encoding:

a : type . t : term a.

P : term a -> prop . Q : term a -> prop .

def example_0 : proof ( imp ( and (P t) ( all a (x => imp (P x) (Q x )))) (Q t)) :=imp_intro

( and (P t) ( all a (x => imp (P x) (Q x )))) (Q t)

(p =>

imp_elim (P t) (Q t)

( all_elim a (x => imp (P x) (Q x))

( and_elim_2 (P t) ( all a (x => imp (P x) (Q x ))) p) ( and_elim_1 (P t) ( all a (xt) => imp (P x) (Q x ))) p )).

In the shallow encoding, this term reduces to the following much shorter proof term:

a : type . t : term a.

P : term a -> prop . Q : term a -> prop .

def example_0 : proof ( imp ( and (P t) ( all a (x => imp (P x) (Q x )))) (Q t)) := p =>

p ( all a (x => imp (P x) (Q x ))) (x => y => y)

t(p (P t) (x => y => x )).