SmallstepSmall-step Operational Semantics
Big-step Evaluation
Our semantics for Imp is written in the so-called "big-step" style...2 + 2 + 3 × 4 ==> 16
Small-step Evaluation
Small-step style: Alternatively, we can show how to "reduce" an expression to a simpler form by performing a single step of computation:2 + 2 + 3 × 4
--> 2 + 2 + 12
--> 4 + 12
--> 16 Advantages of the small-step style include:
- Finer-grained "abstract machine", closer to real
implementations
- Extends smoothly to concurrent languages and languages
with other sorts of computational effects.
- Separates divergence (nontermination) from stuckness (run-time error)
Inductive tm : Type :=
| C : nat → tm (* Constant *)
| P : tm → tm → tm. (* Plus *)
| C : nat → tm (* Constant *)
| P : tm → tm → tm. (* Plus *)
Fixpoint evalF (t : tm) : nat :=
match t with
| C n ⇒ n
| P t1 t2 ⇒ evalF t1 + evalF t2
end.
match t with
| C n ⇒ n
| P t1 t2 ⇒ evalF t1 + evalF t2
end.
Big-step evaluation as a relation
(E_Const) | |
C n ==> n |
t1 ==> n1 | |
t2 ==> n2 | (E_Plus) |
P t1 t2 ==> n1 + n2 |
Inductive eval : tm → nat → Prop :=
| E_Const : ∀ n,
C n ==> n
| E_Plus : ∀ t1 t2 n1 n2,
t1 ==> n1 →
t2 ==> n2 →
P t1 t2 ==> (n1 + n2)
Small-step evaluation relation
(ST_PlusConstConst) | |
P (C n1) (C n2) --> C (n1 + n2) |
t1 --> t1' | (ST_Plus1) |
P t1 t2 --> P t1' t2 |
t2 --> t2' | (ST_Plus2) |
P (C n1) t2 --> P (C n1) t2' |
- each step reduces the leftmost P node that is ready to go
- first rule tells how to rewrite this node
- second and third rules tell where to find it
- first rule tells how to rewrite this node
- constants are not related to anything (i.e., they do not step to anything)
Small-step evaluation in Coq
Inductive step : tm → tm → Prop :=
| ST_PlusConstConst : ∀ n1 n2,
P (C n1) (C n2) --> C (n1 + n2)
| ST_Plus1 : ∀ t1 t1' t2,
t1 --> t1' →
P t1 t2 --> P t1' t2
| ST_Plus2 : ∀ n1 t2 t2',
t2 --> t2' →
P (C n1) t2 --> P (C n1) t2'
Example test_step_1 :
P
(P (C 1) (C 3))
(P (C 2) (C 4))
-->
P
(C 4)
(P (C 2) (C 4)).
P
(P (C 1) (C 3))
(P (C 2) (C 4))
-->
P
(C 4)
(P (C 2) (C 4)).
Proof.
apply ST_Plus1. apply ST_PlusConstConst. Qed.
apply ST_Plus1. apply ST_PlusConstConst. Qed.
What does the following term step to?
P (P (C 1) (C 2)) (P (C 1) (C 2))
(1) C 6
(2) P (C 3) (P (C 1) (C 2))
(3) P (P (C 1) (C 2)) (C 3)
(4) P (C 3) (C 3)
(5) None of the above
_________________________________________________
Inductive step : tm → tm → Prop :=
| ST_PlusConstConst : ∀ n1 n2,
P (C n1) (C n2) --> C (n1 + n2)
| ST_Plus1 : ∀ t1 t1' t2,
t1 --> t1' →
P t1 t2 --> P t1' t2
| ST_Plus2 : ∀ n1 t2 t2',
t2 --> t2' →
P (C n1) t2 --> P (C n1) t2'
P (P (C 1) (C 2)) (P (C 1) (C 2))
_________________________________________________
Inductive step : tm → tm → Prop :=
| ST_PlusConstConst : ∀ n1 n2,
P (C n1) (C n2) --> C (n1 + n2)
| ST_Plus1 : ∀ t1 t1' t2,
t1 --> t1' →
P t1 t2 --> P t1' t2
| ST_Plus2 : ∀ n1 t2 t2',
t2 --> t2' →
P (C n1) t2 --> P (C n1) t2'
What about this one?
C 1
(1) C 1
(2) P (C 0) (C 1)
(3) None of the above
_________________________________________________
Inductive step : tm → tm → Prop :=
| ST_PlusConstConst : ∀ n1 n2,
P (C n1) (C n2) --> C (n1 + n2)
| ST_Plus1 : ∀ t1 t1' t2,
t1 --> t1' →
P t1 t2 --> P t1' t2
| ST_Plus2 : ∀ n1 t2 t2',
t2 --> t2' →
P (C n1) t2 --> P (C n1) t2'
C 1
_________________________________________________
Inductive step : tm → tm → Prop :=
| ST_PlusConstConst : ∀ n1 n2,
P (C n1) (C n2) --> C (n1 + n2)
| ST_Plus1 : ∀ t1 t1' t2,
t1 --> t1' →
P t1 t2 --> P t1' t2
| ST_Plus2 : ∀ n1 t2 t2',
t2 --> t2' →
P (C n1) t2 --> P (C n1) t2'
Relations
Definition relation (X : Type) := X → X → Prop.
The step relation --> is an example of a relation on tm.
One simple property of the --> relation is that, like the
big-step evaluation relation for Imp, it is deterministic.
Theorem: For each t, there is at most one t' such that t
steps to t' (t --> t' is provable).
Formally:
Determinism
Definition deterministic {X : Type} (R : relation X) :=
∀ x y1 y2 : X, R x y1 → R x y2 → y1 = y2.
Theorem step_deterministic:
deterministic step.
∀ x y1 y2 : X, R x y1 → R x y2 → y1 = y2.
Theorem step_deterministic:
deterministic step.
Proof.
unfold deterministic. intros x y1 y2 Hy1 Hy2.
generalize dependent y2.
induction Hy1; intros y2 Hy2.
- (* ST_PlusConstConst *) inversion Hy2; subst.
+ (* ST_PlusConstConst *) reflexivity.
+ (* ST_Plus1 *) inversion H2.
+ (* ST_Plus2 *) inversion H2.
- (* ST_Plus1 *) inversion Hy2; subst.
+ (* ST_PlusConstConst *)
inversion Hy1.
+ (* ST_Plus1 *)
apply IHHy1 in H2. rewrite H2. reflexivity.
+ (* ST_Plus2 *)
inversion Hy1.
- (* ST_Plus2 *) inversion Hy2; subst.
+ (* ST_PlusConstConst *)
inversion Hy1.
+ (* ST_Plus1 *) inversion H2.
+ (* ST_Plus2 *)
apply IHHy1 in H2. rewrite H2. reflexivity.
Qed.
unfold deterministic. intros x y1 y2 Hy1 Hy2.
generalize dependent y2.
induction Hy1; intros y2 Hy2.
- (* ST_PlusConstConst *) inversion Hy2; subst.
+ (* ST_PlusConstConst *) reflexivity.
+ (* ST_Plus1 *) inversion H2.
+ (* ST_Plus2 *) inversion H2.
- (* ST_Plus1 *) inversion Hy2; subst.
+ (* ST_PlusConstConst *)
inversion Hy1.
+ (* ST_Plus1 *)
apply IHHy1 in H2. rewrite H2. reflexivity.
+ (* ST_Plus2 *)
inversion Hy1.
- (* ST_Plus2 *) inversion Hy2; subst.
+ (* ST_PlusConstConst *)
inversion Hy1.
+ (* ST_Plus1 *) inversion H2.
+ (* ST_Plus2 *)
apply IHHy1 in H2. rewrite H2. reflexivity.
Qed.
Ltac solve_by_inverts n :=
match goal with | H : ?T ⊢ _ ⇒
match type of T with Prop ⇒
solve [
inversion H;
match n with S (S (?n')) ⇒ subst; solve_by_inverts (S n') end ]
end end.
Ltac solve_by_invert :=
solve_by_inverts 1.
match goal with | H : ?T ⊢ _ ⇒
match type of T with Prop ⇒
solve [
inversion H;
match n with S (S (?n')) ⇒ subst; solve_by_inverts (S n') end ]
end end.
Ltac solve_by_invert :=
solve_by_inverts 1.
Theorem step_deterministic_alt: deterministic step.
Proof.
intros x y1 y2 Hy1 Hy2.
generalize dependent y2.
induction Hy1; intros y2 Hy2;
inversion Hy2; subst; try solve_by_invert.
- (* ST_PlusConstConst *) reflexivity.
- (* ST_Plus1 *)
apply IHHy1 in H2. rewrite H2. reflexivity.
- (* ST_Plus2 *)
apply IHHy1 in H2. rewrite H2. reflexivity.
Qed.
Values
- At any moment, the state of the machine is a term.
- A step of the machine is an atomic unit of computation --
here, a single "add" operation.
- The halting states of the machine are ones where there is no more computation to be done.
- Take t as the starting state of the machine.
- Repeatedly use the --> relation to find a sequence of
machine states, starting with t, where each state steps to
the next.
- When no more reduction is possible, "read out" the final state of the machine as the result of execution.
Final states of the machine are terms of the form C n for some n. We call such terms values.
Inductive value : tm → Prop :=
| v_const : ∀ n, value (C n).
| v_const : ∀ n, value (C n).
(ST_PlusConstConst) | |
P (C n1) (C n2) --> C (n1 + n2) |
t1 --> t1' | (ST_Plus1) |
P t1 t2 --> P t1' t2 |
value v1 | |
t2 --> t2' | (ST_Plus2) |
P v1 t2 --> P v1 t2' |
Again, variable names carry important information:
- v1 ranges only over values
- t1 and t2 range over arbitrary terms
Here are the formal rules:
Inductive step : tm → tm → Prop :=
| ST_PlusConstConst : ∀ n1 n2,
P (C n1) (C n2)
--> C (n1 + n2)
| ST_Plus1 : ∀ t1 t1' t2,
t1 --> t1' →
P t1 t2 --> P t1' t2
| ST_Plus2 : ∀ v1 t2 t2',
value v1 → (* <--- n.b. *)
t2 --> t2' →
P v1 t2 --> P v1 t2'
Strong Progress and Normal Forms
Theorem strong_progress : ∀ t,
value t ∨ (∃ t', t --> t').
value t ∨ (∃ t', t --> t').
Proof.
induction t.
- (* C *) left. apply v_const.
- (* P *) right. destruct IHt1 as [IHt1 | [t1' Ht1] ].
+ (* l *) destruct IHt2 as [IHt2 | [t2' Ht2] ].
× (* l *) inversion IHt1. inversion IHt2.
∃ (C (n + n0)).
apply ST_PlusConstConst.
× (* r *)
∃ (P t1 t2').
apply ST_Plus2. apply IHt1. apply Ht2.
+ (* r *)
∃ (P t1' t2).
apply ST_Plus1. apply Ht1.
Qed.
induction t.
- (* C *) left. apply v_const.
- (* P *) right. destruct IHt1 as [IHt1 | [t1' Ht1] ].
+ (* l *) destruct IHt2 as [IHt2 | [t2' Ht2] ].
× (* l *) inversion IHt1. inversion IHt2.
∃ (C (n + n0)).
apply ST_PlusConstConst.
× (* r *)
∃ (P t1 t2').
apply ST_Plus2. apply IHt1. apply Ht2.
+ (* r *)
∃ (P t1' t2).
apply ST_Plus1. apply Ht1.
Qed.
Normal forms
Definition normal_form {X : Type}
(R : relation X) (t : X) : Prop :=
¬∃ t', R t t'.
(R : relation X) (t : X) : Prop :=
¬∃ t', R t t'.
Lemma value_is_nf : ∀ v,
value v → normal_form step v.
Lemma nf_is_value : ∀ t,
normal_form step t → value t.
value v → normal_form step v.
Proof.
unfold normal_form. intros v H. destruct H.
intros contra. destruct contra. inversion H.
Qed.
unfold normal_form. intros v H. destruct H.
intros contra. destruct contra. inversion H.
Qed.
Lemma nf_is_value : ∀ t,
normal_form step t → value t.
Proof. (* a corollary of strong_progress... *)
unfold normal_form. intros t H.
assert (G : value t ∨ ∃ t', t --> t').
{ apply strong_progress. }
destruct G as [G | G].
- (* l *) apply G.
- (* r *) exfalso. apply H. assumption.
Qed.
Corollary nf_same_as_value : ∀ t,
normal_form step t ↔ value t.
Proof.
split. apply nf_is_value. apply value_is_nf.
Qed.
unfold normal_form. intros t H.
assert (G : value t ∨ ∃ t', t --> t').
{ apply strong_progress. }
destruct G as [G | G].
- (* l *) apply G.
- (* r *) exfalso. apply H. assumption.
Qed.
Corollary nf_same_as_value : ∀ t,
normal_form step t ↔ value t.
Proof.
split. apply nf_is_value. apply value_is_nf.
Qed.
Why is this interesting?
Because value is a syntactic concept -- it is defined by looking
at the way a term is written -- while normal_form is a semantic
one -- it is defined by looking at how the term steps.
It is not obvious that these concepts should characterize the same
set of terms!
We might, for example, define value so that it
includes some terms that are not finished reducing.
Indeed, we could easily have written the definitions (incorrectly) so that they would not coincide.
Inductive value : tm → Prop :=
| v_const : ∀ n, value (C n)
| v_funny : ∀ t1 n2,
value (P t1 (C n2)). (* <--- *)
Using this wrong definition of value, how many different values
does the following term step to (in zero or more steps)?
P
(P (C 1) (C 2))
(C 3)
________________________________________
Inductive value : tm → Prop :=
| v_const : ∀ n, value (C n)
| v_funny : ∀ t1 n2,
value (P t1 (C n2)).
P
(P (C 1) (C 2))
(C 3)
________________________________________
Inductive value : tm → Prop :=
| v_const : ∀ n, value (C n)
| v_funny : ∀ t1 n2,
value (P t1 (C n2)).
How many different terms does the following term step to
in one step?
P (P (C 1) (C 2)) (P (C 3) (C 4))
________________________________________
Inductive value : tm → Prop :=
| v_const : ∀ n, value (C n)
| v_funny : ∀ t1 n2,
value (P t1 (C n2)).
P (P (C 1) (C 2)) (P (C 3) (C 4))
________________________________________
Inductive value : tm → Prop :=
| v_const : ∀ n, value (C n)
| v_funny : ∀ t1 n2,
value (P t1 (C n2)).
Lemma value_not_same_as_normal_form :
∃ v, value v ∧ ¬normal_form step v.
∃ v, value v ∧ ¬normal_form step v.
Proof.
(* FILL IN HERE *) Admitted.
(* FILL IN HERE *) Admitted.
Or we might (again, wrongly) define step so that it permits something designated as a value to reduce further.
Inductive value : tm → Prop :=
| v_const : ∀ n, value (C n). (* Original definition *)
Inductive step : tm → tm → Prop :=
| ST_Funny : ∀ n,
C n --> P (C n) (C 0) (* <--- NEW *)
| ST_PlusConstConst : ∀ n1 n2,
P (C n1) (C n2) --> C (n1 + n2)
| ST_Plus1 : ∀ t1 t1' t2,
t1 --> t1' →
P t1 t2 --> P t1' t2
| ST_Plus2 : ∀ v1 t2 t2',
value v1 →
t2 --> t2' →
P v1 t2 --> P v1 t2'
How many different terms does the following term step to (in
exactly one step)?
P (C 1) (C 3)
_______________________________________
Inductive step : tm → tm → Prop :=
| ST_Funny : ∀ n,
C n --> P (C n) (C 0)
| ST_PlusConstConst : ∀ n1 n2,
P (C n1) (C n2) --> C (n1 + n2)
| ST_Plus1 : ∀ t1 t1' t2,
t1 --> t1' →
P t1 t2 --> P t1' t2
| ST_Plus2 : ∀ v1 t2 t2',
value v1 →
t2 --> t2' →
P v1 t2 --> P v1 t2'
P (C 1) (C 3)
_______________________________________
Inductive step : tm → tm → Prop :=
| ST_Funny : ∀ n,
C n --> P (C n) (C 0)
| ST_PlusConstConst : ∀ n1 n2,
P (C n1) (C n2) --> C (n1 + n2)
| ST_Plus1 : ∀ t1 t1' t2,
t1 --> t1' →
P t1 t2 --> P t1' t2
| ST_Plus2 : ∀ v1 t2 t2',
value v1 →
t2 --> t2' →
P v1 t2 --> P v1 t2'
Lemma value_not_same_as_normal_form :
∃ v, value v ∧ ¬normal_form step v.
∃ v, value v ∧ ¬normal_form step v.
Proof.
(* FILL IN HERE *) Admitted.
(* FILL IN HERE *) Admitted.
Finally, we might define value and step so that there is some term that is not a value but that also cannot take a step.
Inductive value : tm → Prop :=
| v_const : ∀ n, value (C n).
Inductive step : tm → tm → Prop :=
| ST_PlusConstConst : ∀ n1 n2,
P (C n1) (C n2) --> C (n1 + n2)
| ST_Plus1 : ∀ t1 t1' t2,
t1 --> t1' →
P t1 t2 --> P t1' t2
(Note that ST_Plus2 is missing.)
How many terms does the following term step to (in one step)?
P (C 1) (P (C 1) (C 2))
_________________________________________
Inductive step : tm → tm → Prop :=
| ST_PlusConstConst : ∀ n1 n2,
P (C n1) (C n2) --> C (n1 + n2)
| ST_Plus1 : ∀ t1 t1' t2,
t1 --> t1' →
P t1 t2 --> P t1' t2
P (C 1) (P (C 1) (C 2))
_________________________________________
Inductive step : tm → tm → Prop :=
| ST_PlusConstConst : ∀ n1 n2,
P (C n1) (C n2) --> C (n1 + n2)
| ST_Plus1 : ∀ t1 t1' t2,
t1 --> t1' →
P t1 t2 --> P t1' t2
Lemma value_not_same_as_normal_form :
∃ t, ¬value t ∧ normal_form step t.
∃ t, ¬value t ∧ normal_form step t.
Proof.
(* FILL IN HERE *) Admitted.
(* FILL IN HERE *) Admitted.
Multi-Step Reduction
Inductive multi {X : Type} (R : relation X) : relation X :=
| multi_refl : ∀ (x : X), multi R x x
| multi_step : ∀ (x y z : X),
R x y →
multi R y z →
multi R x z.
| multi_refl : ∀ (x : X), multi R x x
| multi_step : ∀ (x y z : X),
R x y →
multi R y z →
multi R x z.
Full: (In the Rel chapter of Logical Foundations and
the Coq standard library, this relation is called
clos_refl_trans_1n. We give it a shorter name here for the sake
of readability.)
The effect of this definition is that multi R relates two elements x and y if
- x = y, or
- R x y, or
- there is some nonempty sequence z1, z2, ..., zn such that
R x z1
R z1 z2
...
R zn y.
We write -->* for the multi step relation on terms.
Notation " t '-->*' t' " := (multi step t t') (at level 40).
The relation multi R has several crucial properties.
Second, it contains R -- that is, single-step executions are a particular case of multi-step executions. (It is this fact that justifies the word "closure" in the term "multi-step closure of R.")
Theorem multi_R : ∀ (X : Type) (R : relation X) (x y : X),
R x y → (multi R) x y.
R x y → (multi R) x y.
Proof.
intros X R x y H.
apply multi_step with y. apply H. apply multi_refl.
Qed.
intros X R x y H.
apply multi_step with y. apply H. apply multi_refl.
Qed.
Theorem multi_trans :
∀ (X : Type) (R : relation X) (x y z : X),
multi R x y →
multi R y z →
multi R x z.
∀ (X : Type) (R : relation X) (x y z : X),
multi R x y →
multi R y z →
multi R x z.
Proof.
intros X R x y z G H.
induction G.
- (* multi_refl *) assumption.
- (* multi_step *)
apply multi_step with y. assumption.
apply IHG. assumption.
Qed.
intros X R x y z G H.
induction G.
- (* multi_refl *) assumption.
- (* multi_step *)
apply multi_step with y. assumption.
apply IHG. assumption.
Qed.
In particular, for the multi step relation on terms, if
t1 -->* t2 and t2 -->* t3, then t1 -->* t3.
Lemma test_multistep_1:
P
(P (C 0) (C 3))
(P (C 2) (C 4))
-->*
C ((0 + 3) + (2 + 4)).
P
(P (C 0) (C 3))
(P (C 2) (C 4))
-->*
C ((0 + 3) + (2 + 4)).
Proof.
apply multi_step with
(P (C (0 + 3))
(P (C 2) (C 4))).
{ apply ST_Plus1. apply ST_PlusConstConst. }
apply multi_step with
(P (C (0 + 3))
(C (2 + 4))).
{ apply ST_Plus2. apply v_const. apply ST_PlusConstConst. }
apply multi_R.
apply ST_PlusConstConst.
Qed.
apply multi_step with
(P (C (0 + 3))
(P (C 2) (C 4))).
{ apply ST_Plus1. apply ST_PlusConstConst. }
apply multi_step with
(P (C (0 + 3))
(C (2 + 4))).
{ apply ST_Plus2. apply v_const. apply ST_PlusConstConst. }
apply multi_R.
apply ST_PlusConstConst.
Qed.
Normal Forms Again
Definition step_normal_form := normal_form step.
Definition normal_form_of (t t' : tm) :=
(t -->* t' ∧ step_normal_form t').
Definition normal_form_of (t t' : tm) :=
(t -->* t' ∧ step_normal_form t').
Notice:
We say the step relation is normalizing.
- single-step reduction is deterministic
- so, if t can reach a normal form, then this normal form is unique
- so we can pronounce normal_form t t' as "t' is the normal form of t."
Indeed, something stronger is true (for this language):
- the reduction of any term t will eventually reach a normal form
Definition normalizing {X : Type} (R : relation X) :=
∀ t, ∃ t',
(multi R) t t' ∧ normal_form R t'.
∀ t, ∃ t',
(multi R) t t' ∧ normal_form R t'.
Lemma multistep_congr_1 : ∀ t1 t1' t2,
t1 -->* t1' →
P t1 t2 -->* P t1' t2.
Lemma multistep_congr_2 : ∀ t1 t2 t2',
value t1 →
t2 -->* t2' →
P t1 t2 -->* P t1 t2'.
t1 -->* t1' →
P t1 t2 -->* P t1' t2.
Proof.
intros t1 t1' t2 H. induction H.
- (* multi_refl *) apply multi_refl.
- (* multi_step *) apply multi_step with (P y t2).
+ apply ST_Plus1. apply H.
+ apply IHmulti.
Qed.
intros t1 t1' t2 H. induction H.
- (* multi_refl *) apply multi_refl.
- (* multi_step *) apply multi_step with (P y t2).
+ apply ST_Plus1. apply H.
+ apply IHmulti.
Qed.
Lemma multistep_congr_2 : ∀ t1 t2 t2',
value t1 →
t2 -->* t2' →
P t1 t2 -->* P t1 t2'.
Proof.
(* FILL IN HERE *) Admitted.
(* FILL IN HERE *) Admitted.
- t = C n for some n. Here t doesn't take a step, and we
have t' = t. We can derive the left-hand side by reflexivity
and the right-hand side by observing (a) that values are normal
forms (by nf_same_as_value) and (b) that t is a value (by
v_const).
- t = P t1 t2 for some t1 and t2. By the IH, t1 and t2
reduce to normal forms t1' and t2'. Recall that normal
forms are values (by nf_same_as_value); we therefore know that
t1' = C n1 and t2' = C n2, for some n1 and n2. We can
combine the -->* derivations for t1 and t2 using
multi_congr_1 and multi_congr_2 to prove that P t1 t2
reduces in many steps to t' = C (n1 + n2).
Equivalence of Big-Step and Small-Step
Theorem eval__multistep : ∀ t n,
t ==> n → t -->* C n.
t ==> n → t -->* C n.
The key ideas in the proof can be seen in the following picture:
P t1 t2 --> (by ST_Plus1)
P t1' t2 --> (by ST_Plus1)
P t1'' t2 --> (by ST_Plus1)
...
P (C n1) t2 --> (by ST_Plus2)
P (C n1) t2' --> (by ST_Plus2)
P (C n1) t2'' --> (by ST_Plus2)
...
P (C n1) (C n2) --> (by ST_PlusConstConst)
C (n1 + n2) That is, the multistep reduction of a term of the form P t1 t2 proceeds in three phases:
- First, we use ST_Plus1 some number of times to reduce t1 to a normal form, which must (by nf_same_as_value) be a term of the form C n1 for some n1.
- Next, we use ST_Plus2 some number of times to reduce t2 to a normal form, which must again be a term of the form C n2 for some n2.
- Finally, we use ST_PlusConstConst one time to reduce P (C n1) (C n2) to C (n1 + n2).
Proof.
(* FILL IN HERE *) Admitted.
(* FILL IN HERE *) Admitted.
For the other direction, we need one lemma, which establishes a relation between single-step reduction and big-step evaluation.
Lemma step__eval : ∀ t t' n,
t --> t' →
t' ==> n →
t ==> n.
t --> t' →
t' ==> n →
t ==> n.
Proof.
intros t t' n Hs. generalize dependent n.
(* FILL IN HERE *) Admitted.
intros t t' n Hs. generalize dependent n.
(* FILL IN HERE *) Admitted.
The fact that small-step reduction implies big-step evaluation is now
straightforward to prove.
The proof proceeds by induction on the multi-step reduction
sequence that is buried in the hypothesis normal_form_of t t'.
Theorem multistep__eval : ∀ t t',
normal_form_of t t' → ∃ n, t' = C n ∧ t ==> n.
normal_form_of t t' → ∃ n, t' = C n ∧ t ==> n.
Proof.
(* FILL IN HERE *) Admitted.
(* FILL IN HERE *) Admitted.
Small-Step Imp
Inductive aval : aexp → Prop :=
| av_num : ∀ n, aval (ANum n).
| av_num : ∀ n, aval (ANum n).
Small-step evaluation relation for arithmetic expressions
(AS_Id) | |
i / st --> (st i) |
a1 / st --> a1' | (AS_Plus1) |
a1 + a2 / st --> a1' + a2 |
aval v1 a2 / st --> a2' | (AS_Plus2) |
v1 + a2 / st --> v1 + a2' |
(AS_Plus) | |
n1 + n2 / st --> (n1 + n2) |
a1 / st --> a1' | (AS_Minus1) |
a1 - a2 / st --> a1' - a2 |
aval v1 a2 / st --> a2' | (AS_Minus2) |
v1 - a2 / st --> v1 - a2' |
(AS_Minus) | |
n1 - n2 / st --> (n1 - n2) |
a1 / st --> a1' | (AS_Mult1) |
a1 * a2 / st --> a1' * a2 |
aval v1 a2 / st --> a2' | (AS_Mult2) |
v1 * a2 / st --> v1 * a2' |
(AS_Mult) | |
n1 * n2 / st --> (n1 * n2) |
In Coq
Reserved Notation " a '/' st '-->a' a' "
(at level 40, st at level 39).
Inductive astep (st : state) : aexp → aexp → Prop :=
| AS_Id : ∀ (i : string),
i / st -->a (st i)
| AS_Plus1 : ∀ a1 a1' a2,
a1 / st -->a a1' →
<{ a1 + a2 }> / st -->a <{ a1' + a2 }>
| AS_Plus2 : ∀ v1 a2 a2',
aval v1 →
a2 / st -->a a2' →
<{ v1 + a2 }> / st -->a <{ v1 + a2' }>
| AS_Plus : ∀ (n1 n2 : nat),
<{ n1 + n2 }> / st -->a (n1 + n2)
| AS_Minus1 : ∀ a1 a1' a2,
a1 / st -->a a1' →
<{ a1 - a2 }> / st -->a <{ a1' - a2 }>
| AS_Minus2 : ∀ v1 a2 a2',
aval v1 →
a2 / st -->a a2' →
<{ v1 - a2 }> / st -->a <{ v1 - a2' }>
| AS_Minus : ∀ (n1 n2 : nat),
<{ n1 - n2 }> / st -->a (n1 - n2)
| AS_Mult1 : ∀ a1 a1' a2,
a1 / st -->a a1' →
<{ a1 × a2 }> / st -->a <{ a1' × a2 }>
| AS_Mult2 : ∀ v1 a2 a2',
aval v1 →
a2 / st -->a a2' →
<{ v1 × a2 }> / st -->a <{ v1 × a2' }>
| AS_Mult : ∀ (n1 n2 : nat),
<{ n1 × n2 }> / st -->a (n1 × n2)
where " a '/' st '-->a' a' " := (astep st a a').
(at level 40, st at level 39).
Inductive astep (st : state) : aexp → aexp → Prop :=
| AS_Id : ∀ (i : string),
i / st -->a (st i)
| AS_Plus1 : ∀ a1 a1' a2,
a1 / st -->a a1' →
<{ a1 + a2 }> / st -->a <{ a1' + a2 }>
| AS_Plus2 : ∀ v1 a2 a2',
aval v1 →
a2 / st -->a a2' →
<{ v1 + a2 }> / st -->a <{ v1 + a2' }>
| AS_Plus : ∀ (n1 n2 : nat),
<{ n1 + n2 }> / st -->a (n1 + n2)
| AS_Minus1 : ∀ a1 a1' a2,
a1 / st -->a a1' →
<{ a1 - a2 }> / st -->a <{ a1' - a2 }>
| AS_Minus2 : ∀ v1 a2 a2',
aval v1 →
a2 / st -->a a2' →
<{ v1 - a2 }> / st -->a <{ v1 - a2' }>
| AS_Minus : ∀ (n1 n2 : nat),
<{ n1 - n2 }> / st -->a (n1 - n2)
| AS_Mult1 : ∀ a1 a1' a2,
a1 / st -->a a1' →
<{ a1 × a2 }> / st -->a <{ a1' × a2 }>
| AS_Mult2 : ∀ v1 a2 a2',
aval v1 →
a2 / st -->a a2' →
<{ v1 × a2 }> / st -->a <{ v1 × a2' }>
| AS_Mult : ∀ (n1 n2 : nat),
<{ n1 × n2 }> / st -->a (n1 × n2)
where " a '/' st '-->a' a' " := (astep st a a').
Small-step evaluation relation for boolean expressions
a1 / st --> a1' | (BS_Eq1) |
a1 = a2 / st --> a1' = a2 |
aval v1 a2 / st --> a2' | (BS_Eq2) |
v1 = a2 / st --> v1 = a2' |
(BS_Eq) | |
n1 = n2 / st --> (if (n1 =? n2) then true else false) |
a1 / st --> a1' | (BS_LtEq1) |
a1 <= a2 / st --> a1' <= a2 |
aval v1 a2 / st --> a2' | (BS_LtEq2) |
v1 <= a2 / st --> v1 <= a2' |
(BS_LtEq) | |
n1 <= n2 / st --> (if (n1 <=? n2) then true else false) |
b1 / st --> b1' | (BS_NotStep) |
~b1 / st --> ~b1' |
(BS_NotTrue) | |
~ true / st --> false |
(BS_NotFalse) | |
~ false / st --> true |
b1 / st --> b1' | (BS_AndStep) |
b1 && b2 / st --> b1' && b2 |
b2 / st --> b2' | (BS_AndTrueStep) |
true && b2 / st --> true && b2' |
(BS_AndFalse) | |
false && b2 / st --> false |
(BS_AndTrueTrue) | |
true && true / st --> true |
(BS_AndTrueFalse) | |
true && false / st --> false |
In Coq
Reserved Notation " b '/' st '-->b' b' "
(at level 40, st at level 39).
Inductive bstep (st : state) : bexp → bexp → Prop :=
| BS_Eq1 : ∀ a1 a1' a2,
a1 / st -->a a1' →
<{ a1 = a2 }> / st -->b <{ a1' = a2 }>
| BS_Eq2 : ∀ v1 a2 a2',
aval v1 →
a2 / st -->a a2' →
<{ v1 = a2 }> / st -->b <{ v1 = a2' }>
| BS_Eq : ∀ (n1 n2 : nat),
<{ n1 = n2 }> / st -->b
(if (n1 =? n2) then <{ true }> else <{ false }>)
| BS_LtEq1 : ∀ a1 a1' a2,
a1 / st -->a a1' →
<{ a1 ≤ a2 }> / st -->b <{ a1' ≤ a2 }>
| BS_LtEq2 : ∀ v1 a2 a2',
aval v1 →
a2 / st -->a a2' →
<{ v1 ≤ a2 }> / st -->b <{ v1 ≤ a2' }>
| BS_LtEq : ∀ (n1 n2 : nat),
<{ n1 ≤ n2 }> / st -->b
(if (n1 <=? n2) then <{ true }> else <{ false }>)
| BS_NotStep : ∀ b1 b1',
b1 / st -->b b1' →
<{ ¬b1 }> / st -->b <{ ¬b1' }>
| BS_NotTrue : <{ ¬true }> / st -->b <{ false }>
| BS_NotFalse : <{ ¬false }> / st -->b <{ true }>
| BS_AndStep : ∀ b1 b1' b2,
b1 / st -->b b1' →
<{ b1 && b2 }> / st -->b <{ b1' && b2 }>
| BS_AndTrueStep : ∀ b2 b2',
b2 / st -->b b2' →
<{ true && b2 }> / st -->b <{ true && b2' }>
| BS_AndFalse : ∀ b2,
<{ false && b2 }> / st -->b <{ false }>
| BS_AndTrueTrue : <{ true && true }> / st -->b <{ true }>
| BS_AndTrueFalse : <{ true && false }> / st -->b <{ false }>
where " b '/' st '-->b' b' " := (bstep st b b').
(at level 40, st at level 39).
Inductive bstep (st : state) : bexp → bexp → Prop :=
| BS_Eq1 : ∀ a1 a1' a2,
a1 / st -->a a1' →
<{ a1 = a2 }> / st -->b <{ a1' = a2 }>
| BS_Eq2 : ∀ v1 a2 a2',
aval v1 →
a2 / st -->a a2' →
<{ v1 = a2 }> / st -->b <{ v1 = a2' }>
| BS_Eq : ∀ (n1 n2 : nat),
<{ n1 = n2 }> / st -->b
(if (n1 =? n2) then <{ true }> else <{ false }>)
| BS_LtEq1 : ∀ a1 a1' a2,
a1 / st -->a a1' →
<{ a1 ≤ a2 }> / st -->b <{ a1' ≤ a2 }>
| BS_LtEq2 : ∀ v1 a2 a2',
aval v1 →
a2 / st -->a a2' →
<{ v1 ≤ a2 }> / st -->b <{ v1 ≤ a2' }>
| BS_LtEq : ∀ (n1 n2 : nat),
<{ n1 ≤ n2 }> / st -->b
(if (n1 <=? n2) then <{ true }> else <{ false }>)
| BS_NotStep : ∀ b1 b1',
b1 / st -->b b1' →
<{ ¬b1 }> / st -->b <{ ¬b1' }>
| BS_NotTrue : <{ ¬true }> / st -->b <{ false }>
| BS_NotFalse : <{ ¬false }> / st -->b <{ true }>
| BS_AndStep : ∀ b1 b1' b2,
b1 / st -->b b1' →
<{ b1 && b2 }> / st -->b <{ b1' && b2 }>
| BS_AndTrueStep : ∀ b2 b2',
b2 / st -->b b2' →
<{ true && b2 }> / st -->b <{ true && b2' }>
| BS_AndFalse : ∀ b2,
<{ false && b2 }> / st -->b <{ false }>
| BS_AndTrueTrue : <{ true && true }> / st -->b <{ true }>
| BS_AndTrueFalse : <{ true && false }> / st -->b <{ false }>
where " b '/' st '-->b' b' " := (bstep st b b').
- We use skip as a "command value" -- i.e., a command that
has reached a normal form.
- An assignment command reduces to skip (and an updated
state).
- The sequencing command waits until its left-hand
subcommand has reduced to skip, then throws it away so
that reduction can continue with the right-hand
subcommand.
- An assignment command reduces to skip (and an updated
state).
- We reduce a while command by transforming it into a conditional followed by the same while.
Small-step evaluation relation for commands
a1 / st --> a1' | (CS_AsgnStep) |
i := a1 / st --> i := a1' / st |
(CS_Asgn) | |
i := n / st --> skip / (i !-> n ; st) |
c1 / st --> c1' / st' | (CS_SeqStep) |
c1 ; c2 / st --> c1' ; c2 / st' |
(CS_SeqFinish) | |
skip ; c2 / st --> c2 / st |
b1 / st --> b1' | (CS_IfStep) |
if b1 then c1 else c2 end / st --> | |
if b1' then c1 else c2 end / st |
(CS_IfTrue) | |
if true then c1 else c2 end / st --> c1 / st |
(CS_IfFalse) | |
if false then c1 else c2 end / st --> c2 / st |
(CS_While) | |
while b1 do c1 end / st --> | |
if b1 then (c1; while b1 do c1 end) else skip end / st |
In Coq
Reserved Notation " t '/' st '-->' t' '/' st' "
(at level 40, st at level 39, t' at level 39).
Inductive cstep : (com × state) → (com × state) → Prop :=
| CS_AsgnStep : ∀ st i a1 a1',
a1 / st -->a a1' →
<{ i := a1 }> / st --> <{ i := a1' }> / st
| CS_Asgn : ∀ st i (n : nat),
<{ i := n }> / st --> <{ skip }> / (i !-> n ; st)
| CS_SeqStep : ∀ st c1 c1' st' c2,
c1 / st --> c1' / st' →
<{ c1 ; c2 }> / st --> <{ c1' ; c2 }> / st'
| CS_SeqFinish : ∀ st c2,
<{ skip ; c2 }> / st --> c2 / st
| CS_IfStep : ∀ st b1 b1' c1 c2,
b1 / st -->b b1' →
<{ if b1 then c1 else c2 end }> / st
-->
<{ if b1' then c1 else c2 end }> / st
| CS_IfTrue : ∀ st c1 c2,
<{ if true then c1 else c2 end }> / st --> c1 / st
| CS_IfFalse : ∀ st c1 c2,
<{ if false then c1 else c2 end }> / st --> c2 / st
| CS_While : ∀ st b1 c1,
<{ while b1 do c1 end }> / st
-->
<{ if b1 then c1; while b1 do c1 end else skip end }> / st
where " t '/' st '-->' t' '/' st' " := (cstep (t,st) (t',st')).
(at level 40, st at level 39, t' at level 39).
Inductive cstep : (com × state) → (com × state) → Prop :=
| CS_AsgnStep : ∀ st i a1 a1',
a1 / st -->a a1' →
<{ i := a1 }> / st --> <{ i := a1' }> / st
| CS_Asgn : ∀ st i (n : nat),
<{ i := n }> / st --> <{ skip }> / (i !-> n ; st)
| CS_SeqStep : ∀ st c1 c1' st' c2,
c1 / st --> c1' / st' →
<{ c1 ; c2 }> / st --> <{ c1' ; c2 }> / st'
| CS_SeqFinish : ∀ st c2,
<{ skip ; c2 }> / st --> c2 / st
| CS_IfStep : ∀ st b1 b1' c1 c2,
b1 / st -->b b1' →
<{ if b1 then c1 else c2 end }> / st
-->
<{ if b1' then c1 else c2 end }> / st
| CS_IfTrue : ∀ st c1 c2,
<{ if true then c1 else c2 end }> / st --> c1 / st
| CS_IfFalse : ∀ st c1 c2,
<{ if false then c1 else c2 end }> / st --> c2 / st
| CS_While : ∀ st b1 c1,
<{ while b1 do c1 end }> / st
-->
<{ if b1 then c1; while b1 do c1 end else skip end }> / st
where " t '/' st '-->' t' '/' st' " := (cstep (t,st) (t',st')).
Concurrent Imp
Inductive com : Type :=
| CSkip : com
| CAsgn : string → aexp → com
| CSeq : com → com → com
| CIf : bexp → com → com → com
| CWhile : bexp → com → com
| CPar : com → com → com. (* <--- NEW *)
| CSkip : com
| CAsgn : string → aexp → com
| CSeq : com → com → com
| CIf : bexp → com → com → com
| CWhile : bexp → com → com
| CPar : com → com → com. (* <--- NEW *)
Notation "x || y" :=
(CPar x y)
(in custom com at level 90, right associativity).
Notation "'skip'" :=
CSkip (in custom com at level 0).
Notation "x := y" :=
(CAsgn x y)
(in custom com at level 0, x constr at level 0,
y at level 85, no associativity).
Notation "x ; y" :=
(CSeq x y)
(in custom com at level 90, right associativity).
Notation "'if' x 'then' y 'else' z 'end'" :=
(CIf x y z)
(in custom com at level 89, x at level 99,
y at level 99, z at level 99).
Notation "'while' x 'do' y 'end'" :=
(CWhile x y)
(in custom com at level 89, x at level 99, y at level 99).
(CPar x y)
(in custom com at level 90, right associativity).
Notation "'skip'" :=
CSkip (in custom com at level 0).
Notation "x := y" :=
(CAsgn x y)
(in custom com at level 0, x constr at level 0,
y at level 85, no associativity).
Notation "x ; y" :=
(CSeq x y)
(in custom com at level 90, right associativity).
Notation "'if' x 'then' y 'else' z 'end'" :=
(CIf x y z)
(in custom com at level 89, x at level 99,
y at level 99, z at level 99).
Notation "'while' x 'do' y 'end'" :=
(CWhile x y)
(in custom com at level 89, x at level 99, y at level 99).
New small-step evaluation relation for commands
c1 / st --> c1' / st' | (CS_Par1) |
c1 || c2 / st --> c1' || c2 / st' |
c2 / st --> c2' / st' | (CS_Par2) |
c1 || c2 / st --> c1 || c2' / st' |
(CS_ParDone) | |
skip || skip / st --> skip / st |
In Coq
Inductive cstep : (com × state) → (com × state) → Prop :=
(* Old part: *)
| CS_AsgnStep : ∀ st i a1 a1',
a1 / st -->a a1' →
<{ i := a1 }> / st --> <{ i := a1' }> / st
| CS_Asgn : ∀ st i (n : nat),
<{ i := n }> / st --> <{ skip }> / (i !-> n ; st)
| CS_SeqStep : ∀ st c1 c1' st' c2,
c1 / st --> c1' / st' →
<{ c1 ; c2 }> / st --> <{ c1' ; c2 }> / st'
| CS_SeqFinish : ∀ st c2,
<{ skip ; c2 }> / st --> c2 / st
| CS_IfStep : ∀ st b1 b1' c1 c2,
b1 / st -->b b1' →
<{ if b1 then c1 else c2 end }> / st
-->
<{ if b1' then c1 else c2 end }> / st
| CS_IfTrue : ∀ st c1 c2,
<{ if true then c1 else c2 end }> / st --> c1 / st
| CS_IfFalse : ∀ st c1 c2,
<{ if false then c1 else c2 end }> / st --> c2 / st
| CS_While : ∀ st b1 c1,
<{ while b1 do c1 end }> / st
-->
<{ if b1 then c1; while b1 do c1 end else skip end }> / st
(* New part: *)
| CS_Par1 : ∀ st c1 c1' c2 st',
c1 / st --> c1' / st' →
<{ c1 || c2 }> / st --> <{ c1' || c2 }> / st'
| CS_Par2 : ∀ st c1 c2 c2' st',
c2 / st --> c2' / st' →
<{ c1 || c2 }> / st --> <{ c1 || c2' }> / st'
| CS_ParDone : ∀ st,
<{ skip || skip }> / st --> <{ skip }> / st
where " t '/' st '-->' t' '/' st' " := (cstep (t,st) (t',st')).
(* Old part: *)
| CS_AsgnStep : ∀ st i a1 a1',
a1 / st -->a a1' →
<{ i := a1 }> / st --> <{ i := a1' }> / st
| CS_Asgn : ∀ st i (n : nat),
<{ i := n }> / st --> <{ skip }> / (i !-> n ; st)
| CS_SeqStep : ∀ st c1 c1' st' c2,
c1 / st --> c1' / st' →
<{ c1 ; c2 }> / st --> <{ c1' ; c2 }> / st'
| CS_SeqFinish : ∀ st c2,
<{ skip ; c2 }> / st --> c2 / st
| CS_IfStep : ∀ st b1 b1' c1 c2,
b1 / st -->b b1' →
<{ if b1 then c1 else c2 end }> / st
-->
<{ if b1' then c1 else c2 end }> / st
| CS_IfTrue : ∀ st c1 c2,
<{ if true then c1 else c2 end }> / st --> c1 / st
| CS_IfFalse : ∀ st c1 c2,
<{ if false then c1 else c2 end }> / st --> c2 / st
| CS_While : ∀ st b1 c1,
<{ while b1 do c1 end }> / st
-->
<{ if b1 then c1; while b1 do c1 end else skip end }> / st
(* New part: *)
| CS_Par1 : ∀ st c1 c1' c2 st',
c1 / st --> c1' / st' →
<{ c1 || c2 }> / st --> <{ c1' || c2 }> / st'
| CS_Par2 : ∀ st c1 c2 c2' st',
c2 / st --> c2' / st' →
<{ c1 || c2 }> / st --> <{ c1 || c2' }> / st'
| CS_ParDone : ∀ st,
<{ skip || skip }> / st --> <{ skip }> / st
where " t '/' st '-->' t' '/' st' " := (cstep (t,st) (t',st')).
Definition cmultistep := multi cstep.
Notation " t '/' st '-->*' t' '/' st' " :=
(multi cstep (t,st) (t',st'))
(at level 40, st at level 39, t' at level 39).
Notation " t '/' st '-->*' t' '/' st' " :=
(multi cstep (t,st) (t',st'))
(at level 40, st at level 39, t' at level 39).
Which state cannot be obtained as a result of executing the
following program (from some starting state)?
(Y := 1 || Y := 2);
X := Y
(1) Y=0 and X=0
(2) Y=1 and X=1
(3) Y=2 and X=2
(4) None of the above
(Y := 1 || Y := 2);
X := Y
Which state cannot be obtained as a result of executing the
following program (from some starting state)?
(Y := 1 || Y := Y + 1);
X := Y
(1) Y=1 and X=1
(2) Y=0 and X=1
(3) Y=2 and X=2
(4) Y=n and X=n for any n ≥ 1
(5) 2 and 4 above
(6) None of the above
(Y := 1 || Y := Y + 1);
X := Y
How about this one?
( Y := 0; X := Y + 1 ) || ( Y := Y + 1; X := 1 )
(1) Y=0 and X=1
(2) Y=1 and X=1
(3) Y=0 and X=0
(4) None of the above
( Y := 0; X := Y + 1 ) || ( Y := Y + 1; X := 1 )
Among the many interesting properties of this language is the fact that the following program can terminate with the variable X set to any value.
Definition par_loop : com :=
<{ Y := 1 || while (Y = 0) do X := X + 1 end }>.
<{ Y := 1 || while (Y = 0) do X := X + 1 end }>.
Example par_loop_example_0:
∃ st',
par_loop / empty_st -->* <{skip}> / st'
∧ st' X = 0.
∃ st',
par_loop / empty_st -->* <{skip}> / st'
∧ st' X = 0.
Proof.
unfold par_loop.
eexists. split.
eapply multi_step. apply CS_Par1.
apply CS_Asgn.
eapply multi_step. apply CS_Par2. apply CS_While.
eapply multi_step. apply CS_Par2. apply CS_IfStep.
apply BS_Eq1. apply AS_Id.
eapply multi_step. apply CS_Par2. apply CS_IfStep.
apply BS_Eq. simpl.
eapply multi_step. apply CS_Par2. apply CS_IfFalse.
eapply multi_step. apply CS_ParDone.
eapply multi_refl.
reflexivity.
Qed.
unfold par_loop.
eexists. split.
eapply multi_step. apply CS_Par1.
apply CS_Asgn.
eapply multi_step. apply CS_Par2. apply CS_While.
eapply multi_step. apply CS_Par2. apply CS_IfStep.
apply BS_Eq1. apply AS_Id.
eapply multi_step. apply CS_Par2. apply CS_IfStep.
apply BS_Eq. simpl.
eapply multi_step. apply CS_Par2. apply CS_IfFalse.
eapply multi_step. apply CS_ParDone.
eapply multi_refl.
reflexivity.
Qed.
It can also terminate with X set to 2:
Example par_loop_example_2:
∃ st',
par_loop / empty_st -->* <{skip}> / st'
∧ st' X = 2.
∃ st',
par_loop / empty_st -->* <{skip}> / st'
∧ st' X = 2.
Proof.
unfold par_loop.
eexists. split.
eapply multi_step. apply CS_Par2. apply CS_While.
eapply multi_step. apply CS_Par2. apply CS_IfStep.
apply BS_Eq1. apply AS_Id.
eapply multi_step. apply CS_Par2. apply CS_IfStep.
apply BS_Eq. simpl.
eapply multi_step. apply CS_Par2. apply CS_IfTrue.
eapply multi_step. apply CS_Par2. apply CS_SeqStep.
apply CS_AsgnStep. apply AS_Plus1. apply AS_Id.
eapply multi_step. apply CS_Par2. apply CS_SeqStep.
apply CS_AsgnStep. apply AS_Plus.
eapply multi_step. apply CS_Par2. apply CS_SeqStep.
apply CS_Asgn.
eapply multi_step. apply CS_Par2. apply CS_SeqFinish.
eapply multi_step. apply CS_Par2. apply CS_While.
eapply multi_step. apply CS_Par2. apply CS_IfStep.
apply BS_Eq1. apply AS_Id.
eapply multi_step. apply CS_Par2. apply CS_IfStep.
apply BS_Eq. simpl.
eapply multi_step. apply CS_Par2. apply CS_IfTrue.
eapply multi_step. apply CS_Par2. apply CS_SeqStep.
apply CS_AsgnStep. apply AS_Plus1. apply AS_Id.
eapply multi_step. apply CS_Par2. apply CS_SeqStep.
apply CS_AsgnStep. apply AS_Plus.
eapply multi_step. apply CS_Par2. apply CS_SeqStep.
apply CS_Asgn.
eapply multi_step. apply CS_Par1. apply CS_Asgn.
eapply multi_step. apply CS_Par2. apply CS_SeqFinish.
eapply multi_step. apply CS_Par2. apply CS_While.
eapply multi_step. apply CS_Par2. apply CS_IfStep.
apply BS_Eq1. apply AS_Id.
eapply multi_step. apply CS_Par2. apply CS_IfStep.
apply BS_Eq. simpl.
eapply multi_step. apply CS_Par2. apply CS_IfFalse.
eapply multi_step. apply CS_ParDone.
eapply multi_refl.
reflexivity. Qed.
unfold par_loop.
eexists. split.
eapply multi_step. apply CS_Par2. apply CS_While.
eapply multi_step. apply CS_Par2. apply CS_IfStep.
apply BS_Eq1. apply AS_Id.
eapply multi_step. apply CS_Par2. apply CS_IfStep.
apply BS_Eq. simpl.
eapply multi_step. apply CS_Par2. apply CS_IfTrue.
eapply multi_step. apply CS_Par2. apply CS_SeqStep.
apply CS_AsgnStep. apply AS_Plus1. apply AS_Id.
eapply multi_step. apply CS_Par2. apply CS_SeqStep.
apply CS_AsgnStep. apply AS_Plus.
eapply multi_step. apply CS_Par2. apply CS_SeqStep.
apply CS_Asgn.
eapply multi_step. apply CS_Par2. apply CS_SeqFinish.
eapply multi_step. apply CS_Par2. apply CS_While.
eapply multi_step. apply CS_Par2. apply CS_IfStep.
apply BS_Eq1. apply AS_Id.
eapply multi_step. apply CS_Par2. apply CS_IfStep.
apply BS_Eq. simpl.
eapply multi_step. apply CS_Par2. apply CS_IfTrue.
eapply multi_step. apply CS_Par2. apply CS_SeqStep.
apply CS_AsgnStep. apply AS_Plus1. apply AS_Id.
eapply multi_step. apply CS_Par2. apply CS_SeqStep.
apply CS_AsgnStep. apply AS_Plus.
eapply multi_step. apply CS_Par2. apply CS_SeqStep.
apply CS_Asgn.
eapply multi_step. apply CS_Par1. apply CS_Asgn.
eapply multi_step. apply CS_Par2. apply CS_SeqFinish.
eapply multi_step. apply CS_Par2. apply CS_While.
eapply multi_step. apply CS_Par2. apply CS_IfStep.
apply BS_Eq1. apply AS_Id.
eapply multi_step. apply CS_Par2. apply CS_IfStep.
apply BS_Eq. simpl.
eapply multi_step. apply CS_Par2. apply CS_IfFalse.
eapply multi_step. apply CS_ParDone.
eapply multi_refl.
reflexivity. Qed.
Example step_example1 :
(P (C 3) (P (C 3) (C 4)))
-->* (C 10).
Proof.
apply multi_step with (P (C 3) (C 7)).
apply ST_Plus2.
apply v_const.
apply ST_PlusConstConst.
apply multi_step with (C 10).
apply ST_PlusConstConst.
apply multi_refl.
Qed.
(P (C 3) (P (C 3) (C 4)))
-->* (C 10).
Proof.
apply multi_step with (P (C 3) (C 7)).
apply ST_Plus2.
apply v_const.
apply ST_PlusConstConst.
apply multi_step with (C 10).
apply ST_PlusConstConst.
apply multi_refl.
Qed.
Hint Constructors step value : core.
Example step_example1' :
(P (C 3) (P (C 3) (C 4)))
-->* (C 10).
Proof.
eapply multi_step. auto. simpl.
eapply multi_step. auto. simpl.
apply multi_refl.
Qed.
Example step_example1' :
(P (C 3) (P (C 3) (C 4)))
-->* (C 10).
Proof.
eapply multi_step. auto. simpl.
eapply multi_step. auto. simpl.
apply multi_refl.
Qed.
Tactic Notation "print_goal" :=
match goal with ⊢ ?x ⇒ idtac x end.
Tactic Notation "normalize" :=
repeat (print_goal; eapply multi_step ;
[ (eauto 10; fail) | (instantiate; simpl)]);
apply multi_refl.
match goal with ⊢ ?x ⇒ idtac x end.
Tactic Notation "normalize" :=
repeat (print_goal; eapply multi_step ;
[ (eauto 10; fail) | (instantiate; simpl)]);
apply multi_refl.
Example step_example1'' :
(P (C 3) (P (C 3) (C 4)))
-->* (C 10).
Proof.
normalize.
(* The print_goal in the normalize tactic shows
a trace of how the expression reduced...
(P (C 3) (P (C 3) (C 4)) -->* C 10)
(P (C 3) (C 7) -->* C 10)
(C 10 -->* C 10)
*)
Qed.
(P (C 3) (P (C 3) (C 4)))
-->* (C 10).
Proof.
normalize.
(* The print_goal in the normalize tactic shows
a trace of how the expression reduced...
(P (C 3) (P (C 3) (C 4)) -->* C 10)
(P (C 3) (C 7) -->* C 10)
(C 10 -->* C 10)
*)
Qed.
Example step_example1''' : ∃ e',
(P (C 3) (P (C 3) (C 4)))
-->* e'.
Proof.
eexists. normalize.
Qed.
(P (C 3) (P (C 3) (C 4)))
-->* e'.
Proof.
eexists. normalize.
Qed.
This time, the trace is:
(P (C 3) (P (C 3) (C 4)) -->* ?e')
(P (C 3) (C 7) -->* ?e')
(C 10 -->* ?e') where ?e' is the variable ``guessed'' by eapply.
(P (C 3) (P (C 3) (C 4)) -->* ?e')
(P (C 3) (C 7) -->* ?e')
(C 10 -->* ?e') where ?e' is the variable ``guessed'' by eapply.