PR#1675, voir aussi PR#1438

git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@5641 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
master
Damien Doligez 2003-07-01 16:30:12 +00:00
parent 49ee5083e2
commit b37e53cef1
5 changed files with 15 additions and 13 deletions

View File

@ -164,7 +164,7 @@ let scan_format fmt pos cont_s cont_a cont_t cont_f =
if conv = 'c'
then cont_s (String.make 1 c) (succ i)
else cont_s ("'" ^ Char.escaped c ^ "'") (succ i))
| 'b' | 'd' | 'i' | 'o' | 'x' | 'X' | 'u' | 'N' as conv ->
| 'd' | 'i' | 'o' | 'x' | 'X' | 'u' | 'N' as conv ->
Obj.magic(fun (n: int) ->
cont_s (format_int_with_conv conv
(extract_format fmt pos i widths) n)
@ -175,7 +175,7 @@ let scan_format fmt pos cont_s cont_a cont_t cont_f =
if conv = 'F' then string_of_float f else
format_float (extract_format fmt pos i widths) f in
cont_s s (succ i))
| 'B' ->
| 'B' | 'b' ->
Obj.magic(fun (b: bool) ->
cont_s (string_of_bool b) (succ i))
| 'a' ->

View File

@ -35,7 +35,6 @@ val fprintf : out_channel -> ('a, out_channel, unit, unit) format -> 'a
- [X]: convert an integer argument to unsigned hexadecimal,
using uppercase letters.
- [o]: convert an integer argument to unsigned octal.
- [b]: convert an integer argument to unsigned binary.
- [s]: insert a string argument.
- [S]: insert a string argument in Caml syntax (double quotes, escapes).
- [c]: insert a character argument.
@ -49,6 +48,8 @@ val fprintf : out_channel -> ('a, out_channel, unit, unit) format -> 'a
- [g] or [G]: convert a floating-point argument to decimal notation,
in style [f] or [e], [E] (whichever is more compact).
- [B]: convert a boolean argument to the string [true] or [false]
- [b]: convert a boolean argument (for backward compatibility; do not
use in new programs).
- [ld], [li], [lu], [lx], [lX], [lo]: convert an [int32] argument to
the format specified by the second letter (decimal, hexadecimal, etc).
- [nd], [ni], [nu], [nx], [nX], [no]: convert a [nativeint] argument to

View File

@ -659,7 +659,7 @@ let kscanf ib ef fmt f =
let x =
if conv = 'c' then scan_char max ib else scan_Char max ib in
scan_fmt (stack f (token_char ib)) (i + 1)
| 'b' | 'd' | 'i' | 'o' | 'u' | 'x' | 'X' as conv ->
| 'd' | 'i' | 'o' | 'u' | 'x' | 'X' as conv ->
let x = scan_int conv max ib in
scan_fmt (stack f (token_int conv ib)) (i + 1)
| 'f' | 'g' | 'G' | 'e' | 'E' | 'F' ->
@ -677,7 +677,7 @@ let kscanf ib ef fmt f =
| 'S' ->
let x = scan_String max ib in
scan_fmt (stack f (token_string ib)) (i + 1)
| 'B' ->
| 'B' | 'b' ->
let x = scan_bool max ib in
scan_fmt (stack f (token_bool ib)) (i + 1)
| 'l' | 'n' | 'L' as t ->
@ -686,7 +686,7 @@ let kscanf ib ef fmt f =
let x = Scanning.char_count ib in
scan_fmt (stack f x) i else begin
match fmt.[i] with
| 'b' | 'd' | 'i' | 'o' | 'u' | 'x' | 'X' as conv ->
| 'd' | 'i' | 'o' | 'u' | 'x' | 'X' as conv ->
let x = scan_int conv max ib in
begin match t with
| 'l' -> scan_fmt (stack f (token_int32 conv ib)) (i + 1)

View File

@ -113,7 +113,6 @@ val bscanf :
- [u]: reads an unsigned decimal integer.
- [x] or [X]: reads an unsigned hexadecimal integer.
- [o]: reads an unsigned octal integer.
- [b]: reads an unsigned binary integer.
- [s]: reads a string argument (by default strings end with a space).
- [S]: reads a delimited string argument (delimiters and special
escaped characters follow the lexical conventions of Caml).
@ -126,11 +125,13 @@ val bscanf :
floating-point number in decimal notation, in the style [dddd.ddd
e/E+-dd].
- [B]: reads a boolean argument ([true] or [false]).
- [ld], [li], [lu], [lx], [lX], [lo], [lb]: reads an [int32] argument to
- [b]: reads a boolean argument (for backward compatibility; do not use
in new programs).
- [ld], [li], [lu], [lx], [lX], [lo]: reads an [int32] argument to
the format specified by the second letter (decimal, hexadecimal, etc).
- [nd], [ni], [nu], [nx], [nX], [no], [nb]: reads a [nativeint] argument to
- [nd], [ni], [nu], [nx], [nX], [no]: reads a [nativeint] argument to
the format specified by the second letter.
- [Ld], [Li], [Lu], [Lx], [LX], [Lo], [Lb]: reads an [int64] argument to
- [Ld], [Li], [Lu], [Lx], [LX], [Lo]: reads an [int64] argument to
the format specified by the second letter.
- [\[ range \]]: reads characters that matches one of the characters
mentioned in the range of characters [range] (or not mentioned in

View File

@ -685,10 +685,10 @@ let type_format loc fmt =
| '%' | '!' -> scan_format (j + 1)
| 's' | 'S' | '[' -> conversion j Predef.type_string
| 'c' | 'C' -> conversion j Predef.type_char
| 'b' | 'd' | 'i' | 'o' | 'x' | 'X' | 'u' | 'N' ->
| 'd' | 'i' | 'o' | 'x' | 'X' | 'u' | 'N' ->
conversion j Predef.type_int
| 'f' | 'e' | 'E' | 'g' | 'G' | 'F' -> conversion j Predef.type_float
| 'B' -> conversion j Predef.type_bool
| 'B' | 'b' -> conversion j Predef.type_bool
| 'a' ->
let ty_arg = newvar () in
let ty_a = ty_arrow ty_input (ty_arrow ty_arg ty_aresult) in
@ -705,7 +705,7 @@ let type_format loc fmt =
let j = j + 1 in
if j >= len then incomplete i else begin
match fmt.[j] with
| 'b' | 'd' | 'i' | 'o' | 'x' | 'X' | 'u' ->
| 'd' | 'i' | 'o' | 'x' | 'X' | 'u' ->
let ty_arg =
match conv with
| 'l' -> Predef.type_int32