*start* 02291 00024 USt Date: 6 July 1981 12:59 pm PDT (Monday) Subject: Current Level 0/1 Interdoc status To: Guttag, Horning, Lampson cc: Mitchell The low-level syntax for InterDocs is the following (basically it represents the dominant tree structure by the nonterminal "node", each of which can have some set of labels, some structure, which may be subtrees as well as actual data, and a set of transformations on an environment, about which more below): node ::= "(" [label* ":"] [envTrans] structure ")" label ::= "#" atom envTranses ::= "{" envTrans* "}" envTrans ::= [ "'" ] (name | definition) -- a name "invokes" a definition name ::= atom ( "." atom)* definition ::= name rhs rhs ::= bindingOp ( envTranses | content ) | "." envTranses structure ::= content* content ::= literal | node | name -- need "~" for Booleans? literal ::= Boolean | integer | hexint | real | string | label Boolean ::= F | T bindingOp ::= "=" | [ "/" ] ( "_" | "+" | "" | "*" | "/" ) How properties propagate and are inherited: We imagine an InterDoc script being processed in the following manner (or in any algorithmically equivalent way, of course): (1) Parse the script to form a parse tree in which the dominant tree structure is derived directly from the node/structure part of the above grammar and associate with each node its envTranses. (2) As soon as the envTranses for a node have been parsed, its environment can be determined by starting with its parent's environment and modifying it by the new node's envTranses. Any persistent envTranses are made in both the parent's and the node's environments (Is this sufficient? Can persistent transes change higher nodes' environments?). (3) Once a node's environment has been determined, its structure can be parsed and evaluated (in the obvious recursive manner). The structure may use values from the node's environment (e.g., chapter or section numbers). This is why one needs to be able to assign trees to variables in the environment. The only way a value from a node's structure can affect its environment is if a subnode makes a persistent change to a value in the parent node's environment. There is no direct way in which the content of a node can affect its environment since the environment is determined first. *start* 01134 00024 USt Date: 7 July 1981 1:36 pm PDT (Tuesday) From: Mitchell.PA Subject: Basic InterDoc Semantics To: Mitchell Here are the current semantics for interdocs: The kinds of values that can be represented in an InterDoc script are primitiveValue: Booleans, integers, reals, strings, atoms, labels, and sequences of primitiveValues; environment: id > value function: environment > value node: (labels, function, value) The expression forms of interest come from the following set: literal id (should probably also have ~id) id.exp n op v ( op in {+,,*,/,and,or,...}, n a name, v a value) bind(n,v) bindq(n,v) compose(e1,e2) invoke(n) The semantics of these expression forms is defined by the following (E=Eval,  denotes an environment; [id_v]() means " with id bound to v"): E(literal,) = primitiveValue(literal) E(id,) = (id) E(id.n,) = E(n,(id)) E(bindq(id,v),) = [id_v]() E(bindq(id.n,v),) = [id_E(bindq(n,v),(id))]() E(bind(n,v),) = E(bindq(n,E(v,)),) E(n op v,) = E(bindq(n, op(E(n,),E(v,))),) E(compose(e1,e2),) = E(e2,E(e1,)) E(invoke(n),) = E(n,)() *start* 03587 00024 USt Date: 13 July 1981 6:39 pm PDT (Monday) From: Horning.pa Subject: GML paper To: Interdoc At Chuck Geschke's suggestion, I took a look at the paper on GML in the proceedings of the ACM SIGPLAN SIGOA Symposium on Text Manipulation. Apparently some IBM people have been pushing ANSI to adopt GML as a standard for interchange of editable documents. I agree with Chuck that there is nothing astounding in this paper; I like our own preliminary design for Interdoc a lot better. (It should be much easier to translate an arbitrary GML document to Interdoc than the other way around.) However, it is interesting to see Goldfarb confirming some of the basic Interdoc premisses, as indicated in the following excerpts: Procedural markup ... has a number of disadvantages. For one thing, information about the document's attributes is usually lost. ... Procedural markup is also inflexible. If the user decides to change the style of his document (perhaps because he is using a different output device), he will need to repeat the markup process to reflect the changes. ... Moreover, markup with control words can be time-consuming, error-prone, and require a high degree of operator training, particularly when complex typographic results are desired. ... If, as postulated, descriptive markup like this suffices for all processing, it must follow that the processing of a document is a function of its attributes. ... In terms of the document processing model, the advantage of descriptive markup is that is permits the user to define attributes--and therefore element types--not known to the formatter, and to specify the processing for them. ... Generic coding is a considerable improvement over procedural markup in practical use, but it is conceptually unsound. This is because documents are complex objects, and they have other attributes that a markup language must be capable of describing. ... "Content" is, of course, a primary attribute, and is the one that the secondary attributes of an element describe. The content consists of an arrangement of other elements, each of which in turn may have other elements in its content, and so on until further division is impossible. One way in which GML differs from generic coding schemes is in the conceptual and notational tools it provides for dealing with this hierarchical structure. ... Formatting specifications [for Cliff Jones's book "Software Development: A Rigorous Approach"] were provided by the publisher, and no concessions were needed to accomodate the use of GML, despite the markup having existed before the specifications. (On the contrary, the publisher took advantage of GML by changing some of the specifications after he saw the page proofs.) The experiment was completed on time, and the publisher considers it a complete success. (This despite some geographical complications: the publisher was in London, the book's author in Brussels, and this paper's author in California. Almost all communication was done via an international computer network, and the project was nearly completed before all the participants met for the first time.) ... While procedural markup (or no markup at all) leaves a document as a character string that has no form other than that which can be deduced from analysis of the document's meaning, GML markup reduces a document to a regular expression in a known grammar. This permits established techniques of computational linguistics and compiler design to be applied to natural language processing and other document processing applications. *start* 05228 00024 USt Date: 15 July 1981 6:44 pm PDT (Wednesday) From: Mitchell.PA Subject: Current Level 0/1 Interdoc status To: Horning cc: Mitchell Jim, Here is my rendering (rending?) of my whiteboard and an attempt to solve a few loose ends. The item of which I am most unsure is the mechanism for connecting environments and the binding function in the semantics section. Have at it. ---------------------------------- We imagine an InterDoc script being processed in the following manner (or in any algorithmically equivalent way, of course): Parse the script, evaluating environment transformations (called functions in the semantics) as soon as parsed. In general, these functions may return zero or more "values": if zero, then the function has no effect on the tree structure being generated from the script; if one or more, then each of these becomes a leaf subnode of the node currently being elaborated. A node with its own substructure may also be returned. Basic InterDoc Semantics The kinds of values that can be represented in an InterDoc script are primitiveValue: NIL Boolean: {F,T} integer: ... -3, -2, -1, 0, 1, 2, 3, ... real: 1.2E5, . . . string: atom:  (the null id), bold, thisIsAnAtom, Helvetica, . . . label: #A123, #anAtom, #Paragraph the empty environment: nullEnv modifier: {var,local,const,propagate,none} and sequences of primitiveValues; environment: id > value X modifier function: environment > value node: (labels, function) -> function X value The expression forms of interest come from the following set: literal id -- (should probably also have ~id) id.n -- n a name op(n,v,m) -- ( op in {+,,*,/,and,or,...}, v a value, m a modifier) bind(n,v,m) bindq(n,v,m) compose(e1,e2) invoke(n) cond(e1,e2,e3) -- if e1 then e2 else e3 The semantics of these expression forms are defined by the following evaluation rules (E=Eval,  denotes an environment; (id) is the value associated with id in ;  is the modifier of id in ; [id_(v,m)]() means " with id bound to (v,m)"): binding(id,nullEnv)=none binding(id,) = if =none then binding(id,(parent)) else  E(id,) = if =none then E(parent.id,) else (id) E(id,nullEnv) = id E(literal,) = primitiveValue(literal) E(id.n,) = E(n,(id)) E(compose(e1,e2),) = E(e2,E(e1,)) E(invoke(n),) = E(n,)() E(cond(e1,e2,e3),) = if E(e1,)=T then E(e2,) else E(e3,) E(bindq(id,v,m),) = id=parent => [ERROR_T]() binding(id,)=const => [ERROR_T]() m=var and binding(id,)=var => [id_(v,var)]([parent_E(bindq(id,v,propagate),(parent))]()) m=propagate and =none => [parent_E(bindq(id,v,propagate),(parent))]() T => [id_(v,m)]() E(bindq(id.n,v,m),) = [id_E(bindq(n,v,m),(id))]() E(bind(n,v,m),) = E(bindq(n,E(v,),m),) E(op(n,v,m),) = E(bindq(n, op(E(n,),E(v,)),m),) Notes: [ERROR_T]() simply notes that an error has occurred in a bindq in  How semantics are associated with an entire document: Each environment initially contains only its parent (as the id "parent"). When a valid bindq(id,v,var) is evaluated in an environment , it may have environmental impact on both  and (parent). It will have an effect on (parent) if already bound as var in the parent chain, in which case its effect on (parent) is bindq(id,v,propagate), which, since parent is a component of , alters  to be [parent_E(bindq(id,v,propagate),(parent))](); then, this altered , ' is further altered by modifying id, i.e., [id_(v,var)]('). An "propagate" bindq in  has the semantics that it is passed on to (parent) if =none and acts like bindq(id,v,local) otherwise. When an id is referred to and =none, then the value is sought in (parent), i.e., E(parent.id,) is evaluated (this is a recursive definition). I don't think this lengthening rule causes any problems assuming that direct assignments to parent are not allowed (the first line in the semantics of bindq rules this out). Semantics of labels: A label #atom on a node gives that node membership in the set named by atom. Multiple labels place a single node in multiple sets, and a unique label on a node places it in a singleton set, i.e., identifies it uniquely. Interdoc Syntax: The low-level syntax for InterDocs is the following (basically it represents the dominant tree structure by the nonterminal "node", each of which can have some set of labels, some contents, which may be actual data (the body of the document), transformations on the environment, or subtrees: node ::= "(" [label* ":"] structure* ")" label ::= "#" atom structure ::= envTrans | content content ::= literal | ["'"] name | node literal ::= Boolean | integer | hexint | real | string | label name ::= atom ( "." atom)* atom ::= (letter | "" ) ( letter | "" | digit )* -- "" is the null id envTrans ::= singleTrans | compoundTrans singleTrans ::= name [ "%" ] rhs -- % means var rhs ::= Op ( compoundTrans | content ) | "." compoundTrans compoundTrans ::= "{" singleTrans* "}" Op ::= "=" | "_" | "+" | "-" | "*" | "/" | "AND" | "OR" | . . . Missing or in question: literal sequences optional quote before name in a content *start* 01253 00024 USt Date: 15 July 1981 6:46 pm PDT (Wednesday) From: Horning.pa Subject: Draft Interdoc Outline To: Mitchell cc: Horning [Notes for the contents of the document we hope to construct in the next two weeks. * marks items likely to be only sketched at this time. XXX marks placeholders for items needed but not being worked on.] TOWARDS AN INTERCHANGE LANGUAGE FOR EDITABLE DOCUMENTS INTRODUCTION * Rationale and background * Overview Scope Exclusions * Feasibility * CONCEPTS AND GUIDING PRINCIPLES EXAMPLES [hardcopy, private representation, Interdoc script] Laurel message Simple Bravo document BravoX document with styles THE BASE LANGUAGE Syntax Primitive and sequence data types and literals Labels and references PROPERTIES Environments, names, and values Transformations: binding, definitions and invocations Scope and persistence Standard properties CONVENTIONS [Property definitions to be shared by various editor classes] Text Messages * Fonts and formats * Hierarchical documents * Styles XXX Graphics PRAGMATICS * Private encodings and private representations XXX Conversion efficiency XXX APPENDICES GLOSSARY FORMAL SEMANTIC DEFINITION RELATION TO OTHER STANDARDS XXX INDEX *start* 04792 00024 USt Date: 16 July 1981 3:36 pm PDT (Thursday) From: Horning.pa Subject: Current Level 0/1 Interdoc status/rev. 1 To: Mitchell cc: Horning We envision an Interdoc script being processed in any manner equivalent to the following: Parse the script, evaluating environment transformation functions as soon as parsed (so that the environment of each piece of content is available during parsing). In general, these functions may return zero or more "values": if zero, then the function has no effect on the tree structure being generated from the script; if one or more, then each of these becomes a leaf subnode of the node currently being elaborated. A node with its own substructure may also be returned. Basic InterDoc Semantics The kinds of values that can be represented in an InterDoc script are primitiveValue: NIL Boolean: {F, T} integer: ... -3, -2, -1, 0, 1, 2, 3, ... real: 1.2E5, . . . string: id:  (the null id), bold, thisIsAnId, Helvetica, . . . label: #A123, #anAtom, #Paragraph the empty environment: nullEnv modifier: {var, local, const, assign, none} and sequences of primitiveValues; environment: id > value, modifier function: environment > value node: labels, function The functional expressions of interest come from the following set: -- by convention n: name, v: value, m: modifier, e: expression literal name -- id ( '. id)* op(n, v, m) -- ( op in {+, , *, /, and, or, ... }) bindq(n, v, m) bind(n, v, m) compose(e1, e2) invoke(n) cond(e1, e2, e3) -- if e1 then e2 else e3 node(labels, function) The semantics of these expressions are defined by the following evaluation rules (E for evaluate,  denotes an environment; (id) is the value bound to id in ;  is the modifier of id in ; [id_(v, m)]() means " with id bound to (v, m)"): modifier(id, nullEnv)=none modifier(id, ) = if =none then modifier(id, (outer)) else  E(id, nullEnv) = id E(id, ) = if =none then E(id, (outer)) else (id) E(id.n, ) = E(n, (id)) E(literal, ) = primitiveValue(literal) E(compose(e1, e2), ) = E(e2, E(e1, )) E(invoke(n), ) = E(E(n, ), ) E(cond(e1, e2, e3), ) = if E(e1, )=T then E(e2, ) else E(e3, ) E(bindq(id, v, m), ) = modifier(id, )=const =>  m=assign => { =local =>  =var => [id_(v, var)]() =none => [outer_(E(bindq(id, v, assign), (outer)), local)]() } T => [id_(v, m)]() E(bindq(id.n, v, m), ) = [id_E(bindq(n, v, m), (id))]() E(bind(n, v, m), ) = E(bindq(n, E(v, ), m), ) E(op(n, v, m), ) = E(bindq(n, OP(E(n, ), E(v, )), m), ) -- where OP denotes the binary function associated with op E(node(l, f), ) = E(outer, E(f, [outer_(, local)](nullEnv))) How semantics are associated with an entire document: Each environment initially contains only its "inherited" environment (bound to the id "outer"). Most bindings take place directly in . However, the value of a bindq(id, v, assign) in an environment  will change  by rebinding id in the "innermost" environment (following the chain of outer's) in which it is bound, provided that binding has the modifier var. When an id is referred to and =none, then the value is sought recursively in (outer). Perverse explicit bindings to outer might create loops, leaving some ids undefined, but there seems to be little reason to clutter up the semantics by forbidding such assignments. Semantics of labels: A label #atom on a node gives that node membership in the set named by atom. Multiple labels place the node in multiple sets, and a unique label on a node places it in a singleton set, i.e., identifies it uniquely. Interdoc Syntax: Note that we should really be using this syntax above, both to define the syntax of expressions, and in the left-hand side of the semantic equations. The low-level syntax for InterDocs is the following (basically it represents the dominant tree structure by the nonterminal "node", each of which can have some set of labels, some contents, which may be actual data (the body of the document), transformations on the environment, or subtrees: node ::= "(" [label* ":"] content* ")" label ::= "#" id content ::= literal | ["'"] name | node | envTrans literal ::= Boolean | integer | hexint | real | string | label name ::= id ( "." id)* id ::= (letter | "" ) ( letter | "" | digit )* -- "" is the null id envTrans ::= singleTrans | compoundTrans singleTrans ::= name rhs rhs ::= Op ( compoundTrans | content ) | "." compoundTrans compoundTrans ::= "{" singleTrans* "}" Op ::= "=" | "_" | "%" | "+" | "-" | "*" | "/" | "AND" | "OR" | . . . -- % means var Missing or in question: literal sequences optional quote before name in a content *start* 02222 00024 USt Date: 16 July 1981 3:38 pm PDT (Thursday) From: Mitchell.PA Subject: Draft Interdoc Outline and Meeting Reminder To: InterDoc cc: Horning, Mitchell We believe we are at a point where it would be worthwhile meeting tomorrow, Friday, July 17 at the canonical time of 1:30 p.m. in the CSL Commons. Jim H. and Jim M. would like to present the results of their efforts of the last two weeks with John Guttag and Butler Lampson. We would also like to discuss the table of contents for a document on InterDoc, and I have attached that table of contents to this message. Jim H. will be sending a separate message on the semantics and syntax of interdoc scripts today so you will all have a chance to look it over beforehand. See you there. Jim M.  [Notes for the contents of the document we hope to construct in the next two weeks. * marks items likely to be only sketched at this time. XXX marks placeholders for items needed but not being worked on. Explanatory material is in Laurel markers like this] TOWARDS AN INTERCHANGE LANGUAGE FOR EDITABLE DOCUMENTS INTRODUCTION * Rationale and background * Overview Scope Exclusions * Feasibility * CONCEPTS AND GUIDING PRINCIPLES Descriptive rather than procedural Maintaining document structure over edits Using limited editors on rich documents An open-ended standard EXAMPLES [hardcopy, private representation, Interdoc script] Laurel message BravoX document with styles Star document with a bar chart, a simple curve, a table, or a form A GML example (from SIGOA paper) THE BASE LANGUAGE Syntax Primitive and sequence data types and literals Labels and references PROPERTIES Environments, names, and values Transformations: binding, definitions, and invocations Scope and persistence Standard properties CONVENTIONS [Property definitions to be shared by various editor classes] Text Messages * Fonts and formats * Hierarchical documents * Styles XXX Graphics PRAGMATICS * Private encodings and private representations XXX Conversion efficiency XXX APPENDICES GLOSSARY FORMAL SEMANTIC DEFINITION RELATION TO OTHER STANDARDS XXX INDEX *start* 05190 00024 USt Date: 16 July 1981 7:41 pm PDT (Thursday) From: Mitchell.PA Subject: Current Level 0/1 Interdoc status/rev. 2 To: Mitchell cc: Horning We envision an Interdoc script being processed in any manner equivalent to the following: Parse the script, evaluating environment transformation functions as soon as parsed (so that the environment of each piece of content is available during parsing). In general, these functions may return zero or more "values": if zero, then the function has no effect on the tree structure being generated from the script; if one or more, then each of these becomes a leaf subnode of the node currently being elaborated. A node with its own substructure may also be returned. Basic InterDoc Semantics The kinds of values that can be represented in an InterDoc script are primitiveValue: NIL Boolean: {F, T} integer: ... -3, -2, -1, 0, 1, 2, 3, ... real: 1.2E5, . . . string: id:  (the null id), bold, thisIsAnId, Helvetica, . . . label: #A123, #anAtom, #Paragraph the empty environment: nullEnv modifier: {var, local, const, assign, none} and sequences of primitiveValues; environment: id > value, modifier function: environment > value node: labels, function The functional expressions of interest come from the following set: -- by convention n: name, v: value, m: modifier, e: expression literal name -- id ( '. id)* bind(n, m, op, v) -- ( op in {', +, , *, /, and, or, ... }) compose(e1, e2) invoke(n) cond(e1, e2, e3) -- if e1 then e2 else e3 node(labels, function) The semantics of these expressions are defined by the following evaluation rules (E for evaluate, V for value,  denotes an environment; (id) is the value bound to id in ;  is the local modifier of id in ; [id_(v, m)]() means " with id bound to (v, m)"): E(n, ) =  E(literal, ) =  E(compose(e1, e2), ) = E(e2, E(e1, )) E(invoke(n), ) = E(V(n, ), ) E(cond(e1, e2, e3), ) = if V(e1, )=T then E(e2, ) else E(e3, ) E(bind(n, m, op, v), ) = bindq(n, m, apply(op, n, v, ), ) E(node(l, f), ) = E(outer, E(f, [outer_(, local)](nullEnv))) V(id, nullEnv) = id V(id, ) = if =none then V(id, (outer)) else (id) V(id.n, ) = V(n, (id)) V(literal, ) = primitiveValue(literal) V(invoke(n), ) = V(V(n, ), ) V(cond(e1, e2, e3), ) = if V(e1, )=T then V(e2, ) else V(e3, ) V(node(l, f), ) = node(l, evalNode(f, )) bindq(id, m, v, ) = modifier(id, )=const =>  m=assign => { =var => [id_(v, var)]() =none and modifier(id,)=var => [outer_(bindq(id, assign, v, (outer)), local)]() T =>  } T => [id_(v, m)]() bindq(id.n, m, v, ) = [id_bindq(n, m, v, (id))]() modifier(id, nullEnv)=none modifier(id, ) = if =none then modifier(id, (outer)) else  apply(op, n, v, ) = op=QUOTE => v op=PLUS => E(n, )+E(v, ) . . . How semantics are associated with an entire document: Each environment initially contains only its "inherited" environment (bound to the id "outer"). Most bindings take place directly in . However, the value of a bindq(id, assign, v) in an environment  will change  by rebinding id in the "innermost" environment (following the chain of outer's) in which it is bound, provided that binding has the modifier var. When an id is referred to and =none, then the value is sought recursively in (outer). Perverse explicit bindings to outer might create loops, leaving some ids undefined, but there seems to be little reason to clutter up the semantics by forbidding such assignments. Semantics of labels: A label #atom on a node gives that node membership in the set named by atom. Multiple labels place the node in multiple sets, and a unique label on a node places it in a singleton set, i.e., identifies it uniquely. Interdoc Syntax: Note that we should really be using this syntax above, both to define the syntax of expressions, and in the left-hand side of the semantic equations. The low-level syntax for InterDocs is the following (basically it represents the dominant tree structure by the nonterminal "node", each of which can have some set of labels, some contents, which may be actual data (the body of the document), transformations on the environment, or subtrees: node ::= "(" [label* ":"] content* ")" label ::= "#" id content ::= literal | name | node | envTrans literal ::= Boolean | integer | hexint | real | string | label name ::= id ( "." id)* id ::= (letter | "" ) ( letter | "" | digit )* -- "" is the null id envTrans ::= singleTrans | compoundTrans singleTrans ::= name ( "=" | ":" | ":=" | "_" ) rhs rhs ::= [ op ] content | ["."] compoundTrans compoundTrans ::= "{" singleTrans* "}" op ::= "'" | "+" | "-" | "*" | "/" | "AND" | "OR" | . . . Notes: node: the effect of content* is obtained using compose content: if a literal, it becomes part of the fringe and has no effect Missing or in question: literal sequences when explaining semantics of labels, the set of nodes you get are those in the dominant structure, not any nodes salted away in the environment that happen to have labels. *start* 04728 00024 USt Date: 17 July 1981 10:38 am PDT (Friday) From: Mitchell.PA Subject: Current Level 0/1 Interdoc status/rev. 3 To: Interdoc [The following is incomplete, and not internally consistent. We broadcast it in its present state to indicate the style and magnitude of the definition we are proposing. Please do not take the fine details overly seriously.] We envision an Interdoc script being processed in any manner equivalent to the following: Parse the script, evaluating environment transformation functions as soon as parsed (so that the environment of each piece of content is available during parsing). A separate function is used to compute the "value" of a node. Basic InterDoc Semantics The kinds of values that can be represented in an InterDoc script are primitiveValue: NIL Boolean: {F, T} integer: ... -3, -2, -1, 0, 1, 2, 3, ... real: 1.2E5, . . . string: id:  (the null id), bold, thisIsAnId, Helvetica, . . . label: #A123, #anAtom, #Paragraph the empty environment: nullEnv mode: {VAR, LOCAL, CONST, ASSIGN, NONE} and sequences of primitiveValues; environment: id > value, mode function: environment > value node: labels, function The "abstract syntax" of scripts involves the following constructors: -- by convention n: name, v: value, m: mode, e: expression literal name -- id ( '. id)* compose(e1, e2) invoke(n) cond(e1, e2, e3) -- if e1 then e2 else e3 bind(n, m, op, v) -- ( op in {', +, , *, /, and, or, ... }) node(labels, function) The semantics of these expressions are defined by the following evaluation rules (E for evaluate, V for value,  denotes an environment; (id) is the value bound to id in ;  is the LOCAL mode of id in ; [id_(v, m)]() means " with id bound to (v, m)"): E(n, ) =  E(literal, ) =  E(compose(e1, e2), ) = E(e2, E(e1, )) E(invoke(n), ) = E(V(n, ), ) E(cond(e1, e2, e3), ) = if V(e1, )=T then E(e2, ) else E(e3, ) E(bind(n, m, op, v), ) = bindq(n, m, apply(op, n, v, ), ) E(node(l, f), ) = E(outer, E(f, [outer_(, LOCAL)](nullEnv))) V(id, nullEnv) = id V(id, ) = if =NONE then V(id, (outer)) else (id) V(id.n, ) = V(n, (id)) V(literal, ) = primitiveValue(literal) V(invoke(n), ) = V(V(n, ), ) V(cond(e1, e2, e3), ) = if V(e1, )=T then V(e2, ) else V(e3, ) V(node(l, f), ) = node(l, evalNode(f, )) evalNode(f, ) = to be defined bindq(id, m, v, ) = mode(id, )=CONST =>  m=ASSIGN => { =VAR => [id_(v, VAR)]() =NONE and mode(id,)=VAR => bindq(outer.id, ASSIGN, v, ) T =>  } T => [id_(v, m)]() bindq(id.n, m, v, ) = [id_(bindq(n, m, v, (id)), LOCAL)]() mode(id, nullEnv)=NONE mode(id, ) = if =NONE then mode(id, (outer)) else  apply(op, n, v, ) = op=BLANK => V(v, ) op=QUOTE => v op=PLUS => V(n, )+V(v, ) . . . How semantics are associated with an entire document: Each environment initially contains only its "inherited" environment (bound to the id "outer"). Most bindings take place directly in . However, the value of a bindq(id, ASSIGN, v, ) will change  by reBinding id in the "innermost" environment (following the chain of outers) in which it is bound, provided that binding has the mode VAR. When an id is referred to and =NONE, then the value is sought recursively in (outer). Perverse explicit bindings to outer might create loops, leaving some ids undefined, but there seems to be little reason to clutter up the semantics by forbidding such assignments. Semantics of labels: A label #id on a node in the dominant structure gives that node membership in the set named by id. Multiple labels place the node in multiple sets, and a unique label on a node places it in a singleton set, i.e., identifies it uniquely. Interdoc Syntax: The low-level syntax for InterDocs is the following (basically it represents the dominant tree structure by the nonterminal "node", each of which can have some set of labels, some contents, which may be actual data (the body of the document), transformations on the environment, or subtrees: node ::= "(" [label* ":"] content* ")" label ::= "#" id content ::= literal | name | node | binding literal ::= Boolean | integer | hexint | real | string | label name ::= id ( "." id)* id ::= (letter | "" ) ( letter | "" | digit )* -- "" is the null id binding ::= singleBinding | compoundBinding singleBinding ::= name mode rhs mode ::= "=" | ":" | ":=" | "_" rhs ::= [ op ] content | ["."] compoundBinding compoundBinding ::= "{" singleBinding* "}" op ::= "'" | "+" | "-" | "*" | "/" | "AND" | "OR" | . . . Missing or in question: literal sequences *start* 01260 00024 USt Date: 21 July 1981 2:42 pm PDT (Tuesday) From: Mitchell.PA Subject: A Laurel document rendered in syntax of Interdoc 0/1 rev. 5 To: Horning.PA cc: Mitchell ( TextDoc -- has style "TextDoc" justified_F -- "_" means overridable default font_.{family=TimesRoman size=10 face_normal} margins_.{left_2540 right_19050} leading_.{x_1 y_1} -- overridable default leadings MsgInfo= -- Laurel information for easy access; none is changeable { pieces={hdr=#1 body=#2} -- internal references to labelled nodes time=<18 June 1981 9:18 am PDT (Thursday)> from= -- collected by Laurel; could use refs? subject= to= cc= authenticated=T } (#1: -- "#1" is the label of this node Paragraph -- it's a paragraph MsgInfo.time -- place the value of MsgInfo.time here MsgInfo.from MsgInfo.subject MsgInfo.cc ) (#2: leading.y_6 -- override outer y leading (Paragraph ) -- node which is a paragraph (Paragraph ) (Paragraph ) ) ) *start* 05942 00024 USt Date: 17 July 1981 6:41 pm PDT (Friday) From: Horning.pa Subject: Current Level 0/1 Interdoc status/rev. 5 To: Interdoc [Incorporating corrections to the local errors noted during the meeting this afternoon, plus a treatment of environment-valued expressions (see the new cases in apply, E[inner], etc.).] We envision an Interdoc script being processed in any manner equivalent to the following: Parse the script, evaluating environment transformation functions as soon as parsed (so that the environment of each piece of content is available during parsing). A separate function is used to compute the "value" of a node. Basic Interdoc Semantics The kinds of values that can be represented in an Interdoc script are primitiveValue: Boolean: {F, T} integer: ... -3, -2, -1, 0, 1, 2, 3, ... real: 1.2E5, . . . string: id:  (the null id), bold, thisIsAnId, Helvetica, . . . label: #A123, #anId, #Paragraph the empty environment: nullEnv the empty list: NIL environments, which map ids to values and modes expressions The "abstract syntax" of expressions involves the following constructors: -- by convention n: name, e: expression v: value, literal name -- id ( "." id)* quote(e) compose(e1, e2) cond(e1, e2, e3) -- if e1 then e2 else e3 node(labels, e) bind(n, m, op, e) where m is in { =, :, _, := } (or CONST, VAR, ASSIGN, LOCAL, respectively) = denotes constant binding : denotes variable declaration and initialization _ denotes assignment to a previously declared variable := denotes a local binding (cannot be affected by subnodes) and op is in { , ', +, , *, /, AND, OR, , ., ... } (or BLANK, QUOTE, PLUS, MINUS, TIMES, DIVIDE, ... ) binds to the current value of e ' binds to the expression e +, , *, /, AND, OR, ... bind to the result of a binary operation between the current value of n and the current value of e bind to a nested environment containing only the bindings resulting from e . uses e to update the bindings in the environment bound to n The semantics of scripts are defined by the following evaluation rules, where E denotes the environment transformation function V denotes the value function C denotes an environment, generally the "current" one C(id) denotes the value bound to id in C C denotes the mode bound to id in C (NONE, if id isn't bound in C) (C | id_v, m) means "C with (v, m) bound to id" E: expression > ( environment > environment ) V: expression > ( environment > value ) bindq: name, mode, value, environment > environment modeOf: id, environment > mode apply: op, mode, value, environment > value insert: value, list > list E[literal](C) = C E[n](C) = E[V[n](C)](C) E[quote(n)](C) = C E[](C) = C E[e1 e*](C) = E[e*](E[e1](C)) E[cond(e1, e2, e3)](C) = if V[e1](C) then E[e2](E[e1](C)) else E[e3](E[e1](C)) E[node(l, f)](C) = V[outer](E[f](nullEnv | outer_C, LOCAL)) E[bind(n, m, op, e)](C) = bindq(n, m, apply(op, n, e, C), C) E[{inner}](C) = (inner | outer_C, LOCAL) V[literal](C) = literal V[id](nullEnv) = id V[id](C) = if C=NONE then V[id](C(outer)) else C(id) V[id.n](C) = V[n](V[id](C)) V[quote(e)](C) = e V[] = NIL V[e1 e*](C) = insert(V[e1](C), V[e*](E[e1](C))) V[cond(e1, e2, e3)](C) = if V[e1](C) then V[e2](E[e1](C)) else V[e3](E[e1](C)) V[node(l, e)](C) = node(l, V[e](C)) V[bind(n, m, op, v)](C) = NIL V[{inner}](C) = V[inner](C) ? bindq(id, m, v, C) = modeOf(id, C)=CONST => C m=ASSIGN => { C=VAR => (C | id_v, VAR) modeOf(id, C)=VAR => bindq(outer.id, ASSIGN, v, C) T => C } T => (C | id_v, m) bindq(id.n, m, v, C) = (C | id_bindq(n, m, v, C(id)), LOCAL) modeOf(id, nullEnv)=NONE modeOf(id, C) = if C=NONE then modeOf(id, C(outer)) else C apply(op, n, e, C) = op=BLANK => V[e](C) op=QUOTE => e op=PLUS => V[n](C)+V[e](C) op=BRACES => (E[e](nullEnv | outer_C, LOCAL) | outer_nullEnv, LOCAL) op=DOTBRACES => (E[e](V[n](C) | outer_C, LOCAL) | outer_nullEnv, LOCAL) . . . -- insert(NIL, l) = l How semantics are associated with an entire document: Each environment initially contains only its "inherited" environment (bound to the id "outer"). Most bindings take place directly in C. However, the value of a bindq(id, ASSIGN, v, C) will change C by rebinding id in the "innermost" environment (following the chain of outers) in which it is bound, if that binding has the mode VAR. When an id is referred to and C=NONE, then the value is sought recursively in C(outer). Perverse explicit bindings to outer might create loops, leaving some ids undefined, but there seems to be little reason to clutter up the semantics by forbidding such assignments. Semantics of labels: A label #id on a node in the dominant structure gives that node membership in the set named by id. Multiple labels place the node in multiple sets, and a unique label on a node places it in a singleton set, i.e., identifies it uniquely. Interdoc Syntax: The low-level syntax for Interdocs is the following (basically it represents the dominant tree structure by the nonterminal "node", each of which can have some set of labels, some contents, which may be actual data (the body of the document), transformations on the environment, or subtrees: node ::= "(" [label* ":"] content* ")" label ::= "#" id content ::= literal | ["'"] name | node | binding literal ::= Boolean | integer | hexint | real | string | label name ::= id ( "." id)* id ::= (letter | "" ) ( letter | "" | digit )* -- "" is the null id binding ::= singleBinding | compoundBinding singleBinding ::= name mode rhs mode ::= "=" | ":" | ":=" | "_" rhs ::= [ op ] content | ["."] compoundBinding compoundBinding ::= "{" content* "}" op ::= "'" | "+" | "-" | "*" | "/" | "AND" | "OR" | . . . Missing or in question: literal sequences syntax for conditionals *start* 01294 00024 USt Date: 21 July 1981 3:48 pm PDT (Tuesday) From: Horning.pa Subject: Re: A Laurel document rendered in syntax of Interdoc 0/1 rev. 5 In-reply-to: Your message of 21 July 1981 2:42 pm PDT (Tuesday) To: Mitchell cc: Horning Jim, That looks like a fairly reasonable rendition. Do you think that it would be worth including a discussion of the some of the available alternatives? E.g., the "fields" of MsgInfo could be handled using labels, making repetitions OK, and the external environment might well contain a definition of LaurelStyle LaurelStyle= '{ TextDoc P_Paragraph justified_F font_.{family=TimesRoman size=10 face_normal} margins_.{left_2540 right_19050} leading_.{x_1 y_1} (#PrintForm: P #time #from #subject #to leading.y_6 #Body #cc ) } Now the Laurel document would be described by the following script: ( (#Heading: (#time:<18 June 1981 9:18 am PDT (Thursday)>) (#from: authenticated=T ) (#subject:) (#to:) (#cc:) ) (#Body: (P ) (P ) (P ) ) ) *start* 08566 00024 USt Date: 21 July 1981 4:39 pm PDT (Tuesday) From: Mitchell.PA Subject: A Laurel document rendered in syntax of Interdoc 0/1 rev. 6 To: Interdoc Here follow two renderings of a sample Laurel message as an Interdoc script using rev. 6 of the syntax, which is appended to this message. Each assumes some external definitions (e.g., font, margins), which are not specified here. The examples are intended to illustrate different ways of using the language; we have not decided which we prefer. Your comments would be appreciated. (#Rendering1: TextDoc -- has style "TextDoc" justified_F -- "_" means overridable default font_.{family=TimesRoman size=10 face_normal} margins_.{left_2540 right_19050} leading_.{x_1 y_1} -- overridable default leadings LaurelInfo= -- Laurel information for easy access; none is changeable { pieces={hdr=#Heading body=#Body}-- internal references to labelled nodes time=<18 June 1981 9:18 am PDT (Thursday)> from= subject= to= cc= authenticated=T } (#Heading: -- "#Heading" is the label of this node Paragraph -- it's a paragraph LaurelInfo.time -- place the value of LaurelInfo.time here LaurelInfo.from LaurelInfo.subject LaurelInfo.cc ) (#Body: leading.y_6 -- override outer y leading (Paragraph ) -- node which is a paragraph (Paragraph ) (Paragraph ) ) ) --------------------------- The "fields" of MsgInfo could be handled using labels, making repetitions OK, and the external environment might well contain a definition of LaurelStyle LaurelStyle= '{ TextDoc P_Paragraph justified_F font_.{family=TimesRoman size=10 face_normal} margins_.{left_2540 right_19050} leading_.{x_1 y_1} PrintForm= '( P #time #from #subject #to leading.y_6 #Body #cc ) } Now the Laurel document would be described by the following script: (#Rendering2: LaurelStyle (#Heading: (#time:<18 June 1981 9:18 am PDT (Thursday)>) (#from: authenticated=T ) (#subject:) (#to:) (#cc:) ) (#Body: (P ) (P ) (P ) ) ) --------------------------- Current Level 0/1 Interdoc status/rev. 6 [Incorporating corrections to the local errors noted during the meeting this afternoon, plus a treatment of environment-valued expressions (see the new cases in apply, E[inner], etc.).] We envision an Interdoc script being processed in any manner equivalent to the following: Parse the script, evaluating environment transformation functions as soon as parsed (so that the environment of each piece of content is available during parsing). A separate function is used to compute the "value" of a node. Basic Interdoc Semantics The kinds of values that can be represented in an Interdoc script are primitiveValue: Boolean: {F, T} integer: ... -3, -2, -1, 0, 1, 2, 3, ... real: 1.2E5, . . . string: id:  (the null id), bold, thisIsAnId, Helvetica, . . . label: #A123, #anId, #Paragraph the empty environment: nullEnv the empty list: NIL environments, which map ids to values and modes expressions The "abstract syntax" of expressions involves the following constructors: -- by convention n: name, e: expression v: value, literal name -- id ( "." id)* quote(e) compose(e1, e2) cond(e1, e2, e3) -- if e1 then e2 else e3 node(labels, e) bind(n, m, op, e) where m is in { =, :, :=, _ } (or CONST, VAR, ASSIGN, LOCAL, respectively) = denotes constant binding : denotes variable declaration and initialization := denotes assignment to a previously declared variable _ denotes a local binding (cannot be affected by subnodes) and op is in { , ', +, , *, /, AND, OR, , ., ... } (or BLANK, QUOTE, PLUS, MINUS, TIMES, DIVIDE, ... ) binds to the current value of e ' binds to the expression e +, , *, /, AND, OR, ... bind to the result of a binary operation between the current value of n and the current value of e bind to a nested environment containing only the bindings resulting from e . uses e to update the bindings in the environment bound to n The semantics of scripts are defined by the following evaluation rules, where E denotes the environment transformation function V denotes the value function C denotes an environment, generally the "current" one C(id) denotes the value bound to id in C C denotes the mode bound to id in C (NONE, if id isn't bound in C) (C | id_v, m) means "C with (v, m) bound to id" E: expression > ( environment > environment ) V: expression > ( environment > value ) bindq: name, mode, value, environment > environment modeOf: id, environment > mode apply: op, mode, value, environment > value insert: value, list > list E[literal](C) = C E[n](C) = E[V[n](C)](C) E[quote(n)](C) = C E[](C) = C E[e1 e*](C) = E[e*](E[e1](C)) E[cond(e1, e2, e3)](C) = if V[e1](C) then E[e2](E[e1](C)) else E[e3](E[e1](C)) E[node(l, f)](C) = V[outer](E[f](nullEnv | outer_C, LOCAL)) E[bind(n, m, op, e)](C) = bindq(n, m, apply(op, n, e, C), C) E[{inner}](C) = (inner | outer_C, LOCAL) V[literal](C) = literal V[id](nullEnv) = id V[id](C) = if C=NONE then V[id](C(outer)) else C(id) V[id.n](C) = V[n](V[id](C)) V[quote(e)](C) = e V[] = NIL V[e1 e*](C) = insert(V[e1](C), V[e*](E[e1](C))) V[cond(e1, e2, e3)](C) = if V[e1](C) then V[e2](E[e1](C)) else V[e3](E[e1](C)) V[node(l, e)](C) = node(l, V[e](C)) V[bind(n, m, op, v)](C) = NIL V[{inner}](C) = V[inner](C) bindq(id, m, v, C) = modeOf(id, C)=CONST => C m=ASSIGN => { C=VAR => (C | id_v, VAR) modeOf(id, C)=VAR => bindq(outer.id, ASSIGN, v, C) T => C } T => (C | id_v, m) bindq(id.n, m, v, C) = (C | id_bindq(n, m, v, C(id)), LOCAL) modeOf(id, nullEnv)=NONE modeOf(id, C) = if C=NONE then modeOf(id, C(outer)) else C apply(op, n, e, C) = op=BLANK => V[e](C) op=QUOTE => e op=PLUS => V[n](C)+V[e](C) op=BRACES => (E[e](nullEnv | outer_C, LOCAL) | outer_nullEnv, LOCAL) op=DOTBRACES => (E[e](V[n](C) | outer_C, LOCAL) | outer_nullEnv, LOCAL) . . . -- insert(NIL, l) = l How semantics are associated with an entire document: Each environment initially contains only its "inherited" environment (bound to the id "outer"). Most bindings take place directly in C. However, the value of a bindq(id, ASSIGN, v, C) will change C by rebinding id in the "innermost" environment (following the chain of outers) in which it is bound, if that binding has the mode VAR. When an id is referred to and C=NONE, then the value is sought recursively in C(outer). Perverse explicit bindings to outer might create loops, leaving some ids undefined, but there seems to be little reason to clutter up the semantics by forbidding such assignments. Semantics of labels: A label #id on a node in the dominant structure gives that node membership in the set named by id. Multiple labels place the node in multiple sets, and a unique label on a node places it in a singleton set, i.e., identifies it uniquely. Interdoc Syntax: The low-level syntax for Interdocs is the following (basically it represents the dominant tree structure by the nonterminal "node", each of which can have some set of labels, some expression, which may be actual data (the body of the document), transformations on the environment, or subtrees: node ::= "(" [label* ":"] expression* ")" label ::= "#" id expression ::= literal | ["'"] name | node | binding | conditional literal ::= Boolean | integer | hexint | real | string | label name ::= id ( "." id)* id ::= (letter | "" ) ( letter | "" | digit )* -- "" is the null id binding ::= singleBinding | compoundBinding singleBinding ::= name mode rhs mode ::= "=" | ":" | ":=" | "_" rhs ::= [ op ] expression | ["."] compoundBinding compoundBinding ::= "{" expression* "}" op ::= "'" | "+" | "-" | "*" | "/" | "AND" | "OR" | . . . conditional ::= "IF(" expression "," expression [ "," expression ] ")" Missing or in question: literal sequences relational operators Jim H. and Jim M. *start* 04250 00024 USt Date: 22 July 1981 5:10 pm PDT (Wednesday) From: Mitchell.PA Subject: A Star document rendered in Interdoc/rev. 6. To: Horning cc: Mitchell This example is taken from page 130 of the Star Functional Specification and shows a page of a paginated document with a diagram and a footnote (I recommend that you have that page in front of you when analyzing this rendition): Interdoc/Interchange/6.0 -- we probably should have some sort of header (#p7: newPage (Paragraph -- => justified_F (footRef=#fn1 fn1ref_(FootnoteRef 1) fn1ref) -- FootnoteRef style for the contents, "1" < which has shown our techniques to be valid. Other data can be collected by future changes to your accounting and billing packages, which will allow us to perform even better analyses and lead to better problem discovery and correction.> ) (Paragraph ) (#Frame1: Frame frameProps_.{ -- defaults set by invoking Frame horizontal_flushLeft vertical_floating size_{height_7100 width_9300} edges.expandingRightEdge_T border_dots1} (#r1: Rectangle upperleft_{x_2540 y_700} rectProps_.{ -- defaults set by invoking Rectangle size_{height_1000 width_2700} lineType_solid2 shading_7} (Title ) ) --? perhaps rectProps shouldn't be a contained environment (#r2: Rectangle upperleft_{x_7300 y_1500} rectProps_.{ -- defaults set by invoking Rectangle size_{height_1000 width_1800} lineType_solid2 shading_7} (Title ) ) (#r3: Rectangle upperleft_{x_200 y_3000} rectProps_.{ -- defaults set by invoking Rectangle size_{height_1300 width_2500} lineType_solid2 shading_7} (Title ) ) (#r4: Rectangle upperleft_{x_200 y_3000} rectProps_.{ -- defaults set by invoking Rectangle size_{height_1300 width_2800} lineType_solid2 shading_7} (Title ) ) (#r5: Rectangle upperleft_{x_4200 y_5500} rectProps_.{ -- defaults set by invoking Rectangle size_{height_1300 width_1600} lineType_solid2 shading_7} (Title ) ) (#r6: Rectangle upperleft_{x_6700 y_5500} rectProps_.{ -- defaults set by invoking Rectangle size_{height_1300 width_1600} lineType_solid2 shading_7} (Title ) ) (#l1out: Line lineProps_.{lineType_solid2 from_#r1 to_#l24in}) (#l2out: Line lineProps_.{lineType_solid2 from_#r2 to_#l1out}) (#l3in: Line lineProps_.{lineType_solid2 from_#l-34in to_#r3}) (#l-4in: Line lineProps_.{lineType_solid2 from_#l-34in to_#r4}) (#l-34in: Line lineProps_.{lineType_solid2 from_#l3in to_#l4in}) (#l4out: Line lineProps_.{lineType_solid2 from_#r4 to_#l56in}) (#l56in: Line lineProps_.{lineType_solid2 from_#l5in to_#l6in}) (#l5in: Line lineProps_.{lineType_solid2 from_#l56in to_#r5}) (#l6in: Line lineProps_.{lineType_solid2 from_#l56in to_#6}) ) -- end of #Frame1 (Paragraph ) (Paragraph ) (#fn1: Footnote fn1ref -- place the node with the superscripted 1 here ) ) -- end of page *start* 04028 00024 USt Date: 23 July 1981 5:00 pm PDT (Thursday) From: Mitchell.PA Subject: A Star document rendered in Interdoc/rev. 6. To: Interdoc This example is taken from page 130 of the Star Functional Specification and shows one page of a paginated document with a diagram and a footnote (I recommend that you have that page in front of you when analyzing this rendition): . . . -- pages 1 .. 6 supposedly precede this one (#p7: newPage (Paragraph.justified_F -- redefine Paragraph with justification off fn1ref_(FootnoteRef footRef=#fn1 1) -- FootnoteRef node with contents, "1" fn1ref -- place the footnote ref < which has shown our techniques to be valid. Other data can be collected by future changes to your accounting and billing packages, which will allow us to perform even better analyses and lead to better problem discovery and correction.> ) (Paragraph ) (#Frame1: Frame -- defaults are set by invoking Frame horizontal_flushLeft vertical_floating size_{height_7100 width_9300} edges.expandingRightEdge_T border_dots1 (#r1: Rectangle -- defaults are set by invoking Rectangle upperleft_{x_2540 y_700} size_{height_1000 width_2700} lineType_solid2 shading_7 (Title ) ) (#r2: Rectangle upperleft_{x_7300 y_1500} size_{height_1000 width_1800} lineType_solid2 (Title ) ) (#r3: Rectangle upperleft_{x_200 y_3000} size_{height_1300 width_2500} lineType_solid2 (Title ) ) (#r4: Rectangle upperleft_{x_200 y_3000} size_{height_1300 width_2800} lineType_solid2 (Title ) ) (#r5: Rectangle upperleft_{x_4200 y_5500} size_{height_1300 width_1600} lineType_solid2 (Title ) ) (#r6: Rectangle upperleft_{x_6700 y_5500} size_{height_1300 width_1600} lineType_solid2 (Title ) ) (#l1out: Line lineType_solid2 in_#r1 out_#l24in) (#l2out: Line lineType_solid2 in_#r2 out_#l1out) (#l3in: Line lineType_solid2 in_#l-34in out_#r3) (#l-4in: Line lineType_solid2 in_#l-34in out_#r4) (#l-34in: Line lineType_solid2 in_#l3in out_#l4in) (#l4out: Line lineType_solid2 in_#r4 out_#l56in) (#l56in: Line lineType_solid2 in_#l5in out_#l6in) (#l5in: Line lineType_solid2 in_#l56in out_#r5) (#l6in: Line lineType_solid2 in_#l56in out_#6) ) -- end of #Frame1 (Paragraph ) (Paragraph ) (#fn1: Footnote fn1ref -- place the node with the superscripted 1 here ) ) -- end of page Here a few of the definitions of "styles" invoked in the above example (see page 148 of the Star spec for what they mean): Rectangle_{ constraint_UNCONSTRAINED upperleft_{x_0 y_0} size_{height_1000 width_2000} lineType_solid1 shading_0 } Line_{ constraint_UNCONSTRAINED lineType_solid1 arrowHead_{in_none out_none} } *start* 06264 00024 USt Date: 24 July 1981 4:03 pm PDT (Friday) From: Horning.pa Subject: Current Level 0/1 Interdoc status/rev. 7 To: Donahue cc: Mitchell, Horning [Jim D., We'd like you to put on your formal semanticist hat and constructively criticize both the form and the content of the following. Jim H. & Jim M.] We envision an Interdoc script being processed in any manner equivalent to the following: Parse the script, evaluating environment transformation functions as soon as parsed (so that the environment of each piece of content is available during parsing). A separate function is used to compute the "value" of a node. Basic Interdoc The kinds of values that can be appear in an Interdoc script are literals: Boolean: {F, T} integer: ... -3, -2, -1, 0, 1, 2, 3, ... real: 1.2E5, . . . string: id:  (the null id), bold, thisIsAnId, Helvetica, . . . label: #A123, #anId, #Paragraph the empty environment: nullEnv the empty list: NIL environments, which map ids to values and modes expressions The "abstract syntax" of expressions involves the following constructors: -- by convention n: name, e: expression literal name: id ( "." id)* quote(e) compose(e1, e2) cond(e1, e2, e3) -- if e1 then e2 else e3 node(labels, e) bind(n, m, op, e) where m is in { =, :, :=, _ } (or CONST, VAR, ASSIGN, LOCAL, respectively) = denotes constant binding : denotes variable declaration and initialization := denotes assignment to a previously declared variable _ denotes a local binding (cannot be affected by subnodes) and op is in { , ', +, , *, /, AND, OR, , ., ... } (or BLANK, QUOTE, PLUS, MINUS, TIMES, DIVIDE, ... ) binds to the current value of e ' binds to the expression e +, , *, /, AND, OR, ... bind to the result of a binary operation between the current value of n and the current value of e bind to a nested environment containing only the bindings resulting from e . uses e to update the bindings in the environment bound to n The semantics of scripts are defined by the following evaluation rules, where E denotes the environment transformation function V denotes the value function C denotes an environment, generally the "current" one C(id) denotes the value bound to id in C localMode(id, C) denotes the mode bound to id in C (NONE, if id isn't bound in C) (C | id_e, m) means "C with (e, m) bound to id" E: expression > ( environment > environment ) V: expression > ( environment > value ) bindq: name, mode, value, environment > environment modeOf: id, environment > mode apply: op, mode, value, environment > value insert: value, list > list E[literal](C) = C E[n](C) = if modeOf(n, C)=NONE then C else E[V[n](C)](C) E[quote(n)](C) = C E[](C) = C -- Basis E[e1 e*](C) = E[e*](E[e1](C)) -- Composition E[cond(e1, e2, e3)](C) = if V[e1](C) then E[e2](E[e1](C)) else E[e3](E[e1](C)) E[node(l, e)](C) = V[outer](E[e](nullEnv | outer_C, LOCAL)) E[bind(n, m, op, e)](C) = bindq(n, m, apply(op, n, e, C), C) E[{e}](C) = E[e](C) V[literal](C) = literal V[id](nullEnv) = id V[id](C) = if localMode(id, C)=NONE then V[id](C(outer)) else C(id) V[id.n](C) = V[n](V[id](C)) V[quote(e)](C) = e V[] = NIL -- Basis V[e1 e*](C) = insert(V[e1](C), V[e*](E[e1](C))) -- Composition V[cond(e1, e2, e3)](C) = if V[e1](C) then V[e2](E[e1](C)) else V[e3](E[e1](C)) V[node(l, e)](C) = node(l, V[e](nullEnv | outer_C, LOCAL)) V[bind(n, m, op, e)](C) = NIL V[{e}](C) = V[e](C) bindq(id, m, e, C) = modeOf(id, C)=CONST => C m=ASSIGN => { localMode(id, C)=VAR => (C | id_e, VAR) modeOf(id, C)=VAR => bindq(outer.id, m, e, C) T => C } T => (C | id_e, m) bindq(id.n, m, e, C) = (C | id_bindq(n, m, e, V[id](C)), modeOf(id, C)) modeOf(n, nullEnv)=NONE modeOf(id, C) = if localMode(id, C)=NONE then modeOf(id, C(outer)) else localMode(id, C) modeOf(id.n, C) = if localMode(id, C)=NONE then modeOf(id.n, C(outer)) else modeOf(n, V[id](C)) apply(op, n, e, C) = op=BLANK => V[e](C) op=QUOTE => e op=PLUS => V[n](C)+V[e](C) . . . op=BRACES => (E[e](nullEnv | outer_C, LOCAL) | outer_nullEnv, LOCAL) op=DOTBRACES => (E[e](V[n](C) | outer_C, LOCAL) | outer_nullEnv, LOCAL) -- insert(NIL, l) = l How semantics are associated with an entire document: Each environment, C, initially contains only its "inherited" environment (bound to the id "outer"). Most bindings take place directly in C. However, the value of a bindq(id, ASSIGN, e, C) will change C by rebinding id in the "innermost" environment (following the chain of outers) in which it is bound, if that binding has the mode VAR. When an id is referred to and localMode(id, C)=NONE, then the value is sought recursively in C(outer). Perverse explicit bindings to outer might create loops, leaving some ids undefined, but there seems to be little reason to clutter up the semantics by forbidding such assignments. Semantics of labels: A label #id on a node in the dominant structure gives that node membership in the set named by id. Multiple labels place the node in multiple sets, and a unique label on a node places it in a singleton set, i.e., identifies it uniquely. Interdoc Syntax: The low-level syntax for Interdocs is the following (basically it represents the dominant tree structure by the nonterminal "node", each of which can have some set of labels, some expression, which may be actual data (the body of the document), transformations on the environment, or subtrees: node ::= "(" [label* ":"] expression* ")" label ::= "#" id expression ::= literal | ["'"] name | node | binding | conditional literal ::= Boolean | integer | hexint | real | string | label name ::= id ( "." id)* id ::= (letter | "" ) ( letter | "" | digit )* -- "" is the null id binding ::= singleBinding | compoundBinding singleBinding ::= name mode rhs mode ::= "=" | ":" | ":=" | "_" rhs ::= [ op ] expression | ["."] compoundBinding compoundBinding ::= "{" expression* "}" op ::= "'" | "+" | "-" | "*" | "/" | "AND" | "OR" | . . . conditional ::= "IF(" expression "," expression [ "," expression ] ")" Missing or in question: literal sequences relational operators *start* 07836 00024 USt Date: 27 July 1981 10:22 am PDT (Monday) From: Donahue.pa Subject: Re: Current Level 0/1 Interdoc status/rev. 7 In-reply-to: Horning's message of 24 July 1981 4:03 pm PDT (Friday) To: Horning cc: Donahue, Mitchell <> << General comments -- 1. The most important missing piece is a clear description of the underlying value spaces. Several confusions noted below are caused by this. 2. After reading this, I wondered if a "denotational style" semantics is the right way to go -- have you tried a more algebraic approach? >> We envision an Interdoc script being processed in any manner equivalent to the following: Parse the script, evaluating environment transformation functions as soon as parsed (so that the environment of each piece of content is available during parsing). A separate function is used to compute the "value" of a node. Basic Interdoc The kinds of values that can be appear in an Interdoc script are literals: Boolean: {F, T} integer: ... -3, -2, -1, 0, 1, 2, 3, ... real: 1.2E5, . . . string: id:  (the null id), bold, thisIsAnId, Helvetica, . . . label: #A123, #anId, #Paragraph the empty environment: nullEnv the empty list: NIL environments, which map ids to values and modes expressions The "abstract syntax" of expressions involves the following constructors: -- by convention n: name, e: expression literal name: id ( "." id)* quote(e) compose(e1, e2) cond(e1, e2, e3) -- if e1 then e2 else e3 node(labels, e) bind(n, m, op, e) where m is in { =, :, :=, _ } (or CONST, VAR, ASSIGN, LOCAL, respectively) = denotes constant binding : denotes variable declaration and initialization := denotes assignment to a previously declared variable _ denotes a local binding (cannot be affected by subnodes) << You don't say anywhere, but I take it that { =, :, :=, _ } form the set of legal modes. The use of the term mode here is somewhat confusing; if I were an Algol68 freak, I would have read "mode" as meaning "type" and have been led astray. >> and op is in { , ', +, , *, /, AND, OR, , ., ... } (or BLANK, QUOTE, PLUS, MINUS, TIMES, DIVIDE, ... ) binds to the current value of e ' binds to the expression e +, , *, /, AND, OR, ... bind to the result of a binary operation between the current value of n and the current value of e bind to a nested environment containing only the bindings resulting from e . uses e to update the bindings in the environment bound to n The semantics of scripts are defined by the following evaluation rules, where E denotes the environment transformation function V denotes the value function C denotes an environment, generally the "current" one C(id) denotes the value bound to id in C localMode(id, C) denotes the mode bound to id in C (NONE, if id isn't bound in C) (C | id_e, m) means "C with (e, m) bound to id" << I would put the brackets in here, i.e., (C | id _ ) >> E: expression > ( environment > environment ) V: expression > ( environment > value ) bindq: name, mode, value, environment > environment << Again, I would prefer bindq: [ name, (mode, value ] -> environment -> environment >> modeOf: id, environment > mode apply: op, mode, value, environment > value insert: value, list > list E[literal](C) = C E[n](C) = if modeOf(n, C)=NONE then C else E[V[n](C)](C) <> E[quote(n)](C) = C E[](C) = C -- Basis E[e1 e*](C) = E[e*](E[e1](C)) -- Composition E[cond(e1, e2, e3)](C) = if V[e1](C) then E[e2](E[e1](C)) else E[e3](E[e1](C)) E[node(l, e)](C) = V[outer](E[e](nullEnv | outer_C, LOCAL)) << I think there is some error in this equation, but I'm not sure what the fix is. The node label l does not appear in the right-hand side.. ? >> E[bind(n, m, op, e)](C) = bindq(n, m, apply(op, n, e, C), C) << Same problem as before -- bindq takes an expression as its third argument, while apply delivers a value as its result >> E[{e}](C) = E[e](C) V[literal](C) = literal V[id](nullEnv) = id << Just curious -- looking up an identifier in an empty environment yields the identifier?? Is this necessary because of other parts of the equations? >> V[id](C) = if localMode(id, C)=NONE then V[id](C(outer)) else C(id) << How do I know that C(outer) yields an environment? (Note that this makes the value space reflexive: Env = Id -> Value Value = ... + Env ...) If C(outer) is not an environment? >> V[id.n](C) = V[n](V[id](C)) V[quote(e)](C) = e V[] = NIL -- Basis V[e1 e*](C) = insert(V[e1](C), V[e*](E[e1](C))) -- Composition V[cond(e1, e2, e3)](C) = if V[e1](C) then V[e2](E[e1](C)) else V[e3](E[e1](C)) V[node(l, e)](C) = node(l, V[e](nullEnv | outer_C, LOCAL)) V[bind(n, m, op, e)](C) = NIL V[{e}](C) = V[e](C) bindq(id, m, e, C) = modeOf(id, C)=CONST => C m=ASSIGN => { localMode(id, C)=VAR => (C | id_e, VAR) modeOf(id, C)=VAR => bindq(outer.id, m, e, C) T => C } T => (C | id_e, m) bindq(id.n, m, e, C) = (C | id_bindq(n, m, e, V[id](C)), modeOf(id, C)) modeOf(n, nullEnv)=NONE modeOf(id, C) = if localMode(id, C)=NONE then modeOf(id, C(outer)) else localMode(id, C) modeOf(id.n, C) = if localMode(id, C)=NONE then modeOf(id.n, C(outer)) else modeOf(n, V[id](C)) << Again, functionality problem -- V delivers a value, mode expects an environment >> apply(op, n, e, C) = op=BLANK => V[e](C) op=QUOTE => e op=PLUS => V[n](C)+V[e](C) . . . op=BRACES => (E[e](nullEnv | outer_C, LOCAL) | outer_nullEnv, LOCAL) op=DOTBRACES => (E[e](V[n](C) | outer_C, LOCAL) | outer_nullEnv, LOCAL) -- insert(NIL, l) = l How semantics are associated with an entire document: Each environment, C, initially contains only its "inherited" environment (bound to the id "outer"). Most bindings take place directly in C. However, the value of a bindq(id, ASSIGN, e, C) will change C by rebinding id in the "innermost" environment (following the chain of outers) in which it is bound, if that binding has the mode VAR. When an id is referred to and localMode(id, C)=NONE, then the value is sought recursively in C(outer). Perverse explicit bindings to outer might create loops, leaving some ids undefined, but there seems to be little reason to clutter up the semantics by forbidding such assignments. Semantics of labels: A label #id on a node in the dominant structure gives that node membership in the set named by id. Multiple labels place the node in multiple sets, and a unique label on a node places it in a singleton set, i.e., identifies it uniquely. Interdoc Syntax: The low-level syntax for Interdocs is the following (basically it represents the dominant tree structure by the nonterminal "node", each of which can have some set of labels, some expression, which may be actual data (the body of the document), transformations on the environment, or subtrees: node ::= "(" [label* ":"] expression* ")" label ::= "#" id expression ::= literal | ["'"] name | node | binding | conditional literal ::= Boolean | integer | hexint | real | string | label name ::= id ( "." id)* id ::= (letter | "" ) ( letter | "" | digit )* -- "" is the null id binding ::= singleBinding | compoundBinding singleBinding ::= name mode rhs mode ::= "=" | ":" | ":=" | "_" rhs ::= [ op ] expression | ["."] compoundBinding compoundBinding ::= "{" expression* "}" op ::= "'" | "+" | "-" | "*" | "/" | "AND" | "OR" | . . . conditional ::= "IF(" expression "," expression [ "," expression ] ")" Missing or in question: literal sequences relational operators *start* 09829 00024 USt Date: 27 July 1981 11:34 am PDT (Monday) From: Horning.pa Subject: Re: Current Level 0/1 Interdoc status/rev. 7 In-reply-to: Donahue's message of 27 July 1981 10:22 am PDT (Monday) To: Donahue cc: Horning, Mitchell Replies in placeholders. Use Next to sequence through them. <> << General comments -- 1. The most important missing piece is a clear description of the underlying value spaces. Several confusions noted below are caused by this. Yes, I think we confused you in several places. The most important thing to note is that the value space contains expressions. This resolves several of your "type errors." 2. After reading this, I wondered if a "denotational style" semantics is the right way to go -- have you tried a more algebraic approach? >> No, I haven't tried doing it algebraically. My first guess is that it is about the same complexity, and I'm not sure about readability. We envision an Interdoc script being processed in any manner equivalent to the following: Parse the script, evaluating environment transformation functions as soon as parsed (so that the environment of each piece of content is available during parsing). A separate function is used to compute the "value" of a node. Basic Interdoc The kinds of values that can be appear in an Interdoc script are literals: Boolean: {F, T} integer: ... -3, -2, -1, 0, 1, 2, 3, ... real: 1.2E5, . . . string: id:  (the null id), bold, thisIsAnId, Helvetica, . . . label: #A123, #anId, #Paragraph the empty environment: nullEnv the empty list: NIL environments, which map ids to values and modes expressions The "abstract syntax" of expressions involves the following constructors: -- by convention n: name, e: expression literal name: id ( "." id)* quote(e) compose(e1, e2) cond(e1, e2, e3) -- if e1 then e2 else e3 node(labels, e) bind(n, m, op, e) where m is in { =, :, :=, _ } (or CONST, VAR, ASSIGN, LOCAL, respectively) = denotes constant binding : denotes variable declaration and initialization := denotes assignment to a previously declared variable _ denotes a local binding (cannot be affected by subnodes) << You don't say anywhere, but I take it that { =, :, :=, _ } form the set of legal modes. The use of the term mode here is somewhat confusing; if I were an Algol68 freak, I would have read "mode" as meaning "type" and have been led astray. >> Yes, these are the allowed "binding operators." We used "binding" for a time, but found that "mode" confused us less. Any suggestions? and op is in { , ', +, , *, /, AND, OR, , ., ... } (or BLANK, QUOTE, PLUS, MINUS, TIMES, DIVIDE, ... ) binds to the current value of e ' binds to the expression e +, , *, /, AND, OR, ... bind to the result of a binary operation between the current value of n and the current value of e bind to a nested environment containing only the bindings resulting from e . uses e to update the bindings in the environment bound to n The semantics of scripts are defined by the following evaluation rules, where E denotes the environment transformation function V denotes the value function C denotes an environment, generally the "current" one C(id) denotes the value bound to id in C localMode(id, C) denotes the mode bound to id in C (NONE, if id isn't bound in C) (C | id_e, m) means "C with (e, m) bound to id" << I would put the brackets in here, i.e., (C | id _ ) >> I'm responsible for editing out the brackets. Since everything within the parentheses has to be understood as a unit anyhow, these brackets are totally redundant, and I thought they cluttered the equations more than they clarified them. Maybe I should reconsider; brevity isn't everything. E: expression > ( environment > environment ) V: expression > ( environment > value ) bindq: name, mode, value, environment > environment << Again, I would prefer bindq: [ name, (mode, value ] -> environment -> environment >> bindq, modeOf, apply, and insert are all auxiliary functions used purely within the definitions of E and V. Since they are always invoked with all arguments supplied, I don't see the advantage of currying. Please elaborate. modeOf: id, environment > mode apply: op, mode, value, environment > value insert: value, list > list E[literal](C) = C E[n](C) = if modeOf(n, C)=NONE then C else E[V[n](C)](C) <> The environment transformation denoted by a name is the one denoted by the expression that has been bound to that name in the current environment, if any. E[quote(n)](C) = C E[](C) = C -- Basis E[e1 e*](C) = E[e*](E[e1](C)) -- Composition E[cond(e1, e2, e3)](C) = if V[e1](C) then E[e2](E[e1](C)) else E[e3](E[e1](C)) E[node(l, e)](C) = V[outer](E[e](nullEnv | outer_C, LOCAL)) << I think there is some error in this equation, but I'm not sure what the fix is. The node label l does not appear in the right-hand side.. ? >> Right, the labels on a node have no effect on the environment transformation it denotes. E[bind(n, m, op, e)](C) = bindq(n, m, apply(op, n, e, C), C) << Same problem as before -- bindq takes an expression as its third argument, while apply delivers a value as its result >> The value had better be an expression. (Note the rules for V.) We have deliberately omitted specification of error cases to keep the equations simple. E[{e}](C) = E[e](C) V[literal](C) = literal V[id](nullEnv) = id << Just curious -- looking up an identifier in an empty environment yields the identifier?? Is this necessary because of other parts of the equations? >> You read it correctly. This is because the set of "primitives" with which editors deal, such as Bold, Paragraph, and TimesRoman, is completely open-ended. I.e., any identifier that isn't bound is treated as a primitive. V[id](C) = if localMode(id, C)=NONE then V[id](C(outer)) else C(id) << How do I know that C(outer) yields an environment? (Note that this makes the value space reflexive: Env = Id -> Value Value = ... + Env ...) If C(outer) is not an environment? >> This rule is intended to "apply" only if V[id](nullEnv) = id doesn't. I think that you will find that each rule that creates a non-null environment binds outer to an existing environment. V[id.n](C) = V[n](V[id](C)) V[quote(e)](C) = e V[] = NIL -- Basis V[e1 e*](C) = insert(V[e1](C), V[e*](E[e1](C))) -- Composition V[cond(e1, e2, e3)](C) = if V[e1](C) then V[e2](E[e1](C)) else V[e3](E[e1](C)) V[node(l, e)](C) = node(l, V[e](nullEnv | outer_C, LOCAL)) V[bind(n, m, op, e)](C) = NIL V[{e}](C) = V[e](C) bindq(id, m, e, C) = modeOf(id, C)=CONST => C m=ASSIGN => { localMode(id, C)=VAR => (C | id_e, VAR) modeOf(id, C)=VAR => bindq(outer.id, m, e, C) T => C } T => (C | id_e, m) bindq(id.n, m, e, C) = (C | id_bindq(n, m, e, V[id](C)), modeOf(id, C)) modeOf(n, nullEnv)=NONE modeOf(id, C) = if localMode(id, C)=NONE then modeOf(id, C(outer)) else localMode(id, C) modeOf(id.n, C) = if localMode(id, C)=NONE then modeOf(id.n, C(outer)) else modeOf(n, V[id](C)) << Again, functionality problem -- V delivers a value, mode expects an environment >> The value bound to id in C must itself be an environment. Should we call out these error cases, at least in comments? apply(op, n, e, C) = op=BLANK => V[e](C) op=QUOTE => e op=PLUS => V[n](C)+V[e](C) . . . op=BRACES => (E[e](nullEnv | outer_C, LOCAL) | outer_nullEnv, LOCAL) op=DOTBRACES => (E[e](V[n](C) | outer_C, LOCAL) | outer_nullEnv, LOCAL) -- insert(NIL, l) = l How semantics are associated with an entire document: Each environment, C, initially contains only its "inherited" environment (bound to the id "outer"). Most bindings take place directly in C. However, the value of a bindq(id, ASSIGN, e, C) will change C by rebinding id in the "innermost" environment (following the chain of outers) in which it is bound, if that binding has the mode VAR. When an id is referred to and localMode(id, C)=NONE, then the value is sought recursively in C(outer). Perverse explicit bindings to outer might create loops, leaving some ids undefined, but there seems to be little reason to clutter up the semantics by forbidding such assignments. Semantics of labels: A label #id on a node in the dominant structure gives that node membership in the set named by id. Multiple labels place the node in multiple sets, and a unique label on a node places it in a singleton set, i.e., identifies it uniquely. Interdoc Syntax: The low-level syntax for Interdocs is the following (basically it represents the dominant tree structure by the nonterminal "node", each of which can have some set of labels, some expression, which may be actual data (the body of the document), transformations on the environment, or subtrees: node ::= "(" [label* ":"] expression* ")" label ::= "#" id expression ::= literal | ["'"] name | node | binding | conditional literal ::= Boolean | integer | hexint | real | string | label name ::= id ( "." id)* id ::= (letter | "" ) ( letter | "" | digit )* -- "" is the null id binding ::= singleBinding | compoundBinding singleBinding ::= name mode rhs mode ::= "=" | ":" | ":=" | "_" rhs ::= [ op ] expression | ["."] compoundBinding compoundBinding ::= "{" expression* "}" op ::= "'" | "+" | "-" | "*" | "/" | "AND" | "OR" | . . . conditional ::= "IF(" expression "," expression [ "," expression ] ")" Missing or in question: literal sequences relational operators *start* 00397 00024 USt Date: 23 July 1981 12:14 pm PDT (Thursday) From: Haeberli.PA Subject: BravoX External Format Documentation To: Mitchell cc: Haeberli Jim, In our conversation yesterday you expressed interest in the documentation for BravoX External Format. It can be found on: [Ibis]Documentation>ExternalFormat.press Please let me know if you have any further questions. Martin *start* 01533 00024 US Date: 22 July 1981 1:12 pm PDT (Wednesday) From: Horning.pa Subject: FYI: BravoX To: Mitchell, Reid --------------------------- Date: 22 July 1981 1:07 pm PDT (Wednesday) From: bott.PA Subject: Re: BravoX Help system In-reply-to: Horning's message of 22 July 1981 9:51 am PDT (Wednesday) To: Horning cc: Bott, Fiala, Lampson Jim, As far as I know, using BravoX on Dolphins still is not a working proposition: Bravox will occassionally trash the disk badly. Given how difficult these disks are to scavenge, this issue is serious. The problem is a bug in the Dophin microcode. I've heard a rumor that someone in El Segundo might try to look into this, but there is no guarantee. (As you probably know, Xerox has dropped all support of BravoX. This is regrettable in my opinion, but there is nothing that I can do about it.) However, BravoX is quite robust and very nice to use on a widebody Alto (preferably 192 or 256K, but it will run in 128K). If you have access to one of these, I encourage you to give it a try. The nearest satisfied user is probably Brian Reid. In addition, there is a fairly detailed Help system which I recently wrote for BravoX which should make it learnable with very little startup time. If it turns out to be feasible for you to use BravoX, send me a message and I'll send you details and command files for setting both BravoX and the help system up. Ross (PS: Tyronne Davis no longer works for Xerox.) ------------------------------------------------------------ *start* 00759 00024 USt Date: 28 July 1981 10:07 am PDT (Tuesday) From: Horning.pa Subject: Interdoc: Functionality of Expressions and Environments To: Mitchell, Donahue cc: Horning Jims, I am currently trying to see if I can get any mileage out of the following "re-currying" of the functionalities: MEnv[C]: Expression > Expression MExp[e]: Environment > Environment This is not "semantically" different from the V and E functions we wrote before, but it perhaps gives a more intuitive perspective on what is happening: An environment tells how to reduce an expression to one involving only "primitive" identifiers; an expression generally produces a new environment for the subtree to its right. I'll let you know if anything comes of it. Jim H. *start* 06076 00024 USt Date: 28 July 1981 3:45 pm PDT (Tuesday) From: Mitchell.PA Subject: Current Level 0/1 Interdoc status/rev. 9 To: Mitchell, Horning We envision an Interdoc script being processed in any manner equivalent to the following: Parse the script, alternately - reducing each expression to "primitives" by evaluating constant subexpressions and replacing names by the values to which they are bound in the current environment, and - transforming the environment as indicated by the expressions. Basic Interdoc Expressions in an Interdoc script may denote literal values: Boolean: {F, T} integer: ... -3, -2, -1, 0, 1, 2, 3, ... real: 1.2E5, . . . string: id:  (the null id), bold, thisIsAnId, Helvetica, . . . label: #A123, #anId, #Paragraph the empty environment: nullEnv the empty list: NIL environments unevaluated expressions The "abstract syntax" of expressions involves the following constructors: -- by convention n: name, e: expression literal name: id ( "." id)* quote(e) compose(e1, e2) cond(e1, e2, e3) -- if e1 then e2 else e3 node(labels, e) bind(n, m, op, e) where m is in { =, :, :=, _ } (or CONST, VAR, ASSIGN, LOCAL, respectively) = denotes constant binding : denotes variable declaration and initialization := denotes assignment to a previously declared variable _ denotes a local binding (cannot be affected by subnodes) and op is in { , ', +, , *, /, AND, OR, , ., ... } (or BLANK, QUOTE, PLUS, MINUS, TIMES, DIVIDE, ... ) binds to the current value of e ' binds to the expression e +, , *, /, AND, OR, ... bind to the result of a binary operation between the current value of n and the current value of e bind to a nested environment containing only the bindings resulting from e . uses e to update the bindings in the environment bound to n The semantics of scripts are defined by the following evaluation rules, where E denotes the environment transformation function V denotes the value function C denotes an environment, generally the "current" one C(id) denotes the value bound to id in C localMode(id, C) denotes the mode bound to id in C (NONE, if id isn't bound in C) (C | id_e, m) means "C with (e, m) bound to id" E: expression > ( environment > environment ) V: expression > ( environment > value ) bindq: name, mode, value, environment > environment modeOf: id, environment > mode apply: op, mode, value, environment > value insert: value, list > list E[literal](C) = C E[n](C) = if modeOf(n, C)=NONE then C else E[V[n](C)](C) E[quote(n)](C) = C E[](C) = C -- Basis E[e1 e*](C) = E[e*](E[e1](C)) -- Composition E[IF(e1, e2, e3)](C) = if V[e1](C) then E[e2](E[e1](C)) else E[e3](E[e1](C)) E[node(l, e)](C) = V[outer](E[e](nullEnv | outer_C, CONST)) E[bind(n, m, op, e)](C) = bindq(n, m, apply(op, n, e, C), C) E[{e}](C) = E[e](C) V[literal](C) = literal V[id](nullEnv) = id V[id](C) = if localMode(id, C)=NONE then V[id](C(outer)) else C(id) V[id.n](C) = V[n](V[id](C)) V[quote(n)](C) = n V[] = NIL -- Basis V[e1 e*](C) = insert(V[e1](C), V[e*](E[e1](C))) -- Composition V[IF(e1, e2, e3)](C) = if V[e1](C) then V[e2](E[e1](C)) else V[e3](E[e1](C)) V[node(l, e)](C) = node(l, V[e](nullEnv | outer_C, CONST)) V[bind(n, m, op, e)](C) = NIL V[{e}](C) = V[e](C) bindq(id, m, e, C) = modeOf(id, C)=CONST => C m=ASSIGN => assign(id, e, C) T => (C | id_e, m) bindq(id.n, m, e, C) = (C | id_bindq(n, m, e, V[id](C)), modeOf(id, C)) modeOf(n, nullEnv)=NONE modeOf(id, C) = if localMode(id, C)=NONE then modeOf(id, C(outer)) else localMode(id, C) modeOf(id.n, C) = if localMode(id, C)=NONE then modeOf(id.n, C(outer)) else modeOf(n, V[id](C)) assign(id, e, C) = localMode(id, C)=VAR => (C | id_e, VAR) modeOf(id, C)=VAR => bindq(outer.id, ASSIGN, e, C) T => C apply(op, n, e, C) = op=BLANK => V[e](C) op=QUOTE => e op=PLUS => V[n](C)+V[e](C) . . . op=BRACES => (E[e](nullEnv | outer_C, CONST) | outer_nullEnv, CONST) op=DOTBRACES => (E[e](V[n](C) | outer_C, CONST) | outer_nullEnv, CONST) -- insert(NIL, l) = l How semantics are associated with an entire document: Each environment, C, initially contains only its "inherited" environment (bound to the id "outer"). Most bindings take place directly in C. However, the value of a bindq(id, ASSIGN, e, C) will change C by rebinding id in the "innermost" environment (following the chain of outers) in which it is bound, if that binding has the mode VAR. When an id is referred to and localMode(id, C)=NONE, then the value is sought recursively in C(outer). Perverse explicit bindings to outer might create loops, leaving some ids undefined, but there seems to be little reason to clutter up the semantics by forbidding such assignments. Semantics of labels: A label #id on a node in the dominant structure gives that node membership in the set named by id. Multiple labels place the node in multiple sets, and a unique label on a node places it in a singleton set, i.e., identifies it uniquely. Interdoc Syntax: The low-level syntax for Interdocs is the following (basically it represents the dominant tree structure by the nonterminal "node", each of which can have some set of labels, some expression, which may be actual data (the body of the document), transformations on the environment, or subtrees: node ::= "(" [label* ":"] expression* ")" label ::= "#" id expression ::= literal | name | "'" name | conditional | node | binding | "{" expression* "}" literal ::= Boolean | integer | hexint | real | string | label name ::= id ( "." id)* id ::= (letter | "" ) ( letter | "" | digit )* -- "" is the null id binding ::= name mode [ op ] expression mode ::= "=" | ":" | ":=" | "_" op ::= "'" | "." | "+" | "-" | "*" | "/" | "AND" | "OR" | . . . conditional ::= "IF(" expression "," expression [ "," expression ] ")" Missing or in question: literal sequences binary & relational operators quote expressions in general *start* 08976 00024 USt Date: 28 July 1981 7:49 pm PDT (Tuesday) From: Horning.pa Subject: Current Level 0/1 Interdoc status/rev. 10 To: Mitchell, Horning cc: Donahue  Bring the syntax up front.  Further develop parallelism between grammar and semantic equations.  Quote general expressions.  V, E, C > R, T, E .  [...] > <...> for quotation of script expressions.  (E | id_e, m) > [E | id_e, m] for local binding. We envision an Interdoc script being processed in any manner equivalent to the following: Parse the script, alternately - reducing each expression to "primitives" by evaluating constant subexpressions and replacing names by the values to which they are bound in the current environment, and - transforming the environment as indicated by the expressions. BASIC INTERDOC GRAMMAR node ::= "(" labels expression* ")" labels ::= [label* ":"] label ::= "#" id expression ::= literal | name | "'" expression | conditional | binding | node | "{" expression* "}" literal ::= Boolean | integer | hexint | real | string | label name ::= id ( "." id)* id ::= (letter | "" ) ( letter | "" | digit )* -- "" is the null id conditional ::= "IF(" expression "," expression [ "," expression ] ")" binding ::= name mode op expression mode ::= "=" | ":" | ":=" | "_" op ::= | "." | "+" | "-" | "*" | "/" | "AND" | "OR" | . . . SEMANTIC EQUATIONS R denotes the expression reduction function T denotes the environment transformation function E denotes an environment, generally the "current" one E(id) denotes the value bound to id in E localMode(id, E) denotes the mode bound to id in E (None, if id isn't bound in E) [E | id_e, m] means "E with (e, m) bound to id" R: expression > ( environment > expression ) T: expression > ( environment > environment ) R<> = <> -- Basis R(E) = (E) R(T(E))> -- Composition R(E) = R(NullEnv) = R(E) = if localMode(id, E)=None then (E(Outer))> else R(E) = (R(E))> R<"'" e>(E) = R<"IF(" e1 "," e2 "," e3 ")">(E) = if R(E) then (T(E))> else (T(E))> R(E) = <> R<"(" labels e* ")">(E) = <"(" labels R([NullEnv | Outer_E, Const]) ")"> R<"{" e "}">(E) = (E)> T<>(E) = E -- Basis T(E) = T(T(E)) -- Composition T(E) = E T(E) = if modeOf(n, E)=None then E else T(E)>(E) T<"'" e>(E) = E T<"IF(" e1 "," e2 "," e3 ")">(E) = if R(E) then T(T(E)) else T(T(E)) T(E) = bindq(n, m, apply(op, n, e, E), E) T<"(" labels e* ")">(E) = R(T([NullEnv | Outer_E, Const])) T<"{" e "}">(E) = T(E) modeOf(n, NullEnv) = None modeOf(id, E) = if localMode(id, E)=None then modeOf(id, E(Outer)) else localMode(id, E) modeOf(id.n, E) = modeOf(n, R(E)) bindq(id, m, e, E) = modeOf(id, E)=Const => E m=Assign => assign(id, e, E) True => [E | id_e, m] bindq(id.n, m, e, E) = [E | id_bindq(n, m, e, R(E)), modeOf(id, E)] assign(id, e, E) = localMode(id, E)=Var => [E | id_e, Var] modeOf(id, E)=Var => bindq(Outer.id, Assign, e, E) True => E apply(op, n, e, E) = op=BLANK => R(E) op=QUOTE => e op=PLUS => R(E)+R(E) . . . op=BRACES => [T[NullEnv | Outer_E, Const] | Outer_NullEnv, Const] op=DOTBRACES => [T[R(E) | Outer_E, Const] | Outer_NullEnv, Const] Missing or in question: literal sequences binary & relational operators e.id? ------------------- Expressions in an Interdoc script may denote literal values: Boolean: {F, T} integer: ... -3, -2, -1, 0, 1, 2, 3, ... real: 1.2E5, . . . string: id:  (the null id), bold, thisIsAnId, Helvetica, . . . label: #A123, #anId, #Paragraph the empty environment: nullEnv the empty list: NIL environments unevaluated expressions The "abstract syntax" of expressions involves the following constructors: -- by convention n: name, e: expression literal name: id ( "." id)* quote(e) compose(e1, e2) cond(e1, e2, e3) -- if e1 then e2 else e3 node(labels, e) bind(n, m, op, e) where m is in { =, :, :=, _ } (or CONST, VAR, ASSIGN, LOCAL, respectively) = denotes constant binding : denotes variable declaration and initialization := denotes assignment to a previously declared variable _ denotes a local binding (cannot be affected by subnodes) and op is in { , ', +, , *, /, AND, OR, , ., ... } (or BLANK, QUOTE, PLUS, MINUS, TIMES, DIVIDE, ... ) binds to the current value of e ' binds to the expression e +, , *, /, AND, OR, ... bind to the result of a binary operation between the current value of n and the current value of e bind to a nested environment containing only the bindings resulting from e . uses e to update the bindings in the environment bound to n The semantics of scripts are defined by the following evaluation rules, where E denotes the environment transformation function V denotes the value function C denotes an environment, generally the "current" one C(id) denotes the value bound to id in C localMode(id, C) denotes the mode bound to id in C (NONE, if id isn't bound in C) (C | id_e, m) means "C with (e, m) bound to id" E: expression > ( environment > environment ) V: expression > ( environment > value ) bindq: name, mode, value, environment > environment modeOf: id, environment > mode apply: op, mode, value, environment > value insert: value, list > list E[literal](C) = C E[n](C) = if modeOf(n, C)=NONE then C else E[V[n](C)](C) E[quote(n)](C) = C E[](C) = C -- Basis E[e1 e*](C) = E[e*](E[e1](C)) -- Composition E[IF(e1, e2, e3)](C) = if V[e1](C) then E[e2](E[e1](C)) else E[e3](E[e1](C)) E[node(l, e)](C) = V[outer](E[e](nullEnv | outer_C, CONST)) E[bind(n, m, op, e)](C) = bindq(n, m, apply(op, n, e, C), C) E[{e}](C) = E[e](C) V[literal](C) = literal V[id](nullEnv) = id V[id](C) = if localMode(id, C)=NONE then V[id](C(outer)) else C(id) V[id.n](C) = V[n](V[id](C)) V[quote(n)](C) = n V[] = NIL -- Basis V[e1 e*](C) = insert(V[e1](C), V[e*](E[e1](C))) -- Composition V[IF(e1, e2, e3)](C) = if V[e1](C) then V[e2](E[e1](C)) else V[e3](E[e1](C)) V[node(l, e)](C) = node(l, V[e](nullEnv | outer_C, CONST)) V[bind(n, m, op, e)](C) = NIL V[{e}](C) = V[e](C) bindq(id, m, e, C) = modeOf(id, C)=CONST => C m=ASSIGN => assign(id, e, C) T => (C | id_e, m) bindq(id.n, m, e, C) = (C | id_bindq(n, m, e, V[id](C)), modeOf(id, C)) modeOf(n, nullEnv)=NONE modeOf(id, C) = if localMode(id, C)=NONE then modeOf(id, C(outer)) else localMode(id, C) modeOf(id.n, C) = if localMode(id, C)=NONE then modeOf(id.n, C(outer)) else modeOf(n, V[id](C)) assign(id, e, C) = localMode(id, C)=VAR => (C | id_e, VAR) modeOf(id, C)=VAR => bindq(outer.id, ASSIGN, e, C) T => C apply(op, n, e, C) = op=BLANK => V[e](C) op=QUOTE => e op=PLUS => V[n](C)+V[e](C) . . . op=BRACES => (E[e](nullEnv | outer_C, CONST) | outer_nullEnv, CONST) op=DOTBRACES => (E[e](V[n](C) | outer_C, CONST) | outer_nullEnv, CONST) -- insert(NIL, l) = l How semantics are associated with an entire document: Each environment, C, initially contains only its "inherited" environment (bound to the id "outer"). Most bindings take place directly in C. However, the value of a bindq(id, ASSIGN, e, C) will change C by rebinding id in the "innermost" environment (following the chain of outers) in which it is bound, if that binding has the mode VAR. When an id is referred to and localMode(id, C)=NONE, then the value is sought recursively in C(outer). Perverse explicit bindings to outer might create loops, leaving some ids undefined, but there seems to be little reason to clutter up the semantics by forbidding such assignments. Semantics of labels: A label #id on a node in the dominant structure gives that node membership in the set named by id. Multiple labels place the node in multiple sets, and a unique label on a node places it in a singleton set, i.e., identifies it uniquely. Interdoc Syntax: The low-level syntax for Interdocs is the following (basically it represents the dominant tree structure by the nonterminal "node", each of which can have some set of labels, some expression, which may be actual data (the body of the document), transformations on the environment, or subtrees: node ::= "(" [label* ":"] expression* ")" label ::= "#" id expression ::= literal | name | "'" name | conditional | node | binding | "{" expression* "}" literal ::= Boolean | integer | hexint | real | string | label name ::= id ( "." id)* id ::= (letter | "" ) ( letter | "" | digit )* -- "" is the null id binding ::= name mode [ op ] expression mode ::= "=" | ":" | ":=" | "_" op ::= "'" | "." | "+" | "-" | "*" | "/" | "AND" | "OR" | . . . conditional ::= "IF(" expression "," expression [ "," expression ] ")" ------------------- *start* 07854 00024 USt Date: 28 July 1981 12:32 pm PDT (Tuesday) From: Horning.pa Subject: Current Level 0/1 Interdoc status/rev. 8 To: Mitchell, Donahue cc: Horning [Primarily, have a look at SECOND TRY.] We envision an Interdoc script being processed in any manner equivalent to the following: Parse the script, alternately - reducing each expression to "primitives" by evaluating constant subexpressions and replacing names by the values to which they are bound in the current environment, and - transforming the environment as indicated by the expressions. Basic Interdoc Expressions in an Interdoc script may denote literal values: Boolean: {F, T} integer: ... -3, -2, -1, 0, 1, 2, 3, ... real: 1.2E5, . . . string: id:  (the null id), bold, thisIsAnId, Helvetica, . . . label: #A123, #anId, #Paragraph the empty environment: nullEnv the empty list: NIL environments unevaluated expressions The "abstract syntax" of expressions involves the following constructors: -- by convention n: name, e: expression literal name: id ( "." id)* quote(e) compose(e1, e2) cond(e1, e2, e3) -- if e1 then e2 else e3 node(labels, e) bind(n, m, op, e) where m is in { =, :, :=, _ } (or CONST, VAR, ASSIGN, LOCAL, respectively) = denotes constant binding : denotes variable declaration and initialization := denotes assignment to a previously declared variable _ denotes a local binding (cannot be affected by subnodes) and op is in { , ', +, , *, /, AND, OR, , ., ... } (or BLANK, QUOTE, PLUS, MINUS, TIMES, DIVIDE, ... ) binds to the current value of e ' binds to the expression e +, , *, /, AND, OR, ... bind to the result of a binary operation between the current value of n and the current value of e bind to a nested environment containing only the bindings resulting from e . uses e to update the bindings in the environment bound to n  [FIRST TRY] The semantics of scripts are defined by the following equations, where MEnv denotes the "meaning" of an environment MExp denotes the meaning" of an expression C denotes an environment, generally the "current" one MEnv: Environment > ( Expression > Expression ) MExp: Expression > ( Environment > Environment ) lookup: Name, Environment > Expression MEnv(C)[literal] = literal MEnv(C)[n] = lookup(n, C) MEnv(C)[quote(e)] = e MEnv(C)[] = NIL -- Basis MEnv(C)[e1 e*] = insert(MEnv(C)[e1], MEnv[e*](MExp[e1](C))) -- Composition HALT-- THIS DOESN'T LOOK LIKE AN IMPROVEMENT   [SECOND TRY] TYPE Environment OPERATORS null: > Environment bindq: Id, Mode, Expression, Environment > Environment enter: Environment > Environment exit: Environment > Environment lookup: Id, Environment > Expression bindable: Id, Mode, Environment > Boolean persistent: Id, Environment > Boolean AXIOMS lookup(id, null) == id lookup(id, bindq(id', m, e, C)) == if id = id' and bindable(id', m, C) then e else lookup(id, C) lookup(id, enter(C)) == lookup(id, C) exit(null) == null -- or "undefined"? exit(bindq(id, m, e, C)) == if m = ASSIGN and persistent(id, C) then bindq(id, m, e, exit(C)) else exit(C) exit(enter(C)) == C bindable(id, m, null) == TRUE bindable(id, m, bindq(id', m', e, C)) == if id = id' then (m' ~= CONST) and (m = ASSIGN => m' = VAR) and bindable(id, CONST, C) else bindable(id, m, C) bindable(id, m, enter(C)) == bindable(id, m, C) persistent(id, null) == FALSE persistent(id, bindq(id', m', e, C)) == persistent(id, C) and (id = id' => m' = ASSIGN) persistent(id, enter(C)) == bindable(id, ASSIGN, C)  The semantics of scripts are defined by the following evaluation rules, where E denotes the environment transformation function V denotes the value function C denotes an environment, generally the "current" one C(id) denotes the value bound to id in C localMode(id, C) denotes the mode bound to id in C (NONE, if id isn't bound in C) (C | id_e, m) means "C with (e, m) bound to id" E: expression > ( environment > environment ) V: expression > ( environment > value ) bindq: name, mode, value, environment > environment modeOf: id, environment > mode apply: op, mode, value, environment > value insert: value, list > list E[literal](C) = C E[n](C) = if modeOf(n, C)=NONE then C else E[V[n](C)](C) E[quote(n)](C) = C E[](C) = C -- Basis E[e1 e*](C) = E[e*](E[e1](C)) -- Composition E[cond(e1, e2, e3)](C) = if V[e1](C) then E[e2](E[e1](C)) else E[e3](E[e1](C)) E[node(l, e)](C) = V[outer](E[e](nullEnv | outer_C, LOCAL)) E[bind(n, m, op, e)](C) = bindq(n, m, apply(op, n, e, C), C) E[{e}](C) = E[e](C) V[literal](C) = literal V[id](nullEnv) = id V[id](C) = if localMode(id, C)=NONE then V[id](C(outer)) else C(id) V[id.n](C) = V[n](V[id](C)) V[quote(e)](C) = e V[] = NIL -- Basis V[e1 e*](C) = insert(V[e1](C), V[e*](E[e1](C))) -- Composition V[cond(e1, e2, e3)](C) = if V[e1](C) then V[e2](E[e1](C)) else V[e3](E[e1](C)) V[node(l, e)](C) = node(l, V[e](nullEnv | outer_C, LOCAL)) V[bind(n, m, op, e)](C) = NIL V[{e}](C) = V[e](C) bindq(id, m, e, C) = modeOf(id, C)=CONST => C m=ASSIGN => { localMode(id, C)=VAR => (C | id_e, VAR) modeOf(id, C)=VAR => bindq(outer.id, m, e, C) T => C } T => (C | id_e, m) bindq(id.n, m, e, C) = (C | id_bindq(n, m, e, V[id](C)), modeOf(id, C)) modeOf(n, nullEnv)=NONE modeOf(id, C) = if localMode(id, C)=NONE then modeOf(id, C(outer)) else localMode(id, C) modeOf(id.n, C) = if localMode(id, C)=NONE then modeOf(id.n, C(outer)) else modeOf(n, V[id](C)) apply(op, n, e, C) = op=BLANK => V[e](C) op=QUOTE => e op=PLUS => V[n](C)+V[e](C) . . . op=BRACES => (E[e](nullEnv | outer_C, LOCAL) | outer_nullEnv, LOCAL) op=DOTBRACES => (E[e](V[n](C) | outer_C, LOCAL) | outer_nullEnv, LOCAL) -- insert(NIL, l) = l How semantics are associated with an entire document: Each environment, C, initially contains only its "inherited" environment (bound to the id "outer"). Most bindings take place directly in C. However, the value of a bindq(id, ASSIGN, e, C) will change C by rebinding id in the "innermost" environment (following the chain of outers) in which it is bound, if that binding has the mode VAR. When an id is referred to and localMode(id, C)=NONE, then the value is sought recursively in C(outer). Perverse explicit bindings to outer might create loops, leaving some ids undefined, but there seems to be little reason to clutter up the semantics by forbidding such assignments. Semantics of labels: A label #id on a node in the dominant structure gives that node membership in the set named by id. Multiple labels place the node in multiple sets, and a unique label on a node places it in a singleton set, i.e., identifies it uniquely. Interdoc Syntax: The low-level syntax for Interdocs is the following (basically it represents the dominant tree structure by the nonterminal "node", each of which can have some set of labels, some expression, which may be actual data (the body of the document), transformations on the environment, or subtrees: node ::= "(" [label* ":"] expression* ")" label ::= "#" id expression ::= literal | ["'"] name | node | binding | conditional literal ::= Boolean | integer | hexint | real | string | label name ::= id ( "." id)* id ::= (letter | "" ) ( letter | "" | digit )* -- "" is the null id binding ::= singleBinding | compoundBinding singleBinding ::= name mode rhs mode ::= "=" | ":" | ":=" | "_" rhs ::= [ op ] expression | ["."] compoundBinding compoundBinding ::= "{" expression* "}" op ::= "'" | "+" | "-" | "*" | "/" | "AND" | "OR" | . . . conditional ::= "IF(" expression "," expression [ "," expression ] ")" Missing or in question: literal sequences relational operators *start* 05746 00024 USt Date: 29 July 1981 7:46 pm PDT (Wednesday) From: Horning.pa Subject: Current Level 0/1 Interdoc status/rev. 11 To: Mitchell, Horning cc: Donahue [This is shorter, more general, and I hope cleaner than previous versions. Numerous small bugs have been fixed as I tracked down subtleties. I'd particularly like scrutiny of the equations involving nested environments, marked by interior s.]  Bring the syntax up front.  Further develop parallelism between grammar and semantic equations.  Quote general expressions.  V, E, C > R, T, E .  [...] > <...> for quotation of script expressions.  (E | id_e, m) > [E | id_e, m] for local binding.  Introduce primary to disambiguate expression* , factor lhs from binding.  Introduce Sub component to initialize nodes.  Debug (?) semantics of braces and dot.  Mode > binding. We envision an Interdoc script being processed in any manner equivalent to the following: Parse the script, alternately - reducing each expression to "primitives" by evaluating constant subexpressions and replacing names by the values to which they are bound in the current environment, and - transforming the environment as indicated by the expressions. BASIC INTERDOC GRAMMAR node ::= "(" labels expression* ")" labels ::= [label* ":"] label ::= "#" name expression ::= [ lhs ] [ "'" ] primary primary ::= literal | id | primary "." id | conditional | node | "{" expression* "}" literal ::= Boolean | integer | hexint | real | string | label name ::= id ( "." id)* id ::= (letter | "" ) ( letter | "" | digit )* -- "" is the null id conditional ::= "IF(" expression "," expression [ "," expression ] ")" lhs ::= name binding op binding ::= "=" | ":" | ":=" | "_" op ::= | "." | "+" | "-" | "*" | "/" | "AND" | "OR" | . . . SEMANTICS R denotes the expression reduction function: R: expression > ( environment > expression ) T denotes the environment transformation function: T: expression > ( environment > environment ) Environments bind expressions and "modes" to identifiers: Null denotes the "empty" environment [E | id_e, m] means "E with (e, m) bound to id" E(id) denotes the value bound to id in E Null(id) = id [E | id'_e, m](id) = if id=id' then e else E(id) locBinding(id, E) denotes the binding mode of id in E locBinding(id, Null) = None locBinding(id, [E | id'_e, m]) = if id=id' then m else locBinding(id, E) bound(id, E) = (locBinding(id, E) ~= None) R<>(E) = "" -- Basis T<>(E) = E R(E) = R(E) R(T(E)) -- Composition T(E) = T(T(E)) R<"'" p>(E) = p T<"'" p>(E) = E R(E) = literal T(E) = E R(E) = bound(id, E) => E(id) bound(Outer, E) => R(E(Outer)) True => id T(E) = if R(E)=id then E else T(E)>(E) R

(E) = R(R

(E)) T

(E) = T(E)>(E) R<"IF(" e1 "," e2 "," e3 ")">(E) = if R(E) then R(T(E)) else R(T(E)) T<"IF(" e1 "," e2 "," e3 ")">(E) = if R(E) then T(T(E)) else T(T(E)) R(E) = "" T(E) = bindq(n, m, apply(op, n, p, E), E) R<"(" labels e* ")">(E) = "(" labels R([Null | Outer_E, Const]) ")" T<"(" labels e* ")">(E) = (T([Null | Outer_E, Const]))(Outer) R<"{" e* "}">(E) = [T<"{" e* "}">(E) | Outer_Null, Const] ? T<"{" e* "}">(E) = T([Null | Outer_E, Const]) ? bindingOf(id, E) = if ~bound(id, E) and bound(Outer, E) then bindingOf(id, E(Outer)) else locBinding(id, E) bindq(id, m, e, E) = bindingOf(id, E) = "=" => E m = ":=" => assign(id, e, E) True => [E | id_e, m] bindq(id.n, m, e, E) = [E | id_bindq(n, m, e, R(E)), bindingOf(id, E)] assign(id, e, E) = locBinding(id, E) = ":" => [E | id_e, ":"] bindingOf(id, E) = ":" => bindq(Outer.id, ":=", e, E) True => E apply(op, n, p, E) = op = "" => R

(E) op = "." => R

([R(E) | Outer_E, Const]) ? op = "+" => R(E)+R

(E) . . . Missing or in question: literal sequences binary & relational operators ------------------- Expressions in an Interdoc script may denote literal values: Boolean: {F, T} integer: ... -3, -2, -1, 0, 1, 2, 3, ... real: 1.2E5, . . . string: id:  (the null id), bold, thisIsAnId, Helvetica, . . . label: #A123, #anId, #Paragraph the empty environment: nullEnv the empty list: NIL environments unevaluated expressions How semantics are associated with an entire document: Each environment, E, initially contains only its "inherited" environment (bound to the id Outer). Most bindings take place directly in E. However, the value of a bindq(id, ":=", p, E) will change E by rebinding id in the "innermost" environment (following the chain of Outers) in which it is bound, if that binding has the binding ":" (Var). Identifiers bound with binding "=" (Const) may not be rebound in inner environments. When an id is referred to and locBinding(id, E)=None, then the value is sought recursively in E(Outer). Perverse explicit bindings to outer might create loops, leaving some ids undefined, but there seems to be little reason to clutter up the semantics by forbidding such assignments. The contents of each node are implicitly prefixed by Sub, which will generally be bound to an environment transformation in the containing environment. Braces create a nested environment; if preceded by a dot, it is initialized to the value of the name in the binding. Semantics of labels: A label #id on a node in the dominant structure gives that node membership in the set named by id. Multiple labels place the node in multiple sets, and a unique label on a node places it in a singleton set, i.e., identifies it uniquely. *start* 06157 00024 USt Date: 30 July 1981 6:49 pm PDT (Thursday) From: Mitchell.PA Subject: Current Level 0/1 Interdoc status/rev. 12 To: Mitchell, Horning cc: Donahue  Bring the syntax up front.  Further develop parallelism between grammar and semantic equations.  Write semantic equations in terms of concrete syntax.  Quote general expressions.  V, E, C > R, T, E .  [...] > <...> for quotation of script expressions.  (E | id_e, m) > [E | id_e, m] for local binding.  Introduce primary to disambiguate expression* , factor lhs from binding.  Introduce Sub component to initialize nodes.  Debug semantics of braces and dot.  Mode > binding.  Debug semantics of (fix up indirection).  Add VAL.  We envision an Interdoc script being processed in any manner equivalent to the following: Parse the script, alternately - reducing each expression to "primitives" by evaluating constant subexpressions and replacing names by the values to which they are bound in the current environment, and - transforming the environment as indicated by the expressions. BASIC INTERDOC GRAMMAR node ::= "(" labels expression* ")" labels ::= [label* ":"] label ::= "#" name expression ::= [ lhs ] [ "'" ] primary primary ::= literal | id | primary "." id | conditional | node | [ "VAL" ] "{" expression* "}" literal ::= Boolean | integer | hexint | real | string | label name ::= id ( "." id)* id ::= (letter | "" ) ( letter | "" | digit )* -- "" is the null id conditional ::= "IF(" expression "," expression* [ "," expression* ] ")" lhs ::= name binding op binding ::= "=" | ":" | ":=" | "_" op ::= | "." | "+" | "-" | "*" | "/" | "AND" | "OR" | . . . SEMANTICS R denotes the expression reduction function: R: expression > ( environment > expression ) T denotes the environment transformation function: T: expression > ( environment > environment ) Environments bind expressions and "modes" to identifiers: Null denotes the "empty" environment [E | id_e, m] means "E with (e, m) bound to id" E(id) denotes the value locally bound to id in E Null(id) = id [E | id'_e, m](id) = if id=id' then e else E(id) locBinding(id, E) denotes the binding mode of id in E locBinding(id, Null) = None locBinding(id, [E | id'_e, m]) = if id=id' then m else locBinding(id, E) -- Basis R<>(E) = "" -- Empty list T<>(E) = E -- Identity -- Expression sequence R(E) = R(E) R(T(E)) -- List insert T(E) = T(T(E)) -- Composition R<"'" p>(E) = p T<"'" p>(E) = E R(E) = literal T(E) = E R(E) = if valOf(id, E)=id then id else R(E) T(E) = if valOf(id, E)=id then E else T(E) R

(E) = R(R

(E)) T

(E) = if valOf(id, R

(E))=id then E else T(E))>(E) R<"IF(" e1 "," e2* "," e3* ")">(E) = if R(E) then R(T(E)) else R(T(E)) T<"IF(" e1 "," e2* "," e3* ")">(E) = if R(E) then T(T(E)) else T(T(E)) R(E) = "" -- Empty list T(E) = bindq(n, m, apply(op, n, p, E), E) R<"(" labels e* ")">(E) = "(" labels R([Null | Outer_E, Const]) ")" T<"(" labels e* ")">(E) = (T([Null | Outer_E, Const]))(Outer) R<"{" e* "}">(E) = [T<"{" e* "}">(E) | Outer_Null, Const] T<"{" e* "}">(E) = T([Null | Outer_E, Const]) R<"VAL{" e* "}">(E) = R(E) T<"VAL{" e* "}">(E) = E whereBound(id, E) = -- Finds innermost binding locBinding(id, E) ~= None => E locBinding(Outer, E) ~= None => whereBound(id, E(Outer)) True => Null valOf(id, E) = (whereBound(id, E))(id) -- Gets innermost value bindingOf(id, E) = locBinding(id, whereBound(id, E)) -- Gets innermost binding bindq(id, m, e, E) = bindingOf(id, E) = "=" => E m = ":=" => assign(id, e, E) True => [E | id_e, m] bindq(id.n, m, e, E) = [E | id_bindq(n, m, e, R(E)), bindingOf(id, E)] assign(id, e, E) = locBinding(id, E) = ":" => [E | id_e, ":"] bindingOf(id, E) = ":" => bindq(Outer.id, ":=", e, E) True => E apply(op, n, p, E) = op = "" => R

