Lecture notes 20210517 Pointer And Address
Require Import Coq.Relations.Relation_Definitions.
Require Export Coq.ZArith.ZArith.
Require Export Coq.Strings.String.
Require Export Coq.Logic.Classical.
Require Import PL.Imp PL.ImpExt2 PL.ImpExt3.
Open Scope Z.
Require Export Coq.ZArith.ZArith.
Require Export Coq.Strings.String.
Require Export Coq.Logic.Classical.
Require Import PL.Imp PL.ImpExt2 PL.ImpExt3.
Open Scope Z.
A Language With Addresses And Pointers
Definition var: Type := nat.
Inductive aexp : Type :=
| ANum (n : Z)
| AId (X : var)
| APlus (a1 a2 : aexp)
| AMinus (a1 a2 : aexp)
| AMult (a1 a2 : aexp)
| ADeref (a1: aexp) (* <-- new *)
| AAddr (a1: aexp). (* <-- new *)
Inductive bexp : Type :=
| BTrue
| BFalse
| BEq (a1 a2 : aexp)
| BLe (a1 a2 : aexp)
| BNot (b : bexp)
| BAnd (b1 b2 : bexp).
Inductive com : Type :=
| CSkip
| CAss (a1 a2 : aexp) (* <-- new *)
| CSeq (c1 c2 : com)
| CIf (b : bexp) (c1 c2 : com)
| CWhile (b : bexp) (c : com).
Module Example1.
Inductive aexp : Type :=
| ANum (n : Z)
| AId (X : var)
| APlus (a1 a2 : aexp)
| AMinus (a1 a2 : aexp)
| AMult (a1 a2 : aexp)
| ADeref (a1: aexp) (* <-- new *)
| AAddr (a1: aexp). (* <-- new *)
Inductive bexp : Type :=
| BTrue
| BFalse
| BEq (a1 a2 : aexp)
| BLe (a1 a2 : aexp)
| BNot (b : bexp)
| BAnd (b1 b2 : bexp).
Inductive com : Type :=
| CSkip
| CAss (a1 a2 : aexp) (* <-- new *)
| CSeq (c1 c2 : com)
| CIf (b : bexp) (c1 c2 : com)
| CWhile (b : bexp) (c : com).
Module Example1.
We suppose that X and Y are variable 0 and 1.
Definition X := 0%nat.
Definition Y := 1%nat.
Definition Y := 1%nat.
Here is some sample expressions and command.
Example aexp_sample: aexp := ADeref (APlus (AAddr (AId X)) (ANum 1)).
(* It is like the C expression: * (& x + 1) . *)
Example bexp_sample: bexp := BEq (ADeref (AId X)) (ADeref (AId Y)).
(* It is like the C expression: * x == * y . *)
Example com_sample1: com :=
CAss (ADeref (AId X)) (APlus (ADeref (AId X)) (ANum 1)).
(* It is like the C program: ( * x ) ++; . *)
Example com_sample2: com :=
CWhile (BNot (BEq (AId X) (ANum 0)))
(CSeq (CAss (AId Y) (APlus (AId Y) (ANum 1)))
(CAss (AId X) (ADeref (AId X)))).
(* It is like the C program: while (x != 0) { y ++; x = * x; } . *)
End Example1.
(* It is like the C expression: * (& x + 1) . *)
Example bexp_sample: bexp := BEq (ADeref (AId X)) (ADeref (AId Y)).
(* It is like the C expression: * x == * y . *)
Example com_sample1: com :=
CAss (ADeref (AId X)) (APlus (ADeref (AId X)) (ANum 1)).
(* It is like the C program: ( * x ) ++; . *)
Example com_sample2: com :=
CWhile (BNot (BEq (AId X) (ANum 0)))
(CSeq (CAss (AId Y) (APlus (AId Y) (ANum 1)))
(CAss (AId X) (ADeref (AId X)))).
(* It is like the C program: while (x != 0) { y ++; x = * x; } . *)
End Example1.
Expressions' Denotations
Definition var2addr (X: var): Z := Z.of_nat X + 1.
Definition state: Type := Z -> option Z.
Definition state: Type := Z -> option Z.
In order to define a denotational semantics, we define two functions for
expression evaluation: aevalR and aevalL. They define expressions'
rvalue (右值) and lvalue (左值). Rvalues are the values for computation
and lvalues are the addresses for reading and writing. We introduce aevalR
and aevalL by a mutually recursive definition.
Fixpoint aevalR (a: aexp): state -> option Z :=
match a with
| ANum n ⇒ fun _ ⇒ Some n
| AId X ⇒ fun st ⇒ st (var2addr X)
| APlus a1 a2 ⇒ OptF.add (aevalR a1) (aevalR a2)
| AMinus a1 a2 ⇒ OptF.sub (aevalR a1) (aevalR a2)
| AMult a1 a2 ⇒ OptF.mul (aevalR a1) (aevalR a2)
| ADeref a1 ⇒ fun st ⇒
match aevalR a1 st with
| Some n1 ⇒ st n1
| None ⇒ None
end
| AAddr a1 ⇒ aevalL a1
end
with aevalL (a: aexp): state -> option Z :=
match a with
| ANum n ⇒ fun _ ⇒ None
| AId X ⇒ fun st ⇒ Some (var2addr X)
| APlus a1 a2 ⇒ fun _ ⇒ None
| AMinus a1 a2 ⇒ fun _ ⇒ None
| AMult a1 a2 ⇒ fun _ ⇒ None
| ADeref a1 ⇒ aevalR a1
| AAddr a1 ⇒ fun _ ⇒ None
end.
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;
|}.
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 (aevalR a1) (aevalR a2)
| BLe a1 a2 ⇒
opt_test Z.le (aevalR a1) (aevalR 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.
match a with
| ANum n ⇒ fun _ ⇒ Some n
| AId X ⇒ fun st ⇒ st (var2addr X)
| APlus a1 a2 ⇒ OptF.add (aevalR a1) (aevalR a2)
| AMinus a1 a2 ⇒ OptF.sub (aevalR a1) (aevalR a2)
| AMult a1 a2 ⇒ OptF.mul (aevalR a1) (aevalR a2)
| ADeref a1 ⇒ fun st ⇒
match aevalR a1 st with
| Some n1 ⇒ st n1
| None ⇒ None
end
| AAddr a1 ⇒ aevalL a1
end
with aevalL (a: aexp): state -> option Z :=
match a with
| ANum n ⇒ fun _ ⇒ None
| AId X ⇒ fun st ⇒ Some (var2addr X)
| APlus a1 a2 ⇒ fun _ ⇒ None
| AMinus a1 a2 ⇒ fun _ ⇒ None
| AMult a1 a2 ⇒ fun _ ⇒ None
| ADeref a1 ⇒ aevalR a1
| AAddr a1 ⇒ fun _ ⇒ None
end.
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;
|}.
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 (aevalR a1) (aevalR a2)
| BLe a1 a2 ⇒
opt_test Z.le (aevalR a1) (aevalR 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.
Programs' Denotations
Record com_denote: Type := {
com_term: state -> state -> Prop;
com_error: state -> Prop
}.
Definition skip_sem: com_denote :=
{| com_term := BinRel.id;
com_error := Sets.empty;
|}.
Definition asgn_sem (DA1 DA2: state -> option Z): com_denote :=
{| com_term :=
fun st1 st2 ⇒
∃a v,
DA1 st1 = Some a ∧
DA2 st1 = Some v ∧
st1 a ≠ None ∧
st2 a = Some v ∧
∀a', a ≠ a' -> st1 a' = st2 a';
com_error :=
fun st ⇒
DA1 st = None ∨ DA2 st = None ∨
(∃a, DA1 st = Some a ∧ st a = None)
|}.
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 E1 E2 ⇒ asgn_sem (aevalL E1) (aevalR E2)
| 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
}.
Definition skip_sem: com_denote :=
{| com_term := BinRel.id;
com_error := Sets.empty;
|}.
Definition asgn_sem (DA1 DA2: state -> option Z): com_denote :=
{| com_term :=
fun st1 st2 ⇒
∃a v,
DA1 st1 = Some a ∧
DA2 st1 = Some v ∧
st1 a ≠ None ∧
st2 a = Some v ∧
∀a', a ≠ a' -> st1 a' = st2 a';
com_error :=
fun st ⇒
DA1 st = None ∨ DA2 st = None ∨
(∃a, DA1 st = Some a ∧ st a = None)
|}.
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 E1 E2 ⇒ asgn_sem (aevalL E1) (aevalR E2)
| 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.
Inductive aexp_halt: aexp -> Prop :=
| AH_num : ∀n, aexp_halt (ANum n).
Inductive astepR : state -> aexp -> aexp -> Prop :=
| ASR_Id : ∀st X n,
st (var2addr X) = Some n ->
astepR st
(AId X) (ANum n)
| ASR_Plus1 : ∀st a1 a1' a2,
astepR st
a1 a1' ->
astepR st
(APlus a1 a2) (APlus a1' a2)
| ASR_Plus2 : ∀st a1 a2 a2',
aexp_halt a1 ->
astepR st
a2 a2' ->
astepR st
(APlus a1 a2) (APlus a1 a2')
| ASR_Plus : ∀st n1 n2,
astepR st
(APlus (ANum n1) (ANum n2)) (ANum (n1 + n2))
| ASR_Minus1 : ∀st a1 a1' a2,
astepR st
a1 a1' ->
astepR st
(AMinus a1 a2) (AMinus a1' a2)
| ASR_Minus2 : ∀st a1 a2 a2',
aexp_halt a1 ->
astepR st
a2 a2' ->
astepR st
(AMinus a1 a2) (AMinus a1 a2')
| ASR_Minus : ∀st n1 n2,
astepR st
(AMinus (ANum n1) (ANum n2)) (ANum (n1 - n2))
| ASR_Mult1 : ∀st a1 a1' a2,
astepR st
a1 a1' ->
astepR st
(AMult a1 a2) (AMult a1' a2)
| ASR_Mult2 : ∀st a1 a2 a2',
aexp_halt a1 ->
astepR st
a2 a2' ->
astepR st
(AMult a1 a2) (AMult a1 a2')
| ASR_Mult : ∀st n1 n2,
astepR st
(AMult (ANum n1) (ANum n2)) (ANum (n1 * n2))
| ASR_DerefStep : ∀st a1 a1',
astepR st
a1 a1' ->
astepR st
(ADeref a1) (ADeref a1')
| ASR_Deref : ∀st n n',
st n = Some n' ->
astepR st
(ADeref (ANum n)) (ANum n')
| ASR_AddrStep : ∀st a1 a1',
astepL st
a1 a1' ->
astepR st
(AAddr a1) (AAddr a1')
| ASR_Addr : ∀st n,
astepR st
(AAddr (ADeref (ANum n))) (ANum n)
with astepL : state -> aexp -> aexp -> Prop :=
| ASL_Id: ∀st X,
astepL st
(AId X) (ADeref (ANum (var2addr X)))
| ASL_DerefStep: ∀st a1 a1',
astepR st
a1 a1' ->
astepL st
(ADeref a1) (ADeref a1')
.
Inductive bstep : state -> bexp -> bexp -> Prop :=
| BS_Eq1 : ∀st a1 a1' a2,
astepR st
a1 a1' ->
bstep st
(BEq a1 a2) (BEq a1' a2)
| BS_Eq2 : ∀st a1 a2 a2',
aexp_halt a1 ->
astepR 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,
astepR st
a1 a1' ->
bstep st
(BLe a1 a2) (BLe a1' a2)
| BS_Le2 : ∀st a1 a2 a2',
aexp_halt a1 ->
astepR 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.
Here, we assume BAnd expressions use short circuit evaluation.
Small Step Semantics for Program Execution
Inductive cstep : (com * state) -> (com * state) -> Prop :=
| CS_AssStep1 st E1 E1' E2 (* <-- new *)
(H1: astepL st E1 E1'):
cstep (CAss E1 E2, st) (CAss E1' E2, st)
| CS_AssStep2 st n E2 E2' (* <-- new *)
(H1: astepR st E2 E2'):
cstep (CAss (ADeref (ANum n)) E2, st) (CAss (ADeref (ANum n)) E2', st)
| CS_Ass st1 st2 n1 n2 (* <-- new *)
(H1: st1 n1 ≠ None)
(H2: st2 n1 = Some n2)
(H3: ∀n, n1 ≠ n -> st1 n = st2 n):
cstep (CAss (ADeref (ANum n1)) (ANum n2), 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).
Discussion: Type Safety
- CAss (APlus (AId X) (ANum 1)) (ANum 0).
(* 2021-05-17 20:13 *)