*start* 07201 00024 USt Date: 7 Aug. 1981 4:41 pm PDT (Friday) From: Mitchell.PA Subject: Current Level 0/1 Interdoc status/rev. 15 To: Mitchell, Horning Last edited by Mitchell, 7 Aug. 1981 4:40 pm PDT (Friday) Fixed error in semantics when exchanging 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. 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. *start* 07956 00024 USt Date: 13 Aug. 1981 5:36 pm PDT (Thursday) From: Horning.pa Subject: Current Level 0/1 Interdoc status/rev. 16 To: Mitchell, Horning [Jim, I did a fair amount of doodling, primarily in an attempt to transform the semantic equations to a form where their correctness will be "more nearly obvious." Some of the changes I like, but I'm not really wedded to any of them.] Edited by Horning 13 Aug. 1981 4:47 pm PDT (Thursday). E(id) > locVal(id, E) --Remove conflict with f(E). Outer > "Outer" Const > "=" id lookup rule modified (R & T) [E | id_e, m] > [E | id m e] "." as infix op expressions are evaluated left-to-right (except for binding operator) Reverse VAL/ENV default for parens. bindq > bind binding > bindingMode expand definition of apply inline default T(E) = E add comments to semantic equations ------------------- In question: treatment of primitive identifiers side effects in expressions operations on nested environments: font_.(size_10) Missing: literal sequences ------------------- 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 | [ "ENV" ] "(" 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 bindingMode bindingMode ::= "=" | ":" | ":=" | "_" op ::= "." | "+" | "" | "*" | "/" | "MOD" | "AND" | "OR" | "LT" | " LE" | "EQ" | "NE" | "GE" | "GT" SYNTACTIC EXAMPLE: {#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 identifiers to expressions, in various modes ("=", ":", ":=", "_"): Null denotes the "empty" environment [E | id m e] means "E with id mode m bound to e" locBinding(id, E) denotes the binding mode of id in E locBinding(id, Null) = None locBinding(id, [E | id' m e]) = if id=id' then m else locBinding(id, E) locVal(id, E) denotes the value locally bound to id in E, if locBinding(id, E) ~= None locVal(id, [E | id' m e]) = if id=id' then e else locVal(id, E) N. B. T(E) = E , if no explicit value is given below. -- Basis R<>(E) = Nothing -- The empty expression -- Expression sequence R(E) = R(E) R(T(E)) -- List insert T(E) = T(T(E)) -- Composition R(E) = literal R(E) = if bindingOf(id, E)=None then id else R(E) T(E) = if bindingOf(id, E)=None then E else T(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<"NOT" p>(E) = if R

(E) then False else True R(E) = op = "." => R([R(E) | "Outer" = E]) op = "+" => R(E)+R(E) . . . R(E) = Nothing -- Empty list T(E) = bind(n, m, R(E), E) T(E) = bind(n, m, e, E) T(E) = bind(n, m, R(E), E) R<"{" labels e* "}">(E) = "{" labels R([Null | "Outer" = E]) "}" T<"{" labels e* "}">(E) = locVal("Outer", (T<"ENV("Sub e*")">(E))) R<"(" e* ")">(E) = R(E) R<"ENV(" e* ")">(E) = [T<"ENV(" e* ")">(E) | "Outer" = Null] T<"ENV(" e* ")">(E) = T([Null | "Outer" = E]) bindingOf(id, E) = locBinding(id, whereBound(id, E)) -- Gets innermost binding valOf(id, E) = locVal(id, whereBound(id, E)) -- Gets innermost value whereBound(id, E) = -- Finds innermost binding locBinding(id, E) ~= None => E locBinding("Outer", E) ~= None => whereBound(id, locVal("Outer", E)) True => Null bind(id, m, e, E) = bindingOf(id, E) = "=" => E -- Can't rebind constants m = ":=" => assign(id, e, E) -- Assign at right level True => [E | id m e] bind(id.n, m, e, E) = [E | id bindingOf(id, E) bind(n, m, e, R(E))] assign(id, e, E) = locBinding(id, E) = ":" => [E | id ":" e] bindingOf(id, E) = ":" => bind("Outer".id, ":=", e, E) True => E -- Can only assign to vars ------------------- 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 bind(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 locVal("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.  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. 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. Edited by Mitchell, 7 Aug. 1981 4:40 pm PDT (Friday) Fixed error in semantics when exchanging the use of {}s and ()s. *start* 08870 00024 USt Date: 17 Aug. 1981 11:40 am PDT (Monday) From: Horning.pa Subject: Current Level 0/1 Interdoc status/rev. 17 To: Mitchell, Horning [Jim, For discussion this afternoon. Jim H.] Edited by Jim Horning 17 Aug. 1981 10:49 am PDT (Monday) R&T<> Nothing > "" ------------------- In question: treatment of primitive identifiers (vs. labels) side effects in expressions (why only in conditionals?) operations on nested environments: font_.(size_10) merging environments reduced transformations Missing: literal sequences operations on sequences (subscripting) ------------------- 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 | [ "ENV" ] "(" 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 bindingMode bindingMode ::= "=" | ":" | ":=" | "_" op ::= "." | "+" | "" | "*" | "/" | "MOD" | "AND" | "OR" | "LT" | " LE" | "EQ" | "NE" | "GE" | "GT" SYNTACTIC EXAMPLE: {#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 ) R&T(E) denotes the pair R(E); T(E) R&T: ( expression, environment ) > ( expression, environment ) Environments bind identifiers to expressions, in various modes ("=", ":", ":=", "_"): Null denotes the "empty" environment [E | id m e] means "E with id mode m bound to e" locBinding(id, E) denotes the binding mode of id in E locBinding(id, Null) = None locBinding(id, [E | id' m e]) = if id=id' then m else locBinding(id, E) locVal(id, E) denotes the value locally bound to id in E locVal(id, Null) = Null locVal(id, [E | id' m e]) = if id=id' then e else locVal(id, E) R&T<>(E) = ""; E R&T(E) = R(E) R(T(E)); T(T(E)) R&T(E) = literal; E R&T(E) = if bindingOf(id, E)=None then id; E else R&T(E) R&T<"IF(" e1 "," e2* "," e3* ")">(E) = if R(E) then R&T(T(E)) else R&T(T(E)) R&T<"NOT" p>(E) = if R

(E) then False else True; E R&T(E) = op = "." => R([R(E) | "Outer" = E ?]); E op = "+" => R(E)+R(E); E . . . R&T(E) = ""; bind(n, m, R(E), E) R&T(E) = ""; bind(n, m, e, E) R&T(E) = ""; bind(n, m, R(E), E) R&T<"{" labels e* "}">(E) = "{" labels R([Null | "Outer" = E]) "}"; locVal("Outer", (T([Null | "Outer" = E]))) R&T<"(" e* ")">(E) = R(E); E R&T<"ENV(" e* ")">(E) = [T(E) | "Outer" = Null]; T(E) ? bindingOf(id, E) = locBinding(id, whereBound(id, E)) -- Gets innermost binding valOf(id, E) = locVal(id, whereBound(id, E)) -- Gets innermost value whereBound(id, E) = -- Finds innermost binding locBinding(id, E) ~= None => E locBinding("Outer", E) ~= None => whereBound(id, locVal("Outer", E)) True => Null bind(id, m, e, E) = bindingOf(id, E) = "=" => E -- Can't rebind constants m = ":=" => assign(id, e, E) -- Assign at right level True => [E | id m e] bind(id.n, m, e, E) = [E | id bindingOf(id, E) bind(n, m, e, R(E))] assign(id, e, E) = locBinding(id, E) = ":" => [E | id ":" e] bindingOf(id, E) = ":" => bind("Outer".id, ":=", e, E) True => E -- Can only assign to vars ------------------- 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 bind(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 locVal("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. Parentheses create a nested environment; if preceded by a dot, it is initialized to the value of the name in the binding; if not preceded by ENV, 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.  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. 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. Edited by Mitchell, 7 Aug. 1981 4:40 pm PDT (Friday) Fixed error in semantics when exchanging the use of {}s and ()s. Edited by Horning 13 Aug. 1981 4:47 pm PDT (Thursday). E(id) > locVal(id, E) --Remove conflict with f(E). Outer > "Outer" Const > "=" id lookup rule modified (R & T) [E | id_e, m] > [E | id m e] "." as infix op expressions are evaluated left-to-right (except for binding operator) Reverse VAL/ENV default for parens. bindq > bind binding > bindingMode expand definition of apply inline default T(E) = E add comments to semantic equations ------------------- R<>(E) = Nothing -- The empty expression -- Expression sequence R(E) = R(E) R(T(E)) -- List insert T(E) = T(T(E)) -- Composition R(E) = literal R(E) = if bindingOf(id, E)=None then id else R(E) T(E) = if bindingOf(id, E)=None then E else T(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<"NOT" p>(E) = if R