(E) op = "." => R

([R(E) | Outer_E, Const]) op = "+" => R(E)+R

(E) . . . Missing or in question: literal sequences binary & relational operators ------------------- Expressions in an Interdoc script may denote literal values: Boolean: {F, T} integer: ... -3, -2, -1, 0, 1, 2, 3, ... real: 1.2E5, . . . string: label: #A123, #anId, #Paragraph the empty environment: Null the empty list: NIL id:  (the null id), bold, thisIsAnId, Helvetica, . . . (unless bound, taken to denote a primitive) environments unevaluated expressions How semantics are associated with an entire document: Each environment, E, initially contains only its "inherited" environment (bound to the id Outer). Most bindings take place directly in E. However, the value of a bindq(id, ":=", p, E) will change E by rebinding id in the "innermost" environment (following the chain of Outers) in which it is bound, if that binding has the binding ":" (Var). Identifiers bound with binding "=" (Const) may not be rebound in inner environments. When an id is referred to and locBinding(id, E)=None, then the value is sought recursively in E(Outer). Perverse explicit bindings to outer might create loops, leaving some ids undefined, but there seems to be little reason to clutter up the semantics by forbidding such assignments. The contents of each node are implicitly prefixed by Sub, which will generally be bound to an environment transformation in the containing environment. Braces create a nested environment; if preceded by a dot, it is initialized to the value of the name in the binding; if preceded by VAL, it is executed for value, and the environment is then discarded. Semantics of labels: A label #id on a node in the dominant structure gives that node membership in the set named by id. Multiple labels place the node in multiple sets, and a unique label on a node places it in a singleton set, i.e., identifies it uniquely. ------------------------------------------------------------ *start* 06841 00024 USt Date: 30 July 1981 9:55 pm PDT (Thursday) From: Mitchell.PA Subject: Current Level 0/1 Interdoc status/rev. 13 To: Mitchell, Horning Last edited by Mitchell, 30 July 1981 9:21 pm PDT (Thursday): Changed grammar to allow more complete expression syntax; required changing CONST binding op ("=") to "=="; couldn't use "<" or ">" as operators because they delimit strings. Moved history log to end of message. We envision an Interdoc script being processed in any manner equivalent to the following: Parse the script, alternately - reducing each expression to "primitives" by evaluating constant subexpressions and replacing names by the values to which they are bound in the current environment, and - transforming the environment as indicated by the expressions. BASIC INTERDOC GRAMMAR node ::= "(" labels expression* ")" labels ::= [label* ":"] label ::= "#" name expression ::= [ lhs ] [ "'" ] disjunction disjunction ::= [ disjunction "OR" ] conjunction conjunction ::= [ conjunction "AND" ] negation negation ::= [ "NOT" ] relation relation ::= [ sum relOp ] sum relOp ::= "LT" | " LE" | "EQ" | "NE" | "GE" | "GT" sum ::= [ sum addOp ] product addOp ::= "+" | "-" product ::= [ product multOp ] primary multOp ::= "*" | "/" | "MOD" primary ::= literal | id | primary "." id | conditional | node | [ "VAL" ] "{" expression* "}" literal ::= Boolean | integer | hexint | real | string | label name ::= id ( "." id)* id ::= (letter | "" ) ( letter | "" | digit )* -- "" is the null id conditional ::= "IF{" expression "," expression* [ "," expression* ] "}" lhs ::= name binding op binding ::= "==" | ":" | ":=" | "_" op ::= | "." | addOp | multOp a:='NOT VAL{leftMargin=120} r==12.5*pt IF{a=b, leftMargin_5, leftMargin_10} SEMANTICS R denotes the expression reduction function: R: expression > ( environment > expression ) T denotes the environment transformation function: T: expression > ( environment > environment ) Environments bind expressions and "modes" to identifiers: Null denotes the "empty" environment [E | id_e, m] means "E with (e, m) bound to id" E(id) denotes the value locally bound to id in E Null(id) = id [E | id'_e, m](id) = if id=id' then e else E(id) locBinding(id, E) denotes the binding mode of id in E locBinding(id, Null) = None locBinding(id, [E | id'_e, m]) = if id=id' then m else locBinding(id, E) -- Basis R<>(E) = nothing -- just what it says T<>(E) = E -- Identity -- Expression sequence R(E) = R(E) -- "nothing" disappears R(E) = R(E) R(T(E)) -- List insert T(E) = T(T(E)) -- Composition R<"'" p>(E) = p T<"'" p>(E) = E R(E) = literal T(E) = E R(E) = if valOf(id, E)=id then id else R(E) T(E) = if valOf(id, E)=id then E else T(E) R

