Skip to content

Commit

Permalink
webman: Add spaces inside metasyntax braces
Browse files Browse the repository at this point in the history
  • Loading branch information
wikku committed Dec 7, 2021
1 parent c0b0960 commit b165a68
Show file tree
Hide file tree
Showing 10 changed files with 55 additions and 55 deletions.
22 changes: 11 additions & 11 deletions manual/src/refman/classes.etex
Original file line number Diff line number Diff line change
Expand Up @@ -24,8 +24,8 @@ class-type:
| class-body-type
;
class-body-type:
'object' ['(' typexpr ')'] {class-field-spec} 'end'
| ['[' typexpr {',' typexpr} ']'] classtype-path
'object' ['(' typexpr ')'] { class-field-spec } 'end'
| ['[' typexpr { ',' typexpr } ']'] classtype-path
| 'let' 'open' module-path 'in' class-body-type
;
%\end{syntax} \begin{syntax}
Expand Down Expand Up @@ -60,7 +60,7 @@ type @class-type@.
\subsubsection*{sss:clty:body}{Class body type}

The class type expression
@'object' ['(' typexpr ')'] {class-field-spec} 'end'@
@'object' ['(' typexpr ')'] { class-field-spec } 'end'@
is the type of a class body. It specifies its instance variables and
methods. In this type, @typexpr@ is matched against the self type, therefore
providing a name for the self type.
Expand Down Expand Up @@ -169,12 +169,12 @@ specifications expressed in class types.
\begin{syntax}
class-expr:
class-path
| '[' typexpr {',' typexpr} ']' class-path
| '[' typexpr { ',' typexpr } ']' class-path
| '(' class-expr ')'
| '(' class-expr ':' class-type ')'
| class-expr {{argument}}
| 'fun' {{parameter}} '->' class-expr
| 'let' ['rec'] let-binding {'and' let-binding} 'in' class-expr
| class-expr {{ argument }}
| 'fun' {{ parameter }} '->' class-expr
| 'let' ['rec'] let-binding { 'and' let-binding } 'in' class-expr
| 'object' class-body 'end'
| 'let' 'open' module-path 'in' class-expr
;
Expand All @@ -188,8 +188,8 @@ class-field:
| 'val!' ['mutable'] inst-var-name [':' typexpr] '=' expr
| 'val' ['mutable'] 'virtual' inst-var-name ':' typexpr
| 'val' 'virtual' 'mutable' inst-var-name ':' typexpr
| 'method' ['private'] method-name {parameter} [':' typexpr] '=' expr
| 'method!' ['private'] method-name {parameter} [':' typexpr] '=' expr
| 'method' ['private'] method-name { parameter } [':' typexpr] '=' expr
| 'method!' ['private'] method-name { parameter } [':' typexpr] '=' expr
| 'method' ['private'] method-name ':' poly-typexpr '=' expr
| 'method!' ['private'] method-name ':' poly-typexpr '=' expr
| 'method' ['private'] 'virtual' method-name ':' poly-typexpr
Expand Down Expand Up @@ -368,7 +368,7 @@ used polymorphically in programs (even for the same object). The
explicit declaration may be done in one of three ways: (1) by giving an
explicit polymorphic type in the method definition, immediately after
the method name, {\em i.e.}
@'method' ['private'] method-name ':' {{"'" ident}} '.' typexpr '='
@'method' ['private'] method-name ':' {{ "'" ident }} '.' typexpr '='
expr@; (2) by a forward declaration of the explicit polymorphic type
through a virtual method definition; (3) by importing such a
declaration through inheritance and/or constraining the type of {\em
Expand Down Expand Up @@ -448,7 +448,7 @@ class-definition:
;
class-binding:
['virtual'] ['[' type-parameters ']'] class-name
{parameter} [':' class-type] \\ '=' class-expr
{ parameter } [':' class-type] \\ '=' class-expr
;
type-parameters:
"'" ident { "," "'" ident }
Expand Down
2 changes: 1 addition & 1 deletion manual/src/refman/expr.etex
Original file line number Diff line number Diff line change
Expand Up @@ -32,7 +32,7 @@ expr:
| '(' expr ')'
| 'begin' expr 'end'
| '(' expr ':' typexpr ')'
| expr {{',' expr}}
| expr {{ ',' expr }}
| constr expr
| "`"tag-name expr
| expr '::' expr
Expand Down
4 changes: 2 additions & 2 deletions manual/src/refman/extensions/attributes.etex
Original file line number Diff line number Diff line change
Expand Up @@ -62,10 +62,10 @@ constructors in type declarations:

\begin{syntax}
field-decl:
['mutable'] field-name ':' poly-typexpr {attribute}
['mutable'] field-name ':' poly-typexpr { attribute }
;
constr-decl:
(constr-name || '()') [ 'of' constr-args ] {attribute}
(constr-name || '()') [ 'of' constr-args ] { attribute }
;
\end{syntax}

Expand Down
22 changes: 11 additions & 11 deletions manual/src/refman/extensions/extensionsyntax.etex
Original file line number Diff line number Diff line change
Expand Up @@ -11,11 +11,11 @@ vanilla constructions.
\begin{syntax}
infix-symbol:
...
| "#" {operator-char} "#" {operator-char || "#"}
| "#" { operator-char } "#" { operator-char || "#" }
;
prefix-symbol:
...
| ('?' || '~' || '!') {operator-char} "#" {operator-char || "#"}
| ('?' || '~' || '!') { operator-char } "#" { operator-char || "#" }
;
\end{syntax}

Expand All @@ -37,25 +37,25 @@ this example valid.
\begin{syntax}
float-literal:
...
| ["-"] ("0"\ldots"9") {"0"\ldots"9" || "_"} ["." {"0"\ldots"9" || "_"}]
[("e" || "E") ["+" || "-"] ("0"\ldots"9") {"0"\ldots"9" || "_"}]
| ["-"] ("0"\ldots"9") { "0"\ldots"9" || "_" } ["." { "0"\ldots"9" || "_" }]
[("e" || "E") ["+" || "-"] ("0"\ldots"9") { "0"\ldots"9" || "_" }]
["g"\ldots"z" || "G"\ldots"Z"]
| ["-"] ("0x" || "0X")
("0"\ldots"9" || "A"\ldots"F" || "a"\ldots"f")
{"0"\ldots"9" || "A"\ldots"F" || "a"\ldots"f" || "_"}\\
["." {"0"\ldots"9" || "A"\ldots"F" || "a"\ldots"f" || "_"}]
[("p" || "P") ["+" || "-"] ("0"\ldots"9") {"0"\ldots"9" || "_"}]
{ "0"\ldots"9" || "A"\ldots"F" || "a"\ldots"f" || "_" }\\
["." { "0"\ldots"9" || "A"\ldots"F" || "a"\ldots"f" || "_" }]
[("p" || "P") ["+" || "-"] ("0"\ldots"9") { "0"\ldots"9" || "_" }]
["g"\ldots"z" || "G"\ldots"Z"]
;
int-literal:
...
| ["-"] ("0"\ldots"9") {"0"\ldots"9" || "_"}["g"\ldots"z" || "G"\ldots"Z"]
| ["-"] ("0"\ldots"9") { "0"\ldots"9" || "_" }["g"\ldots"z" || "G"\ldots"Z"]
| ["-"] ("0x" || "0X") ("0"\ldots"9" || "A"\ldots"F" || "a"\ldots"f")
{"0"\ldots"9" || "A"\ldots"F" || "a"\ldots"f" || "_"}
{ "0"\ldots"9" || "A"\ldots"F" || "a"\ldots"f" || "_" }
["g"\ldots"z" || "G"\ldots"Z"]
| ["-"] ("0o" || "0O") ("0"\ldots"7") {"0"\ldots"7" || "_"}
| ["-"] ("0o" || "0O") ("0"\ldots"7") { "0"\ldots"7" || "_" }
["g"\ldots"z" || "G"\ldots"Z"]
| ["-"] ("0b" || "0B") ("0"\ldots"1") {"0"\ldots"1" || "_"}
| ["-"] ("0b" || "0B") ("0"\ldots"1") { "0"\ldots"1" || "_" }
["g"\ldots"z" || "G"\ldots"Z"]
;
\end{syntax}
Expand Down
4 changes: 2 additions & 2 deletions manual/src/refman/extensions/gadts.etex
Original file line number Diff line number Diff line change
Expand Up @@ -28,6 +28,6 @@ Explicit naming of existentials. (Introduced in OCaml 4.13.0)
\begin{syntax}
pattern:
...
| constr '(' "type" {{typeconstr-name}} ')' '(' pattern ')'
| constr '(' "type" {{ typeconstr-name }} ')' '(' pattern ')'
;
\end{syntax}
\end{syntax}
6 changes: 3 additions & 3 deletions manual/src/refman/extensions/indexops.etex
Original file line number Diff line number Diff line change
Expand Up @@ -45,9 +45,9 @@ let open Dict in dict.%{"two"};;
\begin{syntax}
expr:
...
| expr '.' [module-path '.'] dot-ext '(' expr {{';' expr }} ')' [ '<-' expr ]
| expr '.' [module-path '.'] dot-ext '[' expr {{';' expr }} ']' [ '<-' expr ]
| expr '.' [module-path '.'] dot-ext '{' expr {{';' expr }} '}' [ '<-' expr ]
| expr '.' [module-path '.'] dot-ext '(' expr {{ ';' expr }} ')' [ '<-' expr ]
| expr '.' [module-path '.'] dot-ext '[' expr {{ ';' expr }} ']' [ '<-' expr ]
| expr '.' [module-path '.'] dot-ext '{' expr {{ ';' expr }} '}' [ '<-' expr ]
;
operator-name:
...
Expand Down
2 changes: 1 addition & 1 deletion manual/src/refman/extensions/locallyabstract.etex
Original file line number Diff line number Diff line change
Expand Up @@ -3,7 +3,7 @@
\begin{syntax}
parameter:
...
| '(' "type" {{typeconstr-name}} ')'
| '(' "type" {{ typeconstr-name }} ')'
\end{syntax}

The expression @"fun" '(' "type" typeconstr-name ')' "->" expr@ introduces a
Expand Down
44 changes: 22 additions & 22 deletions manual/src/refman/lex.etex
Original file line number Diff line number Diff line change
Expand Up @@ -30,10 +30,10 @@ let f = function
\subsubsection*{sss:lex:identifiers}{Identifiers}

\begin{syntax}
ident: (letter || "_") {letter || "0"\ldots"9" || "_" || "'"} ;
capitalized-ident: ("A"\ldots"Z") {letter || "0"\ldots"9" || "_" || "'"} ;
ident: (letter || "_") { letter || "0"\ldots"9" || "_" || "'" } ;
capitalized-ident: ("A"\ldots"Z") { letter || "0"\ldots"9" || "_" || "'" } ;
lowercase-ident:
("a"\ldots"z" || "_") {letter || "0"\ldots"9" || "_" || "'"} ;
("a"\ldots"z" || "_") { letter || "0"\ldots"9" || "_" || "'" } ;
letter: "A"\ldots"Z" || "a"\ldots"z"
\end{syntax}

Expand All @@ -60,11 +60,11 @@ purpose.

\begin{syntax}
integer-literal:
["-"] ("0"\ldots"9") {"0"\ldots"9" || "_"}
["-"] ("0"\ldots"9") { "0"\ldots"9" || "_" }
| ["-"] ("0x" || "0X") ("0"\ldots"9" || "A"\ldots"F" || "a"\ldots"f")
{"0"\ldots"9" || "A"\ldots"F" || "a"\ldots"f" || "_"}
| ["-"] ("0o" || "0O") ("0"\ldots"7") {"0"\ldots"7" || "_"}
| ["-"] ("0b" || "0B") ("0"\ldots"1") {"0"\ldots"1" || "_"}
{ "0"\ldots"9" || "A"\ldots"F" || "a"\ldots"f" || "_" }
| ["-"] ("0o" || "0O") ("0"\ldots"7") { "0"\ldots"7" || "_" }
| ["-"] ("0b" || "0B") ("0"\ldots"1") { "0"\ldots"1" || "_" }
;
int32-literal: integer-literal 'l'
;
Expand Down Expand Up @@ -102,13 +102,13 @@ let counter64bit = ref 0L;;

\begin{syntax}
float-literal:
["-"] ("0"\ldots"9") {"0"\ldots"9" || "_"} ["." {"0"\ldots"9" || "_"}]
[("e" || "E") ["+" || "-"] ("0"\ldots"9") {"0"\ldots"9" || "_"}]
["-"] ("0"\ldots"9") { "0"\ldots"9" || "_" } ["." { "0"\ldots"9" || "_" }]
[("e" || "E") ["+" || "-"] ("0"\ldots"9") { "0"\ldots"9" || "_" }]
| ["-"] ("0x" || "0X")
("0"\ldots"9" || "A"\ldots"F" || "a"\ldots"f")
{"0"\ldots"9" || "A"\ldots"F" || "a"\ldots"f" || "_"} \\
["." {"0"\ldots"9" || "A"\ldots"F" || "a"\ldots"f" || "_"}]
[("p" || "P") ["+" || "-"] ("0"\ldots"9") {"0"\ldots"9" || "_"}]
{ "0"\ldots"9" || "A"\ldots"F" || "a"\ldots"f" || "_" } \\
["." { "0"\ldots"9" || "A"\ldots"F" || "a"\ldots"f" || "_" }]
[("p" || "P") ["+" || "-"] ("0"\ldots"9") { "0"\ldots"9" || "_" }]
\end{syntax}

Floating-point decimal literals consist in an integer part, a
Expand Down Expand Up @@ -182,17 +182,17 @@ let copyright = '\xA9';;

\begin{syntax}
string-literal:
'"' {string-character} '"'
| '{' quoted-string-id '|' {any-char} '|' quoted-string-id '}'
'"' { string-character } '"'
| '{' quoted-string-id '|' { any-char } '|' quoted-string-id '}'
;
quoted-string-id:
{'a'...'z' || '_'}
{ 'a'...'z' || '_' }
;
string-character:
regular-string-char
| escape-sequence
| "\u{" {{"0"\ldots"9" || "A"\ldots"F" || "a"\ldots"f"}} "}"
| '\' newline {space || tab}
| "\u{" {{ "0"\ldots"9" || "A"\ldots"F" || "a"\ldots"f" }} "}"
| '\' newline { space || tab }
\end{syntax}

String literals are delimited by @'"'@ (double quote) characters.
Expand Down Expand Up @@ -274,12 +274,12 @@ there are really 3 tokens, with optional blanks between them.

\begin{syntax}
infix-symbol:
(core-operator-char || '%' || '<') {operator-char}
| "#" {{operator-char}}
(core-operator-char || '%' || '<') { operator-char }
| "#" {{ operator-char }}
;
prefix-symbol:
'!' {operator-char}
| ('?' || '~') {{operator-char}}
'!' { operator-char }
| ('?' || '~') {{ operator-char }}
;
operator-char:
'~' || '!' || '?' || core-operator-char || '%' || '<' || ':' || '.'
Expand Down Expand Up @@ -348,7 +348,7 @@ longest first token.

\begin{syntax}
linenum-directive:
'#' {{"0"\ldots"9"}} '"' {string-character} '"'
'#' {{ "0"\ldots"9" }} '"' { string-character } '"'
\end{syntax}

Preprocessors that generate OCaml source code can insert line number
Expand Down
2 changes: 1 addition & 1 deletion manual/src/refman/modules.etex
Original file line number Diff line number Diff line change
Expand Up @@ -28,7 +28,7 @@ module-expr:
| '(' module-expr ':' module-type ')'
;
module-items:
{';;'} ( definition || expr ) { {';;'} ( definition || ';;' expr) } {';;'}
{ ';;' } ( definition || expr ) { { ';;' } ( definition || ';;' expr) } { ';;' }
;
%\end{syntax} \begin{syntax}
definition:
Expand Down
2 changes: 1 addition & 1 deletion manual/src/refman/types.etex
Original file line number Diff line number Diff line change
Expand Up @@ -206,7 +206,7 @@ an explicit polymorphic type can only be unified to an
equivalent one, where only the order and names of polymorphic
variables may change.

The type @'<' {method-type ';'} '..' '>'@ is the
The type @'<' { method-type ';' } '..' '>'@ is the
type of an object whose method names and types are described by
@method-type_1, \ldots, method-type_n@, and possibly some other
methods represented by the ellipsis. This ellipsis actually is
Expand Down

0 comments on commit b165a68

Please sign in to comment.