(E) then False else True R(E) = op = "." => R([R(E) | "Outer" = E]) op = "+" => R(E)+R(E) . . . R(E) = Nothing -- Empty list T(E) = bind(n, m, R(E), E) T(E) = bind(n, m, e, E) T(E) = bind(n, m, R(E), E) R<"{" labels e* "}">(E) = "{" labels R([Null | "Outer" = E]) "}" T<"{" labels e* "}">(E) = locVal("Outer", (T<"ENV("Sub e*")">(E))) R<"(" e* ")">(E) = R(E) R<"ENV(" e* ")">(E) = [T<"ENV(" e* ")">(E) | "Outer" = Null] T<"ENV(" e* ")">(E) = T([Null | "Outer" = E]) ------------------- *start* 09077 00024 USt Date: 17 Aug. 1981 7:05 pm PDT (Monday) From: Horning.pa Subject: Current Level 0/1 Interdoc status/rev. 18 To: Mitchell, Horning [Jim, Jim H.] Edited by Jim H. on 17 Aug. 1981 4:58 pm PDT (Monday) Remove side-effects from all expressions. Parentheses purely for grouping (don't hide environment transformations). #label > label ! labels within nodes ------------------- In question: operations on nested environments: font_.(size_10) merging environments reduced transformations structured labels getEnv operator labels outside dominant structure non-printing nodes Missing: operations on sequences and environments (subscripting and enumeration) substitution of  for Null, Nil, etc. ------------------- 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 ::= "{" expression* "}" expression ::= [ lhs ] [ "'" | op ] | name ":!" -- :! for label declaration rhs ::= [ "NOT" ] primary ( op primary )* primary ::= literal | id | primary "." id | conditional | node | [ "ENV" ] "(" expression* ")" | label literal ::= Boolean | integer | hexint | real | string | label name ::= id ( "." id)* id ::= (letter | "" ) ( letter | "" | digit )* -- "" is the null id label ::= name "!" conditional ::= "IF(" expression "," expression* [ "," expression* ] ")" lhs ::= name bindingMode bindingMode ::= "=" | ":" | ":=" | "_" op ::= "." | "+" | "" | "*" | "/" | "MOD" | "AND" | "OR" | "LT" | " LE" | "EQ" | "NE" | "GE" | "GT" SYNTACTIC EXAMPLE: {node.example! 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 ) R&T(E) denotes the pair R(E); T(E) R&T: ( expression, environment ) > ( expression, environment ) Environments bind identifiers to expressions, in various modes ("=", ":", ":=", "_"): Null denotes the "empty" environment [E | id m e] means "E with id mode m bound to e" locBinding(id, E) denotes the binding mode of id in E locBinding(id, Null) = None locBinding(id, [E | id' m e]) = if id=id' then m else locBinding(id, E) locVal(id, E) denotes the value locally bound to id in E locVal(id, Null) = Null locVal(id, [E | id' m e]) = if id=id' then e else locVal(id, E) R&T<>(E) = ""; E R&T(E) = R(E) R(T(E)); T(T(E)) R&T(E) = literal; E R&T(E) = if bindingOf(id, E)=None then id; E else R&T(E) R&T<"IF(" e1 "," e2* "," e3* ")">(E) = if R(E) then R&T(E) else R&T(E) R&T<"NOT" p>(E) = if R

(E) then False else True; E R&T(E) = op = "." => R([R(E) | "Outer" = E ?]); E op = "+" => R(E)+R(E); E . . . R&T(E) = ""; bind(n, m, R(E), E) R&T(E) = ""; bind(n, m, e, E) R&T(E) = ""; bind(n, m, R(E), E) R&T<"{" e* "}">(E) = "{" R([Null | "Outer" = E]) "}"; locVal("Outer", (T([Null | "Outer" = E]))) R&T<"(" e* ")">(E) = R&T(E) R&T<"ENV(" e* ")">(E) = [T(E) | "Outer" = Null]; T(E) ? bindingOf(id, E) = locBinding(id, whereBound(id, E)) -- Gets innermost binding valOf(id, E) = locVal(id, whereBound(id, E)) -- Gets innermost value whereBound(id, E) = -- Finds innermost binding locBinding(id, E) ~= None => E locBinding("Outer", E) ~= None => whereBound(id, locVal("Outer", E)) True => Null bind(id, m, e, E) = bindingOf(id, E) = "=" => E -- Can't rebind constants m = ":=" => assign(id, e, E) -- Assign at right level True => [E | id m e] bind(id.n, m, e, E) = [E | id bindingOf(id, E) bind(n, m, e, R(E))] assign(id, e, E) = locBinding(id, E) = ":" => [E | id ":" e] bindingOf(id, E) = ":" => bind("Outer".id, ":=", e, E) True => E -- Can only assign to vars ------------------- 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 bind(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 locVal("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. Parentheses create a nested environment; if preceded by a dot, it is initialized to the value of the name in the binding; ? if not preceded by ENV, 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.  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. 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. Edited by Mitchell, 7 Aug. 1981 4:40 pm PDT (Friday) Fixed error in semantics when exchanging the use of {}s and ()s. Edited by Horning 13 Aug. 1981 4:47 pm PDT (Thursday). E(id) > locVal(id, E) --Remove conflict with f(E). Outer > "Outer" Const > "=" id lookup rule modified (R & T) [E | id_e, m] > [E | id m e] "." as infix op expressions are evaluated left-to-right (except for binding operator) Reverse VAL/ENV default for parens. bindq > bind binding > bindingMode expand definition of apply inline default T(E) = E add comments to semantic equations ------------------- R<>(E) = Nothing -- The empty expression -- Expression sequence R(E) = R(E) R(T(E)) -- List insert T(E) = T(T(E)) -- Composition R(E) = literal R(E) = if bindingOf(id, E)=None then id else R(E) T(E) = if bindingOf(id, E)=None then E else T(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<"NOT" p>(E) = if R

(E) then False else True R(E) = op = "." => R([R(E) | "Outer" = E]) op = "+" => R(E)+R(E) . . . R(E) = Nothing -- Empty list T(E) = bind(n, m, R(E), E) T(E) = bind(n, m, e, E) T(E) = bind(n, m, R(E), E) R<"{" labels e* "}">(E) = "{" labels R([Null | "Outer" = E]) "}" T<"{" labels e* "}">(E) = locVal("Outer", (T<"ENV("Sub e*")">(E))) R<"(" e* ")">(E) = R(E) R<"ENV(" e* ")">(E) = [T<"ENV(" e* ")">(E) | "Outer" = Null] T<"ENV(" e* ")">(E) = T([Null | "Outer" = E]) ------------------- Edited by Jim Horning 17 Aug. 1981 10:49 am PDT (Monday) R&T<> Nothing > "" *start* 09690 00024 USt Date: 19 Aug. 1981 9:58 am PDT (Wednesday) From: Horning.pa Subject: Current Level 0/1 Interdoc status/rev. 19 To: Mitchell, Horning, Lampson Edited by Jim H. on 19 Aug. 1981 9:52 am PDT (Wednesday). Rewrite as syntactic sugar. structured labels re-introduce apply function in R&T correct syntax for "." % for opening an environment (also replaces ENV?) ------------------- In question: subscripting: sequences, yes; nodes, labels, sets, environments, no evaluation of subscript expressions merging environments labels outside dominant structure non-printing nodes generalize apply to non-literal operands (distribute over sequences?) IF, NOT, apply when arguments are not literals, partial evaluation bind op in environment? Missing: operations on sequences and environments (subscripting and enumeration) substitution of  for Null, Nil, etc. ------------------- 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 ::= "{" expression* "}" expression ::= [ lhs ] [ "'" | op ] | name ":!" -- :! for label declaration rhs ::= [ "NOT" ] primary ( op primary )* primary ::= literal | id | primary "." id | conditional | node | [ "ENV" ] "(" expression* ")" | label literal ::= Boolean | integer | hexint | real | string | label name ::= id ( "." id)* id ::= (letter | "" ) ( letter | "" | digit )* -- "" is the null id label ::= name "!" conditional ::= "IF(" expression "," expression* [ "," expression* ] ")" lhs ::= name bindingMode bindingMode ::= "=" | ":" | ":=" | "_" op ::= "%" | "+" | "" | "*" | "/" | "MOD" | "AND" | "OR" | "LT" | " LE" | "EQ" | "NE" | "GE" | "GT" SYNTACTIC EXAMPLE: {node.example! 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 ) R&T(E) denotes the pair R(E); T(E) R&T: ( expression, environment ) > ( expression, environment ) Environments bind identifiers to expressions, in various modes ("=", ":", ":=", "_"): Null denotes the "empty" environment [E | id m e] means "E with id mode m bound to e" locBinding(id, E) denotes the binding mode of id in E locBinding(id, Null) = None locBinding(id, [E | id' m e]) = if id=id' then m else locBinding(id, E) locVal(id, E) denotes the value locally bound to id in E locVal(id, Null) = Null locVal(id, [E | id' m e]) = if id=id' then e else locVal(id, E) R&T<>(E) = ""; E R&T(E) = R(E) R(T(E)); T(T(E)) R&T(E) = literal; E R&T(E) = if bindingOf(id, E)=None then id; E else R&T(E) R&T

(E) = R&T(E))>(E) -- Subscript should go here R&T<"IF(" e1 "," e2* "," e3* ")">(E) = if R(E) then R&T(E) else R&T(E) R&T<"NOT" p>(E) = if R

(E) then False else True; E R&T(E) = p2; E R&T(E) = R([R(E) | "Outer" = E]); [T([R(E) | "Outer" = E]) | "Outer" = Null] R&T(E) = apply(R(E), op, R(E)); E R&T(E) = ""; bind(n, m, R(E), E) = -- Syntactic sugar R&T<"{" e* "}">(E) = "{" R([Null | "Outer" = E]) "}"; locVal("Outer", (T([Null | "Outer" = E]))) R&T<"(" e* ")">(E) = R&T(E) bindingOf(id, E) = locBinding(id, whereBound(id, E)) -- Gets innermost binding valOf(id, E) = locVal(id, whereBound(id, E)) -- Gets innermost value whereBound(id, E) = -- Finds innermost binding locBinding(id, E) ~= None => E locBinding("Outer", E) ~= None => whereBound(id, locVal("Outer", E)) True => Null apply(arg1, op, arg2) = op = "+" => arg1+arg2 . . . bind(id, m, e, E) = bindingOf(id, E) = "=" => E -- Can't rebind constants m = ":=" => assign(id, e, E) -- Assign at right level True => [E | id m e] bind(id.n, m, e, E) = [E | id bindingOf(id, E) bind(n, m, e, R(E))] assign(id, e, E) = locBinding(id, E) = ":" => [E | id ":" e] bindingOf(id, E) = ":" => [E | "Outer" "=" bind(id, ":=", e, locVal("Outer", E))] True => E -- Can only assign to vars ------------------- 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 bind(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 locVal("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. Parentheses create a nested environment; if preceded by a dot, it is initialized to the value of the name in the binding; ? if not preceded by ENV, it is executed for value, and the environment is then discarded. Semantics of labels: A label name! on a node gives that node membership in the sets identified by name (and its prefixes); the "main" identifier of a set name must be declared at the root of a subtree containing all its members. 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.  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. 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. Edited by Mitchell, 7 Aug. 1981 4:40 pm PDT (Friday) Fixed error in semantics when exchanging the use of {}s and ()s. Edited by Horning 13 Aug. 1981 4:47 pm PDT (Thursday). E(id) > locVal(id, E) --Remove conflict with f(E). Outer > "Outer" Const > "=" id lookup rule modified (R & T) [E | id_e, m] > [E | id m e] "." as infix op expressions are evaluated left-to-right (except for binding operator) Reverse VAL/ENV default for parens. bindq > bind binding > bindingMode expand definition of apply inline default T(E) = E add comments to semantic equations ------------------- R<>(E) = Nothing -- The empty expression -- Expression sequence R(E) = R(E) R(T(E)) -- List insert T(E) = T(T(E)) -- Composition R(E) = literal R(E) = if bindingOf(id, E)=None then id else R(E) T(E) = if bindingOf(id, E)=None then E else T(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<"NOT" p>(E) = if R

(E) then False else True R(E) = op = "." => R([R(E) | "Outer" = E]) op = "+" => R(E)+R(E) . . . R(E) = Nothing -- Empty list T(E) = bind(n, m, R(E), E) T(E) = bind(n, m, e, E) T(E) = bind(n, m, R(E), E) R<"{" labels e* "}">(E) = "{" labels R([Null | "Outer" = E]) "}" T<"{" labels e* "}">(E) = locVal("Outer", (T<"ENV("Sub e*")">(E))) R<"(" e* ")">(E) = R(E) R<"ENV(" e* ")">(E) = [T<"ENV(" e* ")">(E) | "Outer" = Null] T<"ENV(" e* ")">(E) = T([Null | "Outer" = E]) ------------------- Edited by Jim Horning 17 Aug. 1981 10:49 am PDT (Monday) R&T<> Nothing > "" Edited by Jim H. on 17 Aug. 1981 4:58 pm PDT (Monday) Remove side-effects from all expressions. Parentheses purely for grouping (don't hide environment transformations). #label > label ! labels within nodes *start* 10516 00024 USt Date: 19 Aug. 1981 6:56 pm PDT (Wednesday) From: Horning.pa Subject: Current Level 0/1 Interdoc status/rev. 20 To: Mitchell, Horning, Lampson Edited by Jim H. on 19 Aug. 1981 6:55 pm PDT (Wednesday). Drop "%"; ENV() is now the only environment-constructing operator. Add SUB operator (first operand: sequence only, second: number only). Add atoms, as distinct from ids. Fix lhs op rhs syntax. ------------------- In question: merging environments (OPEN) declaration of "main" labels labels outside dominant structure non-printing nodes (semicolon?) bind op names in environment? structured primitive names, naming authorities how to syntactically distinguish operator application infix vs. prefix for general operators (APL?) treatment of unbound qualified names  as id vs. binary op vs. sign on numbers Missing: enumeration over sequences and environments substitution of  for Null, Nil, etc., as appropriate ------------------- 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 ::= "{" expression* "}" expression ::= [ lhs ] rhs | name ":!" -- :! for label declaration rhs ::= [ "NOT" ] primary ( op primary )* primary ::= literal | id | primary "." id | conditional | node | [ "ENV" ] "(" expression* ")" literal ::= Boolean | integer | hexint | real | string | label | atom name ::= id ( "." id)* id ::= (letter | "" ) ( letter | "" | digit )* -- "" is the null id label ::= name "!" atom ::= "$" id conditional ::= "IF(" expression "," expression* [ "," expression* ] ")" lhs ::= name bindingMode [ "'" | op ] bindingMode ::= "=" | ":" | ":=" | "_" op ::= "+" | "" | "*" | "/" | "MOD" | "AND" | "OR" | "LT" | " LE" | "EQ" | "NE" | "GE" | "GT" | "SUB" SYNTACTIC EXAMPLE: {node.example! 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 ) R&T(E) denotes the pair R(E); T(E) R&T: ( expression, environment ) > ( expression, environment ) Environments bind identifiers to expressions, in various modes ("=", ":", ":=", "_"): Null denotes the "empty" environment [E | id m e] means "E with id mode m bound to e" locBinding(id, E) denotes the binding mode of id in E locBinding(id, Null) = None locBinding(id, [E | id' m e]) = if id=id' then m else locBinding(id, E) locVal(id, E) denotes the value locally bound to id in E locVal(id, Null) = Null locVal(id, [E | id' m e]) = if id=id' then e else locVal(id, E) R&T(E) = literal; E R&T(E) = if bindingOf(id, E)=None then "$" id; E else R&T(E) R&T

(E) = R&T(E))>(E) R&T<"IF(" e1 "," e2* "," e3* ")">(E) = if R(E) then R&T(E) else R&T(E) R&T<"NOT" p>(E) = NOT R

(E); E R&T(E) = p2; E R&T(E) = apply(R(E), op, R(E)); E R&T(E) = ""; bind(n, m, R(E), E) = -- Syntactic sugar R&T<>(E) = ""; E R&T(E) = R(E) R(T(E)); T(T(E)) R&T<"(" e* ")">(E) = R&T(E) R&T<"ENV(" e* ")">(E) = [T([Null | "Outer" = E]) | "Outer" = Null]; E R&T<"{" e* "}">(E) = "{" R([Null | "Outer" = E]) "}"; locVal("Outer", (T([Null | "Outer" = E]))) R&T(E) =  bindingOf(id, E) = locBinding(id, whereBound(id, E)) -- Gets innermost binding valOf(id, E) = locVal(id, whereBound(id, E)) -- Gets innermost value whereBound(id, E) = -- Finds innermost binding locBinding(id, E) ~= None => E locBinding("Outer", E) ~= None => whereBound(id, locVal("Outer", E)) True => Null apply(arg1, op, arg2) = op = "+" => arg1+arg2 . . . op = "SUB" => arg1[arg2] bind(id, m, e, E) = bindingOf(id, E) = "=" => E -- Can't rebind constants m = ":=" => assign(id, e, E) -- Assign at right level True => [E | id m e] bind(id.n, m, e, E) = [E | id bindingOf(id, E) bind(n, m, e, R(E))] assign(id, e, E) = locBinding(id, E) = ":" => [E | id ":" e] bindingOf(id, E) = ":" => [E | "Outer" "=" bind(id, ":=", e, locVal("Outer", E))] True => E -- Can only assign to vars ------------------- id:  (the null id), bold, thisIsAnId, Helvetica, . . . Expressions in an Interdoc script may denote literal values: Booleans: (F, T) integers: ... -3, -2, -1, 0, 1, 2, 3, ... reals: 1.2E5, . . . strings: labels: A123!, anId!, Paragraph.Example! primitive properties and operators: $id the empty environment: Null the empty list: NIL unevaluated expressions environments sets (sequences) of nodes with given labels 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 bind(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 locVal("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 in the containing environment to a quoted expression performing an environment transformation, and perhaps supplying some properties. Parentheses are used purely for grouping (e.g., creating a sequence value for a binding). ENV is used to create a new environment, which behaves much like a record. Semantics of labels: A label name! on a node gives that node membership in the sets identified by name (and its prefixes); the "main" identifier of a set name must be declared at the root of a subtree containing all its members. 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. OTHER NOTES Conservative rules for editor treatment of script subtrees created by other editors: -It's OK to display a node if you understand at least one of its properties. -It's OK to edit a node if you understand ALL of its properties. (Variant: all properties on the path back to the root.) STANDARD CARD  WE ARE DESIGNING A STANDARD FOR INTERCHANGE, NOT EDITING.  GENSYM IS AN EDITOR, NOT AN INTERCHANGE, FUNCTION.  STANDARDIZE CONCEPTS, NOT NAMES. 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.  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. 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. Edited by Mitchell, 7 Aug. 1981 4:40 pm PDT (Friday) Fixed error in semantics when exchanging the use of {}s and ()s. Edited by Horning 13 Aug. 1981 4:47 pm PDT (Thursday). E(id) > locVal(id, E) --Remove conflict with f(E). Outer > "Outer" Const > "=" id lookup rule modified (R & T) [E | id_e, m] > [E | id m e] "." as infix op expressions are evaluated left-to-right (except for binding operator) Reverse VAL/ENV default for parens. bindq > bind binding > bindingMode expand definition of apply inline default T(E) = E add comments to semantic equations ------------------- R<>(E) = Nothing -- The empty expression -- Expression sequence R(E) = R(E) R(T(E)) -- List insert T(E) = T(T(E)) -- Composition R(E) = literal R(E) = if bindingOf(id, E)=None then id else R(E) T(E) = if bindingOf(id, E)=None then E else T(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<"NOT" p>(E) = if R

(E) then False else True R(E) = op = "." => R([R(E) | "Outer" = E]) op = "+" => R(E)+R(E) . . . R(E) = Nothing -- Empty list T(E) = bind(n, m, R(E), E) T(E) = bind(n, m, e, E) T(E) = bind(n, m, R(E), E) R<"{" labels e* "}">(E) = "{" labels R([Null | "Outer" = E]) "}" T<"{" labels e* "}">(E) = locVal("Outer", (T<"ENV("Sub e*")">(E))) R<"(" e* ")">(E) = R(E) R<"ENV(" e* ")">(E) = [T<"ENV(" e* ")">(E) | "Outer" = Null] T<"ENV(" e* ")">(E) = T([Null | "Outer" = E]) ------------------- Edited by Jim Horning 17 Aug. 1981 10:49 am PDT (Monday) R&T<> Nothing > "" Edited by Jim H. on 17 Aug. 1981 4:58 pm PDT (Monday) Remove side-effects from all expressions. Parentheses purely for grouping (don't hide environment transformations). #label > label ! labels within nodes Edited by Jim H. on 19 Aug. 1981 9:52 am PDT (Wednesday). Rewrite as syntactic sugar. structured labels re-introduce apply function in R&T correct syntax for "." % for opening an environment (also replaces ENV?) *start* 03100 00024 USt Date: 20 Aug. 1981 12:29 pm PDT (Thursday) From: Horning.pa Subject: Minutes from the Midnight Skull Session To: Mitchell, Lampson cc: Horning We started from the following list. In question: merging environments (OPEN) declaration of "main" labels labels outside dominant structure non-printing nodes (semicolon?) bind op names in environment? structured primitive names, naming authorities how to syntactically distinguish operator application infix vs. prefix for general operators (APL?) treatment of unbound qualified names  as id vs. binary op vs. sign on numbers Missing: enumeration over sequences and environments substitution of  for Null, Nil, etc., as appropriate ------------------- Here is my transcription/recollection of their resolution:  merging environments (OPEN) REJECT  declaration of "main" labels ACCEPT (must define semantics precisely) Note that we decided to distinguish between properties (marks) and labels. For properties, the expression preceding # must evaluate to an external ($, atomic) name. The label preceding ! must be a literal name, which is not evaluated. (Analogous to lhs name in a binding.)  labels outside dominant structure Do NOT cause their nodes to be included in labelled set (for templates).  non-printing nodes (semicolon?) ACCEPT. More properly HIDDEN nodes; syntax still debatable.  bind op names in environment? structured primitive names, naming authorities EXTERNAL names will be structured, to allow for NA's. Binding will allow the use of freely-chosen local synonyms. These decisions apply equally to properties and operators.  how to syntactically distinguish operator application Some small variant of Cambridge Polish. BUT, lookup operator in environment before application.  infix vs. prefix for general operators (APL?) All prefix (function application syntax).  treatment of unbound qualified names Should result in Null or ERROR, not an external name (fix equations).   as id vs. binary op vs. sign on numbers REJECT as id. No more infix ops. No ambiguity between sign and op in functional notation  enumeration over sequences and environments REJECT  substitution of  for Null, Nil, etc., as appropriate REJECT OTHER NOTES A "main" label can only be an id, not a qualified name. An atom (external name) can be qualified. Operator ids come out of the grammar; we need to ensure that we define the semantic basis for SEQ/LIST, IF, NOT, ENV, PROG, QUOTE. The presentation of this material could be clarified by a table that relates constructions in the notation to their intended uses and meanings. It should be clarified that the "view" of the dominant structure is ALWAYS controlled by the properties of its nodes. (E.g., text is not always there to be "shown".) The "safety" rules for editing partially understood scripts should be restated entirely in terms of local properties (which may have been implicitly acquired through Sub or other invocations). We should check our characterset for disjointness with Interpress.DoubtfulChars. *start* 11578 00024 USt Date: 20 Aug. 1981 5:40 pm PDT (Thursday) From: Horning.pa Subject: Current Level 0/1 Interdoc status/rev. 22 To: Mitchell, Horning, Lampson [Jim, I think I've fixed the syntax problems we discussed. However, we should discuss how palatable this syntax is--I made a number of relatively arbitrary decisions for the sake of getting something definite as soon as possible. Jim H.] Edited by Jim H. on 20 Aug. 1981 5:29 pm PDT (Thursday). resolve pending questions as per message of 20 Aug. 1981 12:29 pm PDT. distinguish syntactically between properties (marks) and labels. only the "main" id of a label is declarable. eliminate  as an id character. eliminate op ids from grammar. restructure the grammar for "functional" notation for operators. update semantic equations for new grammar, etc. fix treatment of unbound qualified names (now produce Nil). ------------------- Not done: State the formal semantics of labels and properties. ------------------- We envision an Interdoc script being input and viewed in any manner equivalent to the following: Parse the script, alternately - reducing each expression to its "dominant structure," containing only literals, by replacing identifiers by the values to which they are bound in the current environment, by applying operators, and by removing binding items, and - transforming the environment as indicated by the binding items. BASIC INTERDOC GRAMMAR item ::= primary | binding | id ":!" -- :! for label declaration primary ::= id | primary "." id | literal | application | property | node id ::= letter ( letter | digit )* literal ::= Boolean | integer | hexint | real | string | label | external label ::= name "!" name ::= id ( "." id)* external ::= "$" name application ::= ( op | primary ) "(" item* ( "," item* )* ")" op ::= "'" | "+" | "" | "*" | "/" property ::= primary "#" node ::= "{" item* "}" binding ::= name [ op ] bindingMode ( primary | "(" item* ")" ) bindingMode ::= "=" | ":" | ":=" | "_" SYNTACTIC EXAMPLE: {Book.example! -- Places this in Book and Book.example ExampleParagraph -- Invokes a definition $UniqueMark12356# -- Adds a nonstandard property a:='(NOT(EQ(margins.left, 120))) margins.right_100 r=*(12.5, pt) IF(a, margins.left+_5 margins.right_5, margins.left+_10) } SEMANTICS R denotes the expression reduction function: R: expression > ( environment > expression ) T denotes the environment transformation function: T: expression > ( environment > environment ) R&T(E) denotes the pair R(E); T(E) R&T: ( expression, environment ) > ( expression, environment ) Environments bind identifiers to expressions, in various modes ("=", ":", ":=", "_"): Null denotes the "empty" environment [E | id m e] means "E with id mode m bound to e" locBinding(id, E) denotes the binding mode of id in E locBinding(id, Null) = None locBinding(id, [E | id' m e]) = if id=id' then m else locBinding(id, E) locVal(id, E) denotes the value locally bound to id in E locVal(id, Null) = Nil = "" locVal(id, [E | id' m e]) = if id=id' then e else locVal(id, E) R&T(E) = R&T(E) R&T

(E) = R&T(E))>(E) R&T(E) = literal; E R&T(E) = operate(op, arg*, E) R&T

(E) = operate(R

(E), arg*, E) R&T

(E) = R

(E) "#"; E R&T<"{" item* "}">(E) = "{" R<"Sub" item*>([Null | "Outer" = E]) "}"; locVal("Outer", (T<"Sub" item*>([Null | "Outer" = E]))) R&T(E) = ""; bind(n, m, R

(E), E) = -- Syntactic sugar = R&T<"(" item* ")">(E) = R&T(E) R&T<>(E) = ""; E R&T(E) = R(E) R(T(E)); T(T(E)) R&T(E) =  bindingOf(id, E) = locBinding(id, whereBound(id, E)) -- Gets innermost binding valOf(id, E) = locVal(id, whereBound(id, E)) -- Gets innermost value whereBound(id, E) = -- Finds innermost binding locBinding(id, E) ~= None => E locBinding("Outer", E) ~= None => whereBound(id, locVal("Outer", E)) True => Null operate(op, arg*, E) = op = $QUOTE => arg*; E op = $HIDE => ""; E op = $ENV => [T([Null | "Outer" = E]) | "Outer" = Null]; E True => apply(op, eval(arg*, E)) apply(op, val1, ... , valn) = op = $IF => if val1.R then val2 else val3 op = "+" OR op = $PLUS => val1.R + ... + valn.R; E ... op = $LIST => val1 op = $SUBSCRIPT => val1[val2.R] -- val1: sequence, val2.R: int eval("", E) = Nil eval(arg1 arg*, E) = R&T(E), eval(arg*, E) bind(id, m, val, E) = bindingOf(id, E) = "=" => E -- Can't rebind constants m = ":=" => assign(id, val, E) -- Assign at right level True => [E | id m val] bind(id.n, m, val, E) = [E | id bindingOf(id, E) bind(n, m, val, R(E))] assign(id, val, E) = locBinding(id, E) = ":" => [E | id ":" val] bindingOf(id, E) = ":" => [E | "Outer" "=" bind(id, ":=", val, locVal("Outer", E))] True => E -- Can only assign to vars ------------------- Expressions in an Interdoc script may denote literal values: Booleans: (F, T) integers: ... -3, -2, -1, 0, 1, 2, 3, ... reals: 1.2E5, . . . strings: labels: A123!, anId!, Paragraph.Example! external names: $name the empty environment: Null the empty list: NIL sequences of values unevaluated expressions environments sets (sequences) of nodes with given labels 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 bind(id, ":=", val, 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 locVal("Outer"). The (implicit) "outermost" environment binds each id to the external name $id. The contents of each node are implicitly prefixed by Sub, which will generally be bound in the containing environment to a quoted expression performing an environment transformation, and perhaps supplying some properties. Parentheses are used for grouping (e.g., creating a sequence value for a binding), and to delimit the argument list of an operator. The operator $ENV is used to create a new environment, which behaves much like a record. Semantics of labels: A label name! on a node gives that node membership in the sets identified by name (and its prefixes); the "main" identifier of a set name must be declared at the root of a subtree containing all its members. 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. OTHER NOTES It should be clarified that the "view" of the dominant structure is ALWAYS controlled by the properties of its nodes. (E.g., text is not always there to be "shown".) Conservative rules for editor treatment of script subtrees created by other editors: -It's OK to display a node if you understand at least one of its properties. -It's OK to edit a node if you understand ALL of its (local) properties, and don't remove any of them OR if you understand ALL properties of ALL nodes in the path back to the root. The presentation of this material could be clarified by a table that relates constructions in the notation to their intended uses and meanings. We should check our characterset for disjointness with Interpress.DoubtfulChars. STANDARD CARD  WE ARE DESIGNING A STANDARD FOR INTERCHANGE, NOT EDITING.  GENSYM IS AN EDITOR, NOT AN INTERCHANGE, FUNCTION.  STANDARDIZE CONCEPTS, NOT NAMES. 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.  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. 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. Edited by Mitchell, 7 Aug. 1981 4:40 pm PDT (Friday) Fixed error in semantics when exchanging the use of {}s and ()s. Edited by Horning 13 Aug. 1981 4:47 pm PDT (Thursday). E(id) > locVal(id, E) --Remove conflict with f(E). Outer > "Outer" Const > "=" id lookup rule modified (R & T) [E | id_e, m] > [E | id m e] "." as infix op expressions are evaluated left-to-right (except for binding operator) Reverse VAL/ENV default for parens. bindq > bind binding > bindingMode expand definition of apply inline default T(E) = E add comments to semantic equations ------------------- R<>(E) = Nothing -- The empty expression -- Expression sequence R(E) = R(E) R(T(E)) -- List insert T(E) = T(T(E)) -- Composition R(E) = literal R(E) = if bindingOf(id, E)=None then id else R(E) T(E) = if bindingOf(id, E)=None then E else T(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<"NOT" p>(E) = if R

(E) then False else True R(E) = op = "." => R([R(E) | "Outer" = E]) op = "+" => R(E)+R(E) . . . R(E) = Nothing -- Empty list T(E) = bind(n, m, R(E), E) T(E) = bind(n, m, e, E) T(E) = bind(n, m, R(E), E) R<"{" labels e* "}">(E) = "{" labels R([Null | "Outer" = E]) "}" T<"{" labels e* "}">(E) = locVal("Outer", (T<"ENV("Sub e*")">(E))) R<"(" e* ")">(E) = R(E) R<"ENV(" e* ")">(E) = [T<"ENV(" e* ")">(E) | "Outer" = Null] T<"ENV(" e* ")">(E) = T([Null | "Outer" = E]) ------------------- Edited by Jim Horning 17 Aug. 1981 10:49 am PDT (Monday) R&T<> Nothing > "" Edited by Jim H. on 17 Aug. 1981 4:58 pm PDT (Monday) Remove side-effects from all expressions. Parentheses purely for grouping (don't hide environment transformations). #label > label ! labels within nodes Edited by Jim H. on 19 Aug. 1981 9:52 am PDT (Wednesday). Rewrite as syntactic sugar. structured labels re-introduce apply function in R&T correct syntax for "." % for opening an environment (also replaces ENV?) Edited by Jim H. on 19 Aug. 1981 6:55 pm PDT (Wednesday). Drop "%"; ENV() is now the only environment-constructing operator. Add SUB operator (first operand: sequence only, second: number only). Add atoms, as distinct from ids. Fix lhs op rhs syntax. *start* 11654 00024 USt Date: 21 Aug. 1981 6:58 pm PDT (Friday) From: Horning.pa Subject: Current Level 0/1 Interdoc status/rev. 23 To: Mitchell, Horning, Lampson Edited by Jim H. on 21 Aug. 1981 6:58 pm PDT (Friday). restore $val. move quoting to rhs, allow quoted primaries without parentheses. allow an op to be the rhs of a definition. eliminate the functions operate, apply, eval by back substitution. change semantics of () to allow "record" construction without $env. ------------------- Not done: State the formal semantics of labels and properties. Sets of properties, etc. (Cf. Mitchell's Font example.) Sort out "records" vs. quoted bindings. ------------------- We envision an Interdoc script being input and viewed in any manner equivalent to the following: Parse the script, alternately - reducing each expression to its "dominant structure," containing only literals, by replacing identifiers by the values to which they are bound in the current environment, by applying operators, and by removing binding items, and - transforming the environment as indicated by the binding items. BASIC INTERDOC GRAMMAR item ::= primary | binding primary ::= id | primary "." id | literal | application | property | node id ::= letter ( letter | digit )* literal ::= Boolean | integer | hexint | real | string | label | external label ::= name "!" name ::= id ( "." id)* external ::= "$" name | op op ::= "+" | "" | "*" | "/" application ::= primary "(" item* ( "," item* )* ")" property ::= primary "#" node ::= "{" item* "}" binding ::= name [ op ] bindingMode rhs | id ":!" bindingMode ::= "=" | ":" | ":=" | "_" rhs ::= [ "'" ] ( primary | "(" item* ")" ) SYNTACTIC EXAMPLE: {Book.example! -- Places this in Book and Book.example ExampleParagraph -- Invokes a definition $UniqueMark12356# -- Adds a nonstandard property a:='NOT(EQ(margins.left, 120)) margins.right_100 r=*(12.5, pt) IF(a, margins.left+_5 margins.right_5, margins.left+_10) } SEMANTICS R denotes the expression reduction function: R: expression > ( environment > expression ) T denotes the environment transformation function: T: expression > ( environment > environment ) R&T(E) denotes the pair R(E); T(E) R&T: ( expression, environment ) > ( expression, environment ) Environments bind identifiers to expressions, in various modes ("=", ":", ":=", "_"): Null denotes the "empty" environment [E | id m e] means "E with id mode m bound to e" locBinding(id, E) denotes the binding mode of id in E locBinding(id, Null) = None locBinding(id, [E | id' m e]) = if id=id' then m else locBinding(id, E) locVal(id, E) denotes the value locally bound to id in E locVal(id, Null) = Nil = "" locVal(id, [E | id' m e]) = if id=id' then e else locVal(id, E) R&T(E) = R&T(E) R&T

(E) = R&T(E))>(E) R&T(E) = literal; E R&T

(E) = CASE R

(E) OF $if => if R(E) then R&T(E) else R&T(E) "+" => R(E) + ... + R(E); E ... $val => R(E); E $list => R&T(E) $sub => R&T(E)[R(E)] -- Subscript, arg1: sequence | node, arg2.R: int $hide => ""; E R&T

(E) = R

(E) "#"; E R&T<"{" item* "}">(E) = "{" R<"Sub" item*>([Null | "Outer" = E]) "}"; locVal("Outer", (T<"Sub" item*>([Null | "Outer" = E]))) R&T<>(E) = ""; E R&T(E) = R(E) R(T(E)); T(T(E)) R&T(E) = ""; bind(n, m, R(E), E) = -- Syntactic sugar = R&T<"'" p>(E) = p; E R&T<"(" item* ")">(E) = [T([Null | "Outer" = E]) | "Outer" = Null]; E -- Construct a "record" environment value R&T<"'(" item* ")">(E) = item*; E R&T(E) = ??; E bindingOf(id, E) = locBinding(id, whereBound(id, E)) -- Gets innermost binding valOf(id, E) = locVal(id, whereBound(id, E)) -- Gets innermost value whereBound(id, E) = -- Finds innermost binding locBinding(id, E) ~= None => E locBinding("Outer", E) ~= None => whereBound(id, locVal("Outer", E)) True => Null bind(id, m, val, E) = bindingOf(id, E) = "=" => E -- Can't rebind constants m = ":=" => assign(id, val, E) -- Assign at right level True => [E | id m val] bind(id "." n, m, val, E) = [E | id bindingOf(id, E) bind(n, m, val, R(E))] assign(id, val, E) = locBinding(id, E) = ":" => [E | id ":" val] bindingOf(id, E) = ":" => [E | "Outer" "=" bind(id, ":=", val, locVal("Outer", E))] True => E -- Can only assign to vars ------------------- Expressions in an Interdoc script may denote literal values: Booleans: (F, T) integers: ... -3, -2, -1, 0, 1, 2, 3, ... reals: 1.2E5, . . . strings: labels: A123!, anId!, Paragraph.Example! external names: $name the empty environment: Null the empty list: NIL sequences of values unevaluated expressions environments sets (sequences) of nodes with given labels 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 bind(id, ":=", val, 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 locVal("Outer"). The (implicit) "outermost" environment binds each id to the external name $id. The contents of each node are implicitly prefixed by Sub, which will generally be bound in the containing environment to a quoted expression performing an environment transformation, and perhaps supplying some properties. Parentheses are used for grouping (e.g., creating a sequence value for a binding), and to delimit the argument list of an operator. The operator $ENV is used to create a new environment, which behaves much like a record. Semantics of labels: A label name! on a node gives that node membership in the sets identified by name (and its prefixes); the "main" identifier of a set name must be declared at the root of a subtree containing all its members. 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. OTHER NOTES It should be clarified that the "view" of the dominant structure is ALWAYS controlled by the properties of its nodes. (E.g., text is not always there to be "shown".) Conservative rules for editor treatment of script subtrees created by other editors: -It's OK to display a node if you understand at least one of its properties. -It's OK to edit a node if you understand ALL of its (local) properties, and don't remove any of them OR if you understand ALL properties of ALL nodes in the path back to the root. The presentation of this material could be clarified by a table that relates constructions in the notation to their intended uses and meanings. We should check our characterset for disjointness with Interpress.DoubtfulChars. STANDARD CARD  WE ARE DESIGNING A STANDARD FOR INTERCHANGE, NOT EDITING.  GENSYM IS AN EDITOR, NOT AN INTERCHANGE, FUNCTION.  STANDARDIZE CONCEPTS, NOT NAMES. 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.  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. 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. Edited by Mitchell, 7 Aug. 1981 4:40 pm PDT (Friday) Fixed error in semantics when exchanging the use of {}s and ()s. Edited by Horning 13 Aug. 1981 4:47 pm PDT (Thursday). E(id) > locVal(id, E) --Remove conflict with f(E). Outer > "Outer" Const > "=" id lookup rule modified (R & T) [E | id_e, m] > [E | id m e] "." as infix op expressions are evaluated left-to-right (except for binding operator) Reverse VAL/ENV default for parens. bindq > bind binding > bindingMode expand definition of apply inline default T(E) = E add comments to semantic equations ------------------- R<>(E) = Nothing -- The empty expression -- Expression sequence R(E) = R(E) R(T(E)) -- List insert T(E) = T(T(E)) -- Composition R(E) = literal R(E) = if bindingOf(id, E)=None then id else R(E) T(E) = if bindingOf(id, E)=None then E else T(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<"NOT" p>(E) = if R

(E) then False else True R(E) = op = "." => R([R(E) | "Outer" = E]) op = "+" => R(E)+R(E) . . . R(E) = Nothing -- Empty list T(E) = bind(n, m, R(E), E) T(E) = bind(n, m, e, E) T(E) = bind(n, m, R(E), E) R<"{" labels e* "}">(E) = "{" labels R([Null | "Outer" = E]) "}" T<"{" labels e* "}">(E) = locVal("Outer", (T<"ENV("Sub e*")">(E))) R<"(" e* ")">(E) = R(E) R<"ENV(" e* ")">(E) = [T<"ENV(" e* ")">(E) | "Outer" = Null] T<"ENV(" e* ")">(E) = T([Null | "Outer" = E]) ------------------- Edited by Jim Horning 17 Aug. 1981 10:49 am PDT (Monday) R&T<> Nothing > "" Edited by Jim H. on 17 Aug. 1981 4:58 pm PDT (Monday) Remove side-effects from all expressions. Parentheses purely for grouping (don't hide environment transformations). #label > label ! labels within nodes Edited by Jim H. on 19 Aug. 1981 9:52 am PDT (Wednesday). Rewrite as syntactic sugar. structured labels re-introduce apply function in R&T correct syntax for "." % for opening an environment (also replaces ENV?) Edited by Jim H. on 19 Aug. 1981 6:55 pm PDT (Wednesday). Drop "%"; ENV() is now the only environment-constructing operator. Add SUB operator (first operand: sequence only, second: number only). Add atoms, as distinct from ids. Fix lhs op rhs syntax. Edited by Jim H. on 20 Aug. 1981 5:29 pm PDT (Thursday). resolve pending questions as per message of 20 Aug. 1981 12:29 pm PDT. distinguish syntactically between properties (marks) and labels. only the "main" id of a label is declarable. eliminate  as an id character. eliminate op ids from grammar. restructure the grammar for "functional" notation for operators. update semantic equations for new grammar, etc. fix treatment of unbound qualified names (now produce Nil). *start* 12386 00024 USt Date: 24 Aug. 1981 6:42 pm PDT (Monday) From: Horning.pa Subject: Current Level 0/1 Interdoc status/rev. 24 To: Mitchell, Horning Edited by Jim H. on 24 Aug. 1981 6:08 pm PDT (Monday). "It's OK to edit a node if you understand ALL of its (local) properties, and either don't remove any of them or also understand ALL properties of its parent." "Put in contents if: Put in environment if: ..." Add connection syntax to syntactically rule out a+_'b. ------------------- Not done: Determine the (informal) semantics of labels. State the formal semantics of labels and properties. Sets of properties, etc. (Cf. Mitchell's Font example.) SET/LIST operators ($append $union ?) notation for list constants Sort out "records" vs. quoted bindings. Some syntactic marker to replace $env. Consider style for use of temporary local definitions. ------------------- We envision an Interdoc script being input and viewed in any manner equivalent to the following: Parse the script, alternately - reducing each expression to its "dominant structure," containing only literals, by replacing identifiers by the values to which they are bound in the current environment, by applying operators, and by removing binding items, and - transforming the environment as indicated by the binding items. BASIC INTERDOC GRAMMAR item ::= primary | binding primary ::= id | primary "." id | literal | application | property | node id ::= letter ( letter | digit )* literal ::= Boolean | integer | hexint | real | string | label | external label ::= name "!" name ::= id ( "." id)* external ::= "$" name | op op ::= "+" | "" | "*" | "/" application ::= primary "(" item* ( "," item* )* ")" property ::= primary "#" node ::= "{" item* "}" binding ::= name connection rhs | id ":!" connection ::= bindingMode | op bindingMode | bindingMode "'" bindingMode ::= "=" | ":" | ":=" | "_" rhs ::= primary | "(" item* ")" SYNTACTIC EXAMPLE: {Book.example! -- Places this in Book and Book.example ExampleParagraph -- Invokes a definition $UniqueMark12356# -- Adds a property a:='NOT(EQ(margins.left, 120)) margins.right_100 r=*(12.5, pt) IF(a, margins.left+_5 margins.right_5, margins.left+_10) } SEMANTICS R denotes the expression reduction function: R: expression > ( environment > expression ) T denotes the environment transformation function: T: expression > ( environment > environment ) R&T(E) denotes the pair R(E); T(E) R&T: ( expression, environment ) > ( expression, environment ) Environments bind identifiers to expressions, in various modes ("=", ":", ":=", "_"): Null denotes the "empty" environment [E | id m e] means "E with id mode m bound to e" locBinding(id, E) denotes the binding mode of id in E locBinding(id, Null) = None locBinding(id, [E | id' m e]) = if id=id' then m else locBinding(id, E) locVal(id, E) denotes the value locally bound to id in E locVal(id, Null) = Nil = "" locVal(id, [E | id' m e]) = if id=id' then e else locVal(id, E) R&T(E) = R&T(E) R&T

(E) = R&T(E))>(E) R&T(E) = literal; E R&T

(E) = CASE R

(E) OF $if => if R(E) then R&T(E) else R&T(E) "+" => R(E) + ... + R(E); E ... $val => R(E); E $list => R&T(E) $sub => R&T(E)[R(E)] -- Subscript, arg1: sequence | node, arg2.R: int $hide => ""; E R&T

(E) = R

(E) "#"; E R&T<"{" item* "}">(E) = "{" R<"Sub" item*>([Null | "Outer" = E]) "}"; locVal("Outer", (T<"Sub" item*>([Null | "Outer" = E]))) R&T<>(E) = ""; E R&T(E) = R(E) R(T(E)); T(T(E)) R&T(E) = ""; bind(n, m, R(E), E) = -- Syntactic sugar = R&T<"'" p>(E) = p; E R&T<"(" item* ")">(E) = [T([Null | "Outer" = E]) | "Outer" = Null]; E -- Construct a "record" environment value R&T<"'(" item* ")">(E) = item*; E R&T(E) = ??; E bindingOf(id, E) = locBinding(id, whereBound(id, E)) -- Gets innermost binding valOf(id, E) = locVal(id, whereBound(id, E)) -- Gets innermost value whereBound(id, E) = -- Finds innermost binding locBinding(id, E) ~= None => E locBinding("Outer", E) ~= None => whereBound(id, locVal("Outer", E)) True => Null bind(id, m, val, E) = bindingOf(id, E) = "=" => E -- Can't rebind constants m = ":=" => assign(id, val, E) -- Assign at right level True => [E | id m val] bind(id "." n, m, val, E) = [E | id bindingOf(id, E) bind(n, m, val, R(E))] assign(id, val, E) = locBinding(id, E) = ":" => [E | id ":" val] bindingOf(id, E) = ":" => [E | "Outer" "=" bind(id, ":=", val, locVal("Outer", E))] True => E -- Can only assign to vars ------------------- Expressions in an Interdoc script may denote literal values: Booleans: (F, T) integers: ... -3, -2, -1, 0, 1, 2, 3, ... reals: 1.2E5, . . . strings: labels: A123!, anId!, Paragraph.Example! external names: $name the empty environment: Null the empty list: NIL sequences of values unevaluated expressions environments sets (sequences) of nodes with given labels 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 bind(id, ":=", val, 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 locVal("Outer"). The (implicit) "outermost" environment binds each id to the external name $id. The contents of each node are implicitly prefixed by Sub, which will generally be bound in the containing environment to a quoted expression performing an environment transformation, and perhaps supplying some properties. Parentheses are used for grouping (e.g., creating a sequence value for a binding), and to delimit the argument list of an operator. The operator $ENV is used to create a new environment, which behaves much like a record. Semantics of labels: A label name! on a node gives that node membership in the sets identified by name (and its prefixes); the "main" identifier of a set name must be declared at the root of a subtree containing all its members. 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. OTHER NOTES It should be clarified that the "view" of the dominant structure is ALWAYS controlled by the properties of its nodes. (E.g., text is not always there to be "shown".) Conservative rules for editor treatment of script subtrees created by other editors: -It's OK to display a node if you understand at least one of its properties. -It's OK to edit a node if you understand ALL of its (local) properties, and either don't remove any of them or also understand ALL properties of its parent. The presentation of this material could be clarified by a table that relates constructions in the notation to their intended uses and meanings. We should check our characterset for disjointness with Interpress.DoubtfulChars. Put in contents if: Put in environment if: effect is local to node has scope is directly edited is only indirectly edited is to be bound locally needs delayed or global binding STANDARD CARD  WE ARE DESIGNING A STANDARD FOR INTERCHANGE, NOT EDITING.  GENSYM IS AN EDITOR, NOT AN INTERCHANGE, FUNCTION.  STANDARDIZE CONCEPTS, NOT NAMES. 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.  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. 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. Edited by Mitchell, 7 Aug. 1981 4:40 pm PDT (Friday) Fixed error in semantics when exchanging the use of {}s and ()s. Edited by Horning 13 Aug. 1981 4:47 pm PDT (Thursday). E(id) > locVal(id, E) --Remove conflict with f(E). Outer > "Outer" Const > "=" id lookup rule modified (R & T) [E | id_e, m] > [E | id m e] "." as infix op expressions are evaluated left-to-right (except for binding operator) Reverse VAL/ENV default for parens. bindq > bind binding > bindingMode expand definition of apply inline default T(E) = E add comments to semantic equations ------------------- R<>(E) = Nothing -- The empty expression -- Expression sequence R(E) = R(E) R(T(E)) -- List insert T(E) = T(T(E)) -- Composition R(E) = literal R(E) = if bindingOf(id, E)=None then id else R(E) T(E) = if bindingOf(id, E)=None then E else T(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<"NOT" p>(E) = if R

(E) then False else True R(E) = op = "." => R([R(E) | "Outer" = E]) op = "+" => R(E)+R(E) . . . R(E) = Nothing -- Empty list T(E) = bind(n, m, R(E), E) T(E) = bind(n, m, e, E) T(E) = bind(n, m, R(E), E) R<"{" labels e* "}">(E) = "{" labels R([Null | "Outer" = E]) "}" T<"{" labels e* "}">(E) = locVal("Outer", (T<"ENV("Sub e*")">(E))) R<"(" e* ")">(E) = R(E) R<"ENV(" e* ")">(E) = [T<"ENV(" e* ")">(E) | "Outer" = Null] T<"ENV(" e* ")">(E) = T([Null | "Outer" = E]) ------------------- Edited by Jim Horning 17 Aug. 1981 10:49 am PDT (Monday) R&T<> Nothing > "" Edited by Jim H. on 17 Aug. 1981 4:58 pm PDT (Monday) Remove side-effects from all expressions. Parentheses purely for grouping (don't hide environment transformations). #label > label ! labels within nodes Edited by Jim H. on 19 Aug. 1981 9:52 am PDT (Wednesday). Rewrite as syntactic sugar. structured labels re-introduce apply function in R&T correct syntax for "." % for opening an environment (also replaces ENV?) Edited by Jim H. on 19 Aug. 1981 6:55 pm PDT (Wednesday). Drop "%"; ENV() is now the only environment-constructing operator. Add SUB operator (first operand: sequence only, second: number only). Add atoms, as distinct from ids. Fix lhs op rhs syntax. Edited by Jim H. on 20 Aug. 1981 5:29 pm PDT (Thursday). resolve pending questions as per message of 20 Aug. 1981 12:29 pm PDT. distinguish syntactically between properties (marks) and labels. only the "main" id of a label is declarable. eliminate  as an id character. eliminate op ids from grammar. restructure the grammar for "functional" notation for operators. update semantic equations for new grammar, etc. fix treatment of unbound qualified names (now produce Nil). Edited by Jim H. on 21 Aug. 1981 6:58 pm PDT (Friday). restore $val. move quoting to rhs, allow quoted primaries without parentheses. allow an op to be the rhs of a definition. eliminate the functions operate, apply, eval by back substitution. change semantics of () to allow "record" construction without $env. *start* 01734 00024 USt Date: 25 Aug. 1981 9:28 am PDT (Tuesday) From: Horning.pa Subject: Interdoc Label Thoughts To: Mitchell cc: Lampson, Horning Overnight, I've come to the conclusion that the reason we were having trouble yesterday with the semantics of labels is that we were trying to attach too much semantics to them--much as if we had gone beyond numbers to specify the use of numbers in spline curves. I propose that we go back to something much closer to Brian Reid's "link and mark" semantics. I.e., the "meaning" of a reference, mark pair is simply: "record the existence of a directed arc from here to there," without saying what an editor would use such arcs for. They are simply the escape mechanism from a strict tree structure. I believe that we should keep the present "sequence" semantics for multiple nodes marked with the same label (i.e., there is a directed arc from every reference to a label to each node marked with that label.) I also accept your stricture that no environment information should flow along these arcs, so that we can simply ignore them when determining the Reduced&Transformed values of scripts and environments. We should continue to declare the scope of main labels, for all the previously discussed reasons, but we should not try to use the environment to record label values (as (un)evaluated nodes or whatever). We should thus syntactically distinguish a label reference from a name invocation. Except for the syntactic ambiguity, it would be tempting to adopt some "symmetric" notation for references and marks, e.g., name> and >name . However, I don't doubt our ability to find a satisfactory syntax once we have agreed on the semantics. Comments, improvements? Jim H. *start* 13389 00024 USt Date: 25 Aug. 1981 11:34 am PDT (Tuesday) From: Horning.pa Subject: Current Level 0/1 Interdoc status/rev. 25 To: Mitchell, Horning Edited by Jim H. on 25 Aug. 1981 11:33 am PDT (Tuesday). Syntactically separate label references and name invocation. Put in distinct syntax in rhs for environment construction. Informal semantics of labels. ( ... ) > [ ... ] in applications; permitting ( ... ) as a primary. ------------------- Open questions: Use of ( ... ) vs. [ ... ] (especially in application). Sort out "records" vs. quoted bindings. Sets of properties, etc. (Cf. Mitchell's Font example.) SET/LIST operators ($append $union ?) semantics of $list Non-uniform semantics of quote. Subtle distinctions between quoted and unquoted ( ... ) Semantics of quoted [ ... ] ? We should check our characterset for disjointness with Interpress.DoubtfulChars. Not done: State the formal semantics of labels and properties. Consider style for use of temporary local definitions. ------------------- We envision an Interdoc script being input and viewed in any manner equivalent to the following: Parse the script, repeatedly - reducing each expression to its "dominant structure," containing only literals, by replacing identifiers by the values to which they are bound in the current environment, by applying operators, and by removing binding items, - transforming the environment as indicated by the binding items, and - recording the links indicated by label references and marks. BASIC INTERDOC SYNTACTIC EXAMPLE: {Book.example! -- Links to this from Book@ and Book.example@ ExampleParagraph -- Invokes a definition $UniqueMark12356# -- Adds a property a:='NOT[EQ[margins.left, 120]] margins.right_100 r=*[12.5, pt] IF[a, margins.left+_5 margins.right_5, margins.left+_10] } GRAMMAR item ::= primary | binding | label primary ::= literal | invocation | application | property | node | "(" item* ")" literal ::= Boolean | integer | hexint | real | string | external | op external ::= "$" name name ::= id ( "." id)* id ::= letter ( letter | digit )* op ::= "+" | "" | "*" | "/" invocation ::= id | primary "." id application ::= primary "[" item* ( "," item* )* "]" property ::= primary "#" node ::= "{" item* "}" binding ::= name connection rhs connection ::= bindingMode | op bindingMode | bindingMode "'" bindingMode ::= "=" | ":" | ":=" | "_" rhs ::= primary | "[" item* "]" label ::= id ":!" | name "!" | name "@" SEMANTICS R&T(E) = R&T(E) R&T

(E) = R&T(E))>(E) R&T(E) = literal; E R&T

(E) = CASE R

(E) OF $if => if R(E) then R&T(E) else R&T(E) "+" => R(E) + ... + R(E); E ... $val => R(E); E $list => R&T(E) $subscript => R&T(E)[R(E)] -- arg1: sequence | node, arg2.R: int $hide => "" ; E R&T

(E) = R

(E) "#"; E R&T<"{" item* "}">(E) = "{" R<"Sub" item*>([Null | "Outer" = E]) "}"; locVal("Outer", (T<"Sub" item*>([Null | "Outer" = E]))) R&T<"(" item* ")">(E) = "(" R(E) ")" ; E -- List constructor R&T<"[" item* "]">(E) = [T([Null | "Outer" = E]) | "Outer" = Null]; E -- Construct a "record" environment value R&T<>(E) = ""; E R&T(E) = R(E) R(T(E)); T(T(E)) R&T(E) = "" ; bind(n, m, R(E), E) = -- Syntactic sugar = R&T<"'" p>(E) = p; E R&T<"'(" item* ")">(E) = item*; E ?? R&T<"'[" item* "]">(E) = ?? R&T

(E) then False else True R(E) = op = "." => R([R(E) | "Outer" = E]) op = "+" => R(E)+R(E) . . . R(E) = Nothing -- Empty list T(E) = bind(n, m, R(E), E) T(E) = bind(n, m, e, E) T(E) = bind(n, m, R(E), E) R<"{" labels e* "}">(E) = "{" labels R([Null | "Outer" = E]) "}" T<"{" labels e* "}">(E) = locVal("Outer", (T<"ENV("Sub e*")">(E))) R<"(" e* ")">(E) = R(E) R<"ENV(" e* ")">(E) = [T<"ENV(" e* ")">(E) | "Outer" = Null] T<"ENV(" e* ")">(E) = T([Null | "Outer" = E]) ------------------- Edited by Jim Horning 17 Aug. 1981 10:49 am PDT (Monday) R&T<> Nothing > "" Edited by Jim H. on 17 Aug. 1981 4:58 pm PDT (Monday) Remove side-effects from all expressions. Parentheses purely for grouping (don't hide environment transformations). #label > label ! labels within nodes Edited by Jim H. on 19 Aug. 1981 9:52 am PDT (Wednesday). Rewrite as syntactic sugar. structured labels re-introduce apply function in R&T correct syntax for "." % for opening an environment (also replaces ENV?) Edited by Jim H. on 19 Aug. 1981 6:55 pm PDT (Wednesday). Drop "%"; ENV() is now the only environment-constructing operator. Add SUB operator (first operand: sequence only, second: number only). Add atoms, as distinct from ids. Fix lhs op rhs syntax. Edited by Jim H. on 20 Aug. 1981 5:29 pm PDT (Thursday). resolve pending questions as per message of 20 Aug. 1981 12:29 pm PDT. distinguish syntactically between properties (marks) and labels. only the "main" id of a label is declarable. eliminate  as an id character. eliminate op ids from grammar. restructure the grammar for "functional" notation for operators. update semantic equations for new grammar, etc. fix treatment of unbound qualified names (now produce Nil). Edited by Jim H. on 21 Aug. 1981 6:58 pm PDT (Friday). restore $val. move quoting to rhs, allow quoted primaries without parentheses. allow an op to be the rhs of a definition. eliminate the functions operate, apply, eval by back substitution. change semantics of () to allow "record" construction without $env. Edited by Jim H. on 24 Aug. 1981 6:08 pm PDT (Monday). "It's OK to edit a node if you understand ALL of its (local) properties, and either don't remove any of them or also understand ALL properties of its parent." "Put in contents if: Put in environment if: ..." Add connection syntax to syntactically rule out a+_'b. *start* 15765 00024 USt Date: 27 Aug. 1981 7:51 pm PDT (Thursday) From: Horning.pa Subject: Current Level 0/1 Interdoc status/rev. 29 To: Mitchell, Horning Edited by Jim H. on 26 Aug. 1981 7:11 pm PDT (Wednesday). ' ... ' in rhs Restore infix operators, right to left. Modify syntax to rule out more nonsense, add semantically meaningful nonterminals. Introduce special syntax for selections. Eliminate side-effects for $subscript (actually, all applications). Add application of defined functions. Note that Value[ ... ] allows use of temporary (hidden) local definitions, Nil[ ... ] allows placement of hidden nodes. ( ... ) creates list/sequence values (without hiding bindings). Tidy up definition of assign, using bind("Outer." ...). Introduce value nonterminal into grammar (rule out more nonsense). rhs ::= ... | "[" [ lookup ] "|" binding* "]" . Remove $ name from literal (to lookup). Change nonterminal lookup to invocation. ------------------- Open questions: We should rethink our character assignments. check our characterset for disjointness with Interpress.DoubtfulChars. enlarge op with a few more single-character operators? %, &, \ Possible node operators (purely in semantic domain, not operators?). $properties: node, environment > sequence -- All #'s $marks: node, environment > sequence -- All !'s $references: node, environment > sequence -- All @'s $contents: node, environment > sequence -- The rest (fringe) Consider restricting $subscript just to sequences, not nodes. Extend selection to CASE? Not done: ------------------- We envision an Interdoc script being input and viewed in any manner equivalent to the following: Parse the script, repeatedly - reducing each expression to its "dominant structure," containing only literals, by replacing identifiers by the values to which they are bound in the current environment, by applying operators, and by removing binding items, - transforming the environment as indicated by the binding items (recording the components of each node's environment in a form convenient to the editor), and - recording the links indicated by label references and marks. BASIC INTERDOC SYNTACTIC EXAMPLE: {Book.example! -- Links to this from Book@ and Book.example@ ExampleParagraph -- Invokes a definition $UniqueMark12356# -- Adds a property Font_[Font | size_10*pt face_bold] a:='NOT[EQ[margins.left 120]]' margins.right_100 r=12.5*pt (a | margins.left_+5 margins.right_5 | margins.left+_10) -- conditional: Algol68 } GRAMMAR item ::= value | binding | property | label value ::= term | node | sequence term ::= primary | primary op term -- Ops apply right to left primary ::= literal | invocation | application | selection literal ::= Boolean | integer | hexint | real | string | op op ::= "+" | "" | "*" | "/" invocation ::= name | external name ::= id ( "." id )* id ::= letter ( letter | digit )* external ::= "$" name application ::= invocation "[" value* "]" selection ::= "(" term "|" item* "|" item* ")" -- Algol 68 style conditional node ::= "{" item* "}" sequence ::= "(" item* ")" binding ::= name bindingMode rhs bindingMode ::= "=" | ":" | ":=" | "_" rhs ::= value | op term | "'" item* "'" | "[" [ invocation ] "|" binding* "]" property ::= invocation "#" label ::= id ":!" | name "!" | name "@" SEMANTICS R: expression > environment > expression -- Reduction T: expression > environment > environment -- Transformation R&T(E) denotes the pair R(E); T(E) [Unless explicitly given below, T(E) = E.] R(E) = R(E) op R(E) R(E) = literal R&T(E) = R&T(E) R&T(E) = R&T(E))>(E) R<"$" name>(E) = "$" name R(E) = CASE R(E) OF "$equal" => R(E) = R(E) "$greater" => R(E) > R(E) . . . "$subscript" => R(E)[R(E)] -- value1: sequence | node, value2: int ELSE => R([E | "Value" "=" R(E)]) R&T<"(" term "|" item1* "|" item2* ")">(E) = if R(E) then R&T(E) else R&T(E) R&T<"{" item* "}">(E) = "{" R<"Sub" item*>([Null | "Outer" "=" E]) "}"; locVal("Outer", (T<"Sub" item*>([Null | "Outer" "=" E]))) R&T<"(" item* ")">(E) = "(" R(E) ")" ; T(E) R<>(E) = Nil R&T(E) = R(E) R(T(E)); T(T(E)) R&T(E) = Nil; bind(n, m, R(E), E) = -- Syntactic sugar R<"'" item* "'">(E) = item* --Usable only in rhs of binding R<"[" invocation "|" binding* "]">(E) = [T([R(E) | "Outer" "=" E]) | "Outer" "=" Null] R<"[|" binding* "]">(E) = [T([Null | "Outer" "=" E]) | "Outer" "=" Null] R(E) = R(E) "#" R

(E) then False else True R(E) = op = "." => R([R(E) | "Outer" = E]) op = "+" => R(E)+R(E) . . . R(E) = Nothing -- Empty list T(E) = bind(n, m, R(E), E) T(E) = bind(n, m, e, E) T(E) = bind(n, m, R(E), E) R<"{" labels e* "}">(E) = "{" labels R([Null | "Outer" = E]) "}" T<"{" labels e* "}">(E) = locVal("Outer", (T<"ENV("Sub e*")">(E))) R<"(" e* ")">(E) = R(E) R<"ENV(" e* ")">(E) = [T<"ENV(" e* ")">(E) | "Outer" = Null] T<"ENV(" e* ")">(E) = T([Null | "Outer" = E]) ------------------- Edited by Jim Horning 17 Aug. 1981 10:49 am PDT (Monday) R&T<> Nothing > "" Edited by Jim H. on 17 Aug. 1981 4:58 pm PDT (Monday) Remove side-effects from all expressions. Parentheses purely for grouping (don't hide environment transformations). #label > label ! labels within nodes Edited by Jim H. on 19 Aug. 1981 9:52 am PDT (Wednesday). Rewrite as syntactic sugar. structured labels re-introduce apply function in R&T correct syntax for "." % for opening an environment (also replaces ENV?) Edited by Jim H. on 19 Aug. 1981 6:55 pm PDT (Wednesday). Drop "%"; ENV() is now the only environment-constructing operator. Add SUB operator (first operand: sequence only, second: number only). Add atoms, as distinct from ids. Fix lhs op rhs syntax. Edited by Jim H. on 20 Aug. 1981 5:29 pm PDT (Thursday). resolve pending questions as per message of 20 Aug. 1981 12:29 pm PDT. distinguish syntactically between properties (marks) and labels. only the "main" id of a label is declarable. eliminate  as an id character. eliminate op ids from grammar. restructure the grammar for "functional" notation for operators. update semantic equations for new grammar, etc. fix treatment of unbound qualified names (now produce Nil). Edited by Jim H. on 21 Aug. 1981 6:58 pm PDT (Friday). restore $val. move quoting to rhs, allow quoted primaries without parentheses. allow an op to be the rhs of a definition. eliminate the functions operate, apply, eval by back substitution. change semantics of () to allow "record" construction without $env. Edited by Jim H. on 24 Aug. 1981 6:08 pm PDT (Monday). "It's OK to edit a node if you understand ALL of its (local) properties, and either don't remove any of them or also understand ALL properties of its parent." "Put in contents if: Put in environment if: ..." Add connection syntax to syntactically rule out a+_'b. Edited by Jim H. on 25 Aug. 1981 11:33 am PDT (Tuesday). Syntactically separate label references and name invocation. Put in distinct syntax in rhs for environment construction. Informal semantics of labels. ( ... ) > [ ... ] in applications; permitting ( ... ) as a primary. Edited by Jim H. on 25 Aug. 1981 4:08 pm PDT (Tuesday). Add sequence as a nonterminal to the syntax. State the formal semantics of labels and properties. Reorder presentation (hopefully to improve readability). *start* 15962 00024 USt Date: 28 Aug. 1981 2:09 pm PDT (Friday) From: Horning.pa Subject: Current Level 0/1 Interdoc status/rev. 30 To: Mitchell, Horning, Guttag Edited by Jim H. on 28 Aug. 1981 2:08 pm PDT (Friday). [Changes since 25 August] ' ... ' in rhs Restore infix operators, right to left. Modify syntax to rule out more nonsense, add semantically meaningful nonterminals. Introduce special syntax for selections. Eliminate side-effects for $subscript (actually, all applications). Add application of defined functions. Note that Value[ ... ] allows use of temporary (hidden) local definitions, Nil[ ... ] allows placement of hidden nodes. ( ... ) creates list/sequence values (without hiding bindings). Tidy up definition of assign, using bind("Outer." ...). Introduce value nonterminal into grammar (rule out more nonsense). rhs ::= ... | "[" [ lookup ] "|" binding* "]" . Change nonterminal lookup to invocation. Remove $ name from literal (to invocation). Add node operators: $properties -- All #'s $marks -- All !'s $references -- All @'s $contents -- The rest (fringe) Restrict $subscript just to sequences, not nodes. ------------------- Open questions: We should rethink our character assignments. check our characterset for disjointness with Interpress.DoubtfulChars. enlarge op with a few more single-character operators? %, &, \ Possible node operators (purely in semantic domain, not operators?). Extend selection to CASE? Not done: ------------------- We envision an Interdoc script being input and viewed in any manner equivalent to the following: Parse the script, repeatedly - reducing each expression to its "dominant structure," containing only literals, by replacing identifiers by the values to which they are bound in the current environment, by applying operators, and by removing binding items, - transforming the environment as indicated by the binding items (recording the components of each node's environment in a form convenient to the editor), and - recording the links indicated by label references and marks. BASIC INTERDOC SYNTACTIC EXAMPLE: {Book.example! -- Links to this from Book@ and Book.example@ ExampleParagraph -- Invokes a definition $UniqueMark12356# -- Adds a property Font_[Font | size_10*pt face_bold] factorial_'(LT[Value 2] | 1 | Value* factorial(Value-1))' a:='NOT[EQ[margins.left factorial[5]]]' margins.right_100 r=12.5*pt (a | margins.left_+5 margins.right_5 | margins.left+_10) -- conditional: Algol68 } GRAMMAR item ::= value | binding | property | label value ::= term | node | sequence term ::= primary | primary op term -- Ops apply right to left primary ::= literal | invocation | application | selection literal ::= Boolean | integer | hexint | real | string | op op ::= "+" | "" | "*" | "/" invocation ::= name | external name ::= id ( "." id )* id ::= letter ( letter | digit )* external ::= "$" name application ::= invocation "[" value* "]" selection ::= "(" term "|" item* "|" item* ")" -- Algol 68 style conditional node ::= "{" item* "}" sequence ::= "(" item* ")" binding ::= name bindingMode rhs bindingMode ::= "=" | ":" | ":=" | "_" rhs ::= value | op term | "'" item* "'" | "[" [ invocation ] "|" binding* "]" property ::= invocation "#" label ::= id ":!" | name "!" | name "@" SEMANTICS R: expression > environment > expression -- Reduction T: expression > environment > environment -- Transformation R&T(E) denotes the pair R(E); T(E) [Unless explicitly given below, T(E) = E.] R(E) = R(E) op R(E) R(E) = literal R&T(E) = R&T(E) R&T(E) = R&T(E))>(E) R<"$" name>(E) = "$" name R(E) = apply(invocation, R(E), E) apply(invocation, value*, E) = CASE R(E) OF "$equal" => value1 = value2 "$greater" => value1 > value2 . . . "$subscript" => value1[value2] -- value1: sequence, value2: int "$contents" => C "$properties" => P(E) "$marks" => M(E) "$references" => U(E) ELSE => R([E | "Value" "=" value*]) R&T<"(" term "|" item1* "|" item2* ")">(E) = if R(E) then R&T(E) else R&T(E) R&T<"{" item* "}">(E) = "{" R<"Sub" item*>([Null | "Outer" "=" E]) "}"; locVal("Outer", (T<"Sub" item*>([Null | "Outer" "=" E]))) R&T<"(" item* ")">(E) = "(" R(E) ")" ; T(E) R<>(E) = Nil R&T(E) = R(E) R(T(E)); T(T(E)) R&T(E) = Nil; bind(n, m, R(E), E) = -- Syntactic sugar R<"'" item* "'">(E) = item* --Usable only in rhs of binding R<"[" invocation "|" binding* "]">(E) = [T([R(E) | "Outer" "=" E]) | "Outer" "=" Null] R<"[|" binding* "]">(E) = [T([Null | "Outer" "=" E]) | "Outer" "=" Null] R(E) = R(E) "#" R

(E) then False else True R(E) = op = "." => R([R(E) | "Outer" = E]) op = "+" => R(E)+R(E) . . . R(E) = Nothing -- Empty list T(E) = bind(n, m, R(E), E) T(E) = bind(n, m, e, E) T(E) = bind(n, m, R(E), E) R<"{" labels e* "}">(E) = "{" labels R([Null | "Outer" = E]) "}" T<"{" labels e* "}">(E) = locVal("Outer", (T<"ENV("Sub e*")">(E))) R<"(" e* ")">(E) = R(E) R<"ENV(" e* ")">(E) = [T<"ENV(" e* ")">(E) | "Outer" = Null] T<"ENV(" e* ")">(E) = T([Null | "Outer" = E]) ------------------- Edited by Jim Horning 17 Aug. 1981 10:49 am PDT (Monday) R&T<> Nothing > "" Edited by Jim H. on 17 Aug. 1981 4:58 pm PDT (Monday) Remove side-effects from all expressions. Parentheses purely for grouping (don't hide environment transformations). #label > label ! labels within nodes Edited by Jim H. on 19 Aug. 1981 9:52 am PDT (Wednesday). Rewrite as syntactic sugar. structured labels re-introduce apply function in R&T correct syntax for "." % for opening an environment (also replaces ENV?) Edited by Jim H. on 19 Aug. 1981 6:55 pm PDT (Wednesday). Drop "%"; ENV() is now the only environment-constructing operator. Add SUB operator (first operand: sequence only, second: number only). Add atoms, as distinct from ids. Fix lhs op rhs syntax. Edited by Jim H. on 20 Aug. 1981 5:29 pm PDT (Thursday). resolve pending questions as per message of 20 Aug. 1981 12:29 pm PDT. distinguish syntactically between properties (marks) and labels. only the "main" id of a label is declarable. eliminate  as an id character. eliminate op ids from grammar. restructure the grammar for "functional" notation for operators. update semantic equations for new grammar, etc. fix treatment of unbound qualified names (now produce Nil). Edited by Jim H. on 21 Aug. 1981 6:58 pm PDT (Friday). restore $val. move quoting to rhs, allow quoted primaries without parentheses. allow an op to be the rhs of a definition. eliminate the functions operate, apply, eval by back substitution. change semantics of () to allow "record" construction without $env. Edited by Jim H. on 24 Aug. 1981 6:08 pm PDT (Monday). "It's OK to edit a node if you understand ALL of its (local) properties, and either don't remove any of them or also understand ALL properties of its parent." "Put in contents if: Put in environment if: ..." Add connection syntax to syntactically rule out a+_'b. Edited by Jim H. on 25 Aug. 1981 11:33 am PDT (Tuesday). Syntactically separate label references and name invocation. Put in distinct syntax in rhs for environment construction. Informal semantics of labels. ( ... ) > [ ... ] in applications; permitting ( ... ) as a primary. Edited by Jim H. on 25 Aug. 1981 4:08 pm PDT (Tuesday). Add sequence as a nonterminal to the syntax. State the formal semantics of labels and properties. Reorder presentation (hopefully to improve readability). *start* 14892 00024 USt Date: 25 Aug. 1981 4:08 pm PDT (Tuesday) From: Horning.pa Subject: Current Level 0/1 Interdoc status/rev. 26 To: Mitchell, Horning Edited by Jim H. on 25 Aug. 1981 4:08 pm PDT (Tuesday). Add sequence as a nonterminal to the syntax. State the formal semantics of labels and properties. Reorder presentation (hopefully to improve readability). ------------------- Open questions: Use of ( ... ) vs. [ ... ] (especially in application). Sort out "records" vs. quoted bindings. Sets of properties, etc. (Cf. Mitchell's Font example.) SET/LIST operators ($append $union ?) semantics of $list Non-uniform semantics of quote. Subtle distinctions between quoted and unquoted ( ... ) Semantics of quoted [ ... ] ? We should rethink our character assignments. check our characterset for disjointness with Interpress.DoubtfulChars. use of various bracket pairs. enlarge op with a few more single-character operators? Possible node operators (purely in semantic domain, not operators?). $properties: node, environment > sequence -- All #'s $marks: node, environment > sequence -- All !'s $references: node, environment > sequence -- All @'s $contents: node, environment > sequence -- The rest (fringe) Consider restricting $subscript just to sequences, not nodes. Note that $if is the only operator that requires multiple sequences (hence commas, different syntax for argument list and sequence). Worth going back to treating it as a special case? Not done: Consider style for use of temporary local definitions. ------------------- We envision an Interdoc script being input and viewed in any manner equivalent to the following: Parse the script, repeatedly - reducing each expression to its "dominant structure," containing only literals, by replacing identifiers by the values to which they are bound in the current environment, by applying operators, and by removing binding items, - transforming the environment as indicated by the binding items, and - recording the links indicated by label references and marks. BASIC INTERDOC SYNTACTIC EXAMPLE: {Book.example! -- Links to this from Book@ and Book.example@ ExampleParagraph -- Invokes a definition $UniqueMark12356# -- Adds a property a:='NOT[EQ[margins.left, 120]] margins.right_100 r=*[12.5, pt] IF[a, margins.left+_5 margins.right_5, margins.left+_10] } GRAMMAR item ::= primary | binding | label primary ::= literal | invocation | application | property | node | sequence literal ::= Boolean | integer | hexint | real | string | external | op external ::= "$" name name ::= id ( "." id)* id ::= letter ( letter | digit )* op ::= "+" | "" | "*" | "/" invocation ::= id | primary "." id application ::= primary "[" item* ( "," item* )* "]" property ::= primary "#" node ::= "{" item* "}" sequence ::= "(" item* ")" binding ::= name connection rhs connection ::= bindingMode | op bindingMode | bindingMode "'" bindingMode ::= "=" | ":" | ":=" | "_" rhs ::= primary | "[" item* "]" label ::= id ":!" | name "!" | name "@" SEMANTICS R: expression > environment > expression -- Reduction T: expression > environment > environment -- Transformation R&T(E) denotes the pair R(E); T(E) R&T(E) = literal; E R&T(E) = R&T(E) R&T

(E) = R&T(E))>(E) R&T

(E) = CASE R

(E) OF $if => if R(E) then R&T(E) else R&T(E) "+" => R(E) + ... + R(E); E ... $val => R(E); E $list => R&T(E) $subscript => R&T(E)[R(E)] -- arg1: sequence | node, arg2.R: int $hide => "" ; E R&T

(E) = R

(E) "#"; E R&T<"{" item* "}">(E) = "{" R<"Sub" item*>([Null | "Outer" = E]) "}"; locVal("Outer", (T<"Sub" item*>([Null | "Outer" = E]))) R&T<"(" item* ")">(E) = "(" R(E) ")" ; E -- List constructor R&T<"[" item* "]">(E) = [T([Null | "Outer" = E]) | "Outer" = Null]; E -- Construct a "record" environment value R&T<>(E) = ""; E R&T(E) = R(E) R(T(E)); T(T(E)) R&T(E) = "" ; bind(n, m, R(E), E) = -- Syntactic sugar = ?? R&T<"'" p>(E) = p; E R&T<"'(" item* ")">(E) = item*; E ?? R&T<"'[" item* "]">(E) = ?? R&T

(E) = R

(E) M(E) = prefixes(name) U(E) = prefixes(name) P&M&U(E) = P&M&U(E)>(E) P&M&U<"(" item* ")">(E) = P&M&U(E) P&M&U(E) = P(E) P(T(E)); M(E) M(T(E)); U(E) U(T(E)) prefixes(id) = id prefixes(name "." id) = name "." id prefixes(name) NOTATION FOR ENVIRONMENTS Environments bind identifiers to expressions, in various modes ("=", ":", ":=", "_"): Null denotes the "empty" environment [E | id m e] means "E with id mode m bound to e" locBinding(id, E) denotes the binding mode of id in E locBinding(id, Null) = None locBinding(id, [E | id' m e]) = if id=id' then m else locBinding(id, E) locVal(id, E) denotes the value locally bound to id in E locVal(id, Null) = Nil = "" locVal(id, [E | id' m e]) = if id=id' then e else locVal(id, E) VALUE SPACE Expressions in an Interdoc script may denote literal values: Booleans: (F, T) integers: ... -3, -2, -1, 0, 1, 2, 3, ... reals: 1.2E5, . . . strings: labels: A123!, anId!, Paragraph.Example! external names: $name the empty environment: Null the empty list: NIL sequences of values unevaluated expressions environments DISCUSSION 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 bind(id, ":=", val, 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 locVal("Outer"). The (implicit) "outermost" environment binds each id to the external name $id. Nodes are delimited by brackets. The contents of each node are implicitly prefixed by Sub, which will generally be bound in the containing environment to a quoted expression performing an environment transformation, and perhaps supplying some properties and marks. Parentheses are used to denote a sequence value. to delimit the argument list of an operator. Square brackets are used to denote a new environment value, which behaves much like a record. Semantics of labels: A mark name! on a node makes that node a "target" of the label name (and its prefixes); a reference name@ makes it a "source." The "main" identifier of a label must be declared (using name:!) at the root of a subtree containing all its sources and targets. The label represents a set of directed arcs, one from each of its sources to each of its destinations. Multiple marks make the node a target of in multiple labels. A unique label on a node places it in a singleton set, i.e., identifies it uniquely. OTHER NOTES It should be clarified that the "view" of the dominant structure is ALWAYS controlled by the properties of its nodes. (E.g., text is not always there to be "shown".) Conservative rules for editor treatment of script subtrees created by other editors: -It's OK to display a node if you understand at least one of its properties. -It's OK to edit a node if you understand ALL of its (local) properties, and either don't remove any of them or also understand ALL properties of its parent. -It's OK to copy a node if that doesn't move any labels outside their scope, and you understand ALL properties of its new parent. -it's OK to delete a (subtree rooted at a) node if you understand ALL properties of its parent. The presentation of this material could be clarified by a table that relates constructions in the notation to their intended uses and meanings. Put in contents if: Put in environment if: effect is local to node has scope is directly edited is only indirectly edited is to be bound locally needs delayed or global binding STANDARD CARD  WE ARE DESIGNING A STANDARD FOR INTERCHANGE, NOT EDITING.  GENSYM IS AN EDITOR, NOT AN INTERCHANGE, FUNCTION.  STANDARDIZE CONCEPTS, NOT NAMES. 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.  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. 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. Edited by Mitchell, 7 Aug. 1981 4:40 pm PDT (Friday) Fixed error in semantics when exchanging the use of {}s and ()s. Edited by Horning 13 Aug. 1981 4:47 pm PDT (Thursday). E(id) > locVal(id, E) --Remove conflict with f(E). Outer > "Outer" Const > "=" id lookup rule modified (R & T) [E | id_e, m] > [E | id m e] "." as infix op expressions are evaluated left-to-right (except for binding operator) Reverse VAL/ENV default for parens. bindq > bind binding > bindingMode expand definition of apply inline default T(E) = E add comments to semantic equations ------------------- R<>(E) = Nothing -- The empty expression -- Expression sequence R(E) = R(E) R(T(E)) -- List insert T(E) = T(T(E)) -- Composition R(E) = literal R(E) = if bindingOf(id, E)=None then id else R(E) T(E) = if bindingOf(id, E)=None then E else T(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<"NOT" p>(E) = if R

(E) then False else True R(E) = op = "." => R([R(E) | "Outer" = E]) op = "+" => R(E)+R(E) . . . R(E) = Nothing -- Empty list T(E) = bind(n, m, R(E), E) T(E) = bind(n, m, e, E) T(E) = bind(n, m, R(E), E) R<"{" labels e* "}">(E) = "{" labels R([Null | "Outer" = E]) "}" T<"{" labels e* "}">(E) = locVal("Outer", (T<"ENV("Sub e*")">(E))) R<"(" e* ")">(E) = R(E) R<"ENV(" e* ")">(E) = [T<"ENV(" e* ")">(E) | "Outer" = Null] T<"ENV(" e* ")">(E) = T([Null | "Outer" = E]) ------------------- Edited by Jim Horning 17 Aug. 1981 10:49 am PDT (Monday) R&T<> Nothing > "" Edited by Jim H. on 17 Aug. 1981 4:58 pm PDT (Monday) Remove side-effects from all expressions. Parentheses purely for grouping (don't hide environment transformations). #label > label ! labels within nodes Edited by Jim H. on 19 Aug. 1981 9:52 am PDT (Wednesday). Rewrite as syntactic sugar. structured labels re-introduce apply function in R&T correct syntax for "." % for opening an environment (also replaces ENV?) Edited by Jim H. on 19 Aug. 1981 6:55 pm PDT (Wednesday). Drop "%"; ENV() is now the only environment-constructing operator. Add SUB operator (first operand: sequence only, second: number only). Add atoms, as distinct from ids. Fix lhs op rhs syntax. Edited by Jim H. on 20 Aug. 1981 5:29 pm PDT (Thursday). resolve pending questions as per message of 20 Aug. 1981 12:29 pm PDT. distinguish syntactically between properties (marks) and labels. only the "main" id of a label is declarable. eliminate  as an id character. eliminate op ids from grammar. restructure the grammar for "functional" notation for operators. update semantic equations for new grammar, etc. fix treatment of unbound qualified names (now produce Nil). Edited by Jim H. on 21 Aug. 1981 6:58 pm PDT (Friday). restore $val. move quoting to rhs, allow quoted primaries without parentheses. allow an op to be the rhs of a definition. eliminate the functions operate, apply, eval by back substitution. change semantics of () to allow "record" construction without $env. Edited by Jim H. on 24 Aug. 1981 6:08 pm PDT (Monday). "It's OK to edit a node if you understand ALL of its (local) properties, and either don't remove any of them or also understand ALL properties of its parent." "Put in contents if: Put in environment if: ..." Add connection syntax to syntactically rule out a+_'b. Edited by Jim H. on 25 Aug. 1981 11:33 am PDT (Tuesday). Syntactically separate label references and name invocation. Put in distinct syntax in rhs for environment construction. Informal semantics of labels. ( ... ) > [ ... ] in applications; permitting ( ... ) as a primary.