-
Notifications
You must be signed in to change notification settings - Fork 0
/
References.thy
1961 lines (1718 loc) · 72.3 KB
/
References.thy
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
272
273
274
275
276
277
278
279
280
281
282
283
284
285
286
287
288
289
290
291
292
293
294
295
296
297
298
299
300
301
302
303
304
305
306
307
308
309
310
311
312
313
314
315
316
317
318
319
320
321
322
323
324
325
326
327
328
329
330
331
332
333
334
335
336
337
338
339
340
341
342
343
344
345
346
347
348
349
350
351
352
353
354
355
356
357
358
359
360
361
362
363
364
365
366
367
368
369
370
371
372
373
374
375
376
377
378
379
380
381
382
383
384
385
386
387
388
389
390
391
392
393
394
395
396
397
398
399
400
401
402
403
404
405
406
407
408
409
410
411
412
413
414
415
416
417
418
419
420
421
422
423
424
425
426
427
428
429
430
431
432
433
434
435
436
437
438
439
440
441
442
443
444
445
446
447
448
449
450
451
452
453
454
455
456
457
458
459
460
461
462
463
464
465
466
467
468
469
470
471
472
473
474
475
476
477
478
479
480
481
482
483
484
485
486
487
488
489
490
491
492
493
494
495
496
497
498
499
500
501
502
503
504
505
506
507
508
509
510
511
512
513
514
515
516
517
518
519
520
521
522
523
524
525
526
527
528
529
530
531
532
533
534
535
536
537
538
539
540
541
542
543
544
545
546
547
548
549
550
551
552
553
554
555
556
557
558
559
560
561
562
563
564
565
566
567
568
569
570
571
572
573
574
575
576
577
578
579
580
581
582
583
584
585
586
587
588
589
590
591
592
593
594
595
596
597
598
599
600
601
602
603
604
605
606
607
608
609
610
611
612
613
614
615
616
617
618
619
620
621
622
623
624
625
626
627
628
629
630
631
632
633
634
635
636
637
638
639
640
641
642
643
644
645
646
647
648
649
650
651
652
653
654
655
656
657
658
659
660
661
662
663
664
665
666
667
668
669
670
671
672
673
674
675
676
677
678
679
680
681
682
683
684
685
686
687
688
689
690
691
692
693
694
695
696
697
698
699
700
701
702
703
704
705
706
707
708
709
710
711
712
713
714
715
716
717
718
719
720
721
722
723
724
725
726
727
728
729
730
731
732
733
734
735
736
737
738
739
740
741
742
743
744
745
746
747
748
749
750
751
752
753
754
755
756
757
758
759
760
761
762
763
764
765
766
767
768
769
770
771
772
773
774
775
776
777
778
779
780
781
782
783
784
785
786
787
788
789
790
791
792
793
794
795
796
797
798
799
800
801
802
803
804
805
806
807
808
809
810
811
812
813
814
815
816
817
818
819
820
821
822
823
824
825
826
827
828
829
830
831
832
833
834
835
836
837
838
839
840
841
842
843
844
845
846
847
848
849
850
851
852
853
854
855
856
857
858
859
860
861
862
863
864
865
866
867
868
869
870
871
872
873
874
875
876
877
878
879
880
881
882
883
884
885
886
887
888
889
890
891
892
893
894
895
896
897
898
899
900
901
902
903
904
905
906
907
908
909
910
911
912
913
914
915
916
917
918
919
920
921
922
923
924
925
926
927
928
929
930
931
932
933
934
935
936
937
938
939
940
941
942
943
944
945
946
947
948
949
950
951
952
953
954
955
956
957
958
959
960
961
962
963
964
965
966
967
968
969
970
971
972
973
974
975
976
977
978
979
980
981
982
983
984
985
986
987
988
989
990
991
992
993
994
995
996
997
998
999
1000
theory References
imports Main Smallstep begin
(*
(** * References: Typing Mutable References *)
(* $Date: 2011-06-03 13:58:55 -0400 (Fri, 03 Jun 2011) $ *)
Require Export Smallstep.
(** So far, we have considered a variety of _pure_ language features,
including functional abstraction, basic types such as numbers and
booleans, and structured types such as records and variants. These
features form the backbone of most programming languages -- including
purely functional languages such as Haskell, "mostly functional"
languages such as ML, imperative languages such as C, and
object-oriented languages such as Java.
Most practical programming languages also include various _impure_
features that cannot be described in the simple semantic framework
we have used so far. In particular, besides just yielding
results, evaluation of terms in these languages may assign to
mutable variables (reference cells, arrays, mutable record fields,
etc.), perform input and output to files, displays, or network
connections, make non-local transfers of control via exceptions,
jumps, or continuations, engage in inter-process synchronization
and communication, and so on. In the literature on programming
languages, such "side effects" of computation are more generally
referred to as _computational effects_.
In this chapter, we'll see how one sort of computational
effect -- mutable references -- can be added to the calculi we have
studied. The main extension will be dealing explicitly with a
_store_ (or _heap_). This extension is straightforward to define;
the most interesting part is the refinement we need to make to the
statement of the type preservation theorem. *)
(* ###################################################################### *)
(** ** Definitions *)
(** Pretty much every programming language provides some form of
assignment operation that changes the contents of a previously
allocated piece of storage. (Coq's internal language is a rare
exception!)
In some languages -- notably ML and its relatives -- the
mechanisms for name-binding and those for assignment are kept
separate. We can have a variable [x] whose _value_ is the number
[5], or we can have a variable [y] whose value is a
_reference_ (or _pointer_) to a mutable cell whose current
contents is [5]. These are different things, and the difference
is visible to the programmer. We can add [x] to another number,
but not assign to it. We can use [y] directly to assign a new
value to the cell that it points to (by writing [y:=84]), but we
cannot use it directly as an argument to an operation like [+].
Instead, we must explicitly _dereference_ it, writing [!y] to
obtain its current contents.
In most other languages -- in particular, in all members of the C
family, including Java -- _every_ variable name refers to a mutable
cell, and the operation of dereferencing a variable to obtain its
current contents is implicit.
For purposes of formal study, it is useful to keep these
mechanisms separate. The development in this chapter will closely
follow ML's model. Applying the lessons learned here to C-like
languages is a straightforward matter of collapsing some
distinctions and rendering some operations such as dereferencing
implicit instead of explicit.
In this chapter, we study adding mutable references to the
simply-typed lambda calculus with natural numbers. *)
(* ###################################################################### *)
(** ** Syntax *)
Module STLCRef.
(** The basic operations on references are _allocation_,
_dereferencing_, and _assignment_.
- To allocate a reference, we use the [ref] operator, providing
an initial value for the new cell. For example, [ref 5]
creates a new cell containing the value [5], and evaluates to
a reference to that cell.
- To read the current value of this cell, we use the
dereferencing operator [!]; for example, [!(ref 5)] evaluates
to [5].
- To change the value stored in a cell, we use the assignment
operator. If [r] is a reference, [r := 7] will store the
value [7] in the cell referenced by [r]. However, [r := 7]
evaluates to the trivial value [unit]; it exists only to have
the _side effect_ of modifying the contents of a cell. *)
(* ################################### *)
(** *** Types *)
(** We start with the simply typed lambda calculus over the
natural numbers. To the base natural number type and arrow types
we need to add two more types to deal with references. First, we
need the _unit type_, which we will use as the result type of an
assignment operation. We then add _reference types_. *)
(** If [T] is a type, then [Ref T] is the type of references which
point to a cell holding values of type [T].
<<
T ::= Nat
| Unit
| T -> T
| Ref T
>>
*)
Inductive ty : Type :=
| ty_Nat : ty
| ty_Unit : ty
| ty_arrow : ty -> ty -> ty
| ty_Ref : ty -> ty.
*)
datatype ty = TyNat | TyUnit | TyArrow ty ty | TyRef ty
(*
(* ################################### *)
(** *** Terms *)
(** Besides variables, abstractions, applications,
natural-number-related terms, and [unit], we need four more sorts
of terms in order to handle mutable references:
<<
t ::= ... Terms
| ref t allocation
| !t dereference
| t := t assignment
| l location
>>
*)
*)
datatype tm = TmVar id | TmApp tm tm | TmAbs id ty tm
| TmNat nat | TmSucc tm | TmPred tm | TmMult tm tm
| TmIf0 tm tm tm | TmUnit | TmRef tm | TmDeref tm
| TmAssign tm tm | TmLoc nat
(*
Inductive tm : Type :=
(* STLC with numbers: *)
| tm_var : id -> tm
| tm_app : tm -> tm -> tm
| tm_abs : id -> ty -> tm -> tm
| tm_nat : nat -> tm
| tm_succ : tm -> tm
| tm_pred : tm -> tm
| tm_mult : tm -> tm -> tm
| tm_if0 : tm -> tm -> tm -> tm
(* New terms: *)
| tm_unit : tm
| tm_ref : tm -> tm
| tm_deref : tm -> tm
| tm_assign : tm -> tm -> tm
| tm_loc : nat -> tm.
(** Intuitively...
- [ref t] (formally, [tm_ref t]) allocates a new reference cell
with the value [t] and evaluates to the location of the newly
allocated cell;
- [!t] (formally, [tm_deref t]) evaluates to the contents of the
cell referenced by [t];
- [t1 := t2] (formally, [tm_assign t1 t2]) assigns [t2] to the
cell referenced by [t1]; and
- [l] (formally, [tm_loc l]) is a reference to the cell at
location [l]. We'll discuss locations later. *)
(** In informal examples, we'll also freely use the extensions
of the STLC developed in the [MoreStlc] chapter; however, to keep
the proofs small, we won't bother formalizing them again here. It
would be easy to do so, since there are no very interesting
interactions between those features and references. *)
Tactic Notation "tm_cases" tactic(first) ident(c) :=
first;
[ Case_aux c "tm_var" | Case_aux c "tm_app"
| Case_aux c "tm_abs" | Case_aux c "tm_zero"
| Case_aux c "tm_succ" | Case_aux c "tm_pred"
| Case_aux c "tm_mult" | Case_aux c "tm_if0"
| Case_aux c "tm_unit" | Case_aux c "tm_ref"
| Case_aux c "tm_deref" | Case_aux c "tm_assign"
| Case_aux c "tm_loc" ].
Module ExampleVariables.
Definition x := Id 0.
Definition y := Id 1.
Definition r := Id 2.
Definition s := Id 3.
End ExampleVariables.
(* ################################### *)
(** *** Typing (Preview) *)
(** Informally, the typing rules for allocation, dereferencing, and
assignment will look like this:
[[[
Gamma |- t1 : T1
------------------------ (T_Ref)
Gamma |- ref t1 : Ref T1
Gamma |- t1 : Ref T11
--------------------- (T_Deref)
Gamma |- !t1 : T11
Gamma |- t1 : Ref T11
Gamma |- t2 : T11
------------------------ (T_Assign)
Gamma |- t1 := t2 : Unit
]]]
The rule for locations will require a bit more machinery, and this
will motivate some changes to the other rules; we'll come back to
this later. *)
(* ################################### *)
(** *** Values and Substitution *)
(** Besides abstractions and numbers, we have two new types of values:
the unit value, and locations. *)
Inductive value : tm -> Prop :=
| v_abs : forall x T t,
value (tm_abs x T t)
| v_nat : forall n,
value (tm_nat n)
| v_unit :
value tm_unit
| v_loc : forall l,
value (tm_loc l).
*)
inductive val :: "tm \<Rightarrow> bool" where
v_abs : "val (TmAbs x T t)" |
v_nat : "val (TmNat n)" |
v_unit : "val TmUnit" |
v_loc : "val (TmLoc l)"
(*
Hint Constructors value.
(** Extending substitution to handle the new syntax of terms is
straightforward. *)
Fixpoint subst (x:id) (s:tm) (t:tm) : tm :=
match t with
| tm_var x' =>
if beq_id x x' then s else t
| tm_app t1 t2 =>
tm_app (subst x s t1) (subst x s t2)
| tm_abs x' T t1 =>
if beq_id x x' then t else tm_abs x' T (subst x s t1)
| tm_nat n =>
t
| tm_succ t1 =>
tm_succ (subst x s t1)
| tm_pred t1 =>
tm_pred (subst x s t1)
| tm_mult t1 t2 =>
tm_mult (subst x s t1) (subst x s t2)
| tm_if0 t1 t2 t3 =>
tm_if0 (subst x s t1) (subst x s t2) (subst x s t3)
| tm_unit =>
t
| tm_ref t1 =>
tm_ref (subst x s t1)
| tm_deref t1 =>
tm_deref (subst x s t1)
| tm_assign t1 t2 =>
tm_assign (subst x s t1) (subst x s t2)
| tm_loc _ =>
t
end.
(* ###################################################################### *)
(** * Pragmatics *)
(* ################################### *)
(** ** Side Effects and Sequencing *)
(** The fact that the result of an assignment expression is the
trivial value [unit] allows us to use a nice abbreviation for
_sequencing_. For example, we can write
<<
r:=succ(!r); !r
>>
as an abbreviation for
<<
(\x:Unit. !r) (r := succ(!r)).
>>
This has the effect of evaluating two expressions in order and
returning the value of the second. Restricting the type of the first
expression to [Unit] helps the typechecker to catch some silly
errors by permitting us to throw away the first value only if it
is really guaranteed to be trivial.
Notice that, if the second expression is also an assignment, then
the type of the whole sequence will be [Unit], so we can validly
place it to the left of another [;] to build longer sequences of
assignments:
<<
r:=succ(!r); r:=succ(!r); r:=succ(!r); r:=succ(!r); !r
>>
*)
(** Formally, we introduce sequencing as a "derived form"
[tm_seq] that expands into an abstraction and an application. *)
Definition tm_seq t1 t2 :=
tm_app (tm_abs (Id 0) ty_Unit t2) t1.
*)
abbreviation TmSeq where
"TmSeq t1 t2 \<equiv> TmApp (TmAbs (Id 0) TyUnit t2) t1"
(*
(* ################################### *)
(** ** References and Aliasing *)
(** It is important to bear in mind the difference between the
_reference_ that is bound to [r] and the _cell_ in the store that
is pointed to by this reference.
If we make a copy of [r], for example by binding its value to
another variable [s], what gets copied is only the _reference_,
not the contents of the cell itself.
For example, after evaluating
<<
let r = ref 5 in
let s = r in
s := 82;
(!r)+1
>>
the cell referenced by [r] will contain the value [82], while the
result of the whole expression will be [83]. The references [r]
and [s] are said to be _aliases_ for the same cell.
The possibility of aliasing can make programs with references
quite tricky to reason about. For example, the expression
<<
r := 5; r := !s
>>
assigns [5] to [r] and then immediately overwrites it with [s]'s
current value; this has exactly the same effect as the single
assignment
<<
r := !s
>>
_unless_ we happen to do it in a context where [r] and [s] are
aliases for the same cell! *)
(* ################################### *)
(** ** Shared State *)
(** Of course, aliasing is also a large part of what makes references
useful. In particular, it allows us to set up "implicit
communication channels" -- shared state -- between different parts
of a program. For example, suppose we define a reference cell and
two functions that manipulate its contents:
<<
let c = ref 0 in
let incc = \_:Unit. (c := succ (!c); !c) in
let decc = \_:Unit. (c := pred (!c); !c) in
...
>>
*)
(** Note that, since their argument types are [Unit], the
abstractions in the definitions of [incc] and [decc] are not
providing any useful information to the bodies of the
functions (using the wildcard [_] as the name of the bound
variable is a reminder of this). Instead, their purpose is to
"slow down" the execution of the function bodies: since function
abstractions are values, the two [let]s are executed simply by
binding these functions to the names [incc] and [decc], rather
than by actually incrementing or decrementing [c]. Later, each
call to one of these functions results in its body being executed
once and performing the appropriate mutation on [c]. Such
functions are often called _thunks_.
In the context of these declarations, calling [incc] results in
changes to [c] that can be observed by calling [decc]. For
example, if we replace the [...] with [(incc unit; incc unit; decc
unit)], the result of the whole program will be [1]. *)
(** ** Objects *)
(** We can go a step further and write a _function_ that creates [c],
[incc], and [decc], packages [incc] and [decc] together into a
record, and returns this record:
<<
newcounter =
\_:Unit.
let c = ref 0 in
let incc = \_:Unit. (c := succ (!c); !c) in
let decc = \_:Unit. (c := pred (!c); !c) in
{i=incc, d=decc}
>>
*)
(** Now, each time we call [newcounter], we get a new record of
functions that share access to the same storage cell [c]. The
caller of [newcounter] can't get at this storage cell directly,
but can affect it indirectly by calling the two functions. In
other words, we've created a simple form of _object_.
<<
let c1 = newcounter unit in
let c2 = newcounter unit in
// Note that we've allocated two separate storage cells now!
let r1 = c1.i unit in
let r2 = c2.i unit in
r2 // yields 1, not 2!
>>
*)
(** **** Exercise: 1 star *)
(** Draw (on paper) the contents of the store at the point in
execution where the first two [let]s have finished and the third
one is about to begin. *)
(* FILL IN HERE *)
(** [] *)
(* ################################### *)
(** ** References to Compound Types *)
(** A reference cell need not contain just a number: the primitives
we've defined above allow us to create references to values of any
type, including functions. For example, we can use references to
functions to give a (not very efficient) implementation of arrays
of numbers, as follows. Write [NatArray] for the type
[Ref (Nat->Nat)].
Recall the [equal] function from the [MoreStlc] chapter:
<<
equal =
fix
(\eq:Nat->Nat->Bool.
\m:Nat. \n:Nat.
if m=0 then iszero n
else if n=0 then false
else eq (pred m) (pred n))
>>
Now, to build a new array, we allocate a reference cell and fill
it with a function that, when given an index, always returns [0].
<<
newarray = \_:Unit. ref (\n:Nat.0)
>>
To look up an element of an array, we simply apply
the function to the desired index.
<<
lookup = \a:NatArray. \n:Nat. (!a) n
>>
The interesting part of the encoding is the [update] function. It
takes an array, an index, and a new value to be stored at that index, and
does its job by creating (and storing in the reference) a new function
that, when it is asked for the value at this very index, returns the new
value that was given to [update], and on all other indices passes the
lookup to the function that was previously stored in the reference.
<<
update = \a:NatArray. \m:Nat. \v:Nat.
let oldf = !a in
a := (\n:Nat. if equal m n then v else oldf n);
>>
References to values containing other references can also be very
useful, allowing us to define data structures such as mutable
lists and trees. *)
(** **** Exercise: 2 stars *)
(** If we defined [update] more compactly like this
<<
update = \a:NatArray. \m:Nat. \v:Nat.
a := (\n:Nat. if equal m n then v else (!a) n)
>>
would it behave the same? *)
(* FILL IN HERE *)
(** [] *)
(* ################################### *)
(** ** Null References *)
(** There is one more difference between our references and C-style
mutable variables: in C-like languages, variables holding pointers
into the heap may sometimes have the value [NULL]. Dereferencing
such a "null pointer" is an error, and results in an
exception (Java) or in termination of the program (C).
Null pointers cause significant trouble in C-like languages: the
fact that any pointer might be null means that any dereference
operation in the program can potentially fail. However, even in
ML-like languages, there are occasionally situations where we may
or may not have a valid pointer in our hands. Fortunately, there
is no need to extend the basic mechanisms of references to achieve
this: the sum types introduced in the [MoreStlc] chapter already
give us what we need.
First, we can use sums to build an analog of the [option] types
introduced in the [Lists] chapter. Define [Option T] to be an
abbreviation for [Unit + T].
Then a "nullable reference to a [T]" is simply an element of the
type [Ref (Option T)]. *)
(* ################################### *)
(** ** Garbage Collection *)
(** A last issue that we should mention before we move on with
formalizing references is storage _de_-allocation. We have not
provided any primitives for freeing reference cells when they are
no longer needed. Instead, like many modern languages (including
ML and Java) we rely on the run-time system to perform _garbage
collection_, collecting and reusing cells that can no longer be
reached by the program.
This is _not_ just a question of taste in language design: it is
extremely difficult to achieve type safety in the presence of an
explicit deallocation operation. The reason for this is the
familiar _dangling reference_ problem: we allocate a cell holding
a number, save a reference to it in some data structure, use it
for a while, then deallocate it and allocate a new cell holding a
boolean, possibly reusing the same storage. Now we can have two
names for the same storage cell -- one with type [Ref Nat] and the
other with type [Ref Bool]. *)
(** **** Exercise: 1 star *)
(** Show how this can lead to a violation of type safety. *)
(* FILL IN HERE *)
(** [] *)
(* ###################################################################### *)
(** * Operational Semantics *)
(* ################################### *)
(** ** Locations *)
(** The most subtle aspect of the treatment of references
appears when we consider how to formalize their operational
behavior. One way to see why is to ask, "What should be the
_values_ of type [Ref T]?" The crucial observation that we need
to take into account is that evaluating a [ref] operator should
_do_ something -- namely, allocate some storage -- and the result
of the operation should be a reference to this storage.
What, then, is a reference?
The run-time store in most programming language implementations is
essentially just a big array of bytes. The run-time system keeps track
of which parts of this array are currently in use; when we need to
allocate a new reference cell, we allocate a large enough segment from
the free region of the store (4 bytes for integer cells, 8 bytes for
cells storing [Float]s, etc.), mark it as being used, and return the
index (typically, a 32- or 64-bit integer) of the start of the newly
allocated region. These indices are references.
For present purposes, there is no need to be quite so concrete.
We can think of the store as an array of _values_, rather than an
array of bytes, abstracting away from the different sizes of the
run-time representations of different values. A reference, then,
is simply an index into the store. (If we like, we can even
abstract away from the fact that these indices are numbers, but
for purposes of formalization in Coq it is a bit more convenient
to use numbers.) We'll use the word _location_ instead of
_reference_ or _pointer_ from now on to emphasize this abstract
quality.
Treating locations abstractly in this way will prevent us from
modeling the _pointer arithmetic_ found in low-level languages
such as C. This limitation is intentional. While pointer
arithmetic is occasionally very useful, especially for
implementing low-level services such as garbage collectors, it
cannot be tracked by most type systems: knowing that location [n]
in the store contains a [float] doesn't tell us anything useful
about the type of location [n+4]. In C, pointer arithmetic is a
notorious source of type safety violations. *)
(* ################################### *)
(** ** Stores *)
(** Recall that, in the small-step operational semantics for
IMP, the step relation needed to carry along an auxiliary state in
addition to the program being executed. In the same way, once we
have added reference cells to the STLC, our step relation must
carry along a store to keep track of the contents of reference
cells.
We could re-use the same functional representation we used for
states in IMP, but for carrying out the proofs in this chapter it
is actually more convenient to represent a store simply as a
_list_ of values. (The reason we couldn't use this representation
before is that, in IMP, a program could modify any location at any
time, so states had to be ready to map _any_ variable to a value.
However, in the STLC with references, the only way to create a
reference cell is with [tm_ref t1], which puts the value of [t1]
in a new reference cell and evaluates to the location of the newly
created reference cell. When evaluating such an expression, we can
just add a new reference cell to the end of the list representing
the store.) *)
Definition store := list tm.
(** We use [store_lookup n st] to retrieve the value of the reference
cell at location [n] in the store [st]. Note that we must give a
default value to [nth] in case we try looking up an index which is
too large. (In fact, we will never actually do this, but proving
it will of course require some work!) *)
Definition store_lookup (n:nat) (st:store) :=
nth n st tm_unit.
(** To add a new reference cell to the store, we use [snoc]. *)
Fixpoint snoc {A:Type} (l:list A) (x:A) : list A :=
match l with
| nil => x :: nil
| h :: t => h :: snoc t x
end.
(** We will need some boring lemmas about [snoc]. The proofs are
routine inductions. *)
Lemma length_snoc : forall A (l:list A) x,
length (snoc l x) = S (length l).
Proof.
induction l; intros; [ auto | simpl; rewrite IHl; auto ]. Qed.
(* The "solve by inversion" tactic is explained in Stlc.v. *)
Lemma nth_lt_snoc : forall A (l:list A) x d n,
n < length l ->
nth n l d = nth n (snoc l x) d.
Proof.
induction l as [|a l']; intros; try solve by inversion.
Case "l = a :: l'".
destruct n; auto.
simpl. apply IHl'.
simpl in H. apply lt_S_n in H. assumption.
Qed.
Lemma nth_eq_snoc : forall A (l:list A) x d,
nth (length l) (snoc l x) d = x.
Proof.
induction l; intros; [ auto | simpl; rewrite IHl; auto ].
Qed.
(** To update the store, we use the [replace] function, which replaces
the contents of a cell at a particular index. *)
Fixpoint replace {A:Type} (n:nat) (x:A) (l:list A) : list A :=
match l with
| nil => nil
| h :: t =>
match n with
| O => x :: t
| S n' => h :: replace n' x t
end
end.
(** Of course, we also need some boring lemmas about [replace], which
are also fairly straightforward to prove. *)
Lemma replace_nil : forall A n (x:A),
replace n x [] = [].
Proof.
destruct n; auto.
Qed.
Lemma length_replace : forall A n x (l:list A),
length (replace n x l) = length l.
Proof with auto.
intros A n x l. generalize dependent n.
induction l; intros n.
destruct n...
destruct n...
simpl. rewrite IHl...
Qed.
Lemma lookup_replace_eq : forall l t st,
l < length st ->
store_lookup l (replace l t st) = t.
Proof with auto.
intros l t st.
unfold store_lookup.
generalize dependent l.
induction st as [|t' st']; intros l Hlen.
Case "st = []".
inversion Hlen.
Case "st = t' :: st'".
destruct l; simpl...
apply IHst'. simpl in Hlen. omega.
Qed.
Lemma lookup_replace_neq : forall l1 l2 t st,
l1 <> l2 ->
store_lookup l1 (replace l2 t st) = store_lookup l1 st.
Proof with auto.
unfold store_lookup.
induction l1 as [|l1']; intros l2 t st Hneq.
Case "l1 = 0".
destruct st.
SCase "st = []". rewrite replace_nil...
SCase "st = _ :: _". destruct l2... contradict Hneq...
Case "l1 = S l1'".
destruct st as [|t2 st2].
SCase "st = []". destruct l2...
SCase "st = t2 :: st2".
destruct l2...
simpl; apply IHl1'...
Qed.
(* ################################### *)
(** ** Reduction *)
(** Next, we need to extend our operational semantics to take stores
into account. Since the result of evaluating an expression will
in general depend on the contents of the store in which it is
evaluated, the evaluation rules should take not just a term but
also a store as argument. Furthermore, since the evaluation of a
term may cause side effects on the store that may affect the
evaluation of other terms in the future, the evaluation rules need
to return a new store. Thus, the shape of the single-step
evaluation relation changes from [t ==> t'] to [t / st ==> t' /
st'], where [st] and [st'] are the starting and ending states of
the store.
To carry through this change, we first need to augment all of our
existing evaluation rules with stores:
[[[
value v2
------------------------------------- (ST_AppAbs)
(\a:T.t12) v2 / st ==> [v2/a]t12 / st
t1 / st ==> t1' / st'
--------------------------- (ST_App1)
t1 t2 / st ==> t1' t2 / st'
value v1 t2 / st ==> t2' / st'
---------------------------------- (ST_App2)
v1 t2 / st ==> v1 t2' / st'
]]]
Note that the first rule here returns the store unchanged:
function application, in itself, has no side effects. The other two
rules simply propagate side effects from premise to conclusion.
Now, the result of evaluating a [ref] expression will be a fresh
location; this is why we included locations in the syntax of terms
and in the set of values.
It is crucial to note that making this extension to the syntax of
terms does not mean that we intend _programmers_ to write terms
involving explicit, concrete locations: such terms will arise only
as intermediate results of evaluation. This may initially seem
odd, but really it follows naturally from our design decision to
represent the result of every evaluation step by a modified
term. If we had chosen a more "machine-like" model for evaluation,
e.g. with an explicit stack to contain values of bound
identifiers, then the idea of adding locations to the set of
allowed values would probably seem more obvious.
In terms of this expanded syntax, we can state evaluation rules for
the new constructs that manipulate locations and the store. First, to
evaluate a dereferencing expression [!t1], we must first reduce [t1]
until it becomes a value:
[[[
t1 / st ==> t1' / st'
----------------------- (ST_Deref)
!t1 / st ==> !t1' / st'
]]]
Once [t1] has finished reducing, we should have an expression of
the form [!l], where [l] is some location. (A term that attempts
to dereference any other sort of value, such as a function or
[unit], is erroneous, as is a term that tries to derefence a
location that is larger than the size [|st|] of the currently
allocated store; the evaluation rules simply get stuck in this
case. The type safety properties that we'll establish below
assure us that well-typed terms will never misbehave in this way.)
[[[
l < |st|
---------------------------------- (ST_DerefLoc)
!(loc l) / st ==> lookup l st / st
]]]
Next, to evaluate an assignment expression [t1:=t2], we must first
evaluate [t1] until it becomes a value (a location), and then
evaluate [t2] until it becomes a value (of any sort):
[[[
t1 / st ==> t1' / st'
----------------------------------- (ST_Assign1)
t1 := t2 / st ==> t1' := t2 / st'
t2 / st ==> t2' / st'
--------------------------------- (ST_Assign2)
v1 := t2 / st ==> v1 := t2' / st'
]]]
Once we have finished with [t1] and [t2], we have an expression of
the form [l:=v2], which we execute by updating the store to make
location [l] contain [v2]:
[[[
l < |st|
------------------------------------- (ST_Assign)
loc l := v2 / st ==> unit / [v2/l]st
]]]
The notation [[v2/l]st] means "the store that maps [l] to [v2]
and maps all other locations to the same thing as [st.]" Note
that the term resulting from this evaluation step is just [unit];
the interesting result is the updated store.)
Finally, to evaluate an expression of the form [ref t1], we first
evaluate [t1] until it becomes a value:
[[[
t1 / st ==> t1' / st'
----------------------------- (ST_Ref)
ref t1 / st ==> ref t1' / st'
]]]
Then, to evaluate the [ref] itself, we choose a fresh location at
the end of the current store -- i.e., location [|st|] -- and yield
a new store that extends [st] with the new value [v1].
[[[
-------------------------------- (ST_RefValue)
ref v1 / st ==> loc |st| / st,v1
]]]
The value resulting from this step is the newly allocated location
itself. (Formally, [st,v1] means [snoc st v1].)
Note that these evaluation rules do not perform any kind of
garbage collection: we simply allow the store to keep growing
without bound as evaluation proceeds. This does not affect the
correctness of the results of evaluation (after all, the
definition of "garbage" is precisely parts of the store that are
no longer reachable and so cannot play any further role in
evaluation), but it means that a naive implementation of our
evaluator might sometimes run out of memory where a more
sophisticated evaluator would be able to continue by reusing
locations whose contents have become garbage.
Formally... *)
Reserved Notation "t1 '/' st1 '==>' t2 '/' st2"
(at level 40, st1 at level 39, t2 at level 39).
Inductive step : tm * store -> tm * store -> Prop :=
| ST_AppAbs : forall x T t12 v2 st,
value v2 ->
tm_app (tm_abs x T t12) v2 / st ==> subst x v2 t12 / st
| ST_App1 : forall t1 t1' t2 st st',
t1 / st ==> t1' / st' ->
tm_app t1 t2 / st ==> tm_app t1' t2 / st'
| ST_App2 : forall v1 t2 t2' st st',
value v1 ->
t2 / st ==> t2' / st' ->
tm_app v1 t2 / st ==> tm_app v1 t2'/ st'
| ST_SuccNat : forall n st,
tm_succ (tm_nat n) / st ==> tm_nat (S n) / st
| ST_Succ : forall t1 t1' st st',
t1 / st ==> t1' / st' ->
tm_succ t1 / st ==> tm_succ t1' / st'
| ST_PredNat : forall n st,
tm_pred (tm_nat n) / st ==> tm_nat (pred n) / st
| ST_Pred : forall t1 t1' st st',
t1 / st ==> t1' / st' ->
tm_pred t1 / st ==> tm_pred t1' / st'
| ST_MultNats : forall n1 n2 st,
tm_mult (tm_nat n1) (tm_nat n2) / st ==> tm_nat (mult n1 n2) / st
| ST_Mult1 : forall t1 t2 t1' st st',
t1 / st ==> t1' / st' ->
tm_mult t1 t2 / st ==> tm_mult t1' t2 / st'
| ST_Mult2 : forall v1 t2 t2' st st',
value v1 ->
t2 / st ==> t2' / st' ->
tm_mult v1 t2 / st ==> tm_mult v1 t2' / st'
| ST_If0 : forall t1 t1' t2 t3 st st',
t1 / st ==> t1' / st' ->
tm_if0 t1 t2 t3 / st ==> tm_if0 t1' t2 t3 / st'
| ST_If0_Zero : forall t2 t3 st,
tm_if0 (tm_nat 0) t2 t3 / st ==> t2 / st
| ST_If0_Nonzero : forall n t2 t3 st,
tm_if0 (tm_nat (S n)) t2 t3 / st ==> t3 / st
| ST_RefValue : forall v1 st,
value v1 ->
tm_ref v1 / st ==> tm_loc (length st) / snoc st v1
| ST_Ref : forall t1 t1' st st',
t1 / st ==> t1' / st' ->
tm_ref t1 / st ==> tm_ref t1' / st'
| ST_DerefLoc : forall st l,
l < length st ->
tm_deref (tm_loc l) / st ==> store_lookup l st / st
| ST_Deref : forall t1 t1' st st',
t1 / st ==> t1' / st' ->
tm_deref t1 / st ==> tm_deref t1' / st'
| ST_Assign : forall v2 l st,
value v2 ->
l < length st ->
tm_assign (tm_loc l) v2 / st ==> tm_unit / replace l v2 st
| ST_Assign1 : forall t1 t1' t2 st st',
t1 / st ==> t1' / st' ->
tm_assign t1 t2 / st ==> tm_assign t1' t2 / st'
| ST_Assign2 : forall v1 t2 t2' st st',
value v1 ->
t2 / st ==> t2' / st' ->
tm_assign v1 t2 / st ==> tm_assign v1 t2' / st'
where "t1 '/' st1 '==>' t2 '/' st2" := (step (t1,st1) (t2,st2)).
Tactic Notation "step_cases" tactic(first) ident(c) :=
first;
[ Case_aux c "ST_AppAbs" | Case_aux c "ST_App1"
| Case_aux c "ST_App2" | Case_aux c "ST_SuccNat"
| Case_aux c "ST_Succ" | Case_aux c "ST_PredNat"
| Case_aux c "ST_Pred" | Case_aux c "ST_MultNats"
| Case_aux c "ST_Mult1" | Case_aux c "ST_Mult2"
| Case_aux c "ST_If0" | Case_aux c "ST_If0_Zero"
| Case_aux c "ST_If0_Nonzero" | Case_aux c "ST_RefValue"
| Case_aux c "ST_Ref" | Case_aux c "ST_DerefLoc"
| Case_aux c "ST_Deref" | Case_aux c "ST_Assign"
| Case_aux c "ST_Assign1" | Case_aux c "ST_Assign2" ].
Hint Constructors step.
Definition stepmany := (refl_step_closure step).
Notation "t1 '/' st '==>*' t2 '/' st'" := (stepmany (t1,st) (t2,st'))
(at level 40, st at level 39, t2 at level 39).
(* ################################### *)
(** * Typing *)
(** Our contexts for free variables will be exactly the same as for
the STLC, partial maps from identifiers to types. *)
Definition context := partial_map ty.
(* ################################### *)
(** ** Store typings *)
(** Having extended our syntax and evaluation rules to accommodate
references, our last job is to write down typing rules for the new
constructs -- and, of course, to check that they are sound.
Naturally, the key question is, "What is the type of a location?"
First of all, notice that we do _not_ need to answer this question
for purposes of typechecking the terms that programmers actually
write. Concrete location constants arise only in terms that are
the intermediate results of evaluation; they are not in the
language that programmers write. So we only need to determine the
type of a location when we're in the middle of an evaluation
sequence, e.g. trying to apply the progress or preservation
lemmas. Thus, even though we normally think of typing as a
_static_ program property, it makes sense for the typing of
locations to depend on the _dynamic_ progress of the program too.
As a first try, note that when we evaluate a term containing
concrete locations, the type of the result depends on the contents
of the store that we start with. For example, if we evaluate the
term [!(loc 1)] in the store [[unit, unit]], the result is [unit];
if we evaluate the same term in the store [[unit, \x:Unit.x]], the
result is [\x:Unit.x]. With respect to the former store, the
location [1] has type [Unit], and with respect to the latter it
has type [Unit->Unit]. This observation leads us immediately to a
first attempt at a typing rule for locations:
[[[
Gamma |- lookup l st : T1
----------------------------
Gamma |- loc l : Ref T1
]]]
That is, to find the type of a location [l], we look up the
current contents of [l] in the store and calculate the type [T1]
of the contents. The type of the location is then [Ref T1].
Having begun in this way, we need to go a little further to reach a
consistent state. In effect, by making the type of a term depend on
the store, we have changed the typing relation from a three-place
relation (between contexts, terms, and types) to a four-place relation
(between contexts, _stores_, terms, and types). Since the store is,
intuitively, part of the context in which we calculate the type of a
term, let's write this four-place relation with the store to the left
of the turnstile: [Gamma; st |- t : T]. Our rule for typing
references now has the form
[[[
Gamma; st |- lookup l st : T1
--------------------------------
Gamma; st |- loc l : Ref T1
]]]
and all the rest of the typing rules in the system are extended
similarly with stores. The other rules do not need to do anything
interesting with their stores -- just pass them from premise to
conclusion.
However, there are two problems with this rule. First, typechecking
is rather inefficient, since calculating the type of a location [l]