diff options
author | Pierre Weis <Pierre.Weis@inria.fr> | 2013-03-19 07:58:59 +0000 |
---|---|---|
committer | Pierre Weis <Pierre.Weis@inria.fr> | 2013-03-19 07:58:59 +0000 |
commit | 54b4e5e79ec755e064d2cbb001bf1c66723823e6 (patch) | |
tree | b6ed85969bd335dc091c7773ef61130d49b140dd /stdlib | |
parent | 75b8c0184f38ae1c23dec9525cefafed2ea9f2d7 (diff) |
sprintf now compatible with proper %a application with formatters. Deprecating pp_ versions of get/set_all_formatter_output_functions. Documentation review.
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@13411 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
Diffstat (limited to 'stdlib')
-rw-r--r-- | stdlib/format.mli | 102 |
1 files changed, 59 insertions, 43 deletions
diff --git a/stdlib/format.mli b/stdlib/format.mli index d03500e3c..b24056c8c 100644 --- a/stdlib/format.mli +++ b/stdlib/format.mli @@ -378,7 +378,7 @@ type formatter_out_functions = { } ;; -val set_formatter_out_functions: formatter_out_functions -> unit;; +val set_formatter_out_functions : formatter_out_functions -> unit;; (** [set_formatter_out_functions out_funs] Redirect the pretty-printer output to the functions [out_funs.out_string] and [out_funs.out_flush] as described in [set_formatter_output_functions]. In @@ -394,34 +394,11 @@ val set_formatter_out_functions: formatter_out_functions -> unit;; values for [out_space] and [out_newline] are [out_string (String.make n ' ') 0 n] and [out_string "\n" 0 1]. *) -val get_formatter_out_functions: unit -> formatter_out_functions;; +val get_formatter_out_functions : unit -> formatter_out_functions;; (** Return the current output functions of the pretty-printer, including line breaking and indentation functions. Useful to record the current setting and restore it afterwards. *) -val set_all_formatter_output_functions : - out:(string -> int -> int -> unit) -> - flush:(unit -> unit) -> - newline:(unit -> unit) -> - spaces:(int -> unit) -> - unit -;; -(** - Deprecated. - @since 4.0. -*) - -val get_all_formatter_output_functions : - unit -> - (string -> int -> int -> unit) * - (unit -> unit) * - (unit -> unit) * - (int -> unit) -;; -(** - Deprecated. - @since 4.0. -*) (** {6:tagsmeaning Changing the meaning of printing semantics tags} *) type formatter_tag_functions = { @@ -565,21 +542,18 @@ val pp_set_formatter_output_functions : val pp_get_formatter_output_functions : formatter -> unit -> (string -> int -> int -> unit) * (unit -> unit) ;; -val pp_set_all_formatter_output_functions : - formatter -> out:(string -> int -> int -> unit) -> flush:(unit -> unit) -> - newline:(unit -> unit) -> spaces:(int -> unit) -> unit -;; -val pp_get_all_formatter_output_functions : - formatter -> unit -> - (string -> int -> int -> unit) * (unit -> unit) * (unit -> unit) * - (int -> unit) -;; val pp_set_formatter_tag_functions : formatter -> formatter_tag_functions -> unit ;; val pp_get_formatter_tag_functions : formatter -> unit -> formatter_tag_functions ;; +val pp_set_formatter_out_functions : + formatter -> formatter_out_functions -> unit +;; +val get_formatter_out_functions : + formatter -> unit -> formatter_out_functions +;; (** These functions are the basic ones: usual functions operating on the standard formatter are defined via partial evaluation of these primitives. For instance, @@ -615,18 +589,15 @@ val fprintf : formatter -> ('a, formatter, unit) format -> 'a;; For more details about boxes, see the various box opening functions [open_*box]. - [@\]]: close the most recently opened pretty-printing box. - - [@,]: output a good break as with [print_cut ()]. - - [@ ]: output a space, as with [print_space ()]. - - [@\n]: force a newline, as with [force_newline ()]. - - [@;]: output a good break as with [print_break]. The + - [@,]: output a good break hint, as with [print_cut ()]. + - [@ ]: output a good break space, as with [print_space ()]. + - [@;]: output a fully specified good break as with [print_break]. The [nspaces] and [offset] parameters of the break may be optionally specified with the following syntax: the [<] character, followed by an integer [nspaces] value, then an integer [offset], and a closing [>] character. If no parameters are provided, the good break defaults to a - space. - - [@?]: flush the pretty printer as with [print_flush ()]. - This is equivalent to the conversion [%!]. + good break space. - [@.]: flush the pretty printer and output a new line, as with [print_newline ()]. - [@<n>]: print the following item as if it were of length [n]. @@ -644,6 +615,9 @@ val fprintf : formatter -> ('a, formatter, unit) format -> 'a;; For more details about tags, see the functions [open_tag] and [close_tag]. - [@\}]: close the most recently opened tag. + - [@?]: flush the pretty printer as with [print_flush ()]. + This is equivalent to the conversion [%!]. + - [@\n]: force a newline, as with [force_newline ()]. Example: [printf "@[%s@ %d@]@." "x =" 1] is equivalent to [open_box (); print_string "x ="; print_space (); @@ -664,7 +638,7 @@ val printf : ('a, formatter, unit) format -> 'a;; val eprintf : ('a, formatter, unit) format -> 'a;; (** Same as [fprintf] above, but output on [err_formatter]. *) -val sprintf : ('a, unit, string) format -> 'a;; +val sprintf : ('a, formatter, unit, string) format4 -> 'a; (** Same as [printf] above, but instead of printing on a formatter, returns a string containing the result of formatting the arguments. Note that the pretty-printer queue is flushed at the end of {e each @@ -677,7 +651,11 @@ val sprintf : ('a, unit, string) format -> 'a;; Alternatively, you can use [Format.fprintf] with a formatter writing to a buffer of your own: flushing the formatter and the buffer at the end of - pretty-printing returns the desired string. *) + pretty-printing returns the desired string. + + The type of [sprintf] is general enough to interact nicely with [%a] conversions. + @since 4.0 + *) val ifprintf : formatter -> ('a, formatter, unit) format -> 'a;; (** Same as [fprintf] above, but does not print anything. @@ -716,3 +694,41 @@ val bprintf : Buffer.t -> ('a, formatter, unit) format -> 'a;; val kprintf : (string -> 'a) -> ('b, unit, string, 'a) format4 -> 'b;; (** A deprecated synonym for [ksprintf]. *) + +val set_all_formatter_output_functions : + out:(string -> int -> int -> unit) -> + flush:(unit -> unit) -> + newline:(unit -> unit) -> + spaces:(int -> unit) -> + unit +;; +(** Deprecated. Subsumed by [set_formatter_out_functions]. + @since 4.0. +*) + +val get_all_formatter_output_functions : + unit -> + (string -> int -> int -> unit) * + (unit -> unit) * + (unit -> unit) * + (int -> unit) +;; +(** Deprecated. Subsumed by [get_formatter_out_functions]. + @since 4.0. +*) +val pp_set_all_formatter_output_functions : + formatter -> out:(string -> int -> int -> unit) -> flush:(unit -> unit) -> + newline:(unit -> unit) -> spaces:(int -> unit) -> unit +;; +(** Deprecated. Subsumed by [pp_set_formatter_out_functions]. + @since 4.0. +*) + +val pp_get_all_formatter_output_functions : + formatter -> unit -> + (string -> int -> int -> unit) * (unit -> unit) * (unit -> unit) * + (int -> unit) +;; +(** Deprecated. Subsumed by [pp_get_formatter_out_functions]. + @since 4.0. +*) |