-
Notifications
You must be signed in to change notification settings - Fork 2
/
SfLib.v
269 lines (215 loc) · 7.04 KB
/
SfLib.v
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
(** * SfLib: Software Foundations Library *)
(* $Date: 2012-04-05 12:16:07 -0400 (Thu, 05 Apr 2012) $ *)
(** Here we collect together several useful definitions and theorems
from Basics.v, List.v, Poly.v, Ind.v, and Logic.v that are not
already in the Coq standard library. From now on we can [Import]
or [Export] this file, instead of cluttering our environment with
all the examples and false starts in those files. *)
(** * From the Coq Standard Library *)
Require Omega. (* needed for using the [omega] tactic *)
Require Export Bool.
Require Export List.
Require Export Arith.
Require Export Arith.EqNat. (* Contains [beq_nat], among other things *)
(** * From Basics.v *)
Definition admit {T: Type} : T. Admitted.
Require String. Open Scope string_scope.
Ltac move_to_top x :=
match reverse goal with
| H : _ |- _ => try move x after H
end.
Tactic Notation "assert_eq" ident(x) constr(v) :=
let H := fresh in
assert (x = v) as H by reflexivity;
clear H.
Tactic Notation "Case_aux" ident(x) constr(name) :=
first [
set (x := name); move_to_top x
| assert_eq x name; move_to_top x
| fail 1 "because we are working on a different case" ].
Tactic Notation "Case" constr(name) := Case_aux Case name.
Tactic Notation "SCase" constr(name) := Case_aux SCase name.
Tactic Notation "SSCase" constr(name) := Case_aux SSCase name.
Tactic Notation "SSSCase" constr(name) := Case_aux SSSCase name.
Tactic Notation "SSSSCase" constr(name) := Case_aux SSSSCase name.
Tactic Notation "SSSSSCase" constr(name) := Case_aux SSSSSCase name.
Tactic Notation "SSSSSSCase" constr(name) := Case_aux SSSSSSCase name.
Tactic Notation "SSSSSSSCase" constr(name) := Case_aux SSSSSSSCase name.
Fixpoint ble_nat (n m : nat) : bool :=
match n with
| O => true
| S n' =>
match m with
| O => false
| S m' => ble_nat n' m'
end
end.
Theorem andb_true_elim1 : forall b c,
andb b c = true -> b = true.
Proof.
intros b c H.
destruct b.
Case "b = true".
reflexivity.
Case "b = false".
rewrite <- H. reflexivity. Qed.
Theorem andb_true_elim2 : forall b c,
andb b c = true -> c = true.
Proof.
(* An exercise in Basics.v *)
Admitted.
Theorem beq_nat_sym : forall (n m : nat),
beq_nat n m = beq_nat m n.
(* An exercise in Lists.v *)
Admitted.
(* From Poly.v *)
Notation "[ ]" := nil.
Notation "[ x , .. , y ]" := (cons x .. (cons y []) ..).
Notation "x ++ y" := (app x y)
(at level 60, right associativity).
(** * From Props.v *)
Inductive ev : nat -> Prop :=
| ev_0 : ev O
| ev_SS : forall n:nat, ev n -> ev (S (S n)).
(** * From Logic.v *)
Theorem andb_true : forall b c,
andb b c = true -> b = true /\ c = true.
Proof.
intros b c H.
destruct b.
destruct c.
apply conj. reflexivity. reflexivity.
inversion H.
inversion H. Qed.
Theorem not_eq_beq_false : forall n n' : nat,
n <> n' ->
beq_nat n n' = false.
Proof.
(* An exercise in Logic.v *)
Admitted.
Theorem ex_falso_quodlibet : forall (P:Prop),
False -> P.
Proof.
intros P contra.
inversion contra. Qed.
Theorem ev_not_ev_S : forall n,
ev n -> ~ ev (S n).
Proof.
(* An exercise in Logic.v *)
Admitted.
Theorem ble_nat_true : forall n m,
ble_nat n m = true -> n <= m.
(* An exercise in Logic.v *)
Admitted.
Theorem ble_nat_false : forall n m,
ble_nat n m = false -> ~(n <= m).
(* An exercise in Logic.v *)
Admitted.
Inductive appears_in (n : nat) : list nat -> Prop :=
| ai_here : forall l, appears_in n (n::l)
| ai_later : forall m l, appears_in n l -> appears_in n (m::l).
Inductive next_nat (n:nat) : nat -> Prop :=
| nn : next_nat n (S n).
Inductive total_relation : nat -> nat -> Prop :=
tot : forall n m : nat, total_relation n m.
Inductive empty_relation : nat -> nat -> Prop := .
(** * From Later Files *)
Definition relation (X:Type) := X -> X -> Prop.
Definition deterministic {X: Type} (R: relation X) :=
forall x y1 y2 : X, R x y1 -> R x y2 -> y1 = y2.
Inductive multi (X:Type) (R: relation X)
: X -> X -> Prop :=
| multi_refl : forall (x : X),
multi X R x x
| multi_step : forall (x y z : X),
R x y ->
multi X R y z ->
multi X R x z.
Implicit Arguments multi [[X]].
Tactic Notation "multi_cases" tactic(first) ident(c) :=
first;
[ Case_aux c "multi_refl" | Case_aux c "multi_step" ].
Theorem multi_R : forall (X:Type) (R:relation X) (x y : X),
R x y -> multi R x y.
Proof.
intros X R x y r.
apply multi_step with y. apply r. apply multi_refl. Qed.
Theorem multi_trans :
forall (X:Type) (R: relation X) (x y z : X),
multi R x y ->
multi R y z ->
multi R x z.
Proof.
(* FILL IN HERE *) Admitted.
(* Identifiers and polymorphic partial maps. *)
Inductive id : Type :=
Id : nat -> id.
Definition beq_id id1 id2 :=
match (id1, id2) with
(Id n1, Id n2) => beq_nat n1 n2
end.
Theorem beq_id_refl : forall i,
true = beq_id i i.
Proof.
intros. destruct i.
apply beq_nat_refl. Qed.
Theorem beq_id_eq : forall i1 i2,
true = beq_id i1 i2 -> i1 = i2.
Proof.
intros i1 i2 H.
destruct i1. destruct i2.
apply beq_nat_eq in H. subst.
reflexivity. Qed.
Theorem beq_id_false_not_eq : forall i1 i2,
beq_id i1 i2 = false -> i1 <> i2.
Proof.
intros i1 i2 H.
destruct i1. destruct i2.
apply beq_nat_false in H.
intros C. apply H. inversion C. reflexivity. Qed.
Theorem not_eq_beq_id_false : forall i1 i2,
i1 <> i2 -> beq_id i1 i2 = false.
Proof.
intros i1 i2 H.
destruct i1. destruct i2.
assert (n <> n0).
intros C. subst. apply H. reflexivity.
apply not_eq_beq_false. assumption. Qed.
Theorem beq_id_sym: forall i1 i2,
beq_id i1 i2 = beq_id i2 i1.
Proof.
intros i1 i2. destruct i1. destruct i2. apply beq_nat_sym. Qed.
Definition partial_map (A:Type) := id -> option A.
Definition empty {A:Type} : partial_map A := (fun _ => None).
Definition extend {A:Type} (Gamma : partial_map A) (x:id) (T : A) :=
fun x' => if beq_id x x' then Some T else Gamma x'.
Lemma extend_eq : forall A (ctxt: partial_map A) x T,
(extend ctxt x T) x = Some T.
Proof.
intros. unfold extend. rewrite <- beq_id_refl. auto.
Qed.
Lemma extend_neq : forall A (ctxt: partial_map A) x1 T x2,
beq_id x2 x1 = false ->
(extend ctxt x2 T) x1 = ctxt x1.
Proof.
intros. unfold extend. rewrite H. auto.
Qed.
Lemma extend_shadow : forall A (ctxt: partial_map A) t1 t2 x1 x2,
extend (extend ctxt x2 t1) x2 t2 x1 = extend ctxt x2 t2 x1.
Proof with auto.
intros. unfold extend. destruct (beq_id x2 x1)...
Qed.
(** * Some useful tactics *)
Tactic Notation "solve_by_inversion_step" tactic(t) :=
match goal with
| H : _ |- _ => solve [ inversion H; subst; t ]
end
|| fail "because the goal is not solvable by inversion.".
Tactic Notation "solve" "by" "inversion" "1" :=
solve_by_inversion_step idtac.
Tactic Notation "solve" "by" "inversion" "2" :=
solve_by_inversion_step (solve by inversion 1).
Tactic Notation "solve" "by" "inversion" "3" :=
solve_by_inversion_step (solve by inversion 2).
Tactic Notation "solve" "by" "inversion" :=
solve by inversion 1.