10
10
11
11
> % access public export
12
12
> % default total
13
+ > % hide Smallstep . Tm
14
+ > % hide Types . progress
15
+
16
+
13
17
14
18
In this chapter, we develop the fundamental theory of the Simply
15
19
Typed Lambda Calculus -- in particular, the type safety
@@ -36,7 +40,7 @@ lambda-abstractions.
36
40
> canonical_forms_fun : {t : Tm} -> {ty1, ty2: Ty} ->
37
41
> empty |- t :: (ty1 :=> ty2) . ->
38
42
> Value t ->
39
- > (x : String ** u : Tm ** t = Tabs x ty1 u)
43
+ > (x : Id ** u : Tm ** t = Tabs x ty1 u)
40
44
41
45
> canonical_forms_fun {t = Ttrue } T_True _ impossible
42
46
> canonical_forms_fun {t = Tfalse } T_False _ impossible
@@ -103,194 +107,186 @@ _Proof_: By induction on the derivation of `|- t \in T`
103
107
> progress {t= Tfalse } _ = Left V_false
104
108
> progress {t= Tabs x ty t1} _ = Left V_abs
105
109
> progress {t= tl # tr} (T_App hl hr) =
106
- > let indHypl = StlcProp . progress {t= tl} hl
110
+ > let indHypl = progress {t= tl} hl
107
111
> in case indHypl of
108
- > Right (t' ** hyp ) => Right (t' # tr ** ST_App1 hyp )
112
+ > Right (t' ** step ) => Right (t' # tr ** ST_App1 step )
109
113
> Left vl =>
110
- > let indHypR = StlcProp . progress {t= tr} hr
114
+ > let indHypR = progress {t= tr} hr
111
115
> in case indHypR of
112
- > Right (t' ** hyp ) => Right (tl # t' ** ST_App2 vl hyp )
116
+ > Right (t' ** step ) => Right (tl # t' ** ST_App2 vl step )
113
117
> Left vr =>
114
118
> case vl of
115
119
> V_abs {x} {t= tl} => Right (subst x tr tl ** ST_AppAbs vr)
116
- > progress {t= Tif tb tp tn} {ty} _ = ? hole
117
-
118
-
119
- (** **** Exercise : 3 stars, advanced (progress_from_term_ind) *)
120
- (** Show that progress can also be proved by induction on terms
121
- instead of induction on typing derivations. * )
122
-
123
- Theorem progress' : forall t T,
124
- empty |- t \ in T ->
125
- value t \/ exists t', t ==> t'.
126
- Proof .
127
- intros t.
128
- induction t; intros T Ht ; auto.
129
- (* FILL IN HERE * ) Admitted .
130
- (** `` * )
131
-
132
- (* ################################################################# * )
133
- (** * Preservation * )
134
-
135
- (** The other half of the type soundness property is the
136
- preservation of types during reduction. For this part, we'll need
137
- to develop some technical machinery for reasoning about variables
138
- and substitution. Working from top to bottom (from the high- level
139
- property we are actually interested in to the lowest- level
140
- technical lemmas that are needed by various cases of the more
141
- interesting proofs), the story goes like this :
142
-
143
- - The _preservation theorem_ is proved by induction on a typing
144
- derivation, pretty much as we did in the `Types` chapter.
145
- The one case that is significantly different is the one for
146
- the `ST_AppAbs` rule, whose definition uses the substitution
147
- operation. To see that this step preserves typing, we need to
148
- know that the substitution itself does. So we prove a...
149
-
150
- - _substitution lemma_, stating that substituting a (closed)
151
- term `s` for a variable `x` in a term `t` preserves the type
152
- of `t` . The proof goes by induction on the form of `t` and
153
- requires looking at all the different cases in the definition
154
- of substitition. This time, the tricky cases are the ones for
155
- variables and for function abstractions. In both, we discover
156
- that we need to take a term `s` that has been shown to be
157
- well- typed in some context `Gamma` and consider the same term
158
- `s` in a slightly different context `Gamma'` . For this we
159
- prove a...
160
-
161
- - _context invariance_ lemma, showing that typing is preserved
162
- under " inessential changes" to the context `Gamma` -- in
163
- particular, changes that do not affect any of the free
164
- variables of the term. And finally, for this, we need a
165
- careful definition of ...
166
-
167
- - the _free variables_ in a term -- i.e., variables that are
168
- used in the term and where these uses are _not_ in the scope of
169
- an enclosing function abstraction binding a variable of the
170
- same name.
171
-
172
- To make Coq happy, we need to formalize the story in the opposite
173
- order... * )
174
-
175
- (* ================================================================= * )
176
- (** ** Free Occurrences * )
177
-
178
- (** A variable `x` _appears free in_ a term _t_ if `t` contains some
179
- occurrence of `x` that is not under an abstraction labeled `x` .
180
- For example :
181
- - `y` appears free, but `x` does not , in `\ x : T-> U. x y`
182
- - both `x` and `y` appear free in `(\ x : T-> U. x y) x`
183
- - no variables appear free in `\ x : T-> U. \y:T. x y`
184
-
185
- Formally : *)
186
-
187
- Inductive appears_free_in : string -> tm -> Prop :=
188
- | afi_var : forall x,
189
- appears_free_in x (tvar x)
190
- | afi_app1 : forall x t1 t2,
191
- appears_free_in x t1 ->
192
- appears_free_in x (tapp t1 t2)
193
- | afi_app2 : forall x t1 t2,
194
- appears_free_in x t2 ->
195
- appears_free_in x (tapp t1 t2)
196
- | afi_abs : forall x y T11 t12,
197
- y <> x ->
198
- appears_free_in x t12 ->
199
- appears_free_in x (tabs y T11 t12)
200
- | afi_if1 : forall x t1 t2 t3,
201
- appears_free_in x t1 ->
202
- appears_free_in x (tif t1 t2 t3)
203
- | afi_if2 : forall x t1 t2 t3,
204
- appears_free_in x t2 ->
205
- appears_free_in x (tif t1 t2 t3)
206
- | afi_if3 : forall x t1 t2 t3,
207
- appears_free_in x t3 ->
208
- appears_free_in x (tif t1 t2 t3).
209
-
210
- Hint Constructors appears_free_in.
211
-
212
- (** The _free variables_ of a term are just the variables that appear
213
- free in it. A term with no free variables is said to be
214
- _closed_. * )
215
-
216
- Definition closed (t : tm) :=
217
- forall x, ~ appears_free_in x t.
218
-
219
- (** An _open_ term is one that may contain free variables. (I . e. , every
220
- term is an open term; the closed terms are a subset of the open ones.
221
- " Open" really means " possibly containing free variables." ) * )
222
-
223
- (** **** Exercise : 1 star (afi) *)
224
- (** In the space below, write out the rules of the `appears_free_in`
225
- relation in informal inference- rule notation. (Use whatever
226
- notational conventions you like -- the point of the exercise is
227
- just for you to think a bit about the meaning of each rule. )
228
- Although this is a rather low- level, technical definition,
229
- understanding it is crucial to understanding substitution and its
230
- properties, which are really the crux of the lambda- calculus. * )
120
+ > progress {t= Tif tb tp tn} (T_If hb hp hr) =
121
+ > let indHyp = progress {t= tb} hb
122
+ > in case indHyp of
123
+ > Left vl =>
124
+ > case vl of
125
+ > V_true => Right (tp ** ST_IfTrue )
126
+ > V_false => Right (tn ** ST_IfFalse )
127
+ > Right (t' ** step) => Right (Tif t' tp tn ** ST_If step)
128
+
129
+ == Preservation
130
+
131
+ The other half of the type soundness property is the
132
+ preservation of types during reduction. For this part, we'll need
133
+ to develop some technical machinery for reasoning about variables
134
+ and substitution. Working from top to bottom (from the high- level
135
+ property we are actually interested in to the lowest- level
136
+ technical lemmas that are needed by various cases of the more
137
+ interesting proofs), the story goes like this :
138
+
139
+ - The _preservation theorem_ is proved by induction on a typing
140
+ derivation, pretty much as we did in the `Types` chapter.
141
+ The one case that is significantly different is the one for
142
+ the `ST_AppAbs` rule, whose definition uses the substitution
143
+ operation. To see that this step preserves typing, we need to
144
+ know that the substitution itself does. So we prove a...
145
+
146
+ - _substitution lemma_, stating that substituting a (closed)
147
+ term `s` for a variable `x` in a term `t` preserves the type
148
+ of `t` . The proof goes by induction on the form of `t` and
149
+ requires looking at all the different cases in the definition
150
+ of substitition. This time, the tricky cases are the ones for
151
+ variables and for function abstractions. In both, we discover
152
+ that we need to take a term `s` that has been shown to be
153
+ well- typed in some context `Gamma` and consider the same term
154
+ `s` in a slightly different context `Gamma'` . For this we
155
+ prove a...
156
+
157
+ - _context invariance_ lemma, showing that typing is preserved
158
+ under " inessential changes" to the context `Gamma` -- in
159
+ particular, changes that do not affect any of the free
160
+ variables of the term. And finally, for this, we need a
161
+ careful definition of ...
162
+
163
+ - the _free variables_ in a term -- i.e., variables that are
164
+ used in the term and where these uses are _not_ in the scope of
165
+ an enclosing function abstraction binding a variable of the
166
+ same name.
167
+
168
+ To make Idris happy, we need to formalize the story in the opposite
169
+ order...
170
+
171
+ === Free Occurrences
172
+
173
+ A variable `x` _appears free in_ a term _t_ if `t` contains some
174
+ occurrence of `x` that is not under an abstraction labeled `x` .
175
+ For example :
176
+ - `y` appears free, but `x` does not , in `\ x : T-> U. x y`
177
+ - both `x` and `y` appear free in `(\ x : T-> U. x y) x`
178
+ - no variables appear free in `\ x : T-> U. \y:T. x y`
179
+
180
+ Formally :
181
+
182
+ > data Appears_free_in : Id -> Tm -> Type where
183
+ > Afi_var : {x : Id} ->
184
+ > Appears_free_in x (Tvar x)
185
+ > Afi_app1 : {x : Id} -> {t1, t2: Tm} ->
186
+ > Appears_free_in x t1 ->
187
+ > Appears_free_in x (t1 # t2)
188
+ > Afi_app2 : {x : Id} -> {t1, t2: Tm} ->
189
+ > Appears_free_in x t2 ->
190
+ > Appears_free_in x (t1 # t2)
191
+ > Afi_abs : {x,y : Id} -> {t12 : Tm} -> {T11 : Ty} ->
192
+ > Not (y = x) ->
193
+ > Appears_free_in x t12 ->
194
+ > Appears_free_in x (Tabs y T11 t12)
195
+ > Afi_if1 : {x : Id} -> {t1, t2, t3: Tm} ->
196
+ > Appears_free_in x t1 ->
197
+ > Appears_free_in x (Tif t1 t2 t3)
198
+ > Afi_if2 : {x : Id} -> {t1, t2, t3: Tm} ->
199
+ > Appears_free_in x t2 ->
200
+ > Appears_free_in x (Tif t1 t2 t3)
201
+ > Afi_if3 : {x : Id} -> {t1, t2, t3: Tm} ->
202
+ > Appears_free_in x t3 ->
203
+ > Appears_free_in x (Tif t1 t2 t3)
204
+
205
+
206
+ The _free variables_ of a term are just the variables that appear
207
+ free in it. A term with no free variables is said to be _closed_.
208
+
209
+ > closed : Tm -> Type
210
+ > closed t = Not (x : Id ** Appears_free_in x t)
211
+
212
+ An _open_ term is one that may contain free variables. (I . e. , every
213
+ term is an open term; the closed terms are a subset of the open ones.
214
+ " Open" really means " possibly containing free variables." )
215
+
216
+ ==== Exercise : 1 star (afi)
217
+
218
+ In the space below, write out the rules of the `appears_free_in`
219
+ relation in informal inference- rule notation. (Use whatever
220
+ notational conventions you like -- the point of the exercise is
221
+ just for you to think a bit about the meaning of each rule. )
222
+ Although this is a rather low- level, technical definition,
223
+ understanding it is crucial to understanding substitution and its
224
+ properties, which are really the crux of the lambda- calculus.
231
225
232
226
(* FILL IN HERE * )
233
- (** `` * )
234
-
235
- (* ================================================================= * )
236
- (** ** Substitution * )
237
-
238
- (** To prove that substitution preserves typing, we first need a
239
- technical lemma connecting free variables and typing contexts : If
240
- a variable `x` appears free in a term `t` , and if we know `t` is
241
- well typed in context `Gamma` , then it must be the case that
242
- `Gamma` assigns a type to `x` . * )
243
-
244
- Lemma free_in_context : forall x t T Gamma,
245
- appears_free_in x t ->
246
- Gamma |- t \ in T ->
247
- exists T' , Gamma x = Some T' .
248
-
249
- (** _Proof_ : We show, by induction on the proof that `x` appears free
250
- in `t` , that, for all contexts `Gamma` , if `t` is well typed
251
- under `Gamma` , then `Gamma` assigns some type to `x` .
252
-
253
- - If the last rule used is `afi_var` , then `t = x`, and from the
254
- assumption that `t` is well typed under `Gamma` we have
255
- immediately that `Gamma` assigns a type to `x` .
256
-
257
- - If the last rule used is `afi_app1` , then `t = t1 t2` and `x`
258
- appears free in `t1` . Since `t` is well typed under `Gamma` ,
259
- we can see from the typing rules that `t1` must also be, and
260
- the IH then tells us that `Gamma` assigns `x` a type.
261
-
262
- - Almost all the other cases are similar : `x` appears free in a
263
- subterm of `t` , and since `t` is well typed under `Gamma` , we
264
- know the subterm of `t` in which `x` appears is well typed
265
- under `Gamma` as well, and the IH gives us exactly the
266
- conclusion we want.
267
-
268
- - The only remaining case is `afi_abs` . In this case `t =
269
- \ y : T11.t12` and `x` appears free in `t12`, and we also know
270
- that `x` is different from `y` . The difference from the
271
- previous cases is that, whereas `t` is well typed under
272
- `Gamma` , its body `t12` is well typed under `(Gamma & {{y-- >T11}}`,
273
- so the IH allows us to conclude that `x` is assigned some type
274
- by the extended context `(Gamma & {{y-- >T11}}`. To conclude that
275
- `Gamma` assigns a type to `x` , we appeal to lemma
276
- `update_neq` , noting that `x` and `y` are different
277
- variables. * )
278
-
279
- Proof .
280
- intros x t T Gamma H H0 . generalize dependent Gamma .
281
- generalize dependent T .
282
- induction H ;
283
- intros; try solve `inversion H0 ; eauto`.
284
- - (* afi_abs * )
285
- inversion H1 ; subst.
286
- apply IHappears_free_in in H7 .
287
- rewrite update_neq in H7 ; assumption.
288
- Qed .
289
227
290
- (** Next , we'll need the fact that any term `t` that is well typed in
291
- the empty context is closed (it has no free variables). * )
228
+ === Substitution
229
+
230
+ To prove that substitution preserves typing, we first need a
231
+ technical lemma connecting free variables and typing contexts : If
232
+ a variable `x` appears free in a term `t` , and if we know `t` is
233
+ well typed in context `Gamma` , then it must be the case that
234
+ `Gamma` assigns a type to `x` . * )
235
+
236
+ -- > free_in_context : {x : Id} -> {t: Tm} -> {ty: Ty} -> {gamma: Context} ->
237
+ -- > Appears_free_in x t ->
238
+ -- > gamma |- t :: T . ->
239
+ -- > (t' : Ty ** gamma x = Just t')
240
+
241
+ _Proof_ : We show, by induction on the proof that `x` appears free
242
+ in `t` , that, for all contexts `Gamma` , if `t` is well typed
243
+ under `Gamma` , then `Gamma` assigns some type to `x` .
244
+
245
+ - If the last rule used is `afi_var` , then `t = x`, and from the
246
+ assumption that `t` is well typed under `Gamma` we have
247
+ immediately that `Gamma` assigns a type to `x` .
248
+
249
+ - If the last rule used is `afi_app1` , then `t = t1 t2` and `x`
250
+ appears free in `t1` . Since `t` is well typed under `Gamma` ,
251
+ we can see from the typing rules that `t1` must also be, and
252
+ the IH then tells us that `Gamma` assigns `x` a type.
253
+
254
+ - Almost all the other cases are similar : `x` appears free in a
255
+ subterm of `t` , and since `t` is well typed under `Gamma` , we
256
+ know the subterm of `t` in which `x` appears is well typed
257
+ under `Gamma` as well, and the IH gives us exactly the
258
+ conclusion we want.
259
+
260
+ - The only remaining case is `afi_abs` . In this case `t =
261
+ \ y : T11.t12` and `x` appears free in `t12`, and we also know
262
+ that `x` is different from `y` . The difference from the
263
+ previous cases is that, whereas `t` is well typed under
264
+ `Gamma` , its body `t12` is well typed under `(Gamma & {{y-- >T11}}`,
265
+ so the IH allows us to conclude that `x` is assigned some type
266
+ by the extended context `(Gamma & {{y-- >T11}}`. To conclude that
267
+ `Gamma` assigns a type to `x` , we appeal to lemma
268
+ `update_neq` , noting that `x` and `y` are different
269
+ variables. * )
270
+
271
+ > free_in_context : {x : Id} -> {t : Tm} -> {ty : Ty} -> {gamma : Context} ->
272
+ > Appears_free_in x t ->
273
+ > gamma |- t :: ty . ->
274
+ > (t' : Ty ** gamma x = Just t')
275
+ > free_in_context {ty} Afi_var (T_Var h1) = (ty ** h1)
276
+ > free_in_context {t = t1 # t2} (Afi_app1 h) (T_App h1 h2) = free_in_context h h1
277
+ > free_in_context {t = t1 # t2} (Afi_app2 h) (T_App h1 h2) = free_in_context h h2
278
+ > free_in_context {t = Tif tb tp tn} (Afi_if1 h) (T_If h1 h2 h3) = free_in_context h h1
279
+ > free_in_context {t = Tif tb tp tn} (Afi_if2 h) (T_If h1 h2 h3) = free_in_context h h2
280
+ > free_in_context {t = Tif tb tp tn} (Afi_if3 h) (T_If h1 h2 h3) = free_in_context h h3
281
+ > free_in_context {x} {gamma} {t = Tabs id ty tm} (Afi_abs h1 h2) (T_Abs h) =
282
+ > let (ty ** ih) = free_in_context h2 h
283
+ > in (ty ** rewrite (sym (update_neq {m= gamma} {v= ty} h1)) in ih)
284
+
285
+ Next , we'll need the fact that any term `t` that is well typed in
286
+ the empty context is closed (it has no free variables).
287
+
288
+ ==== Exercise : 2 stars, optional (typable_empty__closed)
292
289
293
- (** **** Exercise : 2 stars, optional (typable_empty__closed) *)
294
290
Corollary typable_empty__closed : forall t T,
295
291
empty |- t \ in T ->
296
292
closed t.
0 commit comments