Skip to content

Commit

Permalink
Merge pull request #10589 from wiktorkuchta/manual-spaces
Browse files Browse the repository at this point in the history
manual: Remove space inserting code from syntaxdef.hva
  • Loading branch information
Octachron committed Dec 14, 2021
2 parents 7a0e1d2 + bbc9ac7 commit c2b2e9a
Show file tree
Hide file tree
Showing 14 changed files with 84 additions and 83 deletions.
3 changes: 3 additions & 0 deletions Changes
Expand Up @@ -15,6 +15,9 @@ Working version

### Manual and documentation:

- #10589: Fix many typos (excess/inconsistent spaces) in the HTML manual.
(Wiktor Kuchta, review by Florian Angeletti)

### Compiler user-interface and warnings:

### Internal/compiler-libs changes:
Expand Down
6 changes: 3 additions & 3 deletions manual/src/cmds/unified-options.etex
Expand Up @@ -110,10 +110,10 @@ This causes the given C library to be linked with the program.
\notop{%
\item["-ccopt" \var{option}]
Pass the given option to the C compiler and linker.
\comp{When linking in ``custom runtime'' mode, for instance}%
\nat{For instance,}%
\comp{When linking in ``custom runtime'' mode, for instance }%
\nat{For instance, }%
"-ccopt -L"\var{dir} causes the C linker to search for C libraries in
directory \var{dir}.\comp{(See the "-custom" option.)}
directory \var{dir}. \comp{(See the "-custom" option.)}
}%notop

\notop{%
Expand Down
22 changes: 11 additions & 11 deletions manual/src/refman/classes.etex
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
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
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
38 changes: 19 additions & 19 deletions manual/src/refman/extensions/extensionsyntax.etex
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,26 +37,26 @@ this example valid.
\begin{syntax}
float-literal:
...
| ["-"] ("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"||"_" }]
["g"\ldots"z"||"G"\ldots"Z"]
| ["-"] ("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" || "_" }]
["g"\ldots"z" || "G"\ldots"Z"]
;
int-literal:
...
| ["-"] ("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"||"_" }
["g"\ldots"z"||"G"\ldots"Z"]
| ["-"] ("0o"||"0O") ("0"\ldots"7") { "0"\ldots"7"||"_" }
["g"\ldots"z"||"G"\ldots"Z"]
| ["-"] ("0b"||"0B") ("0"\ldots"1") { "0"\ldots"1"||"_" }
["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" || "_" }
["g"\ldots"z" || "G"\ldots"Z"]
| ["-"] ("0o" || "0O") ("0"\ldots"7") { "0"\ldots"7" || "_" }
["g"\ldots"z" || "G"\ldots"Z"]
| ["-"] ("0b" || "0B") ("0"\ldots"1") { "0"\ldots"1" || "_" }
["g"\ldots"z" || "G"\ldots"Z"]
;
\end{syntax}
Int and float literals followed by an one-letter identifier in the
Expand Down
4 changes: 2 additions & 2 deletions manual/src/refman/extensions/gadts.etex
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}
8 changes: 4 additions & 4 deletions manual/src/refman/extensions/indexops.etex
Expand Up @@ -6,7 +6,7 @@ dot-ext:
| dot-operator-char { operator-char }
;
dot-operator-char:
'!' || '?' || core-operator-char || '%' || ':'
'!' || '?' || core-operator-char || '%' || ':'
;
expr:
...
Expand Down 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
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
4 changes: 2 additions & 2 deletions manual/src/refman/extensions/signaturesubstitution.etex
Expand Up @@ -107,8 +107,8 @@ end [@@expect error];;
\begin{syntax}
mod-constraint:
...
| 'module ' 'type' modtype-path '=' module-type
| 'module ' 'type' modtype-path ':=' module-type
| 'module' 'type' modtype-path '=' module-type
| 'module' 'type' modtype-path ':=' module-type
\end{syntax}

Module type substitution essentially behaves like type substitutions.
Expand Down
44 changes: 22 additions & 22 deletions manual/src/refman/lex.etex
Expand Up @@ -30,11 +30,11 @@ 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" || "_" || "'" } ;
letter: "A" \ldots "Z" || "a" \ldots "z"
("a"\ldots"z" || "_") { letter || "0"\ldots"9" || "_" || "'" } ;
letter: "A"\ldots"Z" || "a"\ldots"z"
\end{syntax}

Identifiers are sequences of letters, digits, "_" (the underscore
Expand All @@ -61,10 +61,10 @@ purpose.
\begin{syntax}
integer-literal:
["-"] ("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"||"_" }
| ["-"] ("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" || "_" }
;
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"||"_" }]
| ["-"] ("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") { "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" || "_" }]
\end{syntax}

