2.3. Formal Semantics for Interscript
A type describing a list of items of type
T can be defined as "
LIST OF
T" (in these semantics,
T will always take the form "
REF
T'" for some type
T'). A list element can be created by the operation
CONS: PROC[first, rest: LIST OF T] RETURNS[LIST OF T]
2.3.1. Semantics organized according to the abstract grammar
The semantics of the base language are described by the function
S:
S: PROC[e: Env, nt: NonTerminal] RETURNS[vs: Vs]
where a NonTerminal represents a node of an abstract parse tree (not defined here).
Vs: TYPE=LIST OF V
V: TYPE = REF VRec
Conceptually, a
VRec is a triple consisting of a mark,
m, some contents,
c, and sometimes extra information,
x, which is primarily for recording a name (e.g., for a binding). To get the maximum benefit of type checking the definition of
S without encumbering the definition with a lot of extraneous type coercions, a
Vrec is defined to contain a set of fields,
c
a, one for each type of content (
c
a is one of
cV,
cVs,
cNum,
cStr,
cId,
cTerm). For similar reasons, the
x component may be one of
xId,
xName, or
xEnv. In any given
Vrec at most one of the
c fields and at most one of the
x fields will actually be used; e.g., a tuple representing the number 3.14 has the form
VRec[
m:
num,
cNum: 3.14], and a tuple representing the name
a.
b.
c as an atom has the form
VRec[
m:
atom,
xName:
CONS[
c,
CONS[
b,
CONS[
a,
NIL]]] ]. Here are the complete definitions of
VRec and
Mark:
VRec:
TYPE =
RECORD[
m:
Mark,
cVs: Vs←NIL, cV: V←NIL, cNum: Number𡤀.0, cStr: STRING←NIL, cId: Id←NIL,
cTerm: NonTerminal←NIL,
xId: Id←NIL, xName: Name←NIL, xEnv: Env←NIL];
Mark: TYPE= {atom, num, string, node, -- base values
tag, bind, scope, bindStruc, evalStruc, onodeStruc, quotedTerm, vOfQ, evalSentinel};
S is defined in terms of various subsidiary semantic functions, which divide naturally into two groups: those that require an environment as a parameter and those that do not. The type signatures of the functions in the two groups are
(1) functions with an environment parameter:
MkNode: PROC[e: Env, vs: Vs] RETURNS [V -- node--]
MkBinding: PROC[e: Env, v: V, n: Name, kind: Mark] RETURNS [V]
Lookup: PROC[e: Env, n: Name] RETURNS [V]
EvalName: PROC[e: Env, n: Name] RETURNS [V]
RelBindings: PROC[e: Env, vs: Vs --tag items only--] RETURNS [Vs]
(2) functions independent of environment (dealing only with tuples or lists of tuples):
Apply: PROC[op: Op, v1: V, v2: V] RETURNS [result: V]
Bindings: PROC[v: V] RETURNS [Env]
Contents: PROC[vs: Vs] RETURNS [Vs]
Tags: PROC[vs: Vs] RETURNS [Vs --tag items only--]
Items: PROC[v: V] RETURNS [Vs]
MkScope: PROC[vs: Vs] RETURNS [Vs]
S is written in a "distributed" manner in the table below. It associates the parts of S with non-terminals of the abstract grammar. If S were written as a single function, it would look like a large case statement with one arm for each non-terminal of the abstract grammar and the lines under the column heading S[e, Alternative] as the code for the arms of the case statement.
e denotes the current environment argument of S. An environment is simply a sequence of bindings just like those that are relevant to a node. Some of the semantic rules pass a modified e to recursive application of S; see, e.g., the rule defining items. An environment can be augmented by one or more bindings, bind*, denoted by ConcatVs[bind*, e].
Only the semantics for "interesting" alternatives of the grammar are given below. For any alternative lhs ::= rhs whose semantics are not presented, its value semantics are S[e, lhs]=S[e, rhs].
When S maps a nonterminal of the abstract grammar into its tuple form, it is said to be elaborated.
Lefthand Side Alternative S[e, Alternative]
script ::= node S[
X, node]
The environment for the root node of an abstracted script is the external environment X.
node ::= items {t: Vs=S[
e, items]; RETURN[
MkNode[ConcatVs[Bindings[t],
e], t]
Make a node from the list of items using the environment obtained by appending bindings in the node with the current environment.
items ::=
empty
empty
| items item {t: VS=S[
e, items];
RETURN[
ConcatVs[t, S[ConcatVs[Bindings[t],
e], item]}
Recursively elaborate items and then elaborate the last item using the environment formed by appending the bindings in the preceding items to the current environment. Thus bindings affect things to their right in a list of items.
tag ::= primary MkTag[
e, S[
e, primary]]
Elaborate the primary. That should produce a (possibly qualified) name to use as the tag.
scope ::= items MkScope[S[e, items]] -- see MkScope below
openedNode ::= term Items[S[
e, term]]
| name Mk
V[m: onodeStruc,
cVs: Items[EvalName[
e, S[
NIL, name]]], name]
If a term (non-structural openedNode), then use the Items function to pull all the necessary elaborated items from the node value that the term must elaborate to. If a structural openedNode, embed the elaborated items of the named node in a tuple marked as an onodeStruc in order to remember the name from which the items were obtained.
binding ::= name term MkBinding[
e, S[
e, term], S[
NIL, name], bind]
Elaborate the term in the current environment. and make a (nonstructural) binding between the name and the resultant value. See MkBinding for details, especially for how values are bound to qualified names.
sBinding ::= name sRhs MkBinding[
e, S[
e, sRhs], S[
NIL, name], bindStruc]
Elaborate the term in the current environment. and make a structural binding between the name and the resultant value. See MkBinding for details, especially for how values are bound to qualified names.
quoted ::= term Mk
V[m:
quotedTerm, cTerm: term]
Simply make a quotedTerm tuple to hold the term for later elaboration.
term ::= term op primary apply[op, S[
e, term], S[
e, primary]]
Elaborate the term, then the primary, and then apply the op to the result.
literal ::= name Mk
V[m: atom, xName: S[
NIL, name]]
| number Mk
V[m: num, cNum: number]
| string Mk
V[m: string, cStr: string]
A name as a literal is just made into an atom tuple. A numeric literal is stored as a num tuple. And, a string literal is stored as a string tuple.
name ::= id MkAtom[id]
| name id
CONS[MkAtom[id], S[
NIL, name]]
A qualified name is mapped into a list with the most highly qualified identifier first and the head, unqualified identifier last.
invocation ::= primary EvalName[
e, S[
e, primary].xName]
Elaborate the primary to obtain a name to invoke (stored as the xName component of the resultant tuple). Then use EvalName to lookup and evaluate the name.
indirection ::= name Mk
V[m: evalStruc,
cV: EvalName[
e, S[
NIL, name]],
xName: S[
NIL, name]]
Use EvalName to lookup and evaluate the name and embed the resultant value in an evalStruc tuple along with the name from which it came.
2.3.2. Definitions of semantics as a Mesa function
Groundrule: Once constructed, no values or lists of values are ever modified (except in Lookup). Therefore, they can be handed around without regard for being changed in situ later.
S: PROC[e: Env, nt: NonTerminal] RETURNS[vs: Vs] = {--TBD--};
NonTerminal: TYPE = REF --ParseNode--;
Error: ERROR[ec: {BoundsFault, InvalidTag, NotSingleton, UnboundId, WrongType}] = CODE;
*******VALUES*******
V: TYPE = REF VRec;
Number: TYPE = REAL;
VRec:
TYPE =
RECORD[m: Mark,
cVs: Vs←NIL, cV: V←NIL, cNum: Number𡤀.0, cStr: STRING←NIL, cId: Id←NIL, -- Contents
cTerm: NonTerminal←NIL, -- used for representing quoted terms
xId: Id←NIL, xName: Name←NIL, xEnv: Env←NIL]; -- eXtra information
Mark: TYPE= {atom, num, string, node, -- base values
tag, bind, scope, bindStruc, evalStruc, onodeStruc, quotedTerm, vOfQ, evalSentinel};
MarkAsAtom: ARRAY Mark OF ATOM = [$atom, $num, $string, $node, $tag, $bind, $scope, $bindStruc, $evalStruc, $onodeStruc, $quotedTerm, $vOfQ, $evalSentinel];
Vs, Env: TYPE=LIST OF V; -- for an Env, all items have mark bind or bindStruc
X: Env ← NIL; -- stand-in for the eXternal environment
Mk
V:
PROC[m: Mark, cVs: Vs←
NIL, cV: V←
NIL, cNum: Number𡤀.0, cStr:
STRING←
NIL,
cId: Id←
NIL, cTerm: NonTerminal←
NIL, xId: Id←
NIL, xName: Name←
NIL, xEnv: Env←
NIL]
RETURNS[V] = {
-- The basic function for making a tuple
RETURN[NEW[VRec ← [m: m, cVs: cVs, cV: cV, cNum: cNum, cStr: cStr, cId: cId, cTerm: cTerm, xId: xId, xName: xName, xEnv: xEnv]]]};
True: V=Mk
V[m: num, cNum: 1.0]; False: V=Mk
V[m: num, cNum: 0.0];
TRUE and FALSE as tuples.
Mk
Vs:
PROC[v1, v2, v3: V←
NIL]
RETURNS [vs: Vs] = {
Make a list of Vs from individual Vs.
vs←NIL; IF v3#NIL THEN vs←CONS[v3, vs];
IF v2#NIL THEN vs←CONS[v2, vs]; IF v1#NIL THEN vs←CONS[v1, vs] };
ConcatVs:
PROC[v1, v2, v3: Vs←
NIL]
RETURNS [vs: Vs] = {
Concatenate a number of individual lists into one list (in order v1, v2, v3).
AppendToT:
PROC[list: Vs] = {
UNTIL list=NIL DO t.rest ← CONS[list.first, NIL]; t ← t.rest; list ← list.rest ENDLOOP};
t: Vs ← (vs←CONS[NIL, NIL]);
AppendToT[v1]; AppendToT[v2]; AppendToT[v3]};
NthItem:
PROC[vs: Vs, n:
INT]
RETURNS [V] = {
-- indexing into a list
IF vs=NIL OR n<0 THEN Error[BoundsFault];
RETURN[ IF n=0 THEN vs.first ELSE NthItem[vs.rest, n-1] ]};
Name, Ids:
TYPE=
LIST
OF Id; Id:
TYPE =
ATOM;
A Name is never empty; it always comes from the parser
MkName: PROC[a: ATOM, hd: Name←NIL] RETURNS[Name] = {RETURN[CONS[a, hd]]};
EqName:
PROC[n1, n2: Name]
RETURNS[
BOOL] = {
UNTIL n1=
NIL
OR n2=
NIL
DO
IF n1.first#n2.first THEN RETURN[FALSE];
n1←n1.rest; n2←n2.rest;
ENDLOOP;
RETURN[n1=n2]};
*******REAL WORK*******
MkScope:
PROC[vs: Vs]
RETURNS [Vs] = {
RETURN[
Unless a scope contains some structural items, its contents simply become contents of the surrounding node.
(IF HasStruc[vs] THEN MkVs[MkV[m: scope, cVs: Contents[vs]]] ELSE Contents[vs])]};
HasStruc:
PROC[vs: Vs]
RETURNS [
BOOL] = {
Tests if a list of Vs has any structural items (binds, indirections, or structurally opened node).
One:
PROC[v: V]
RETURNS [
BOOL] = {
RETURN[v.m=bindStruc OR v.m=evalStruc OR v.m=onodeStruc OR v.m=quotedTerm]};
RETURN[ IF vs=NIL THEN FALSE ELSE (One[vs.first] OR HasStruc[vs.rest]) ]};
MkTag:
PROC[
e: Env, n: Name]
RETURNS [V
--tag--] = {
For every valid tag in a script there must be a tag definition (section 3.1.1). That definition is given as a (structural) binding of a TAG$ node to the tag's name. capture that definition in the tuple representing the tag along with its name (remember these are value semantics, not an implementation: a real implementation would avoid copying the definition and point to it somehow).
tagDef: --node--V = EvalName[e, n];
IF NOT HasTag[tagDef.cVs, $TAG] THEN Error[InvalidTag];
RETURN[MkV[m: tag, cV: tagDef, xName: n]]};
MkNode:
PROC[
e: Env, vs: Vs]
RETURNS [V
-- node--] = {
--[note 1]--
The canonical form for a node is a list of all its tags followed by its contents, followed by a sequence of the relevant bindings for each of the tags.
RETURN[MkV[node, ConcatVs[Tags[vs], Contents[vs], RelBindings[e, Tags[vs]]]]]};
The semantic procedures MkBinding, Lookup, EvalName, and Eval are a closely related set and provide the central definition of how names are used in Interscript and how bindings are handled.
MkBinding:
PROC[
e: Env, v: V, n: Name, kind: Mark
--bind|bindStruc--]
RETURNS [
--bind|bindStruc-- V] = {
The only difference between a ← and a %← is that the tuple is marked as such.
IF n.rest=
NIL
THEN
RETURN[Mk
V[m: kind, cV: v, xId: n.first]]
A binding to a simple id results in a simple tuple being made.
ELSE {t: V=EvalName[
e, n.rest];
IF t.m#node
THEN Error[WrongType];
RETURN[MkBinding[e, MkNode[e, ConcatVs[t.cVs, MkVs[MkV[m: kind, cV: v, xId: n.first]]]], n.rest, kind]]};
A binding to a qualified name is handled by copying the binding corresponding to the prefix of the name (it will be bound to a node value) with a new binding tuple added to the end of the node value. Any future use of EvalName for the name will find that binding first.
};
Lookup:
PROC[
e: Env, n: Name]
RETURNS [V] = {
looking up a simple identifier in an environment is a simple process of marching down the environment list until a binding to that identifier is reached or the end of the list is encountered.
One:
PROC[
e: Env, id: Id]
RETURNS [V] = {
-- local procedure to handle simple ids
b: V ← IF e=NIL THEN NIL ELSE IF e.first.xId=id THEN e.first ELSE One[e.rest, id];
IF
e.first.m=evalSentinel
AND b#
NIL
THEN
e.first.xEnv ←
CONS[b,
e.first.xEnv];
see note in Eval to explain why the above statement hangs bindings off sentinels put into environments
RETURN[b.cV]};
Looking up a qualified name requires that we first evaluate the prefix of the name without its last identifier using EvalName (which must yield a node value), then make an environment from the bindings of that prefix in which to look up the suffix identifier.
RETURN[ IF n=NIL THEN NIL ELSE One[Bindings[EvalName[e, n.rest]], n.first] ]};
EvalName:
PROC[
e: Env, n: Name]
RETURNS [V] = {
Lookup the name and evaluate it (it might be a quoted term)
RETURN[Eval[e, Lookup[e, n]]]};
Eval:
PROC[
e: Env, v: V]
RETURNS [V] = {
IF v.m=quotedTerm
THEN {
ePlus: Env =
CONS[Mk
V[m: evalSentinel, xId:
NIL],
e];
We push an evalSentinel tuple on the top of the environment so that lookup can collect all the bindings needed to evaluate this quotedTerm. The environment that ends up hanging off the evalSentinel tuple is then tucked away in the vOfQ tuple that results from evaluating the quoted term. This information is needed to correctly externalize an indirection that caused a quoted term to be evaluated. If the bindings in the xEnv component of the vOfQ tuple match those extant when the document is externalized, then the editor can simply output the indirection that gave rise to the vOfQ tuple safe in the assurance that its value is unchanged.
RETURN MkV[m: vOfQ, cV: S[ePlus, v.cTerm].first, xEnv: ePlus.first.xEnv]}
ELSE RETURN[BaseVal[v]]};
BaseVal:
PROC[v: V]
RETURNS [V] = {
RETURN[
(IF v.m=evalStruc THEN BaseVal[v.cV.cV -- it must be a vOfQ--] ELSE v)]};
Op: TYPE={ADD, SUB, MUL, DIV, LT, EQ, SUBSCRIPT};
IsInteger:
PROC[v: V]
RETURNS[
BOOL] = {
-- check that a number is actually an integer
IF v.m#num THEN Error[WrongType];
RETURN[Real.Float[Real.Fix[v.cNum]]=v.cNum]};
Apply:
PROC[op: Op, v1: V, v2: V]
RETURNS [result: V] = {
apply the operator to the base values for v1 and v2 (i.e., evaluate any quoted terms that you encounter)
vv1: V = BaseVal[v1]; vv2: V = BaseVal[v2];
SELECT op
FROM
ADD,
SUB,
MUL,
DIV,
LT => {
IF vv1.m#num
OR vv2.m#num
THEN Error[WrongType];
RETURN[(
SELECT op
FROM
ADD => MkV[m: num, cNum: (vv1.cNum+vv2.cNum)],
SUB => MkV[m: num, cNum: (vv1.cNum-vv2.cNum)],
MUL => MkV[m: num, cNum: (vv1.cNum*vv2.cNum)],
DIV => MkV[m: num, cNum: (vv1.cNum/vv2.cNum)],
LT => (IF vv1.cNum<vv2.cNum THEN True ELSE False),
ENDCASE => NIL)]};
EQ => {
IF v1.m#v2.m
THEN
RETURN[False];
Tuple marks have to be the same if they are to be equal
SELECT vv1.m
FROM
node => RETURN[False]; -- two separate node values are never equal
atom => RETURN[IF (vv1.cId=vv2.cId) THEN True ELSE False];
num => RETURN[IF (vv1.cNum=vv2.cNum) THEN True ELSE False];
string => RETURN[IF String.EqualString[vv1.cStr, vv2.cStr] THEN True ELSE False];
ENDCASE => Error[WrongType]};
SUBSCRIPT =>
-- use v2 as an index into the node v1
IF NOT IsInteger[vv2] OR vv1.m#node THEN Error[WrongType]
ELSE RETURN[NthItem[Contents[Items[vv1]], Real.Fix[vv2.cNum]]];
ENDCASE};
Tags:
PROC[vs: Vs]
RETURNS [Vs
--tag items only--] = {
RETURN[(Sort[GetTags[vs]])]};
GetTags:
PROC[vs: Vs]
RETURNS [Vs
--tag items only--] = {
One: PROC[v: V] RETURNS[Vs] = {RETURN[(IF v.m=tag THEN MkVs[v] ELSE NIL)]};
RETURN[ IF vs=NIL THEN NIL ELSE ConcatVs[One[vs.first], GetTags[vs.rest]] ]};
Sort: PROC[vs: Vs --tag items only--] RETURNS [sVs: Vs --tag items only--] = {--[note 2]--};
Items:
PROC[v: V]
RETURNS [Vs] = {
IF v.m=node THEN RETURN[RawItems[v.cVs]] ELSE Error[WrongType]};
RawItems:
PROC[vs: Vs]
RETURNS[Vs] = {
Pull all the basic items out of a list, burrowing into evalStruc, onodeStruc, or scope tuples to extract their contained items
One:
PROC[v: V]
RETURNS[Vs] = {
Local procedure to look at a single tuple and pull items out of it if it is an evalStruc, onodeStruc, or a scope. Otherwise the value is returned.
RETURN[(
SELECT v.m
FROM
evalStruc, onodeStruc => v.cVs,
scope => RawItems[v.cVs],
ENDCASE => MkVs[v])]};
RETURN[IF vs=NIL THEN NIL ELSE ConcatVs[One[vs.first], RawItems[vs.rest]]]};
Bindings:
PROC[v: V]
RETURNS [Env] = {
Make an environment from the bindings in the node v.
IF v.m=node THEN RETURN[GetBindings[Items[v]]] ELSE Error[WrongType]};
GetBindings:
PROC[vs: Vs]
RETURNS[
e: Env] = {
One:
PROC[v: V]
RETURNS[
e: Env] = {
-- local procedure for catching bindings
RETURN[IF v.m=bind OR v.m=bindStruc THEN MkVs[v] ELSE NIL]};
RETURN[IF vs=NIL THEN NIL ELSE ConcatVs[GetBindings[vs.rest], One[vs.first]]]};
RelBindings:
PROC[
e: Env, vs: Vs
--tag items only--]
RETURNS [Vs] = {
Find all the relevant bindings for the tags in vs and make an environment from them.
One:
PROC[
e: Env, v: V]
RETURNS [Vs] = {
IF v.m#tag THEN Error[WrongType];
RETURN[RefineBindings[e, PullDefaults[Bindings[
EvalName[e, MkName[$attributes, v.xName]]]]]]};
RETURN[IF vs=NIL THEN NIL ELSE ConcatVs[One[e, vs.first], RelBindings[e, vs.rest]]]};
RefineBindings:
PROC[
e: Env, basis: Vs]
RETURNS [Vs] = {
For every identifier bound non-structurally in basis, place a binding in the result Vs. If there is a binding in the environment for the identifier use that; if not, use the one for it in basis (which provides a default value).
One:
PROC[
e: Env, b: V]
RETURNS [Vs] = {
IF b.m#bind AND b.m#bindStruc THEN Error[WrongType];
RETURN[
IF b.m=bindStruc
THEN
NIL
ELSE MkVs[MkV[
m: bind, cV: Lookup[ConcatVs[e, MkVs[b]], MkName[b.xId]], xId: b.xId]]]};
RETURN[
IF basis=
NIL
THEN
NIL
ELSE ConcatVs[RefineBindings[e, basis.rest], One[e, basis.first]]]};
PullDefaults:
PROC[
e: Env]
RETURNS [Vs] = {
For every binding in the environment return a binding that gives a default value for that identifier. Every identifier in the incoming environment is bound to a TYPE$ node (because relBindings reaches into the attributes attribute for a TAG$ node to get these type definitions). The result Vs is not an environment, but is in the same left-to-right order as the bindings occuring in the attributes attribute for the TAG$ node from which they came.
One:
PROC[b: V]
RETURNS [Env] = {
IF b.cV.m=node
AND HasTag[Items[b.cV], $
TYPE]
THEN
RETURN[MkVs[MkV
[m: bind, cV: Lookup[Bindings[b.cV], MkName[$default]], xId: b.xId]]]
ELSE Error[WrongType]};
RETURN[IF e=NIL THEN NIL ELSE ConcatVs[PullDefaults[e.rest], One[e.first]]]};
HasTag:
PROC[vs: Vs, id: Id]
RETURNS[
BOOL] = {
Checks whether a given id occurs in the list of tags.
RETURN[ IF vs.first.m=tag AND vs.first.cId=id THEN TRUE ELSE HasTag[vs.rest, id] ]};
Contents:
PROC[vs: Vs]
RETURNS [Vs] = {
The contents of a node are all the tuples in it except tags and non-structural bindings (it thus includes all other values, structural bindings, structured openedNodes, and indirections).
One:
PROC[v: V]
RETURNS [Vs] = {
RETURN[(IF v.m=tag OR v.m=bind THEN NIL ELSE MkVs[v])]};
RETURN[ IF vs=NIL THEN NIL ELSE ConcatVs[One[vs.first], Contents[vs.rest]] ]};