Wrong quoting chase.

git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@13717 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
master
Pierre Weis 2013-05-29 18:03:55 +00:00
parent ef26391063
commit 626c696aee
12 changed files with 76 additions and 70 deletions

View File

@ -13,7 +13,7 @@
(** MD5 message digest.
This module provides functions to compute 128-bit ``digests'' of
This module provides functions to compute 128-bit 'digests' of
arbitrary-length strings or files. The digests are of cryptographic
quality: it is very hard, given a digest, to forge a string having
that digest. The algorithm used is MD5. This module should not be

View File

@ -11,7 +11,7 @@
(* *)
(***********************************************************************)
(* A pretty-printing facility and definition of formatters for ``parallel''
(* A pretty-printing facility and definition of formatters for 'parallel'
(i.e. unrelated or independent) pretty-printing on multiple out channels. *)
(**************************************************************
@ -217,7 +217,7 @@ let pp_clear_queue state =
(* Pp_infinity: large value for default tokens size.
Pp_infinity is documented as being greater than 1e10; to avoid
confusion about the word ``greater'', we choose pp_infinity greater
confusion about the word 'greater', we choose pp_infinity greater
than 1e10 + 1; for correct handling of tests in the algorithm,
pp_infinity must be even one more than 1e10 + 1; let's stand on the
safe side by choosing 1.e10+10.
@ -1051,7 +1051,7 @@ module Tformat = Printf.CamlinternalPr.Tformat;;
(* Trailer: giving up at character number ... *)
let giving_up mess fmt i =
Printf.sprintf
"Format.fprintf: %s ``%s'', giving up at character number %d%s"
"Format.fprintf: %s \'%s\', giving up at character number %d%s"
mess (Sformat.to_string fmt) i
(if i < Sformat.length fmt
then Printf.sprintf " (%c)." (Sformat.get fmt i)

View File

@ -14,7 +14,7 @@
(** Pretty printing.
This module implements a pretty-printing facility to format text
within ``pretty-printing boxes''. The pretty-printer breaks lines
within 'pretty-printing boxes'. The pretty-printer breaks lines
at specified break hints, and indents lines according to the box
structure.
@ -78,7 +78,7 @@ val open_box : int -> unit;;
(** [open_box d] opens a new pretty-printing box
with offset [d].
This box is the general purpose pretty-printing box.
Material in this box is displayed ``horizontal or vertical'':
Material in this box is displayed 'horizontal or vertical':
break hints inside the box may lead to a new line, if there
is no more room on the line to print the remainder of the box,
or if a new line may lead to a new indentation
@ -200,13 +200,13 @@ val over_max_boxes : unit -> bool;;
val open_hbox : unit -> unit;;
(** [open_hbox ()] opens a new pretty-printing box.
This box is ``horizontal'': the line is not split in this box
This box is 'horizontal': the line is not split in this box
(new lines may still occur inside boxes nested deeper). *)
val open_vbox : int -> unit;;
(** [open_vbox d] opens a new pretty-printing box
with offset [d].
This box is ``vertical'': every break hint inside this
This box is 'vertical': every break hint inside this
box leads to a new line.
When a new line is printed in the box, [d] is added to the
current indentation. *)
@ -214,16 +214,16 @@ val open_vbox : int -> unit;;
val open_hvbox : int -> unit;;
(** [open_hvbox d] opens a new pretty-printing box
with offset [d].
This box is ``horizontal-vertical'': it behaves as an
``horizontal'' box if it fits on a single line,
otherwise it behaves as a ``vertical'' box.
This box is 'horizontal-vertical': it behaves as an
'horizontal' box if it fits on a single line,
otherwise it behaves as a 'vertical' box.
When a new line is printed in the box, [d] is added to the
current indentation. *)
val open_hovbox : int -> unit;;
(** [open_hovbox d] opens a new pretty-printing box
with offset [d].
This box is ``horizontal or vertical'': break hints
This box is 'horizontal or vertical': break hints
inside this box may lead to a new line, if there is no more room
on the line to print the remainder of the box.
When a new line is printed in the box, [d] is added to the
@ -274,13 +274,13 @@ type tag = string;;
entities (e.g. HTML or TeX elements or terminal escape sequences).
By default, those tags do not influence line breaking calculation:
the tag ``markers'' are not considered as part of the printing
the tag 'markers' are not considered as part of the printing
material that drives line breaking (in other words, the length of
those strings is considered as zero for line breaking).
Thus, tag handling is in some sense transparent to pretty-printing
and does not interfere with usual indentation. Hence, a single
pretty printing routine can output both simple ``verbatim''
pretty printing routine can output both simple 'verbatim'
material or richer decorated output depending on the treatment of
tags. By default, tags are not active, hence the output is not
decorated with tag information. Once [set_tags] is set to [true],
@ -288,14 +288,14 @@ type tag = string;;
accordingly.
When a tag has been opened (or closed), it is both and successively
``printed'' and ``marked''. Printing a tag means calling a
'printed' and 'marked'. Printing a tag means calling a
formatter specific function with the name of the tag as argument:
that ``tag printing'' function can then print any regular material
that 'tag printing' function can then print any regular material
to the formatter (so that this material is enqueued as usual in the
formatter queue for further line-breaking computation). Marking a
tag means to output an arbitrary string (the ``tag marker''),
tag means to output an arbitrary string (the 'tag marker'),
directly into the output device of the formatter. Hence, the
formatter specific ``tag marking'' function must return the tag
formatter specific 'tag marking' function must return the tag
marker string associated to its tag argument. Being flushed
directly into the output device of the formatter, tag marker
strings are not considered as part of the printing material that
@ -412,10 +412,10 @@ type formatter_tag_functions = {
}
;;
(** The tag handling functions specific to a formatter:
[mark] versions are the ``tag marking'' functions that associate a string
[mark] versions are the 'tag marking' functions that associate a string
marker to a tag in order for the pretty-printing engine to flush
those markers as 0 length tokens in the output device of the formatter.
[print] versions are the ``tag printing'' functions that can perform
[print] versions are the 'tag printing' functions that can perform
regular printing when a tag is closed or opened. *)
val set_formatter_tag_functions : formatter_tag_functions -> unit;;
@ -585,11 +585,11 @@ val fprintf : formatter -> ('a, formatter, unit) format -> 'a;;
then an optional integer offset, and the closing [>] character.
Box type is one of [h], [v], [hv], [b], or [hov],
which stand respectively for an horizontal box, a vertical box,
an ``horizontal-vertical'' box, or an ``horizontal or
vertical'' box ([b] standing for an ``horizontal or
vertical'' box demonstrating indentation and [hov] standing
for a regular``horizontal or vertical'' box).
For instance, [@\[<hov 2>] opens an ``horizontal or vertical''
an 'horizontal-vertical' box, or an 'horizontal or
vertical' box ([b] standing for an 'horizontal or
vertical' box demonstrating indentation and [hov] standing
for a regular'horizontal or vertical' box).
For instance, [@\[<hov 2>] opens an 'horizontal or vertical'
box with indentation 2 as obtained with [open_hovbox 2].
For more details about boxes, see the various box opening
functions [open_*box].

View File

@ -19,7 +19,6 @@ type token =
| String of string
| Char of char
(* The string buffering machinery *)
let initial_buffer = String.create 32
@ -79,7 +78,7 @@ let make_lexer keywords =
Some '\'' -> Stream.junk strm__; Some (Char c)
| _ -> raise (Stream.Error "")
end
| Some '"' ->
| Some '\"' ->
Stream.junk strm__;
let s = strm__ in reset_buffer (); Some (String (string s))
| Some '-' -> Stream.junk strm__; neg_number strm__
@ -133,7 +132,7 @@ let make_lexer keywords =
| _ -> Some (Float (float_of_string (get_string ())))
and string (strm__ : _ Stream.t) =
match Stream.peek strm__ with
Some '"' -> Stream.junk strm__; get_string ()
Some '\"' -> Stream.junk strm__; get_string ()
| Some '\\' ->
Stream.junk strm__;
let c =

View File

@ -14,7 +14,7 @@
(** A generic lexical analyzer.
This module implements a simple ``standard'' lexical analyzer, presented
This module implements a simple 'standard' lexical analyzer, presented
as a function from character streams to token streams. It implements
roughly the lexical conventions of OCaml, but is parameterized by the
set of keywords of your language.
@ -48,9 +48,9 @@
string literals, enclosed in double quotes; [Char] for
character literals, enclosed in single quotes; [Ident] for
identifiers (either sequences of letters, digits, underscores
and quotes, or sequences of ``operator characters'' such as
and quotes, or sequences of 'operator characters' such as
[+], [*], etc); and [Kwd] for keywords (either identifiers or
single ``special characters'' such as [(], [}], etc). *)
single 'special characters' such as [(], [}], etc). *)
type token =
Kwd of string
| Ident of string

View File

@ -134,14 +134,14 @@ val to_string : int32 -> string
external bits_of_float : float -> int32 = "caml_int32_bits_of_float"
(** Return the internal representation of the given float according
to the IEEE 754 floating-point ``single format'' bit layout.
to the IEEE 754 floating-point 'single format' bit layout.
Bit 31 of the result represents the sign of the float;
bits 30 to 23 represent the (biased) exponent; bits 22 to 0
represent the mantissa. *)
external float_of_bits : int32 -> float = "caml_int32_float_of_bits"
(** Return the floating-point number whose internal representation,
according to the IEEE 754 floating-point ``single format'' bit layout,
according to the IEEE 754 floating-point 'single format' bit layout,
is the given [int32]. *)
type t = int32

View File

@ -156,14 +156,14 @@ val to_string : int64 -> string
external bits_of_float : float -> int64 = "caml_int64_bits_of_float"
(** Return the internal representation of the given float according
to the IEEE 754 floating-point ``double format'' bit layout.
to the IEEE 754 floating-point 'double format' bit layout.
Bit 63 of the result represents the sign of the float;
bits 62 to 52 represent the (biased) exponent; bits 51 to 0
represent the mantissa. *)
external float_of_bits : int64 -> float = "caml_int64_float_of_bits"
(** Return the floating-point number whose internal representation,
according to the IEEE 754 floating-point ``double format'' bit layout,
according to the IEEE 754 floating-point 'double format' bit layout,
is the given [int64]. *)
type t = int64

View File

@ -76,7 +76,7 @@ val to_channel : out_channel -> 'a -> extern_flags list -> unit
If [flags] does not contain [Marshal.Closures],
marshaling fails when it encounters a functional value
inside [v]: only ``pure'' data structures, containing neither
inside [v]: only 'pure' data structures, containing neither
functions nor objects, can safely be transmitted between
different programs. If [flags] contains [Marshal.Closures],
functional values will be marshaled as a position in the code

View File

@ -120,7 +120,7 @@ external not : bool -> bool = "%boolnot"
(** The boolean negation. *)
external ( && ) : bool -> bool -> bool = "%sequand"
(** The boolean ``and''. Evaluation is sequential, left-to-right:
(** The boolean 'and'. Evaluation is sequential, left-to-right:
in [e1 && e2], [e1] is evaluated first, and if it returns [false],
[e2] is not evaluated at all. *)
@ -128,7 +128,7 @@ external ( & ) : bool -> bool -> bool = "%sequand"
(** @deprecated {!Pervasives.( && )} should be used instead. *)
external ( || ) : bool -> bool -> bool = "%sequor"
(** The boolean ``or''. Evaluation is sequential, left-to-right:
(** The boolean 'or'. Evaluation is sequential, left-to-right:
in [e1 || e2], [e1] is evaluated first, and if it returns [true],
[e2] is not evaluated at all. *)
@ -232,7 +232,7 @@ external ( asr ) : int -> int -> int = "%asrint"
Floating-point operations never raise an exception on overflow,
underflow, division by zero, etc. Instead, special IEEE numbers
are returned as appropriate, such as [infinity] for [1.0 /. 0.0],
[neg_infinity] for [-1.0 /. 0.0], and [nan] (``not a number'')
[neg_infinity] for [-1.0 /. 0.0], and [nan] ('not a number')
for [0.0 /. 0.0]. These special numbers then propagate through
floating-point computations as expected: for instance,
[1.0 /. infinity] is [0.0], and any arithmetic operation with [nan]
@ -393,7 +393,7 @@ val neg_infinity : float
val nan : float
(** A special floating-point value denoting the result of an
undefined operation such as [0.0 /. 0.0]. Stands for
``not a number''. Any floating-point operation with [nan] as
'not a number'. Any floating-point operation with [nan] as
argument returns [nan] as result. As for floating-point comparisons,
[=], [<], [<=], [>] and [>=] return [false] and [<>] returns [true]
if one or both of their arguments is [nan]. *)
@ -948,7 +948,7 @@ val at_exit : (unit -> unit) -> unit
termination time. The functions registered with [at_exit]
will be called when the program executes {!Pervasives.exit},
or terminates, either normally or because of an uncaught exception.
The functions are called in ``last in, first out'' order:
The functions are called in 'last in, first out' order:
the function most recently added with [at_exit] is called first. *)
(**/**)

View File

@ -64,7 +64,7 @@ end
let bad_conversion sfmt i c =
invalid_arg
("Printf: bad conversion %" ^ String.make 1 c ^ ", at char number " ^
string_of_int i ^ " in format string ``" ^ sfmt ^ "''")
string_of_int i ^ " in format string \'" ^ sfmt ^ "\'")
;;
let bad_conversion_format fmt i c =
@ -73,8 +73,8 @@ let bad_conversion_format fmt i c =
let incomplete_format fmt =
invalid_arg
("Printf: premature end of format string ``" ^
Sformat.to_string fmt ^ "''")
("Printf: premature end of format string \'" ^
Sformat.to_string fmt ^ "\'")
;;
(* Parses a string conversion to return the specified length and the
@ -320,7 +320,7 @@ let list_iter_i f l =
loop 0 l
;;
(* ``Abstracting'' version of kprintf: returns a (curried) function that
(* 'Abstracting' version of kprintf: returns a (curried) function that
will print when totally applied.
Note: in the following, we are careful not to be badly caught
by the compiler optimizations for the representation of arrays. *)
@ -371,17 +371,17 @@ type positional_specification =
(* To scan an optional positional parameter specification,
i.e. an integer followed by a [$].
Calling [got_spec] with appropriate arguments, we ``return'' a positional
Calling [got_spec] with appropriate arguments, we 'return' a positional
specification and an index to go on scanning the [fmt] format at hand.
Note that this is optimized for the regular case, i.e. no positional
parameter, since in this case we juste ``return'' the constant
[Spec_none]; in case we have a positional parameter, we ``return'' a
parameter, since in this case we juste 'return' the constant
[Spec_none]; in case we have a positional parameter, we 'return' a
[Spec_index] [positional_specification] which is a bit more costly.
Note also that we do not support [*$] specifications, since this would
lead to type checking problems: a [*$] positional specification means
``take the next argument to [printf] (which must be an integer value)'',
'take the next argument to [printf] (which must be an integer value)',
name this integer value $n$; [*$] now designates parameter $n$.
Unfortunately, the type of a parameter specified via a [*$] positional
@ -466,11 +466,16 @@ let format_float_lexeme =
After consuming the appropriate number of arguments and formatting
them, one of the following five continuations described below is called:
- [cont_s] for outputting a string (arguments: arg num, string, next pos)
- [cont_a] for performing a %a action (arguments: arg num, fn, arg, next pos)
- [cont_t] for performing a %t action (arguments: arg num, fn, next pos)
- [cont_f] for performing a flush action (arguments: arg num, next pos)
- [cont_m] for performing a %( action (arguments: arg num, sfmt, next pos)
- [cont_s] for outputting a string
(arguments: arg num, string, next pos)
- [cont_a] for performing a %a action
(arguments: arg num, fn, arg, next pos)
- [cont_t] for performing a %t action
(arguments: arg num, fn, next pos)
- [cont_f] for performing a flush action
(arguments: arg num, next pos)
- [cont_m] for performing a %( action
(arguments: arg num, sfmt, next pos)
"arg num" is the index in array [args] of the next argument to [printf].
"next pos" is the position in [fmt] of the first character following

View File

@ -258,7 +258,7 @@ module Scanning : SCANNING = struct
We cannot prevent the scanning mechanism to use one lookahead character,
if needed by the semantics of the format string specifications (e.g. a
trailing ``skip space'' specification in the format string); in this case,
trailing 'skip space' specification in the format string); in this case,
the mandatory lookahead character is indeed read from the input and not
used to return the token read. It is thus mandatory to be able to store
an unused lookahead character somewhere to get it as the first character
@ -292,8 +292,8 @@ module Scanning : SCANNING = struct
This phenomenon of reading mess is even worse when one defines more than
one scanning buffer reading from the same input channel
[ic]. Unfortunately, we have no simple way to get rid of this problem
(unless the basic input channel API is modified to offer a ``consider this
char as unread'' procedure to keep back the unused lookahead character as
(unless the basic input channel API is modified to offer a 'consider this
char as unread' procedure to keep back the unused lookahead character as
available in the input channel for further reading).
To prevent some of the confusion the scanning buffer allocation function
@ -340,14 +340,14 @@ module Scanning : SCANNING = struct
One could try to define [stdib] as a scanning buffer reading a character
at a time (no bufferization at all), but unfortunately the top-level
interaction would be wrong. This is due to some kind of
``race condition'' when reading from [Pervasives.stdin],
'race condition' when reading from [Pervasives.stdin],
since the interactive compiler and [scanf] will simultaneously read the
material they need from [Pervasives.stdin]; then, confusion will result
from what should be read by the top-level and what should be read
by [scanf].
This is even more complicated by the one character lookahead that [scanf]
is sometimes obliged to maintain: the lookahead character will be available
for the next ([scanf]) entry, seemingly coming from nowhere.
is sometimes obliged to maintain: the lookahead character will be
available for the next ([scanf]) entry, seemingly coming from nowhere.
Also no [End_of_file] is raised when reading from stdin: if not enough
characters have been read, we simply ask to read more. *)
let stdin =
@ -448,12 +448,12 @@ let bad_conversion fmt i c =
invalid_arg
(Printf.sprintf
"scanf: bad conversion %%%C, at char number %i \
in format string ``%s''" c i (Sformat.to_string fmt))
in format string \'%s\'" c i (Sformat.to_string fmt))
;;
let incomplete_format fmt =
invalid_arg
(Printf.sprintf "scanf: premature end of format string ``%s''"
(Printf.sprintf "scanf: premature end of format string \'%s\'"
(Sformat.to_string fmt))
;;
@ -471,7 +471,7 @@ let character_mismatch c ci =
let format_mismatch_err fmt1 fmt2 =
Printf.sprintf
"format read ``%s'' does not match specification ``%s''" fmt1 fmt2
"format read \'%s\' does not match specification \'%s\'" fmt1 fmt2
;;
let format_mismatch fmt1 fmt2 = bad_input (format_mismatch_err fmt1 fmt2);;
@ -493,8 +493,8 @@ let compatible_format_type fmt1 fmt2 =
to complete scanning"!)
That's why, waiting for a better solution, we use checked_peek_char here.
We are also careful to treat "\r\n" in the input as an end of line marker: it
always matches a '\n' specification in the input format string. *)
We are also careful to treat "\r\n" in the input as an end of line marker:
it always matches a '\n' specification in the input format string. *)
let rec check_char ib c =
let ci = Scanning.checked_peek_char ib in
if ci = c then Scanning.invalidate_current_char ib else begin
@ -934,8 +934,10 @@ let scan_Char width ib =
and find_char width =
match check_next_char_for_char width ib with
| '\\' -> find_stop (scan_backslash_char (Scanning.ignore_char width ib) ib)
| c -> find_stop (Scanning.store_char width ib c)
| '\\' ->
find_stop (scan_backslash_char (Scanning.ignore_char width ib) ib)
| c ->
find_stop (Scanning.store_char width ib c)
and find_stop width =
match check_next_char_for_char width ib with
@ -1263,7 +1265,7 @@ let rec skip_whites ib =
let scanf_bad_input ib = function
| Scan_failure s | Failure s ->
let i = Scanning.char_count ib in
bad_input (Printf.sprintf "scanf: bad input at char number %i: ``%s''" i s)
bad_input (Printf.sprintf "scanf: bad input at char number %i: \'%s\'" i s)
| x -> raise x
;;

View File

@ -100,7 +100,7 @@ type scanbuf = in_channel;;
input, and a token buffer to store the string matched so far.
Note: a scanning action may often require to examine one character in
advance; when this ``lookahead'' character does not belong to the token
advance; when this 'lookahead' character does not belong to the token
read, it is stored back in the scanning buffer and becomes the next
character yet to be read.
*)
@ -263,7 +263,7 @@ val bscanf : Scanning.in_channel -> ('a, 'b, 'c, 'd) scanner;;
special exceptions to this rule: the space character ([' '] or ASCII code
32) and the line feed character (['\n'] or ASCII code 10).
A space does not match a single space character, but any amount of
``whitespace'' in the input. More precisely, a space inside the format
'whitespace' in the input. More precisely, a space inside the format
string matches {e any number} of tab, space, line feed and carriage
return characters. Similarly, a line feed character in the format string
matches either a single line feed or a carriage return followed by a line