(E) = R(R

(E)) T

(E) = if valOf(id, R

(E))=id then E else T(E))>(E) R<"IF(" e1 "," e2* "," e3* ")">(E) = if R(E) then R(T(E)) else R(T(E)) T<"IF(" e1 "," e2* "," e3* ")">(E) = if R(E) then T(T(E)) else T(T(E)) R(E) = "" -- Empty list T(E) = bindq(n, m, apply(op, n, p, E), E) R<"(" labels e* ")">(E) = "(" labels R([Null | Outer_E, Const]) ")" T<"(" labels e* ")">(E) = (T([Null | Outer_E, Const]))(Outer) R<"{" e* "}">(E) = [T<"{" e* "}">(E) | Outer_Null, Const] T<"{" e* "}">(E) = T([Null | Outer_E, Const]) R<"VAL{" e* "}">(E) = R(E) T<"VAL{" e* "}">(E) = E whereBound(id, E) = -- Finds innermost binding locBinding(id, E) ~= None => E locBinding(Outer, E) ~= None => whereBound(id, E(Outer)) True => Null valOf(id, E) = (whereBound(id, E))(id) -- Gets innermost value bindingOf(id, E) = locBinding(id, whereBound(id, E)) -- Gets innermost binding bindq(id, m, e, E) = bindingOf(id, E) = "==" => E m = ":=" => assign(id, e, E) True => [E | id_e, m] bindq(id.n, m, e, E) = [E | id_bindq(n, m, e, R(E)), bindingOf(id, E)] assign(id, e, E) = locBinding(id, E) = ":" => [E | id_e, ":"] bindingOf(id, E) = ":" => bindq(Outer.id, ":=", e, E) True => E apply(op, lhs, rhs, E) = op = "" => R(E) op = "." => R([R(E) | Outer_E, Const]) op = "+" => R(E)+R(E) . . . Missing or in question: literal sequences binary & relational operators ------------------- Expressions in an Interdoc script may denote literal values: Boolean: {F, T} integer: ... -3, -2, -1, 0, 1, 2, 3, ... real: 1.2E5, . . . string: label: #A123, #anId, #Paragraph the empty environment: Null the empty list: NIL id:  (the null id), bold, thisIsAnId, Helvetica, . . . (unless bound, taken to denote a primitive) environments unevaluated expressions How semantics are associated with an entire document: Each environment, E, initially contains only its "inherited" environment (bound to the id Outer). Most bindings take place directly in E. However, the value of a bindq(id, ":=", p, E) will change E by rebinding id in the "innermost" environment (following the chain of Outers) in which it is bound, if that binding has the binding ":" (Var). Identifiers bound with binding "==" (Const) may not be rebound in inner environments. When an id is referred to and locBinding(id, E)=None, then the value is sought recursively in E(Outer). Perverse explicit bindings to outer might create loops, leaving some ids undefined, but there seems to be little reason to clutter up the semantics by forbidding such assignments. The contents of each node are implicitly prefixed by Sub, which will generally be bound to an environment transformation in the containing environment. Braces create a nested environment; if preceded by a dot, it is initialized to the value of the name in the binding; if preceded by VAL, it is executed for value, and the environment is then discarded. Semantics of labels: A label #id on a node in the dominant structure gives that node membership in the set named by id. Multiple labels place the node in multiple sets, and a unique label on a node places it in a singleton set, i.e., identifies it uniquely. Log of Changes  Bring the syntax up front.  Further develop parallelism between grammar and semantic equations.  Write semantic equations in terms of concrete syntax.  Quote general expressions.  V, E, C > R, T, E .  [...] > <...> for quotation of script expressions.  (E | id_e, m) > [E | id_e, m] for local binding.  Introduce primary to disambiguate expression* , factor lhs from binding.  Introduce Sub component to initialize nodes.  Debug semantics of braces and dot.  Mode > binding.  Debug semantics of (fix up indirection).  Add VAL.  *start* 08096 00024 USt Date: 30 July 1981 11:04 pm PDT (Thursday) From: Mitchell.PA Subject: First cut at some Interdoc level 2 issues - Comments appreciated To: Horning cc: Mitchell Last Edited by Mitchell, 30 July 1981 11:01 pm PDT (Thursday) Began to flesh out section on CONVENTIONS, esp. some standard definitions for paragraphs, fonts, etc. and notions of editor-specific and interchange-standard scripts. TOWARDS AN INTERCHANGE LANGUAGE FOR EDITABLE DOCUMENTS INTRODUCTION * Rationale and background * Overview Scope Exclusions * Feasibility * CONCEPTS AND GUIDING PRINCIPLES Descriptive with a procedural basis Maintaining document structure over edits Using limited editors on rich documents An open-ended standard EXAMPLES [hardcopy, private representation, Interdoc script] Laurel message BravoX document with styles Star document with a bar chart, a simple curve, a table, or a form A GML example (from SIGOA paper) THE BASE LANGUAGE Syntax Primitive and sequence data types and literals Labels and references PROPERTIES Environments, names, and values Transformations: binding, definitions, and invocations Scope and persistence Standard properties CONVENTIONS Node Types: From an editor's point of view, each node in an Interdoc script has a set of types associated with it. For example, a node might be a textDocument and a LaurelMessage, meaning that it can be expected to have, roughly speaking, the union of the attributes normally associated with a textDocument and a LaurelMessage. A type is associated with a node by adding a binding of the form typeName=T to the attribute TYPE (which must be an environment) in the local environment. Thus, to assert that a node is both a textDocument and a LaurelMessage, the following bindings would have to be done in the context of the node: TYPE.textDocument_T TYPE.LaurelMessage_T An editor can then determine all the types of a node by enumerating the TYPE component of the node's environment. Standard and Editor-Specific Renderings: We need a two-level structure for documents expressed in the base language to be both (a) interchangeable among different editors, and (b) retain information of special significance to a specific editor. Let us call (a) the interchange standard information, or standard information and (b) editor-specific information. Basically, an editor X is free to couch attributes in its own terms, which can make it easy for it to consume an Interdoc script produced by itself, but it must provide a set of mappings which will transform attributes into the interchange standard. The recommended method for doing this is to invoke its name as the very first expression in any node that it has produced in its X-specific variant (the rules for inheritance of properties mean that often only the root node of a document will need to have this property, but there is nothing wrong with nodes being in different editor-specific terms provided they invoke the appropriate editor properties). Now, to be a valid standard script, the document must have the definition of X placed in the script itself (Although there is nothing wrong with having libraries of editor-specific -> standard mappings in a library of some sort to avoid having copies of them in each script). When X parses an X-specific script, it will use its X-specific attributes and never invoke the mappings from X-specific information to standard terms. However, when a document is to be interpreted by some other editor Y, any time it tries to access a standard name, the mapping associated with that name will be invoked to compute its value in terms of the X-specific values in the script. What guarantee is there that this can always be done? It is worth noting first that we are speaking here of a script being interpreted by an editor, rather than produced. Consequently, it will never need to access standard names in left-hand contexts; i.e., it need do no bindings that are not part of the script in order to interpret it. It may, however, need to access the components of environments in order to map the script into its private format. These are always values in right-hand side contexts, and must be computed in terms of the X-specific information that X put in the script. We can examine this issue on a case-by-case basis. Below is a list of examples of possible editor-specific uses of the base language and the mappings that would allow another editor to treat the document in standard terms: Symbolic values used instead of numbers: supply standard values for the symbolic values; e.g., Editor-specific: Paragraph.leading.betweenLines_single mapping: '{single=2*pt} Different names used for standard names: supply a binding to the standard name from the editor-specific name using a quoted expression so that it is only evaluated when needed in a right-hand side context; e.g., Editor-specific: Paragraph_.{ Space_{ BetweenLines_single BeforePara_double AfterPara_single } } mapping: Paragraph_.{ leading_.{ betweenLines_'Paragraph.Space.BetweenLines beforePara _ 'Paragraph.Space.BeforePara afterPara _ 'Paragraph.Space.AfterPara } } In general, one can use the facilities of the base language to write essentially arbitrary programs that can, by being quoted, be bound to a standard identifier to cause the appropriate value to be computed based on editor-specific information put in the document by the editor that produced it. Moreover, since the mappings provided by editor X can be overridden in any subtree of the document, an editor that does not "understand" some subtree of a document produced by another editor Y can simply leave that subtree intact when producing an edited version of the original script except to ensure that that subtree's root node's first expression is an invocation of "Y", which will cause Y's editor-specific mappings to obtain in that subtree. [Property definitions to be shared by various editor classes] Text Messages Standard External Environment: UNITS: internally distances are kept in meters and angles are kept in degrees meter==1.0 mica==1.E-5*meter inch==.0254*meter pt==inch/72. -- actual Anglo/American standard is pt==.013837*inch pica==12*pt tenPitch==inch/10. twelvePitch==inch/12. In general, the following definitions are not bound as CONST ("==") because it seems perfectly reasonable to embellish them with other attributes. The base language doesn't allow one to delete bindings, so we are guaranteed that every instance of a Font environment, for instance, will contain values for family, face, size, and position. Font_{ family_ITCTiffany -- a font name face_{ weight_normal -- IN {extralight light normal book demi medium semibold heavy bold black} slant_none -- IN {none italic oblique} underlined_F smallCaps_F } size_10*pt -- distance position_0 -- distance: rel. to baseline; for subscripting, etc. } Paragraph_{TYPE.para_T margins_{ left_1.*inch -- distance right_7.5*inch -- distance } alignment_flushLeft -- IN {flushLeft centered flushRight} justified_F -- Boolean leading_{ betweenLines_1*pt -- distance beforePara _ 12*pt -- distance afterPara _ 0 -- distance } fonts_{ use SUB for this? normal_{Font.family_TimesRoman} emphasis1_{Font_normal Font.face.italic_T} emphasis2_{Font_normal Font.face.bold_T} } hyphenation_F keep_NIL -- IN {NIL, heading, start, continue, a distance} bX: 5.9 } Frame_{ scale_{ -- default is the identity transformation X_1 -- expression Y_1 -- expression } topMargin_1.0*inch -- distance bottomMargin_1.0*inch -- distance leftMargin_1.*inch -- distance rightMargin_7.5*inch -- distance transformation_'VAL{VAL{1 0 0} VAL{0 1 0} VAL {0 0 1}} ? } * Fonts and formats * Hierarchical documents * Styles XXX Graphics  PRAGMATICS * Private encodings and private representations XXX Conversion efficiency XXX APPENDICES GLOSSARY FORMAL SEMANTIC DEFINITION RELATION TO OTHER STANDARDS XXX INDEX *start* 00808 00024 USt Date: 31 July 1981 10:39 am PDT (Friday) From: Horning.pa Subject: Re: Current Level 0/1 Interdoc status/rev. 13 In-reply-to: Your message of 30 July 1981 9:55 pm PDT (Thursday) To: Mitchell cc: Horning Jim, Given the expected infrequency of Boolean expressions (or infix operators), I guess I'm not enamoured of adding that much syntax for precedence. Left-to-right plus explicit bracketing will be OK. I suggest instead expression ::= [ lhs ] [ "'" | "." | op ] primary primary ::= literal | id | primary "." id | conditional | node | [ "VAL" ] "{" expression ( [ op ] expression )* "}" op ::= "+" | "" | "*" | "/" | "MOD" | "NOT" | "AND" | "OR" | "LT" | " LE" | "EQ" | "NE" | "GE" | "GT" Note that since you use EQ, "=" is still available for Const binding. Jim H. *start* 07079 00024 USt Date: 31 July 1981 4:28 pm PDT (Friday) From: Mitchell.PA Subject: Current Level 0/1 Interdoc status/rev. 14 To: Mitchell, Horning Last edited by Mitchell, 31 July 1981 12:20 pm PDT (Friday) Simplified expression syntax. Expressions with embedded binary operators are simply interpreted in a right-to-left fashion; e.g., x_a*b+c means x_a*(b+c). Fixed up semantic equations to reflect this. Exchanged the use of {}s and ()s. We envision an Interdoc script being processed in any manner equivalent to the following: Parse the script, alternately - reducing each expression to "primitives" by evaluating constant subexpressions and replacing names by the values to which they are bound in the current environment, and - transforming the environment as indicated by the expressions. BASIC INTERDOC GRAMMAR node ::= "{" labels expression* "}" labels ::= [label* ":"] label ::= "#" name expression ::= [ lhs ] [ "'" | "." | op ] rhs rhs ::= [ "NOT" ] primary ( op primary )* primary ::= literal | id | primary "." id | conditional | node | [ "VAL" ] "(" expression* ")" literal ::= Boolean | integer | hexint | real | string | label name ::= id ( "." id)* id ::= (letter | "" ) ( letter | "" | digit )* -- "" is the null id conditional ::= "IF(" expression "," expression* [ "," expression* ] ")" lhs ::= name binding binding ::= "=" | ":" | ":=" | "_" op ::= "+" | "" | "*" | "/" | "MOD" | "AND" | "OR" | "LT" | " LE" | "EQ" | "NE" | "GE" | "GT" SYNTACTIC EXAMPLES: {#examplenode: a:='NOT margins.left EQ 120 margins.left_100 r=12.5*pt IF(a, leftMargin_+5, leftMargin_+10) } SEMANTICS R denotes the expression reduction function: R: expression > ( environment > expression ) T denotes the environment transformation function: T: expression > ( environment > environment ) Environments bind expressions and "modes" to identifiers: Null denotes the "empty" environment [E | id_e, m] means "E with (e, m) bound to id" E(id) denotes the value locally bound to id in E Null(id) = id [E | id'_e, m](id) = if id=id' then e else E(id) locBinding(id, E) denotes the binding mode of id in E locBinding(id, Null) = None locBinding(id, [E | id'_e, m]) = if id=id' then m else locBinding(id, E) -- Basis R<>(E) = nothing -- just what it says T<>(E) = E -- Identity -- Expression sequence R(E) = R(E) -- "nothing" disappears R(E) = R(E) R(T(E)) -- List insert T(E) = T(T(E)) -- Composition R<"'" p>(E) = p T<"'" p>(E) = E R(E) = literal T(E) = E R(E) = if valOf(id, E)=id then id else R(E) T(E) = if valOf(id, E)=id then E else T(E) R

