Acknowledgements
This material is taken verbatim from Software Foundations V4.0
Copyright (c) 2016
Permission is hereby granted, free of charge, to any person obtaining a copy
of this software and associated documentation files (the "Software"), to deal
in the Software without restriction, including without limitation the rights
to use, copy, modify, merge, publish, distribute, sublicense, and/or sell
copies of the Software, and to permit persons to whom the Software is
furnished to do so, subject to the following conditions:
The above copyright notice and this permission notice shall be included in
all copies or substantial portions of the Software.
THE SOFTWARE IS PROVIDED "AS IS", WITHOUT WARRANTY OF ANY KIND, EXPRESS OR
IMPLIED, INCLUDING BUT NOT LIMITED TO THE WARRANTIES OF MERCHANTABILITY,
FITNESS FOR A PARTICULAR PURPOSE AND NONINFRINGEMENT. IN NO EVENT SHALL THE
AUTHORS OR COPYRIGHT HOLDERS BE LIABLE FOR ANY CLAIM, DAMAGES OR OTHER
LIABILITY, WHETHER IN AN ACTION OF CONTRACT, TORT OR OTHERWISE, ARISING FROM,
OUT OF OR IN CONNECTION WITH THE SOFTWARE OR THE USE OR OTHER DEALINGS IN
THE SOFTWARE.
Assumed Knowledge:
* Can reason with inductively designed propositions in Coq.
Learning Outcomes:
* TODO
Grab the Coq source file
Imp.v
In this chapter, we begin a new direction that will continue for
the rest of the course. Up to now most of our attention has been
focused on various aspects of Coq itself, while from now on we'll
mostly be using Coq to formalize other things. (We'll continue to
pause from time to time to introduce a few additional aspects of
Coq.)
Our first case study is a
simple imperative programming language
called Imp, embodying a tiny core fragment of conventional
mainstream languages such as C and Java. Here is a familiar
mathematical function written in Imp.
Z ::=
X;;
Y ::= 1;;
WHILE not (
Z = 0)
DO
Y ::=
Y *
Z;;
Z ::=
Z - 1
END
This chapter looks at how to define the
syntax and
semantics
of Imp; the chapters that follow develop a theory of
program
equivalence and introduce
Hoare Logic, a widely used logic for
reasoning about imperative programs.
Arithmetic and Boolean Expressions
We'll present Imp in three parts: first a core language of
arithmetic and boolean expressions, then an extension of these
expressions with
variables, and finally a language of
commands
including assignment, conditions, sequencing, and loops.
These two definitions specify the abstract syntax of
arithmetic and boolean expressions.
In this chapter, we'll elide the translation from the
concrete syntax that a programmer would actually write to these
abstract syntax trees — the process that, for example, would
translate the string
"1+2*3" to the AST
APlus (ANum
1) (AMult (ANum 2) (ANum 3)). The optional chapter
ImpParser
develops a simple implementation of a lexical analyzer and parser
that can perform this translation. You do
not need to
understand that chapter to understand this one, but if you haven't
taken a course where these techniques are covered (e.g., a
compilers course) you may want to skim it.
For comparison, here's a conventional BNF (Backus-Naur Form)
grammar defining the same abstract syntax:
a ::=
nat
|
a +
a
|
a -
a
|
a *
a
b ::=
true
|
false
|
a =
a
|
a ≤
a
|
not b
|
b and b
Compared to the Coq version above...
- The BNF is more informal — for example, it gives some
suggestions about the surface syntax of expressions (like the
fact that the addition operation is written + and is an
infix symbol) while leaving other aspects of lexical analysis
and parsing (like the relative precedence of +, -, and
*, the use of parens to explicitly group subexpressions,
etc.) unspecified. Some additional information (and human
intelligence) would be required to turn this description into
a formal definition, for example when implementing a
compiler.
The Coq version consistently omits all this information and
concentrates on the abstract syntax only.
- On the other hand, the BNF version is lighter and easier to
read. Its informality makes it flexible, which is a huge
advantage in situations like discussions at the blackboard,
where conveying general ideas is more important than getting
every detail nailed down precisely.
Indeed, there are dozens of BNF-like notations and people
switch freely among them, usually without bothering to say
which form of BNF they're using because there is no need to:
a rough-and-ready informal understanding is all that's
important.
It's good to be comfortable with both sorts of notations:
informal ones for communicating between humans and formal ones for
carrying out implementations and proofs.
Evaluation
Evaluating an arithmetic expression produces a number.
Similarly, evaluating a boolean expression yields a boolean.
Optimization
We haven't defined very much yet, but we can already get
some mileage out of the definitions. Suppose we define a function
that takes an arithmetic expression and slightly simplifies it,
changing every occurrence of
0+e (i.e.,
(APlus (ANum 0) e)
into just
e.
To make sure our optimization is doing the right thing we
can test it on some examples and see if the output looks OK.
But if we want to be sure the optimization is correct —
i.e., that evaluating an optimized expression gives the same
result as the original — we should prove it.
Theorem optimize_0plus_sound:
∀a,
aeval (
optimize_0plus a) =
aeval a.
Proof.
intros a.
induction a.
-
reflexivity.
-
destruct a1.
+
destruct n.
*
simpl.
apply IHa2.
*
simpl.
rewrite IHa2.
reflexivity.
+
simpl.
simpl in IHa1.
rewrite IHa1.
rewrite IHa2.
reflexivity.
+
simpl.
simpl in IHa1.
rewrite IHa1.
rewrite IHa2.
reflexivity.
+
simpl.
simpl in IHa1.
rewrite IHa1.
rewrite IHa2.
reflexivity.
-
simpl.
rewrite IHa1.
rewrite IHa2.
reflexivity.
-
simpl.
rewrite IHa1.
rewrite IHa2.
reflexivity.
Qed.
Coq Automation
The repetition in this last proof is starting to be a little
annoying. If either the language of arithmetic expressions or the
optimization being proved sound were significantly more complex,
it would begin to be a real problem.
So far, we've been doing all our proofs using just a small handful
of Coq's tactics and completely ignoring its powerful facilities
for constructing parts of proofs automatically. This section
introduces some of these facilities, and we will see more over the
next several chapters. Getting used to them will take some
energy — Coq's automation is a power tool — but it will allow us
to scale up our efforts to more complex definitions and more
interesting properties without becoming overwhelmed by boring,
repetitive, low-level details.
Tacticals
Tacticals is Coq's term for tactics that take other tactics as
arguments — "higher-order tactics," if you will.
The try Tactical
If
T is a tactic, then
try T is a tactic that is just like
T
except that, if
T fails,
try T successfully does nothing at
all (instead of failing).
Theorem silly1 :
∀ae,
aeval ae =
aeval ae.
Proof.
try reflexivity.
Qed.
Theorem silly2 :
∀(
P :
Prop),
P → P.
Proof.
intros P HP.
try reflexivity.
apply HP.
Qed.
There is no real reason to use try in completely manual
proofs like these, but we'll see below that it is very useful for
doing automated proofs in conjunction with the ; tactical.
The ; Tactical (Simple Form)
In its most common form, the
; tactical takes two tactics as
arguments. The compound tactic
T;T' first performs
T and then
performs
T' on
each subgoal generated by
T.
For example, consider the following trivial lemma:
Lemma foo :
∀n,
leb 0
n =
true.
Proof.
intros.
destruct n.
-
simpl.
reflexivity.
-
simpl.
reflexivity.
Qed.
We can simplify this proof using the ; tactical:
Lemma foo' :
∀n,
leb 0
n =
true.
Proof.
intros.
destruct n;
simpl;
reflexivity.
Qed.
Using try and ; together, we can get rid of the repetition in
the proof that was bothering us a little while ago.
Theorem optimize_0plus_sound':
∀a,
aeval (
optimize_0plus a) =
aeval a.
Proof.
intros a.
induction a;
try (
simpl;
rewrite IHa1;
rewrite IHa2;
reflexivity).
-
reflexivity.
-
destruct a1;
try (
simpl;
simpl in IHa1;
rewrite IHa1;
rewrite IHa2;
reflexivity).
+
destruct n;
simpl;
rewrite IHa2;
reflexivity.
Qed.
Coq experts often use this "
...; try... " idiom after a tactic
like
induction to take care of many similar cases all at once.
Naturally, this practice has an analog in informal proofs.
Here is an informal proof of this theorem that matches the
structure of the formal one:
Theorem: For all arithmetic expressions
a,
aeval (
optimize_0plus a) =
aeval a.
Proof: By induction on
a. Most cases follow directly from the IH.
The remaining cases are as follows:
- Suppose a = ANum n for some n. We must show
aeval (
optimize_0plus (
ANum n)) =
aeval (
ANum n).
This is immediate from the definition of optimize_0plus.
- Suppose a = APlus a1 a2 for some a1 and a2. We
must show
aeval (
optimize_0plus (
APlus a1 a2))
=
aeval (
APlus a1 a2).
Consider the possible forms of a1. For most of them,
optimize_0plus simply calls itself recursively for the
subexpressions and rebuilds a new expression of the same form
as a1; in these cases, the result follows directly from the
IH.
The interesting case is when a1 = ANum n for some n.
If n = ANum 0, then
optimize_0plus (
APlus a1 a2) =
optimize_0plus a2
and the IH for a2 is exactly what we need. On the other
hand, if n = S n' for some n', then again optimize_0plus
simply calls itself recursively, and the result follows from
the IH. ☐
This proof can still be improved: the first case (for
a = ANum
n) is very trivial — even more trivial than the cases that we
said simply followed from the IH — yet we have chosen to write it
out in full. It would be better and clearer to drop it and just
say, at the top, "Most cases are either immediate or direct from
the IH. The only interesting case is the one for
APlus..." We
can make the same improvement in our formal proof too. Here's how
it looks:
Theorem optimize_0plus_sound'':
∀a,
aeval (
optimize_0plus a) =
aeval a.
Proof.
intros a.
induction a;
try (
simpl;
rewrite IHa1;
rewrite IHa2;
reflexivity);
try reflexivity.
-
destruct a1;
try (
simpl;
simpl in IHa1;
rewrite IHa1;
rewrite IHa2;
reflexivity).
+
destruct n;
simpl;
rewrite IHa2;
reflexivity.
Qed.
The ; Tactical (General Form)
The
; tactical also has a more general form than the simple
T;T' we've seen above. If
T,
T1, ...,
Tn are tactics,
then
is a tactic that first performs
T and then performs
T1 on the
first subgoal generated by
T, performs
T2 on the second
subgoal, etc.
So
T;T' is just special notation for the case when all of the
Ti's are the same tactic — i.e.,
T;T' is shorthand for:
The repeat Tactical
The
repeat tactical takes another tactic and keeps applying this
tactic until it fails. Here is an example showing that
10 is in
a long list using repeat.
Theorem In10 :
In 10 [1;2;3;4;5;6;7;8;9;10].
Proof.
repeat (
try (
left;
reflexivity);
right).
Qed.
The repeat T tactic never fails: if the tactic T doesn't apply
to the original goal, then repeat still succeeds without changing
the original goal (i.e., it repeats zero times).
Theorem In10' :
In 10 [1;2;3;4;5;6;7;8;9;10].
Proof.
repeat (
left;
reflexivity).
repeat (
right;
try (
left;
reflexivity)).
Qed.
The
repeat T tactic also does not have any upper bound on the
number of times it applies
T. If
T is a tactic that always
succeeds, then repeat
T will loop forever (e.g.,
repeat simpl
loops forever, since
simpl always succeeds). While Coq's term
language is guaranteed to terminate, Coq's tactic language is
not!
Exercise: 3 stars (optimize_0plus_b)
Since the
optimize_0plus transformation doesn't change the value
of
aexps, we should be able to apply it to all the
aexps that
appear in a
bexp without changing the
bexp's value. Write a
function which performs that transformation on
bexps, and prove
it is sound. Use the tacticals we've just seen to make the proof
as elegant as possible.
☐
Exercise: 4 stars, optional (optimizer)
Design exercise: The optimization implemented by our
optimize_0plus function is only one of many possible
optimizations on arithmetic and boolean expressions. Write a more
sophisticated optimizer and prove it correct.
☐
Defining New Tactic Notations
Coq also provides several ways of "programming" tactic scripts.
- The Tactic Notation idiom illustrated below gives a handy way to
define "shorthand tactics" that bundle several tactics into a
single command.
- For more sophisticated programming, Coq offers a small built-in
programming language called Ltac with primitives that can
examine and modify the proof state. The details are a bit too
complicated to get into here (and it is generally agreed that
Ltac is not the most beautiful part of Coq's design!), but they
can be found in the reference manual and other books on Coq, and
there are many examples of Ltac definitions in the Coq standard
library that you can use as examples.
- There is also an OCaml API, which can be used to build tactics
that access Coq's internal structures at a lower level, but this
is seldom worth the trouble for ordinary Coq users.
The
Tactic Notation mechanism is the easiest to come to grips with,
and it offers plenty of power for many purposes. Here's an example.
Tactic Notation "simpl_and_try" tactic(c) :=
simpl;
try c.
This defines a new tactical called simpl_and_try that takes one
tactic c as an argument and is defined to be equivalent to the
tactic simpl; try c. For example, writing "simpl_and_try
reflexivity." in a proof would be the same as writing "simpl;
try reflexivity."
The omega Tactic
The
omega tactic implements a decision procedure for a subset of
first-order logic called
Presburger arithmetic. It is based on
the Omega algorithm invented in 1991 by William Pugh
[Pugh 1991].
If the goal is a universally quantified formula made out of
- numeric constants, addition (+ and S), subtraction (-
and pred), and multiplication by constants (this is what
makes it Presburger arithmetic),
- equality (= and ≠) and inequality (≤), and
- the logical connectives ∧, ∨, ¬, and →,
then invoking
omega will either solve the goal or tell you that
it is actually false.
Leibniz wrote, "It is unworthy of excellent men to lose
hours like slaves in the labor of calculation which could be
relegated to anyone else if machines were used." We recommend
that excellent people of all genders use the omega tactic whenever
possible.
A Few More Handy Tactics
Finally, here are some miscellaneous tactics that you may find
convenient.
- clear H: Delete hypothesis H from the context.
- subst x: Find an assumption x = e or e = x in the
context, replace x with e throughout the context and
current goal, and clear the assumption.
- subst: Substitute away all assumptions of the form x = e
or e = x.
- rename... into...: Change the name of a hypothesis in the
proof context. For example, if the context includes a variable
named x, then rename x into y will change all occurrences
of x to y.
- assumption: Try to find a hypothesis H in the context that
exactly matches the goal; if one is found, behave just like
apply H.
- contradiction: Try to find a hypothesis H in the current
context that is logically equivalent to False. If one is
found, solve the goal.
- constructor: Try to find a constructor c (from some
Inductive definition in the current environment) that can be
applied to solve the current goal. If one is found, behave
like apply c.
We'll see many examples of these in the proofs below.
Evaluation as a Relation
We have presented
aeval and
beval as functions defined by
Fixpoints. Another way to think about evaluation — one that we
will see is often more flexible — is as a
relation between
expressions and their values. This leads naturally to
Inductive
definitions like the following one for arithmetic expressions...
As is often the case with relations, we'll find it
convenient to define infix notation for aevalR. We'll write e
⇓ n to mean that arithmetic expression e evaluates to value
n. (This notation is one place where the limitation to ASCII
symbols becomes a little bothersome. The standard notation for
the evaluation relation is a double down-arrow. We'll typeset it
like this in the HTML version of the notes and use a double slash
as the closest approximation in .v files.)
In fact, Coq provides a way to use this notation in the definition
of
aevalR itself. This avoids situations where we're working on
a proof involving statements in the form
e ⇓ n but we have to
refer back to a definition written using the form
aevalR e n.
We do this by first "reserving" the notation, then giving the
definition together with a declaration of what the notation
means.
Inference Rule Notation
In informal discussions, it is convenient to write the rules for
aevalR and similar relations in the more readable graphical form
of
inference rules, where the premises above the line justify
the conclusion below the line (we have already seen them in the
Prop chapter).
For example, the constructor
E_APlus...
|
E_APlus :
∀(
e1 e2:
aexp) (
n1 n2:
nat),
aevalR e1 n1 →
aevalR e2 n2 →
aevalR (
APlus e1 e2) (
n1 +
n2)
...would be written like this as an inference rule:
e1 ⇓ n1 |
|
e2 ⇓ n2 |
(E_APlus)
|
|
APlus e1 e2 ⇓ n1+n2 |
|
Formally, there is nothing deep about inference rules: they
are just implications. You can read the rule name on the right as
the name of the constructor and read each of the linebreaks
between the premises above the line and the line itself as
→.
All the variables mentioned in the rule (
e1,
n1, etc.) are
implicitly bound by universal quantifiers at the beginning. (Such
variables are often called
metavariables to distinguish them
from the variables of the language we are defining. At the
moment, our arithmetic expressions don't include variables, but
we'll soon be adding them.) The whole collection of rules is
understood as being wrapped in an
Inductive declaration. In
informal prose, this is either elided or else indicated by saying
something like "Let
aevalR be the smallest relation closed under
the following rules...".
For example,
⇓ is the smallest relation closed under these
rules:
e1 ⇓ n1 |
|
e2 ⇓ n2 |
(E_APlus)
|
|
APlus e1 e2 ⇓ n1+n2 |
|
e1 ⇓ n1 |
|
e2 ⇓ n2 |
(E_AMinus)
|
|
AMinus e1 e2 ⇓ n1-n2 |
|
e1 ⇓ n1 |
|
e2 ⇓ n2 |
(E_AMult)
|
|
AMult e1 e2 ⇓ n1*n2 |
|
Equivalence of the Definitions
It is straightforward to prove that the relational and functional
definitions of evaluation agree, for all arithmetic expressions...
Theorem aeval_iff_aevalR :
∀a n,
(
a ⇓ n)
↔ aeval a =
n.
Proof.
split.
-
intros H.
induction H;
simpl.
+
reflexivity.
+
rewrite IHaevalR1.
rewrite IHaevalR2.
reflexivity.
+
rewrite IHaevalR1.
rewrite IHaevalR2.
reflexivity.
+
rewrite IHaevalR1.
rewrite IHaevalR2.
reflexivity.
-
generalize dependent n.
induction a;
simpl;
intros;
subst.
+
apply E_ANum.
+
apply E_APlus.
apply IHa1.
reflexivity.
apply IHa2.
reflexivity.
+
apply E_AMinus.
apply IHa1.
reflexivity.
apply IHa2.
reflexivity.
+
apply E_AMult.
apply IHa1.
reflexivity.
apply IHa2.
reflexivity.
Qed.
We can make the proof quite a bit shorter by making more
use of tacticals...
Theorem aeval_iff_aevalR' :
∀a n,
(
a ⇓ n)
↔ aeval a =
n.
Proof.
split.
-
intros H;
induction H;
subst;
reflexivity.
-
generalize dependent n.
induction a;
simpl;
intros;
subst;
constructor;
try apply IHa1;
try apply IHa2;
reflexivity.
Qed.
Exercise: 3 stars (bevalR)
Write a relation
bevalR in the same style as
aevalR, and prove that it is equivalent to
beval.
☐
Computational vs. Relational Definitions
For the definitions of evaluation for arithmetic and boolean
expressions, the choice of whether to use functional or relational
definitions is mainly a matter of taste. In general, Coq has
somewhat better support for working with relations. On the other
hand, in some sense function definitions carry more information,
because functions are by definition deterministic and defined on
all arguments; for a relation we have to show these properties
explicitly if we need them. Functions also take advantage of
Coq's computation mechanism.
However, there are circumstances where relational definitions of
evaluation are preferable to functional ones.
For example, suppose that we wanted to extend the arithmetic
operations by considering also a division operation:
Extending the definition of aeval to handle this new operation
would not be straightforward (what should we return as the result
of ADiv (ANum 5) (ANum 0)?). But extending aevalR is
straightforward.
Adding Nondeterminism
Suppose, instead, that we want to extend the arithmetic operations
by a nondeterministic number generator
any that, when evaluated,
may yield any number. (Note that this is not the same as making a
probabilistic choice among all possible numbers — we're not
specifying any particular distribution of results, but just saying
what results are
possible.)
Again, extending aeval would be tricky, since now evaluation is
not a deterministic function from expressions to numbers, but
extending aevalR is no problem:
Expressions With Variables
Let's turn our attention back to defining Imp. The next thing we
need to do is to enrich our arithmetic and boolean expressions
with variables. To keep things simple, we'll assume that all
variables are global and that they only hold numbers.
States
Since we'll want to look variables up to find out their current
values, we'll reuse the type
id from the
Maps chapter for the
type of variables in Imp.
A
machine state (or just
state) represents the current values
of
all variables at some point in the execution of a program.
For simplicity, we assume that the state is defined for
all variables, even though any given program is only going to
mention a finite number of them. The state captures all of the
information stored in memory. For Imp programs, because each
variable stores a natural number, we can represent the state as a
mapping from identifiers to
nat. For more complex programming
languages, the state might have more structure.
Syntax
We can add variables to the arithmetic expressions we had before by
simply adding one more constructor:
Defining a few variable names as notational shorthands will make
examples easier to read:
Definition X :
id :=
Id 0.
Definition Y :
id :=
Id 1.
Definition Z :
id :=
Id 2.
(This convention for naming program variables (
X,
Y,
Z) clashes a bit with our earlier use of uppercase letters for
types. Since we're not using polymorphism heavily in this part of
the course, this overloading should not cause confusion.)
The definition of
bexps is unchanged (except for using the new
aexps):
Evaluation
The arith and boolean evaluators are extended to handle
variables in the obvious way, taking a state as an extra
argument:
Commands
Now we are ready define the syntax and behavior of Imp
commands (sometimes called
statements).
Syntax
Informally, commands
c are described by the following BNF
grammar. (We choose this slightly awkward concrete syntax for the
sake of being able to define Imp syntax using Coq's Notation
mechanism. In particular, we use
IFB to avoid conflicting with
the
if notation from the standard library.)
c ::=
SKIP |
x ::=
a |
c ;;
c |
IFB b THEN c ELSE c FI
|
WHILE b DO c END
For example, here's factorial in Imp:
Z ::=
X;;
Y ::= 1;;
WHILE not (
Z = 0)
DO
Y ::=
Y *
Z;;
Z ::=
Z - 1
END
When this command terminates, the variable
Y will contain the
factorial of the initial value of
X.
Here is the formal definition of the abstract syntax of
commands:
As usual, we can use a few Notation declarations to make things
more readable. To avoid conflicts with Coq's built-in notations,
we keep this light — in particular, we don't introduce any
notations for aexps and bexps to avoid confusion with the
numeric and boolean operators we've already defined.
Notation "'SKIP'" :=
CSkip.
Notation "x '::=' a" :=
(
CAss x a) (
at level 60).
Notation "c
1 ;; c
2" :=
(
CSeq c1 c2) (
at level 80,
right associativity).
Notation "'WHILE' b 'DO' c 'END'" :=
(
CWhile b c) (
at level 80,
right associativity).
Notation "'IFB' c
1 'THEN' c
2 'ELSE' c
3 'FI'" :=
(
CIf c1 c2 c3) (
at level 80,
right associativity).
For example, here is the factorial function again, written as a
formal definition to Coq:
Evaluation
Next we need to define what it means to evaluate an Imp command.
The fact that
WHILE loops don't necessarily terminate makes defining
an evaluation function tricky...
Evaluation as a Function (Failed Attempt)
Here's an attempt at defining an evaluation function for commands,
omitting the
WHILE case.
In a traditional functional programming language like OCaml or
Haskell we could add the
WHILE case as follows:
Fixpoint ceval_fun (st : state) (c : com) : state :=
match c with
...
| WHILE b DO c END =>
if (beval st b)
then ceval_fun st (c; WHILE b DO c END)
else st
end.
Coq doesn't accept such a definition ("Error: Cannot guess
decreasing argument of fix") because the function we want to
define is not guaranteed to terminate. Indeed, it
doesn't always
terminate: for example, the full version of the
ceval_fun
function applied to the
loop program above would never
terminate. Since Coq is not just a functional programming
language, but also a consistent logic, any potentially
non-terminating function needs to be rejected. Here is
an (invalid!) Coq program showing what would go wrong if Coq
allowed non-terminating recursive functions:
Fixpoint loop_false (n : nat) : False := loop_false n.
That is, propositions like
False would become provable
(e.g.,
loop_false 0 would be a proof of
False), which
would be a disaster for Coq's logical consistency.
Thus, because it doesn't terminate on all inputs, the full version
of
ceval_fun cannot be written in Coq — at least not without
additional tricks (see chapter
ImpCEvalFun if you're curious
about what those might be).
Evaluation as a Relation
Here's a better way: define
ceval as a
relation rather than a
function — i.e., define it in
Prop instead of
Type, as we
did for
aevalR above.
This is an important change. Besides freeing us from the awkward
workarounds that would be needed to define evaluation as a
function, it gives us a lot more flexibility in the definition.
For example, if we add nondeterministic features like
any to the
language, we want the definition of evaluation to be
nondeterministic — i.e., not only will it not be total, it will
not even be a function! We'll use the notation
c / st ⇓ st' for our
ceval relation:
c / st ⇓ st' means that executing program
c in a starting
state
st results in an ending state
st'. This can be
pronounced "
c takes state
st to
st'".
Operational Semantics
Here is an informal definition of evaluation, presented as inference
rules for the sake of readability:
aeval st a1 = n |
(E_Ass)
|
|
x := a1 / st ⇓ (t_update st x n) |
|
c1 / st ⇓ st' |
|
c2 / st' ⇓ st'' |
(E_Seq)
|
|
c1;;c2 / st ⇓ st'' |
|
beval st b1 = true |
|
c1 / st ⇓ st' |
(E_IfTrue)
|
|
IF b1 THEN c1 ELSE c2 FI / st ⇓ st' |
|
beval st b1 = false |
|
c2 / st ⇓ st' |
(E_IfFalse)
|
|
IF b1 THEN c1 ELSE c2 FI / st ⇓ st' |
|
beval st b = false |
(E_WhileEnd)
|
|
WHILE b DO c END / st ⇓ st |
|
beval st b = true |
|
c / st ⇓ st' |
|
WHILE b DO c END / st' ⇓ st'' |
(E_WhileLoop)
|
|
WHILE b DO c END / st ⇓ st'' |
|
Here is the formal definition. Make sure you understand
how it corresponds to the inference rules.
The cost of defining evaluation as a relation instead of a
function is that we now need to construct proofs that some
program evaluates to some result state, rather than just letting
Coq's computation mechanism do it for us.
Exercise: 2 stars (ceval_example2)
☐
Exercise: 3 stars, advanced (pup_to_n)
Write an Imp program that sums the numbers from
1 to
X (inclusive:
1 + 2 + ... + X) in the variable
Y.
Prove that this program executes as intended for
X =
2
(the latter is trickier than you might expect).
☐
Determinism of Evaluation
Changing from a computational to a relational definition of
evaluation is a good move because it allows us to escape from the
artificial requirement that evaluation should be a total function.
But it also raises a question: Is the second definition of
evaluation really a partial function? Or is it possible that,
beginning from the same state
st, we could evaluate some command
c in different ways to reach two different output states
st'
and
st''?
In fact, this cannot happen:
ceval is a partial function:
Theorem ceval_deterministic:
∀c st st1 st2,
c /
st ⇓ st1 →
c /
st ⇓ st2 →
st1 =
st2.
Proof.
intros c st st1 st2 E1 E2.
generalize dependent st2.
induction E1;
intros st2 E2; inversion E2; subst.
- reflexivity.
- reflexivity.
-
assert (st' = st'0) as EQ1.
{ apply IHE1_1; assumption. }
subst st'0.
apply IHE1_2. assumption.
-
apply IHE1. assumption.
-
rewrite H in H5. inversion H5.
-
rewrite H in H5. inversion H5.
-
apply IHE1. assumption.
-
reflexivity.
-
rewrite H in H2. inversion H2.
-
rewrite H in H4. inversion H4.
-
assert (st' = st'0) as EQ1.
{ apply IHE1_1; assumption. }
subst st'0.
apply IHE1_2. assumption. Qed.
Reasoning About Imp Programs
We'll get much deeper into systematic techniques for reasoning
about Imp programs in the following chapters, but we can do quite
a bit just working with the bare definitions.
This section explores some examples.
Inverting Heval essentially forces Coq to expand one step of
the ceval computation — in this case revealing that st'
must be st extended with the new value of X, since plus2
is an assignment
inversion Heval.
subst.
clear Heval.
simpl.
apply t_update_eq.
Qed.
Exercise: 3 stars, recommended (XtimesYinZ_spec)
State and prove a specification of
XtimesYinZ.
☐
Exercise: 3 stars, recommended (loop_never_stops)
Proceed by induction on the assumed derivation showing that
loopdef terminates. Most of the cases are immediately
contradictory (and so can be solved in one step with
inversion).
Admitted.
☐
Exercise: 3 stars (no_whilesR)
Consider the definition of the
no_whiles boolean predicate below:
This predicate yields true just on programs that have no while
loops. Using Inductive, write a property no_whilesR such that
no_whilesR c is provable exactly when c is a program with no
while loops. Then prove its equivalence with no_whiles.
☐
Exercise: 4 stars (no_whiles_terminating)
Imp programs that don't involve while loops always terminate.
State and prove a theorem
no_whiles_terminating that says this. Use either
no_whiles or
no_whilesR, as you prefer.
☐
Additional Exercises
Exercise: 3 stars (stack_compiler)
HP Calculators, programming languages like Forth and Postscript,
and abstract machines like the Java Virtual Machine all evaluate
arithmetic expressions using a stack. For instance, the expression
(2*3)+(3*(4-2))
would be entered as
2 3 * 3 4 2 - * +
and evaluated like this (where we show the program being evaluated
on the right and the contents of the stack on the left):
[] | 2 3 * 3 4 2 - * +
[2] | 3 * 3 4 2 - * +
[3, 2] | * 3 4 2 - * +
[6] | 3 4 2 - * +
[3, 6] | 4 2 - * +
[4, 3, 6] | 2 - * +
[2, 4, 3, 6] | - * +
[2, 3, 6] | * +
[6, 6] | +
[12] |
The task of this exercise is to write a small compiler that
translates
aexps into stack machine instructions.
The instruction set for our stack language will consist of the
following instructions:
- SPush n: Push the number n on the stack.
- SLoad x: Load the identifier x from the store and push it
on the stack
- SPlus: Pop the two top numbers from the stack, add them, and
push the result onto the stack.
- SMinus: Similar, but subtract.
- SMult: Similar, but multiply.
Write a function to evaluate programs in the stack language. It
should take as input a state, a stack represented as a list of
numbers (top stack item is the head of the list), and a program
represented as a list of instructions, and it should return the
stack after executing the program. Test your function on the
examples below.
Note that the specification leaves unspecified what to do when
encountering an
SPlus,
SMinus, or
SMult instruction if the
stack contains less than two elements. In a sense, it is
immaterial what we do, since our compiler will never emit such a
malformed program.
Next, write a function that compiles an aexp into a stack
machine program. The effect of running the program should be the
same as pushing the value of the expression on the stack.
After you've defined s_compile, prove the following to test
that it works.
☐
Exercise: 4 stars, advanced (stack_compiler_correct)
Now we'll prove the correctness of the compiler implemented in the
previous exercise. Remember that the specification left
unspecified what to do when encountering an
SPlus,
SMinus, or
SMult instruction if the stack contains less than two
elements. (In order to make your correctness proof easier you
might find it helpful to go back and change your implementation!)
Prove the following theorem. You will need to start by stating a
more general lemma to get a usable induction hypothesis; the main
theorem will then be a simple corollary of this lemma.
☐
Exercise: 5 stars, advanced (break_imp)
Imperative languages like C and Java often include a break or
similar statement for interrupting the execution of loops. In this
exercise we consider how to add break to Imp. First, we need to
enrich the language of commands with an additional case.
Next, we need to define the behavior of
BREAK. Informally,
whenever
BREAK is executed in a sequence of commands, it stops
the execution of that sequence and signals that the innermost
enclosing loop should terminate. (If there aren't any
enclosing loops, then the whole program simply terminates.) The
final state should be the same as the one in which the
BREAK
statement was executed.
One important point is what to do when there are multiple loops
enclosing a given
BREAK. In those cases,
BREAK should only
terminate the
innermost loop. Thus, after executing the
following...
X ::= 0;;
Y ::= 1;;
WHILE 0 ≠
Y DO
WHILE TRUE DO
BREAK
END;;
X ::= 1;;
Y ::=
Y - 1
END
... the value of
X should be
1, and not
0.
One way of expressing this behavior is to add another parameter to
the evaluation relation that specifies whether evaluation of a
command executes a
BREAK statement:
Intuitively,
c / st ⇓ s / st' means that, if
c is started in
state
st, then it terminates in state
st' and either signals
that the innermost surrounding loop (or the whole program) should
exit immediately (
s = SBreak) or that execution should continue
normally (
s = SContinue).
The definition of the "
c / st ⇓ s / st'" relation is very
similar to the one we gave above for the regular evaluation
relation (
c / st ⇓ st') — we just need to handle the
termination signals appropriately:
- If the command is SKIP, then the state doesn't change, and
execution of any enclosing loop can continue normally.
- If the command is BREAK, the state stays unchanged, but we
signal a SBreak.
- If the command is an assignment, then we update the binding for
that variable in the state accordingly and signal that execution
can continue normally.
- If the command is of the form IFB b THEN c1 ELSE c2 FI, then
the state is updated as in the original semantics of Imp, except
that we also propagate the signal from the execution of
whichever branch was taken.
- If the command is a sequence c1 ;; c2, we first execute
c1. If this yields a SBreak, we skip the execution of c2
and propagate the SBreak signal to the surrounding context;
the resulting state is the same as the one obtained by
executing c1 alone. Otherwise, we execute c2 on the state
obtained after executing c1, and propagate the signal
generated there.
- Finally, for a loop of the form WHILE b DO c END, the
semantics is almost the same as before. The only difference is
that, when b evaluates to true, we execute c and check the
signal that it raises. If that signal is SContinue, then the
execution proceeds as in the original semantics. Otherwise, we
stop the execution of the loop, and the resulting state is the
same as the one resulting from the execution of the current
iteration. In either case, since BREAK only terminates the
innermost loop, WHILE signals SContinue.
Based on the above description, complete the definition of the
ceval relation.
Now prove the following properties of your definition of ceval:
Exercise: 3 stars, advanced, optional (while_break_true)
Exercise: 4 stars, advanced, optional (ceval_deterministic)
☐
Exercise: 3 stars, optional (short_circuit)
Most modern programming languages use a "short-circuit" evaluation
rule for boolean
and: to evaluate
BAnd b1 b2, first evaluate
b1. If it evaluates to
false, then the entire
BAnd
expression evaluates to
false immediately, without evaluating
b2. Otherwise,
b2 is evaluated to determine the result of the
BAnd expression.
Write an alternate version of
beval that performs short-circuit
evaluation of
BAnd in this manner, and prove that it is
equivalent to
beval.
☐
Exercise: 4 stars, optional (add_for_loop)
Add C-style
for loops to the language of commands, update the
ceval definition to define the semantics of
for loops, and add
cases for
for loops as needed so that all the proofs in this file
are accepted by Coq.
A
for loop should be parameterized by (a) a statement executed
initially, (b) a test that is run on each iteration of the loop to
determine whether the loop should continue, (c) a statement
executed at the end of each loop iteration, and (d) a statement
that makes up the body of the loop. (You don't need to worry
about making up a concrete Notation for
for loops, but feel free
to play with this too if you like.)
☐