Lecture notes 20210508 Error 1
Require Export Coq.ZArith.ZArith.
Require Export Coq.Strings.String.
Require Export Coq.Logic.Classical.
Require Import PL.Imp.
Definition var: Type := nat.
Definition state: Type := var -> Z.
Open Scope Z.
Require Export Coq.Strings.String.
Require Export Coq.Logic.Classical.
Require Import PL.Imp.
Definition var: Type := nat.
Definition state: Type := var -> Z.
Open Scope Z.
Error in Expression Evaluation
Inductive aexp : Type :=
| ANum (n : Z)
| AId (X : var)
| APlus (a1 a2 : aexp)
| AMinus (a1 a2 : aexp)
| AMult (a1 a2 : aexp)
| ADiv (a1 a2 : aexp). (* <-- New *)
| ANum (n : Z)
| AId (X : var)
| APlus (a1 a2 : aexp)
| AMinus (a1 a2 : aexp)
| AMult (a1 a2 : aexp)
| ADiv (a1 a2 : aexp). (* <-- New *)
Originally, an aexp expression's denotation has type state -> Z. Now,
we cannot do that any longer, the evaluation result may be undefined at some
point — if the divisor is zero.
One potential solution is to use Coq's option type.
Print option.
(* Inductive option (A : Type) : Type :=
Some : A -> option A | None : option A *)
(* Inductive option (A : Type) : Type :=
Some : A -> option A | None : option A *)
We can use Some cases of option types to represent "defined" and use
None cases of option types to represent "undefined".
Module OptF.
Definition add {A: Type} (f g: A -> option Z): A -> option Z :=
fun st ⇒
match f st, g st with
| Some v1, Some v2 ⇒ Some (v1 + v2)
| _, _ ⇒ None
end.
Definition sub {A: Type} (f g: A -> option Z): A -> option Z :=
fun st ⇒
match f st, g st with
| Some v1, Some v2 ⇒ Some (v1 - v2)
| _, _ ⇒ None
end.
Definition mul {A: Type} (f g: A -> option Z): A -> option Z :=
fun st ⇒
match f st, g st with
| Some v1, Some v2 ⇒ Some (v1 * v2)
| _, _ ⇒ None
end.
Definition add {A: Type} (f g: A -> option Z): A -> option Z :=
fun st ⇒
match f st, g st with
| Some v1, Some v2 ⇒ Some (v1 + v2)
| _, _ ⇒ None
end.
Definition sub {A: Type} (f g: A -> option Z): A -> option Z :=
fun st ⇒
match f st, g st with
| Some v1, Some v2 ⇒ Some (v1 - v2)
| _, _ ⇒ None
end.
Definition mul {A: Type} (f g: A -> option Z): A -> option Z :=
fun st ⇒
match f st, g st with
| Some v1, Some v2 ⇒ Some (v1 * v2)
| _, _ ⇒ None
end.
When defining the semantics of ADiv, we can state that the result is
defined only when the evaluation result of both sides are defined and the
divisor does not evaluate to zero.
Definition div {A: Type} (f g: A -> option Z): A -> option Z :=
fun st ⇒
match f st, g st with
| Some v1, Some v2 ⇒
if Z.eq_dec v2 0
then None
else Some (v1 / v2)
| _, _ ⇒ None
end.
fun st ⇒
match f st, g st with
| Some v1, Some v2 ⇒
if Z.eq_dec v2 0
then None
else Some (v1 / v2)
| _, _ ⇒ None
end.
Here, Z.eq_dec determines whether two integers are equivalent or not.
Check Z.eq_dec.
(* Z.eq_dec
: forall x y : Z, {x = y} + {x <> y} *)
End OptF.
Module Denote_Aexp.
Fixpoint aeval (a : aexp): state -> option Z :=
match a with
| ANum n ⇒ fun _ ⇒ Some n
| AId X ⇒ fun st ⇒ Some (st X)
| APlus a1 a2 ⇒ OptF.add (aeval a1) (aeval a2)
| AMinus a1 a2 ⇒ OptF.sub (aeval a1) (aeval a2)
| AMult a1 a2 ⇒ OptF.mul (aeval a1) (aeval a2)
| ADiv a1 a2 ⇒ OptF.div (aeval a1) (aeval a2)
end.
End Denote_Aexp.
(* Z.eq_dec
: forall x y : Z, {x = y} + {x <> y} *)
End OptF.
Module Denote_Aexp.
Fixpoint aeval (a : aexp): state -> option Z :=
match a with
| ANum n ⇒ fun _ ⇒ Some n
| AId X ⇒ fun st ⇒ Some (st X)
| APlus a1 a2 ⇒ OptF.add (aeval a1) (aeval a2)
| AMinus a1 a2 ⇒ OptF.sub (aeval a1) (aeval a2)
| AMult a1 a2 ⇒ OptF.mul (aeval a1) (aeval a2)
| ADiv a1 a2 ⇒ OptF.div (aeval a1) (aeval a2)
end.
End Denote_Aexp.
Module Small_Step_Aexp.
Inductive aexp_halt: aexp -> Prop :=
| AH_num : ∀n, aexp_halt (ANum n).
Inductive astep : state -> aexp -> aexp -> Prop :=
| AS_Id : ∀st X,
astep st
(AId X) (ANum (st X))
| AS_Plus1 : ∀st a1 a1' a2,
astep st
a1 a1' ->
astep st
(APlus a1 a2) (APlus a1' a2)
| AS_Plus2 : ∀st a1 a2 a2',
aexp_halt a1 ->
astep st
a2 a2' ->
astep st
(APlus a1 a2) (APlus a1 a2')
| AS_Plus : ∀st n1 n2,
astep st
(APlus (ANum n1) (ANum n2)) (ANum (n1 + n2))
| AS_Minus1 : ∀st a1 a1' a2,
astep st
a1 a1' ->
astep st
(AMinus a1 a2) (AMinus a1' a2)
| AS_Minus2 : ∀st a1 a2 a2',
aexp_halt a1 ->
astep st
a2 a2' ->
astep st
(AMinus a1 a2) (AMinus a1 a2')
| AS_Minus : ∀st n1 n2,
astep st
(AMinus (ANum n1) (ANum n2)) (ANum (n1 - n2))
| AS_Mult1 : ∀st a1 a1' a2,
astep st
a1 a1' ->
astep st
(AMult a1 a2) (AMult a1' a2)
| AS_Mult2 : ∀st a1 a2 a2',
aexp_halt a1 ->
astep st
a2 a2' ->
astep st
(AMult a1 a2) (AMult a1 a2')
| AS_Mult : ∀st n1 n2,
astep st
(AMult (ANum n1) (ANum n2)) (ANum (n1 * n2))
| AS_Div1 : ∀st a1 a1' a2, (* <-- new *)
astep st
a1 a1' ->
astep st
(ADiv a1 a2) (ADiv a1' a2)
| AS_Div2 : ∀st a1 a2 a2', (* <-- new *)
aexp_halt a1 ->
astep st
a2 a2' ->
astep st
(ADiv a1 a2) (ADiv a1 a2')
| AS_Div : ∀st n1 n2, (* <-- new *)
n2 ≠ 0 ->
astep st
(ADiv (ANum n1) (ANum n2)) (ANum (n1 / n2))
.
Notice that there are two situations that no further evaluation step can
happen.
When there is no a2 such that astep st a1 a2, the predicate
aexp_halt a1 judges which situation between these two above describes the
current evulation status.
- Evaluation terminates.
- Evaluation arrives at an error state.
End Small_Step_Aexp.
Boolean Expressions
Inductive bexp : Type :=
| BTrue
| BFalse
| BEq (a1 a2 : aexp)
| BLe (a1 a2 : aexp)
| BNot (b : bexp)
| BAnd (b1 b2 : bexp).
| BTrue
| BFalse
| BEq (a1 a2 : aexp)
| BLe (a1 a2 : aexp)
| BNot (b : bexp)
| BAnd (b1 b2 : bexp).
Then we define the set of program states which make a boolean expression
true, which make a bool expression false and which cause errors.
Record bexp_denote: Type := {
true_set: state -> Prop;
false_set: state -> Prop;
error_set: state -> Prop;
}.
Definition opt_test (R: Z -> Z -> Prop) (X Y: state -> option Z): bexp_denote :=
{|
true_set := fun st ⇒
match X st, Y st with
| Some n1, Some n2 ⇒ R n1 n2
| _, _ ⇒ False
end;
false_set := fun st ⇒
match X st, Y st with
| Some n1, Some n2 ⇒ ¬R n1 n2
| _, _ ⇒ False
end;
error_set := fun st ⇒
match X st, Y st with
| Some n1, Some n2 ⇒ False
| _, _ ⇒ True
end;
|}.
Module Sets.
Definition union {A: Type} (X Y: A -> Prop): A -> Prop :=
fun a ⇒ X a ∨ Y a.
Definition omega_union {A} (X: nat -> A -> Prop): A -> Prop :=
fun a ⇒ ∃n, X n a.
End Sets.
Module Denote_Bexp.
Import Denote_Aexp.
Fixpoint beval (b: bexp): bexp_denote :=
match b with
| BTrue ⇒
{| true_set := Sets.full;
false_set := Sets.empty;
error_set := Sets.empty;
|}
| BFalse ⇒
{| true_set := Sets.empty;
false_set := Sets.full;
error_set := Sets.empty;
|}
| BEq a1 a2 ⇒
opt_test Z.eq (aeval a1) (aeval a2)
| BLe a1 a2 ⇒
opt_test Z.le (aeval a1) (aeval a2)
| BNot b ⇒
{| true_set := false_set (beval b);
false_set := true_set (beval b);
error_set := error_set (beval b);
|}
| BAnd b1 b2 ⇒
{| true_set := Sets.intersect
(true_set (beval b1))
(true_set (beval b2));
false_set := Sets.union
(false_set (beval b1))
(Sets.intersect
(true_set (beval b1))
(false_set (beval b2)));
error_set := Sets.union
(error_set (beval b1))
(Sets.intersect
(true_set (beval b1))
(error_set (beval b2)));
|}
end.
End Denote_Bexp.
Module Small_Step_Bexp.
Import Small_Step_Aexp.
true_set: state -> Prop;
false_set: state -> Prop;
error_set: state -> Prop;
}.
Definition opt_test (R: Z -> Z -> Prop) (X Y: state -> option Z): bexp_denote :=
{|
true_set := fun st ⇒
match X st, Y st with
| Some n1, Some n2 ⇒ R n1 n2
| _, _ ⇒ False
end;
false_set := fun st ⇒
match X st, Y st with
| Some n1, Some n2 ⇒ ¬R n1 n2
| _, _ ⇒ False
end;
error_set := fun st ⇒
match X st, Y st with
| Some n1, Some n2 ⇒ False
| _, _ ⇒ True
end;
|}.
Module Sets.
Definition union {A: Type} (X Y: A -> Prop): A -> Prop :=
fun a ⇒ X a ∨ Y a.
Definition omega_union {A} (X: nat -> A -> Prop): A -> Prop :=
fun a ⇒ ∃n, X n a.
End Sets.
Module Denote_Bexp.
Import Denote_Aexp.
Fixpoint beval (b: bexp): bexp_denote :=
match b with
| BTrue ⇒
{| true_set := Sets.full;
false_set := Sets.empty;
error_set := Sets.empty;
|}
| BFalse ⇒
{| true_set := Sets.empty;
false_set := Sets.full;
error_set := Sets.empty;
|}
| BEq a1 a2 ⇒
opt_test Z.eq (aeval a1) (aeval a2)
| BLe a1 a2 ⇒
opt_test Z.le (aeval a1) (aeval a2)
| BNot b ⇒
{| true_set := false_set (beval b);
false_set := true_set (beval b);
error_set := error_set (beval b);
|}
| BAnd b1 b2 ⇒
{| true_set := Sets.intersect
(true_set (beval b1))
(true_set (beval b2));
false_set := Sets.union
(false_set (beval b1))
(Sets.intersect
(true_set (beval b1))
(false_set (beval b2)));
error_set := Sets.union
(error_set (beval b1))
(Sets.intersect
(true_set (beval b1))
(error_set (beval b2)));
|}
end.
End Denote_Bexp.
Module Small_Step_Bexp.
Import Small_Step_Aexp.
The small step semantics of bexp is not interesting at all. Although error
may occur inside internal integer expression's evaluation, we just need to
copy-paste our original small step definition for bexp.
Inductive bexp_halt: bexp -> Prop :=
| BH_True : bexp_halt BTrue
| BH_False : bexp_halt BFalse.
Inductive bstep : state -> bexp -> bexp -> Prop :=
| BS_Eq1 : ∀st a1 a1' a2,
astep st
a1 a1' ->
bstep st
(BEq a1 a2) (BEq a1' a2)
| BS_Eq2 : ∀st a1 a2 a2',
aexp_halt a1 ->
astep st
a2 a2' ->
bstep st
(BEq a1 a2) (BEq a1 a2')
| BS_Eq_True : ∀st n1 n2,
n1 = n2 ->
bstep st
(BEq (ANum n1) (ANum n2)) BTrue
| BS_Eq_False : ∀st n1 n2,
n1 ≠ n2 ->
bstep st
(BEq (ANum n1) (ANum n2)) BFalse
| BS_Le1 : ∀st a1 a1' a2,
astep st
a1 a1' ->
bstep st
(BLe a1 a2) (BLe a1' a2)
| BS_Le2 : ∀st a1 a2 a2',
aexp_halt a1 ->
astep st
a2 a2' ->
bstep st
(BLe a1 a2) (BLe a1 a2')
| BS_Le_True : ∀st n1 n2,
n1 ≤ n2 ->
bstep st
(BLe (ANum n1) (ANum n2)) BTrue
| BS_Le_False : ∀st n1 n2,
n1 > n2 ->
bstep st
(BLe (ANum n1) (ANum n2)) BFalse
| BS_NotStep : ∀st b1 b1',
bstep st
b1 b1' ->
bstep st
(BNot b1) (BNot b1')
| BS_NotTrue : ∀st,
bstep st
(BNot BTrue) BFalse
| BS_NotFalse : ∀st,
bstep st
(BNot BFalse) BTrue
| BS_AndStep : ∀st b1 b1' b2,
bstep st
b1 b1' ->
bstep st
(BAnd b1 b2) (BAnd b1' b2)
| BS_AndTrue : ∀st b,
bstep st
(BAnd BTrue b) b
| BS_AndFalse : ∀st b,
bstep st
(BAnd BFalse b) BFalse.
End Small_Step_Bexp.
| BH_True : bexp_halt BTrue
| BH_False : bexp_halt BFalse.
Inductive bstep : state -> bexp -> bexp -> Prop :=
| BS_Eq1 : ∀st a1 a1' a2,
astep st
a1 a1' ->
bstep st
(BEq a1 a2) (BEq a1' a2)
| BS_Eq2 : ∀st a1 a2 a2',
aexp_halt a1 ->
astep st
a2 a2' ->
bstep st
(BEq a1 a2) (BEq a1 a2')
| BS_Eq_True : ∀st n1 n2,
n1 = n2 ->
bstep st
(BEq (ANum n1) (ANum n2)) BTrue
| BS_Eq_False : ∀st n1 n2,
n1 ≠ n2 ->
bstep st
(BEq (ANum n1) (ANum n2)) BFalse
| BS_Le1 : ∀st a1 a1' a2,
astep st
a1 a1' ->
bstep st
(BLe a1 a2) (BLe a1' a2)
| BS_Le2 : ∀st a1 a2 a2',
aexp_halt a1 ->
astep st
a2 a2' ->
bstep st
(BLe a1 a2) (BLe a1 a2')
| BS_Le_True : ∀st n1 n2,
n1 ≤ n2 ->
bstep st
(BLe (ANum n1) (ANum n2)) BTrue
| BS_Le_False : ∀st n1 n2,
n1 > n2 ->
bstep st
(BLe (ANum n1) (ANum n2)) BFalse
| BS_NotStep : ∀st b1 b1',
bstep st
b1 b1' ->
bstep st
(BNot b1) (BNot b1')
| BS_NotTrue : ∀st,
bstep st
(BNot BTrue) BFalse
| BS_NotFalse : ∀st,
bstep st
(BNot BFalse) BTrue
| BS_AndStep : ∀st b1 b1' b2,
bstep st
b1 b1' ->
bstep st
(BAnd b1 b2) (BAnd b1' b2)
| BS_AndTrue : ∀st b,
bstep st
(BAnd BTrue b) b
| BS_AndFalse : ∀st b,
bstep st
(BAnd BFalse b) BFalse.
End Small_Step_Bexp.
Module BinRel.
Definition dia {A B} (F: A -> B -> Prop) (X: B -> Prop): A -> Prop :=
fun a ⇒ ∃b, F a b ∧ X b.
End BinRel.
Inductive com : Type :=
| CSkip
| CAss (X: var) (a : aexp)
| CSeq (c1 c2 : com)
| CIf (b : bexp) (c1 c2 : com)
| CWhile (b : bexp) (c : com).
Originally, we use binary relations among beginning states and ending
states to represent different program commands' denotations. Specifically,
we did define a ternary Coq predicate ceval such that:
Now, a program may crush — terminate unexpectedly by an error. A natural
idea is to formalize program commands' denotations by a relation:
This does NOT work because we cannot talk about nonterminating execution
then. Thus, we define com_denote as follows.
- ceval c st1 st2 when executing c from state st1 will terminate
in program state st2;
- there is no st2 such that ceval c st1 st2 when executing c from state st1 will not terminate.
- ceval c st1 st2 when executing c from state st1 is safe and will
terminate in program state st2;
- there is no st2 such that ceval c st1 st2 when executing c from state st1 will cause error.
Record com_denote: Type := {
com_term: state -> state -> Prop;
com_error: state -> Prop
}.
Module Denote_Com.
Import Denote_Aexp.
Import Denote_Bexp.
Definition skip_sem: com_denote :=
{| com_term := BinRel.id;
com_error := Sets.empty;
|}.
Definition asgn_sem (X: var) (DA: state -> option Z): com_denote :=
{| com_term :=
fun st1 st2 ⇒
Some (st2 X) = DA st1 ∧
∀Y, X ≠ Y -> st1 Y = st2 Y;
com_error :=
fun st ⇒
None = DA st
|}.
Definition seq_sem (DC1 DC2: com_denote): com_denote :=
{| com_term :=
BinRel.concat (com_term DC1) (com_term DC2);
com_error :=
Sets.union
(com_error DC1)
(BinRel.dia (com_term DC1) (com_error DC2))
|}.
Definition if_sem (DB: bexp_denote) (DC1 DC2: com_denote): com_denote :=
{| com_term :=
BinRel.union
(BinRel.concat (BinRel.test_rel (true_set DB)) (com_term DC1))
(BinRel.concat (BinRel.test_rel (false_set DB)) (com_term DC2));
com_error :=
Sets.union
(error_set DB)
(Sets.union
(BinRel.dia (BinRel.test_rel (true_set DB)) (com_error DC1))
(BinRel.dia (BinRel.test_rel (false_set DB)) (com_error DC2)))
|}.
Fixpoint iter_loop_body (DB: bexp_denote)
(DC: com_denote)
(n: nat): com_denote :=
match n with
| O ⇒
{| com_term :=
BinRel.test_rel (false_set DB);
com_error :=
Sets.union
(error_set DB)
(BinRel.dia
(BinRel.test_rel (true_set DB))
(com_error DC))
|}
| S n' ⇒
{| com_term :=
BinRel.concat
(BinRel.test_rel (true_set DB))
(BinRel.concat
(com_term DC)
(com_term (iter_loop_body DB DC n')));
com_error :=
BinRel.dia
(BinRel.test_rel (true_set DB))
(BinRel.dia
(com_term DC)
(com_error (iter_loop_body DB DC n')));
|}
end.
Definition loop_sem (DB: bexp_denote) (DC: com_denote): com_denote :=
{| com_term :=
BinRel.omega_union
(fun n ⇒ com_term (iter_loop_body DB DC n));
com_error :=
Sets.omega_union
(fun n ⇒ com_error (iter_loop_body DB DC n))
|}.
Fixpoint ceval (c: com): com_denote :=
match c with
| CSkip ⇒ skip_sem
| CAss X E ⇒ asgn_sem X (aeval E)
| CSeq c1 c2 ⇒ seq_sem (ceval c1) (ceval c2)
| CIf b c1 c2 ⇒ if_sem (beval b) (ceval c1) (ceval c2)
| CWhile b c ⇒ loop_sem (beval b) (ceval c)
end.
com_term: state -> state -> Prop;
com_error: state -> Prop
}.
Module Denote_Com.
Import Denote_Aexp.
Import Denote_Bexp.
Definition skip_sem: com_denote :=
{| com_term := BinRel.id;
com_error := Sets.empty;
|}.
Definition asgn_sem (X: var) (DA: state -> option Z): com_denote :=
{| com_term :=
fun st1 st2 ⇒
Some (st2 X) = DA st1 ∧
∀Y, X ≠ Y -> st1 Y = st2 Y;
com_error :=
fun st ⇒
None = DA st
|}.
Definition seq_sem (DC1 DC2: com_denote): com_denote :=
{| com_term :=
BinRel.concat (com_term DC1) (com_term DC2);
com_error :=
Sets.union
(com_error DC1)
(BinRel.dia (com_term DC1) (com_error DC2))
|}.
Definition if_sem (DB: bexp_denote) (DC1 DC2: com_denote): com_denote :=
{| com_term :=
BinRel.union
(BinRel.concat (BinRel.test_rel (true_set DB)) (com_term DC1))
(BinRel.concat (BinRel.test_rel (false_set DB)) (com_term DC2));
com_error :=
Sets.union
(error_set DB)
(Sets.union
(BinRel.dia (BinRel.test_rel (true_set DB)) (com_error DC1))
(BinRel.dia (BinRel.test_rel (false_set DB)) (com_error DC2)))
|}.
Fixpoint iter_loop_body (DB: bexp_denote)
(DC: com_denote)
(n: nat): com_denote :=
match n with
| O ⇒
{| com_term :=
BinRel.test_rel (false_set DB);
com_error :=
Sets.union
(error_set DB)
(BinRel.dia
(BinRel.test_rel (true_set DB))
(com_error DC))
|}
| S n' ⇒
{| com_term :=
BinRel.concat
(BinRel.test_rel (true_set DB))
(BinRel.concat
(com_term DC)
(com_term (iter_loop_body DB DC n')));
com_error :=
BinRel.dia
(BinRel.test_rel (true_set DB))
(BinRel.dia
(com_term DC)
(com_error (iter_loop_body DB DC n')));
|}
end.
Definition loop_sem (DB: bexp_denote) (DC: com_denote): com_denote :=
{| com_term :=
BinRel.omega_union
(fun n ⇒ com_term (iter_loop_body DB DC n));
com_error :=
Sets.omega_union
(fun n ⇒ com_error (iter_loop_body DB DC n))
|}.
Fixpoint ceval (c: com): com_denote :=
match c with
| CSkip ⇒ skip_sem
| CAss X E ⇒ asgn_sem X (aeval E)
| CSeq c1 c2 ⇒ seq_sem (ceval c1) (ceval c2)
| CIf b c1 c2 ⇒ if_sem (beval b) (ceval c1) (ceval c2)
| CWhile b c ⇒ loop_sem (beval b) (ceval c)
end.
We can also define loops' semantics using Bourbaki-Witt fix point theorem.
It is suffice to comfirm that the following function is monotonic and
continuous.
Definition loop_rec (DB: bexp_denote) (DC: com_denote): com_denote -> com_denote :=
fun D ⇒ if_sem DB (seq_sem D DC) skip_sem.
End Denote_Com.
Module Small_Step_Com.
Import Small_Step_Aexp.
Import Small_Step_Bexp.
fun D ⇒ if_sem DB (seq_sem D DC) skip_sem.
End Denote_Com.
Module Small_Step_Com.
Import Small_Step_Aexp.
Import Small_Step_Bexp.
The small step semantic definition is again not very interesting. Our
original one is just good to use.
Inductive cstep : (com * state) -> (com * state) -> Prop :=
| CS_AssStep st X a a'
(H1: astep st a a'):
cstep (CAss X a, st) (CAss X a', st)
| CS_Ass st1 st2 X n
(H1: st2 X = n)
(H2: ∀Y, X ≠ Y -> st1 Y = st2 Y):
cstep (CAss X (ANum n), st1) (CSkip, st2)
| CS_SeqStep st c1 c1' st' c2
(H1: cstep (c1, st) (c1', st')):
cstep (CSeq c1 c2 , st) (CSeq c1' c2, st')
| CS_Seq st c2:
cstep (CSeq CSkip c2, st) (c2, st)
| CS_IfStep st b b' c1 c2
(H1: bstep st b b'):
cstep (CIf b c1 c2, st) (CIf b' c1 c2, st)
| CS_IfTrue st c1 c2:
cstep (CIf BTrue c1 c2, st) (c1, st)
| CS_IfFalse st c1 c2:
cstep (CIf BFalse c1 c2, st) (c2, st)
| CS_While st b c:
cstep
(CWhile b c, st)
(CIf b (CSeq c (CWhile b c)) CSkip, st).
| CS_AssStep st X a a'
(H1: astep st a a'):
cstep (CAss X a, st) (CAss X a', st)
| CS_Ass st1 st2 X n
(H1: st2 X = n)
(H2: ∀Y, X ≠ Y -> st1 Y = st2 Y):
cstep (CAss X (ANum n), st1) (CSkip, st2)
| CS_SeqStep st c1 c1' st' c2
(H1: cstep (c1, st) (c1', st')):
cstep (CSeq c1 c2 , st) (CSeq c1' c2, st')
| CS_Seq st c2:
cstep (CSeq CSkip c2, st) (c2, st)
| CS_IfStep st b b' c1 c2
(H1: bstep st b b'):
cstep (CIf b c1 c2, st) (CIf b' c1 c2, st)
| CS_IfTrue st c1 c2:
cstep (CIf BTrue c1 c2, st) (c1, st)
| CS_IfFalse st c1 c2:
cstep (CIf BFalse c1 c2, st) (c2, st)
| CS_While st b c:
cstep
(CWhile b c, st)
(CIf b (CSeq c (CWhile b c)) CSkip, st).
Using multi-step relation, we can classify different execution traces:
- multi_cstep (c, st1) (CSkip, st2), if executing c from state st1
is safe and will terminate in program state st2;
- multi_cstep (c, st1) (c', st') and there is no c'' and st'' such
that cstep (c', st') (c'', st''), if executing c from state st1
will cause error;
- for any c' and st', if multi_cstep (c, st1) (c', st') then there exists c'' and st'' such that cstep (c', st') (c'', st'') — this condition tells that executing c from state st1 is safe but will not terminate.
End Small_Step_Com.
Hoare Logic
The meaning of a Hoare triple
- If command c is started in a state satisfying assertion P, its execution is always safe. In addition, if it terminates, the ending state should satisfy Q.
Unchanged rules
Axiom hoare_seq : ∀(P Q R: Assertion) (c1 c2: com),
{{P}} c1 {{Q}} ->
{{Q}} c2 {{R}} ->
{{P}} c1;;c2 {{R}} .
Axiom hoare_skip : ∀P,
{{P}} Skip {{P}} .
Axiom hoare_consequence : ∀(P P' Q Q' : Assertion) c,
P ⊢ P' ->
{{P'}} c {{Q'}} ->
Q' ⊢ Q ->
{{P}} c {{Q}} .
{{P}} c1 {{Q}} ->
{{Q}} c2 {{R}} ->
{{P}} c1;;c2 {{R}} .
Axiom hoare_skip : ∀P,
{{P}} Skip {{P}} .
Axiom hoare_consequence : ∀(P P' Q Q' : Assertion) c,
P ⊢ P' ->
{{P'}} c {{Q'}} ->
Q' ⊢ Q ->
{{P}} c {{Q}} .
Rules with evaluation
Axiom hoare_if : ∀P Q b c1 c2,
{{ P AND [[b]] }} c1 {{ Q }} ->
{{ P AND NOT [[b]] }} c2 {{ Q }} ->
{{ P AND Safe(b) }} If b Then c1 Else c2 EndIf {{ Q }} .
Axiom hoare_while : ∀P b c,
P ⊢ Safe(b) ->
{{ P AND [[b]] }} c {{P}} ->
{{P}} While b Do c EndWhile {{ P AND NOT [[b]] }} .
Axiom hoare_asgn_fwd : ∀P (X: var) E,
{{ P AND Safe(E) }}
X ::= E
{{ EXISTS x, P [X ⟼ x] AND
[[X]] == [[ E [X ⟼ x] ]] }} .
Axiom hoare_asgn_bwd : ∀P (X: var) E,
{{ P [ X ⟼ E] AND Safe(E) }} X ::= E {{ P }} .
{{ P AND [[b]] }} c1 {{ Q }} ->
{{ P AND NOT [[b]] }} c2 {{ Q }} ->
{{ P AND Safe(b) }} If b Then c1 Else c2 EndIf {{ Q }} .
Axiom hoare_while : ∀P b c,
P ⊢ Safe(b) ->
{{ P AND [[b]] }} c {{P}} ->
{{P}} While b Do c EndWhile {{ P AND NOT [[b]] }} .
Axiom hoare_asgn_fwd : ∀P (X: var) E,
{{ P AND Safe(E) }}
X ::= E
{{ EXISTS x, P [X ⟼ x] AND
[[X]] == [[ E [X ⟼ x] ]] }} .
Axiom hoare_asgn_bwd : ∀P (X: var) E,
{{ P [ X ⟼ E] AND Safe(E) }} X ::= E {{ P }} .
(* 2021-05-08 10:54 *)