(E) = R(R

(E)) T

(E) = if valOf(id, R

(E))=id then E else T(E))>(E) R<"IF(" e1 "," e2* "," e3* ")">(E) = if R(E) then R(T(E)) else R(T(E)) T<"IF(" e1 "," e2* "," e3* ")">(E) = if R(E) then T(T(E)) else T(T(E)) R(E) = apply(op, p1, p2, E) T(E) = E R<"NOT" p>(E) = if R

(E)=True then False else True T<"NOT" p>(E) = E R(E) = nothing -- Empty list T(E) = bindq(n, m, apply(op, n, e, E), E) R<"(" labels e* ")">(E) = "(" labels R([Null | Outer_E, Const]) ")" T<"(" labels e* ")">(E) = (T([Null | Outer_E, Const]))(Outer) R<"(" e* ")">(E) = [T<"(" e* ")">(E) | Outer_Null, Const] T<"(" e* ")">(E) = T([Null | Outer_E, Const]) R<"VAL(" e* ")">(E) = R(E) T<"VAL(" e* ")">(E) = E whereBound(id, E) = -- Finds innermost binding locBinding(id, E) ~= None => E locBinding(Outer, E) ~= None => whereBound(id, E(Outer)) True => Null valOf(id, E) = (whereBound(id, E))(id) -- Gets innermost value bindingOf(id, E) = locBinding(id, whereBound(id, E)) -- Gets innermost binding bindq(id, m, e, E) = bindingOf(id, E) = "=" => E m = ":=" => assign(id, e, E) True => [E | id_e, m] bindq(id.n, m, e, E) = [E | id_bindq(n, m, e, R(E)), bindingOf(id, E)] assign(id, e, E) = locBinding(id, E) = ":" => [E | id_e, ":"] bindingOf(id, E) = ":" => bindq(Outer.id, ":=", e, E) True => E apply(op, lhs, rhs, E) = op = "" => R(E) op = "." => R([R(E) | Outer_E, Const]) op = "+" => R(E)+R(E) . . . Missing or in question: literal sequences binary & relational operators ------------------- Expressions in an Interdoc script may denote literal values: Boolean: (F, T) integer: ... -3, -2, -1, 0, 1, 2, 3, ... real: 1.2E5, . . . string: label: #A123, #anId, #Paragraph the empty environment: Null the empty list: NIL id:  (the null id), bold, thisIsAnId, Helvetica, . . . (unless bound, taken to denote a primitive) environments unevaluated expressions How semantics are associated with an entire document: Each environment, E, initially contains only its "inherited" environment (bound to the id Outer). Most bindings take place directly in E. However, the value of a bindq(id, ":=", p, E) will change E by rebinding id in the "innermost" environment (following the chain of Outers) in which it is bound, if that binding has the binding ":" (Var). Identifiers bound with binding "=" (Const) may not be rebound in inner environments. When an id is referred to and locBinding(id, E)=None, then the value is sought recursively in E(Outer). Perverse explicit bindings to outer might create loops, leaving some ids undefined, but there seems to be little reason to clutter up the semantics by forbidding such assignments. The contents of each node are implicitly prefixed by Sub, which will generally be bound to an environment transformation in the containing environment. Braces create a nested environment; if preceded by a dot, it is initialized to the value of the name in the binding; if preceded by VAL, it is executed for value, and the environment is then discarded. Semantics of labels: A label #id on a node in the dominant structure gives that node membership in the set named by id. Multiple labels place the node in multiple sets, and a unique label on a node places it in a singleton set, i.e., identifies it uniquely. HISTORY LOG  Bring the syntax up front.  Further develop parallelism between grammar and semantic equations.  Write semantic equations in terms of concrete syntax.  Quote general expressions.  V, E, C > R, T, E .  [...] > <...> for quotation of script expressions.  (E | id_e, m) > [E | id_e, m] for local binding.  Introduce primary to disambiguate expression* , factor lhs from binding.  Introduce Sub component to initialize nodes.  Debug semantics of braces and dot.  Mode > binding.  Debug semantics of (fix up indirection).  Add VAL.  Last edited by Mitchell, 30 July 1981 9:21 pm PDT (Thursday): Changed grammar to allow more complete expression syntax; couldn't use "<" or ">" as operators because they delimit strings. Moved history log to end of message.