Introducing format %$ (to print strings with variables substitution)

and %! (to flush the output). See printf.mli for details.


git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@5517 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
master
Pierre Weis 2003-04-28 09:44:21 +00:00
parent e9cda5216b
commit 9e6895aded
3 changed files with 18 additions and 6 deletions

View File

@ -113,6 +113,11 @@ let extract_format fmt start stop widths =
Buffer.add_char b c; fill_format (succ i) w
in fill_format start (List.rev widths)
let substitute_string f s =
let b = Buffer.create (2 * String.length s) in
Buffer.add_substitute b f s;
Buffer.contents b;;
let format_int_with_conv conv fmt i =
match conv with
| 'b' -> format_binary_int fmt i
@ -212,8 +217,11 @@ let scan_format fmt pos cont_s cont_a cont_t cont_f =
| _ ->
bad_format fmt pos
end
| '$' ->
| '!' ->
Obj.magic (cont_f (succ i))
| '$' ->
Obj.magic (fun f s ->
cont_s (substitute_string f s) (succ i))
| _ ->
bad_format fmt pos
in scan_flags [] (pos + 1)
@ -281,5 +289,3 @@ let bprintf dest fmt =
printer dest; doprn i
and cont_f i = doprn i
in doprn 0

View File

@ -63,7 +63,8 @@ val fprintf : out_channel -> ('a, out_channel, unit, unit) format -> 'a
in the output of [fprintf] at the current point.
- [t]: same as [%a], but takes only one argument (with type
[out_channel -> unit]) and apply it to [outchan].
- [$]: take no argument and flush the output.
- [!]: take no argument and flush the output.
- [$]: take two arguments.
- [%]: take no argument and output one [%] character.
The optional flags include:

View File

@ -682,7 +682,7 @@ let type_format loc fmt =
and scan_conversion i j =
if j >= len then incomplete i else
match fmt.[j] with
| '%' | '$' -> scan_format (j + 1)
| '%' | '!' -> 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' ->
@ -690,10 +690,15 @@ let type_format loc fmt =
| 'f' | 'e' | 'E' | 'g' | 'G' | 'F' -> conversion j Predef.type_float
| 'B' -> conversion j Predef.type_bool
| 'a' ->
let ty_arg = newvar() in
let ty_arg = newvar () in
let ty_a = ty_arrow ty_input (ty_arrow ty_arg ty_aresult) in
let ty_aresult, ty_result = conversion j ty_arg in
ty_aresult, ty_arrow ty_a ty_result
| '$' ->
let ty_arg = Predef.type_string in
let ty_f = ty_arrow Predef.type_string Predef.type_string in
let ty_aresult, ty_result = conversion j ty_arg in
ty_aresult, ty_arrow ty_f ty_result
| 'r' ->
let ty_res = newvar() in
let ty_r = ty_arrow ty_input ty_res in