fixing quotes and other formatting problems
git-svn-id: http://caml.inria.fr/svn/ocamldoc/trunk@12178 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02master
parent
792fa3c54f
commit
85e10f36c0
|
@ -31,7 +31,9 @@ manual: files
|
|||
TEXINPUTS=$(TEXINPUTS) latex manual.tex
|
||||
|
||||
index::
|
||||
cd texstuff; makeindex manual.idx
|
||||
cd texstuff && \
|
||||
../../tools/fix_index.sh manual.idx && \
|
||||
makeindex manual.idx
|
||||
cd texstuff; makeindex manual.kwd.idx
|
||||
|
||||
pdfmanual: files
|
||||
|
@ -39,7 +41,9 @@ pdfmanual: files
|
|||
TEXINPUTS=$(TEXINPUTS) pdflatex pdfmanual.tex
|
||||
|
||||
index::
|
||||
cd texstuff; makeindex pdfmanual.idx
|
||||
cd texstuff && \
|
||||
../../tools/fix_index.sh pdfmanual.idx && \
|
||||
makeindex pdfmanual.idx
|
||||
cd texstuff; makeindex pdfmanual.kwd.idx
|
||||
|
||||
html: files
|
||||
|
|
|
@ -77,7 +77,12 @@ Display a short usage summary and exit.
|
|||
\section{Syntax of lexer definitions}
|
||||
|
||||
The format of lexer definitions is as follows:
|
||||
\begingroup\newcommand{\sub}[1]{$_{#1}$}
|
||||
\begingroup%
|
||||
\newcommand{\sub}[1]{$_{#1}$}%
|
||||
\renewcommand{\{}{\char`\{}%
|
||||
\renewcommand{\}}{\char`\}}%
|
||||
\renewcommand{\\}{\char`\\}%
|
||||
\renewcommand{\%}{\char`\%}%
|
||||
\begin{alltt}
|
||||
\{ \var{header} \}
|
||||
let \var{ident} = \var{regexp} \ldots
|
||||
|
@ -290,15 +295,15 @@ extended as follows:
|
|||
can be matched without binding this variable.
|
||||
\end{itemize}
|
||||
For instance, in
|
||||
\verb+('a' as x) | ( 'a' (_ as x) )+ the variable \verb+x+ is of type
|
||||
"('a' as x) | ( 'a' (_ as x) )" the variable "x" is of type
|
||||
"char", whereas in
|
||||
\verb+("ab" as x) | ( 'a' (_ as x) ? )+ the variable \verb+x+ is of type
|
||||
"(\"ab\" as x) | ( 'a' (_ as x) ? )" the variable "x" is of type
|
||||
"string option".
|
||||
|
||||
|
||||
In some cases, a sucessful match may not yield a unique set of bindings.
|
||||
For instance the matching of \verb+aba+ by the regular expression
|
||||
\verb+(('a'|"ab") as x) (("ba"|'a') as y)+ may result in binding
|
||||
"(('a'|\"ab\") as x) ((\"ba\"|'a') as y)" may result in binding
|
||||
either
|
||||
\verb+x+ to \verb+"ab"+ and \verb+y+ to \verb+"a"+, or
|
||||
\verb+x+ to \verb+"a"+ and \verb+y+ to \verb+"ba"+.
|
||||
|
@ -339,6 +344,11 @@ the concrete type "token", defined in the interface file
|
|||
\section{Syntax of grammar definitions}
|
||||
|
||||
Grammar definitions have the following format:
|
||||
\begingroup%
|
||||
\renewcommand{\{}{\char`\{}%
|
||||
\renewcommand{\}}{\char`\}}%
|
||||
\renewcommand{\\}{\char`\\}%
|
||||
\renewcommand{\%}{\char`\%}%
|
||||
\begin{alltt}
|
||||
\%\{
|
||||
\var{header}
|
||||
|
@ -349,6 +359,7 @@ Grammar definitions have the following format:
|
|||
\%\%
|
||||
\var{trailer}
|
||||
\end{alltt}
|
||||
\endgroup
|
||||
|
||||
Comments are enclosed between \verb|/*| and \verb|*/| (as in C) in the
|
||||
``declarations'' and ``rules'' sections, and between \verb|(*| and
|
||||
|
@ -448,6 +459,12 @@ resolve reduce/reduce and shift/reduce conflicts:
|
|||
\subsection{Rules}
|
||||
|
||||
The syntax for rules is as usual:
|
||||
\begingroup%
|
||||
\newcommand{\sub}[1]{$_{#1}$}%
|
||||
\renewcommand{\{}{\char`\{}%
|
||||
\renewcommand{\}}{\char`\}}%
|
||||
\renewcommand{\\}{\char`\\}%
|
||||
\renewcommand{\%}{\char`\%}%
|
||||
\begin{alltt}
|
||||
\var{nonterminal} :
|
||||
\var{symbol} \ldots \var{symbol} \{ \var{semantic-action} \}
|
||||
|
@ -455,6 +472,7 @@ The syntax for rules is as usual:
|
|||
| \var{symbol} \ldots \var{symbol} \{ \var{semantic-action} \}
|
||||
;
|
||||
\end{alltt}
|
||||
\endgroup
|
||||
%
|
||||
Rules can also contain the \verb"%prec "{\it symbol} directive in the
|
||||
right-hand side part, to override the default precedence and
|
||||
|
|
|
@ -337,7 +337,7 @@ At start-up, the toplevel system contains implementations for all the
|
|||
modules in the the standard library. Implementations for user modules
|
||||
can be entered with the "#load" directive described above. Referencing
|
||||
a unit for which no implementation has been provided
|
||||
results in the error ``Reference to undefined global `\ldots'\,''.
|
||||
results in the error "Reference to undefined global `...'".
|
||||
|
||||
Note that entering "open "\var{Mod} merely accesses the compiled
|
||||
interface (".cmi" file) for \var{Mod}, but does not load the
|
||||
|
|
|
@ -94,7 +94,7 @@
|
|||
\setbox\@tempboxa\hbox{\makelabel{#1}}%
|
||||
\global\setbox\@labels
|
||||
\ifdim \wd\@tempboxa >\labelwidth
|
||||
\hbox{\unhbox\@labels
|
||||
\hbox{\unhbox\@labels
|
||||
\hskip -\leftmargin
|
||||
\box\@tempboxa}\hfil\break
|
||||
\else
|
||||
|
|
|
@ -217,9 +217,9 @@ is introduced by the keyword "function":
|
|||
\ikwd{function\@\texttt{function}}
|
||||
|
||||
$$\begin{array}{rlll}
|
||||
\token{function} & {\sl pattern}_1 & \token{->} & {\sl expr}_1 \\
|
||||
\token{function} & \textsl{pattern}_1 & \token{->} & \textsl{expr}_1 \\
|
||||
\token{|} & \ldots \\
|
||||
\token{|} & {\sl pattern}_n & \token{->} & {\sl expr}_n
|
||||
\token{|} & \textsl{pattern}_n & \token{->} & \textsl{expr}_n
|
||||
\end{array}$$
|
||||
This expression evaluates to a functional value with one argument.
|
||||
When this function is applied to a value \var{v}, this value is
|
||||
|
@ -390,10 +390,10 @@ The @"else" expr_3@ part can be omitted, in which case it defaults to
|
|||
|
||||
The expression
|
||||
$$\begin{array}{rlll}
|
||||
\token{match} & {\sl expr} \\
|
||||
\token{with} & {\sl pattern}_1 & \token{->} & {\sl expr}_1 \\
|
||||
\token{match} & \textsl{expr} \\
|
||||
\token{with} & \textsl{pattern}_1 & \token{->} & \textsl{expr}_1 \\
|
||||
\token{|} & \ldots \\
|
||||
\token{|} & {\sl pattern}_n & \token{->} & {\sl expr}_n
|
||||
\token{|} & \textsl{pattern}_n & \token{->} & \textsl{expr}_n
|
||||
\end{array}$$
|
||||
matches the value of @expr@ against the patterns @pattern_1@ to
|
||||
@pattern_n@. If the matching against @pattern_i@ succeeds, the
|
||||
|
@ -413,7 +413,7 @@ The expression @expr_1 '&&' expr_2@ evaluates to @'true'@ if both
|
|||
@expr_1@ and @expr_2@ evaluate to @'true'@; otherwise, it evaluates to
|
||||
@'false'@. The first component, @expr_1@, is evaluated first. The
|
||||
second component, @expr_2@, is not evaluated if the first component
|
||||
evaluates to @'false'@. Hence, the expression @expr_1 '&&' expr_2@ behaves
|
||||
evaluates to @'false'@. Hence, the expression @expr_1 '&&' expr_2@ behaves
|
||||
exactly as
|
||||
\begin{center}
|
||||
@'if' expr_1 'then' expr_2 'else' 'false'@.
|
||||
|
@ -423,7 +423,7 @@ The expression @expr_1 '||' expr_2@ evaluates to @'true'@ if one of
|
|||
@expr_1@ and @expr_2@ evaluates to @'true'@; otherwise, it evaluates to
|
||||
@'false'@. The first component, @expr_1@, is evaluated first. The
|
||||
second component, @expr_2@, is not evaluated if the first component
|
||||
evaluates to @'true'@. Hence, the expression @expr_1 '||' expr_2@ behaves
|
||||
evaluates to @'true'@. Hence, the expression @expr_1 '||' expr_2@ behaves
|
||||
exactly as
|
||||
\begin{center}
|
||||
@'if' expr_1 'then' 'true' 'else' expr_2@.
|
||||
|
@ -466,10 +466,10 @@ value @'()'@.
|
|||
|
||||
The expression
|
||||
$$\begin{array}{rlll}
|
||||
\token{try~} & {\sl expr} \\
|
||||
\token{with} & {\sl pattern}_1 & \token{->} & {\sl expr}_1 \\
|
||||
\token{try~} & \textsl{expr} \\
|
||||
\token{with} & \textsl{pattern}_1 & \token{->} & \textsl{expr}_1 \\
|
||||
\token{|} & \ldots \\
|
||||
\token{|} & {\sl pattern}_n & \token{->} & {\sl expr}_n
|
||||
\token{|} & \textsl{pattern}_n & \token{->} & \textsl{expr}_n
|
||||
\end{array}$$
|
||||
evaluates the expression @expr@ and returns its value if the
|
||||
evaluation of @expr@ does not raise any exception. If the evaluation
|
||||
|
|
|
@ -214,8 +214,8 @@ specification:
|
|||
{ 'and' module-name':' module-type }
|
||||
\end{syntax}
|
||||
|
||||
Recursive module definitions, introduced by the 'module rec' \ldots
|
||||
'and' \ldots\ construction, generalize regular module definitions
|
||||
Recursive module definitions, introduced by the "module rec" \ldots
|
||||
"and" \ldots\ construction, generalize regular module definitions
|
||||
@'module' module-name '=' module-expr@ and module specifications
|
||||
@'module' module-name ':' module-type@ by allowing the defining
|
||||
@module-expr@ and the @module-type@ to refer recursively to the module
|
||||
|
|
|
@ -207,12 +207,12 @@ otherwise:
|
|||
%
|
||||
The following character sequences are also keywords:
|
||||
%
|
||||
\begin{verbatim}
|
||||
!= # & && ' ( ) * + , -
|
||||
-. -> . .. : :: := :> ; ;; <
|
||||
<- = > >] >} ? ?? [ [< [> [|
|
||||
] _ ` { {< | |] } ~
|
||||
\end{verbatim}
|
||||
\begin{alltt}
|
||||
" != # & && ' ( ) * + , -"
|
||||
" -. -> . .. : :: := :> ; ;; <"
|
||||
" <- = > >] >} ? ?? [ [< [> [|"
|
||||
" ] _ ` { {< | |] } ~"
|
||||
\end{alltt}
|
||||
%
|
||||
Note that the following identifiers are keywords of the Camlp4
|
||||
extensions and should be avoided for compatibility reasons.
|
||||
|
|
|
@ -254,27 +254,27 @@ their nature or role. Best labels combine in their meaning nature and
|
|||
role. When this is not possible the role is to prefer, since the nature will
|
||||
often be given by the type itself. Obscure abbreviations should be
|
||||
avoided.
|
||||
\caml
|
||||
\:ListLabels.map : f:('a -> 'b) -> 'a list -> 'b list
|
||||
\:UnixLabels.write : file_descr -> buf:string -> pos:int -> len:int -> unit
|
||||
\endcaml
|
||||
\begin{alltt}
|
||||
"ListLabels.map : f:('a -> 'b) -> 'a list -> 'b list"
|
||||
UnixLabels.write : file_descr -> buf:string -> pos:int -> len:int -> unit
|
||||
\end{alltt}
|
||||
|
||||
When there are several objects of same nature and role, they are all
|
||||
left unlabeled.
|
||||
\caml
|
||||
\:ListLabels.iter2 : f:('a -> 'b -> 'c) -> 'a list -> 'b list -> unit
|
||||
\endcaml
|
||||
\begin{alltt}
|
||||
"ListLabels.iter2 : f:('a -> 'b -> 'c) -> 'a list -> 'b list -> unit"
|
||||
\end{alltt}
|
||||
|
||||
When there is no preferable object, all arguments are labeled.
|
||||
\caml
|
||||
\:StringLabels.blit :
|
||||
\: src:string -> src_pos:int -> dst:string -> dst_pos:int -> len:int -> unit
|
||||
\endcaml
|
||||
\begin{alltt}
|
||||
StringLabels.blit :
|
||||
src:string -> src_pos:int -> dst:string -> dst_pos:int -> len:int -> unit
|
||||
\end{alltt}
|
||||
|
||||
However, when there is only one argument, it is often left unlabeled.
|
||||
\caml
|
||||
\:StringLabels.create : int -> string
|
||||
\endcaml
|
||||
\begin{alltt}
|
||||
StringLabels.create : int -> string
|
||||
\end{alltt}
|
||||
This principle also applies to functions of several arguments whose
|
||||
return type is a type variable, as long as the role of each argument
|
||||
is not ambiguous. Labeling such functions may lead to awkward error
|
||||
|
|
|
@ -0,0 +1,45 @@
|
|||
#!/bin/sh
|
||||
|
||||
# usage: fix_index.sh <file>.idx
|
||||
|
||||
# This script works around a hyperref bug: hyperref does not handle
|
||||
# quotes in \index arguments properly.
|
||||
#
|
||||
# Symptom:
|
||||
# When \index{-pipe-pipe@\verb`("|"|)`} appears in your .tex, the hyperref
|
||||
# package mangles it and produces this line in your .idx:
|
||||
# \indexentry{(-pipe-pipe)@\verb`("|hyperindexformat{\"}}{292}
|
||||
# instead of the expected:
|
||||
# \indexentry{(-pipe-pipe)@\verb`("|"|)`|hyperpage}{292}
|
||||
#
|
||||
# This is because it fails to handle quoted characters correctly.
|
||||
#
|
||||
# The workaround:
|
||||
# Look for the buggy line in the given .idx file and change it.
|
||||
|
||||
# Note: this bug will happen every time you have a | (pipe) character
|
||||
# in an index entry (properly quoted with a " (double-quote) before it).
|
||||
# We fix only the one case that appears in the OCaml documentation.
|
||||
# We do not attempt a general solution because hyperref erases part
|
||||
# of the argument, so we cannot recover the correct string from its
|
||||
# output.
|
||||
|
||||
usage(){
|
||||
echo "usage: fix_index.sh <file>.idx" >&2
|
||||
exit 2
|
||||
}
|
||||
|
||||
case $# in
|
||||
1) ;;
|
||||
*) usage;;
|
||||
esac
|
||||
|
||||
ed "$1" <<'EOF' >/dev/null
|
||||
/-pipe-pipe/s/verb`("|hyperindexformat{\\"}/verb`("|"|)`|hyperpage/
|
||||
w
|
||||
q
|
||||
EOF
|
||||
|
||||
case $? in
|
||||
0) echo "fix_index.sh: fixed $1 successfully.";;
|
||||
esac
|
|
@ -86,7 +86,11 @@ int main(argc, argv)
|
|||
for (p = (unsigned char *) line; *p != 0; p++) {
|
||||
c = *p;
|
||||
if (inverb) {
|
||||
if (c == inverb) inverb = 0;
|
||||
if (c == inverb){
|
||||
inverb = 0;
|
||||
}else if (c == '\'' || c == '`'){
|
||||
fprintf (stderr, "Warning: %c found in \\verb\n", c);
|
||||
}
|
||||
putchar(c);
|
||||
continue;
|
||||
}
|
||||
|
|
|
@ -1,4 +1,14 @@
|
|||
{ open Lexing;; }
|
||||
{
|
||||
open Lexing;;
|
||||
open Printf;;
|
||||
|
||||
let print_char_repr c =
|
||||
match c with
|
||||
| '\'' -> printf "{\\textquotesingle}"
|
||||
| '`' -> printf "{\\textasciigrave}"
|
||||
| _ -> printf "\\char%d" (int_of_char c);
|
||||
;;
|
||||
}
|
||||
|
||||
rule main = parse
|
||||
"\\begin{syntax}" {
|
||||
|
@ -83,8 +93,7 @@ and indoublequote = parse
|
|||
print_string "}";
|
||||
syntax lexbuf }
|
||||
| _ {
|
||||
print_string "\\char";
|
||||
print_int (int_of_char (lexeme_char lexbuf 0));
|
||||
print_char_repr (lexeme_char lexbuf 0);
|
||||
indoublequote lexbuf }
|
||||
|
||||
|
||||
|
|
Loading…
Reference in New Issue