Floating-point decimal literals consist in an integer part, a
Expand Down Expand Up @@ -149,10 +149,10 @@ char-literal:
| "'" escape-sequence "'"
;
escape-sequence:
"\" ( "\" || '"' || "'" || "n" || "t" || "b" || "r" || space )
"\" ("\" || '"' || "'" || "n" || "t" || "b" || "r" || space)
| "\" ("0"\ldots"9") ("0"\ldots"9") ("0"\ldots"9")
| "\x" ("0"\ldots"9"||"A"\ldots"F"||"a"\ldots"f")
("0"\ldots"9"||"A"\ldots"F"||"a"\ldots"f")
| "\x" ("0"\ldots"9" || "A"\ldots"F" || "a"\ldots"f")
("0"\ldots"9" || "A"\ldots"F" || "a"\ldots"f")
| "\o" ("0"\ldots"3") ("0"\ldots"7") ("0"\ldots"7")
\end{syntax}

Expand Down Expand Up @@ -183,15 +183,15 @@ let copyright = '\xA9';;
\begin{syntax}
string-literal:
'"' { string-character } '"'
| '{' quoted-string-id '|' { any-char } '|' quoted-string-id '}'
| '{' quoted-string-id '|' { any-char } '|' quoted-string-id '}'
;
quoted-string-id:
{ 'a'...'z' || '_' }
;
string-character:
regular-string-char
| escape-sequence
| "\u{" {{ "0"\ldots"9"||"A"\ldots"F"||"a"\ldots"f" }} "}"
| "\u{" {{ "0"\ldots"9" || "A"\ldots"F" || "a"\ldots"f" }} "}"
| '\' newline { space || tab }
\end{syntax}

Expand Down Expand Up @@ -274,7 +274,7 @@ there are really 3 tokens, with optional blanks between them.

\begin{syntax}
infix-symbol:
( core-operator-char || '%' || '<' ) { operator-char }
(core-operator-char || '%' || '<') { operator-char }
| "#" {{ operator-char }}
;
prefix-symbol:
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
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
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
26 changes: 12 additions & 14 deletions manual/styles/syntaxdef.hva
Expand Up @@ -24,8 +24,6 @@
%\stx@alias{name}{othername}
%will make reference to 'name' point to the definition of non-terminal
%'othername'
\newif\ifspace
\def\addspace{\ifspace\;\spacefalse\fi}
\ifhtml
\newcommand{\token}[1]{\textnormal{\@span{class=syntax-token}#1}}
\newstyle{.syntax-token}{color:blue;font-family:monospace}
Expand Down Expand Up @@ -137,23 +135,23 @@
\def\nt#1{\textnormal{\@span{class=nonterminal}#1}}
\newstyle{.nonterminal}{color:maroon;font-style:oblique}
%%%Link for non-terminal and format
\def\nonterm#1{\addspace\nt{\@anchor{#1}}\spacetrue}
\def\brepet{\addspace\{}
\def\nonterm#1{\nt{\@anchor{#1}}}
\def\brepet{\{}
\def\erepet{\}}
\def\boption{\addspace[}
\def\boption{[}
\def\eoption{]}
\def\brepets{\addspace\{}
\def\brepets{\{}
\def\erepets{\}^+}
\def\bparen{\addspace(}
\def\bparen{(}
\def\eparen{)}
\def\orelse{\mid \spacefalse}
\def\is{ & ::= & \spacefalse }
\def\alt{ \\ & \mid & \spacefalse }
\def\sep{ \\ \\ \spacefalse }
\def\orelse{\mid}
\def\is{&::=&}
\def\alt{\\&\mid&}
\def\sep{\\\\}
\def\cutline{}
\def\emptystring{\epsilon}
\def\syntax{\@open{div}{class="syntax"}$$\begin{array}{>{\set@name}rcl}\spacefalse}
\def\syntax{\@open{div}{class="syntax"}$$\begin{array}{>{\set@name}rcl}}
\def\endsyntax{\end{array}$$\@close{div}}
\def\syntaxleft{\@open{div}{class="syntaxleft"}$\begin{array}{>{\set@name}rcl}\spacefalse}
\def\syntaxleft{\@open{div}{class="syntaxleft"}$\begin{array}{>{\set@name}rcl}}
\def\endsyntaxleft{\end{array}$\@close{div}}
\def\synt#1{$\spacefalse#1$}
\def\synt#1{$#1$}

0 comments on commit c2b2e9a

Please sign in to comment.