summaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
authorPierre Weis <Pierre.Weis@inria.fr>2001-11-04 21:25:23 +0000
committerPierre Weis <Pierre.Weis@inria.fr>2001-11-04 21:25:23 +0000
commit4fcb648544e4aeb954cd94dcc0077c6f522ceac9 (patch)
tree33f81cba4d4acace5feba3f2af6623d3867fac41
parentbae5c6bfdd6c4e05140addc75e7311c8aed75b00 (diff)
Revu encore une fois la doc. Details + explications supplementaires
pour sprintf et surtout bprintf qui sont d'emploi delicat si l'on veut en faire des appels repetes et correles (faut-il supprimer bprintf pour format ?)... git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@3974 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
-rw-r--r--stdlib/format.mli166
1 files changed, 87 insertions, 79 deletions
diff --git a/stdlib/format.mli b/stdlib/format.mli
index e29522b73..6341b4a68 100644
--- a/stdlib/format.mli
+++ b/stdlib/format.mli
@@ -70,6 +70,7 @@
(** {2 Boxes} *)
+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.
@@ -80,53 +81,51 @@
(demonstrating the indentation of the box).
When a new line is printed in the box, [d] is added to the
current indentation. *)
-val open_box : int -> unit;;
-
-(** Close the most recently opened pretty-printing box. *)
val close_box : unit -> unit;;
-
+(** Close the most recently opened pretty-printing box. *)
(** {2 Formatting functions} *)
-(** [print_string str] prints [str] in the current box. *)
val print_string : string -> unit;;
+(** [print_string str] prints [str] in the current box. *)
+val print_as : int -> string -> unit;;
(** [print_as len str] prints [str] in the
current box. The pretty-printer formats [str] as if
it were of length [len]. *)
-val print_as : int -> string -> unit;;
-(** Print an integer in the current box. *)
val print_int : int -> unit;;
+(** Print an integer in the current box. *)
-(** Print a floating point number in the current box. *)
val print_float : float -> unit;;
+(** Print a floating point number in the current box. *)
-(** Print a character in the current box. *)
val print_char : char -> unit;;
+(** Print a character in the current box. *)
-(** Print an boolean in the current box. *)
val print_bool : bool -> unit;;
+(** Print a boolean in the current box. *)
(** {2 Break hints} *)
+val print_space : unit -> unit;;
(** [print_space ()] is used to separate items (typically to print
a space between two words).
It indicates that the line may be split at this
point. It either prints one space or splits the line.
It is equivalent to [print_break 1 0]. *)
-val print_space : unit -> unit;;
+val print_cut : unit -> unit;;
(** [print_cut ()] is used to mark a good break position.
It indicates that the line may be split at this
point. It either prints nothing or splits the line.
This allows line splitting at the current
point, without printing spaces or adding indentation.
It is equivalent to [print_break 0 0]. *)
-val print_cut : unit -> unit;;
+val print_break : int -> int -> unit;;
(** Insert a break hint in a pretty-printing box.
[print_break nspaces offset] indicates that the line may
be split (a newline character is printed) at this point,
@@ -135,84 +134,84 @@ val print_cut : unit -> unit;;
If the line is split at that point, [offset] is added to
the current indentation. If the line is not split,
[nspaces] spaces are printed. *)
-val print_break : int -> int -> unit;;
+val print_flush : unit -> unit;;
(** Flush the pretty printer: all opened boxes are closed,
and all pending text is displayed. *)
-val print_flush : unit -> unit;;
-(** Equivalent to [print_flush] followed by a new line. *)
val print_newline : unit -> unit;;
+(** Equivalent to [print_flush] followed by a new line. *)
+val force_newline : unit -> unit;;
(** Force a newline in the current box. Not the normal way of
pretty-printing, you should prefer break hints. *)
-val force_newline : unit -> unit;;
+val print_if_newline : unit -> unit;;
(** Execute the next formatting command if the preceding line
has just been split. Otherwise, ignore the next formatting
command. *)
-val print_if_newline : unit -> unit;;
(** {2 Margin} *)
+val set_margin : int -> unit;;
(** [set_margin d] sets the value of the right margin
to [d] (in characters): this value is used to detect line
overflows that leads to split lines.
Nothing happens if [d] is smaller than 2 or
bigger than 999999999. *)
-val set_margin : int -> unit;;
-(** Return the position of the right margin. *)
val get_margin : unit -> int;;
+(** Return the position of the right margin. *)
(** {2 Maximum indentation limit} *)
+val set_max_indent : int -> unit;;
(** [set_max_indent d] sets the value of the maximum
indentation limit to [d] (in characters):
once this limit is reached, boxes are rejected to the left,
if they do not fit on the current line.
Nothing happens if [d] is smaller than 2 or
bigger than 999999999. *)
-val set_max_indent : int -> unit;;
-(** Return the value of the maximum indentation limit (in characters). *)
val get_max_indent : unit -> int;;
+(** Return the value of the maximum indentation limit (in characters). *)
(** {2 Formatting depth: maximum number of boxes allowed before ellipsis} *)
+val set_max_boxes : int -> unit;;
(** [set_max_boxes max] sets the maximum number
of boxes simultaneously opened.
Material inside boxes nested deeper is printed as an
ellipsis (more precisely as the text returned by
[get_ellipsis_text ()]).
Nothing happens if [max] is not greater than 1. *)
-val set_max_boxes : int -> unit;;
-(** Return the maximum number of boxes allowed before ellipsis. *)
val get_max_boxes : unit -> int;;
+(** Return the maximum number of boxes allowed before ellipsis. *)
-(** Test the maximum number of boxes allowed have already been opened. *)
val over_max_boxes : unit -> bool;;
+(** Test if the maximum number of boxes allowed have already been opened. *)
(** {2 Advanced formatting} *)
+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
(new lines may still occur inside boxes nested deeper). *)
-val open_hbox : unit -> unit;;
+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
box leads to a new line.
When a new line is printed in the box, [d] is added to the
current indentation. *)
-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
@@ -220,8 +219,8 @@ val open_vbox : int -> unit;;
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_hvbox : int -> unit;;
+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
@@ -229,17 +228,17 @@ val open_hvbox : int -> unit;;
on the line to print the remainder of the box.
When a new line is printed in the box, [d] is added to the
current indentation. *)
-val open_hovbox : int -> unit;;
(** {2 Tabulations} *)
-(** Open a tabulation box. *)
val open_tbox : unit -> unit;;
+(** Open a tabulation box. *)
-(** Close the most recently opened tabulation box. *)
val close_tbox : unit -> unit;;
+(** Close the most recently opened tabulation box. *)
+val print_tbreak : int -> int -> unit;;
(** Break hint in a tabulation box.
[print_tbreak spaces offset] moves the insertion point to
the next tabulation ([spaces] being added to this position).
@@ -250,51 +249,53 @@ val close_tbox : unit -> unit;;
tabulation of the box.
If a new line is printed, [offset] is added to the current
indentation. *)
-val print_tbreak : int -> int -> unit;;
-(** Set a tabulation mark at the current insertion point. *)
val set_tab : unit -> unit;;
+(** Set a tabulation mark at the current insertion point. *)
-(** [print_tab ()] is equivalent to [print_tbreak (0,0)]. *)
val print_tab : unit -> unit;;
+(** [print_tab ()] is equivalent to [print_tbreak (0,0)]. *)
(** {2 Ellipsis} *)
+val set_ellipsis_text : string -> unit;;
(** Set the text of the ellipsis printed when too many boxes
are opened (a single dot, [.], by default). *)
-val set_ellipsis_text : string -> unit;;
-(** Return the text of the ellipsis. *)
val get_ellipsis_text : unit -> string;;
+(** Return the text of the ellipsis. *)
(** {2 Redirecting formatter output} *)
-(** Redirect the pretty-printer output to the given channel. *)
val set_formatter_out_channel : out_channel -> unit;;
+(** Redirect the pretty-printer output to the given channel. *)
(** {2 Changing the meaning of printing material} *)
+val set_formatter_output_functions :
+ (string -> int -> int -> unit) -> (unit -> unit) -> unit;;
(** [set_formatter_output_functions out flush] redirects the
pretty-printer output to the functions [out] and [flush].
The [out] function performs the pretty-printer output.
It is called with a string [s], a start position [p],
and a number of characters [n]; it is supposed to output
- characters [p] to [p+n-1] of [s]. The [flush] function is
+ characters [p] to [p + n - 1] of [s]. The [flush] function is
called whenever the pretty-printer is flushed using
[print_flush] or [print_newline]. *)
-val set_formatter_output_functions :
- (string -> int -> int -> unit) -> (unit -> unit) -> unit;;
-(** Return the current output functions of the pretty-printer. *)
val get_formatter_output_functions :
unit -> (string -> int -> int -> unit) * (unit -> unit);;
+(** Return the current output functions of the pretty-printer. *)
(** {2 Changing the meaning of pretty printing (indentation, line breaking, and printing material)} *)
+val set_all_formatter_output_functions :
+ out:(string -> int -> int -> unit) -> flush:(unit -> unit) ->
+ newline:(unit -> unit) -> spaces:(int -> unit) -> unit;;
(** [set_all_formatter_output_functions out flush outnewline outspace]
redirects the pretty-printer output to the functions
[out] and [flush] as described in
@@ -310,81 +311,72 @@ val get_formatter_output_functions :
connected to [out] and [flush]: respective default values for
[outspace] and [outnewline] are [out (String.make n ' ') 0 n]
and [out "\n" 0 1]. *)
-val set_all_formatter_output_functions :
- out:(string -> int -> int -> unit) -> flush:(unit -> unit) ->
- newline:(unit -> unit) -> spaces:(int -> unit) -> unit;;
-(** Return the current output functions of the pretty-printer,
- including line breaking and indentation functions. *)
val get_all_formatter_output_functions : unit ->
(string -> int -> int -> unit) * (unit -> unit) *
(unit -> unit) * (int -> unit);;
+(** Return the current output functions of the pretty-printer,
+ including line breaking and indentation functions. *)
(** {2 Multiple formatted output} *)
+type formatter;;
(** Abstract data type corresponding to a pretty-printer and
all its machinery.
Defining new pretty-printers permits the output of
material in parallel on several channels.
- Parameters of the pretty-printer are local to the pretty-printer:
+ Parameters of a pretty-printer are local to this pretty-printer:
margin, maximum indentation limit, maximum number of boxes
simultaneously opened, ellipsis, and so on, are specific to
each pretty-printer and may be fixed independently.
Given an output channel [oc], a new formatter writing to
that channel is obtained by calling [formatter_of_out_channel oc].
- Alternatively the [make_formatter] function allocates a new
+ Alternatively, the [make_formatter] function allocates a new
formatter with explicit output and flushing functions
(convenient to output material to strings for instance). *)
-type formatter;;
+val formatter_of_out_channel : out_channel -> formatter;;
(** [formatter_of_out_channel oc] returns a new formatter that
writes to the corresponding channel [oc]. *)
-val formatter_of_out_channel : out_channel -> formatter;;
+val std_formatter : formatter;;
(** The standard formatter used by the formatting functions
above. It is defined as [formatter_of_out_channel stdout]. *)
-val std_formatter : formatter;;
+val err_formatter : formatter;;
(** A formatter to use with formatting functions below for
output to standard error. It is defined as
[formatter_of_out_channel stderr]. *)
-val err_formatter : formatter;;
+val formatter_of_buffer : Buffer.t -> formatter;;
(** [formatter_of_buffer b] returns a new formatter writing to
buffer [b]. As usual, the formatter has to be flushed at
the end of pretty printing, using [pp_print_flush] or
- [pp_print_newline], to display all the pending material. In
- this case the buffer is also flushed using [flush]. *)
-val formatter_of_buffer : Buffer.t -> formatter;;
+ [pp_print_newline], to display all the pending material. *)
-(** The string buffer in which [str_formatter] writes. *)
val stdbuf : Buffer.t;;
+(** The string buffer in which [str_formatter] writes. *)
+val str_formatter : formatter;;
(** A formatter to use with formatting functions below for
output to the [stdbuf] string buffer.
[str_formatter] is defined as
[formatter_of_buffer stdbuf]. *)
-val str_formatter : formatter;;
+val flush_str_formatter : unit -> string;;
(** Returns the material printed with [str_formatter], flushes
the formatter and reset the corresponding buffer. *)
-val flush_str_formatter : unit -> string;;
+val make_formatter :
+ (string -> int -> int -> unit) -> (unit -> unit) -> formatter;;
(** [make_formatter out flush] returns a new formatter that
writes according to the output function [out], and the flushing
- function [flush]. Hence, a formatter to out channel [oc]
+ function [flush]. Hence, a formatter to the out channel [oc]
is returned by [make_formatter (output oc) (fun () -> flush oc)]. *)
-val make_formatter :
- (string -> int -> int -> unit) -> (unit -> unit) -> formatter;;
-
-(** {2 Basic functions to use with formatters} *)
-(** These functions are the basic ones: usual functions
- operating on the standard formatter are defined via partial
- evaluation of these primitives. For instance,
- [print_string] is equal to [pp_print_string std_formatter]. *)
+(** {2 Basic functions to use with formatters} *)
val pp_open_hbox : formatter -> unit -> unit;;
val pp_open_vbox : formatter -> int -> unit;;
@@ -430,9 +422,15 @@ val pp_set_all_formatter_output_functions : formatter ->
val pp_get_all_formatter_output_functions : formatter -> unit ->
(string -> int -> int -> unit) * (unit -> unit) *
(unit -> unit) * (int -> unit);;
+(** These functions are the basic ones: usual functions
+ operating on the standard formatter are defined via partial
+ evaluation of these primitives. For instance,
+ [print_string] is equal to [pp_print_string std_formatter]. *)
+
-(** {2 } *)
+(** {2 [printf] like functions for pretty-printing.} *)
+val fprintf : formatter -> ('a, formatter, unit) format -> 'a;;
(** [fprintf ff format arg1 ... argN] formats the arguments
[arg1] to [argN] according to the format string [format],
and outputs the resulting string on the formatter [ff].
@@ -478,22 +476,32 @@ val pp_get_all_formatter_output_functions : formatter -> unit ->
Example: [printf "@[%s@ %d@]" "x =" 1] is equivalent to
[open_box (); print_string "x ="; print_space (); print_int 1; close_box ()].
It prints [x = 1] within a pretty-printing box. *)
-val fprintf : formatter -> ('a, formatter, unit) format -> 'a;;
-(** Same as [fprintf] above, but instead of printing on a formatter,
- writes into the buffer argument. *)
-val bprintf: Buffer.t -> ('a, formatter, unit) format -> 'a;;
-
-(** Same as [fprintf] above, but output on [std_formatter]. *)
val printf : ('a, formatter, unit) format -> 'a;;
+(** Same as [fprintf] above, but output on [std_formatter]. *)
-(** Same as [fprintf] above, but output on [err_formatter]. *)
val eprintf: ('a, formatter, unit) format -> 'a;;
+(** Same as [fprintf] above, but output on [err_formatter]. *)
-(** Same as [printf] above, but instead of printing on a formatter,
- return a string containing the result of formatting the arguments. *)
val sprintf: ('a, unit, string) format -> 'a;;
+(** Same as [printf] above, but instead of printing on a formatter,
+ return a string containing the result of formatting the arguments.
+ Note that the pretty-printer queue is flushed at the end of each
+ call to [sprintf].
+ In case of multiple and related calls to [sprintf] to output material on a
+ string, you should consider using [fprintf] with a
+ formatter writing to a buffer: flushing the buffer at the
+ end of pretty-printing returns the desired string. You can use the
+ predefined formatter [str_formatter] and call [flush_str_formatter
+ ()] to get the result. *)
-
-
-
+val bprintf: Buffer.t -> ('a, formatter, unit) format -> 'a;;
+(** Same as [sprintf] above, but instead of printing on a string,
+ writes into the given extensible buffer.
+ As for [sprintf], the pretty-printer queue is flushed at the end of each
+ call to [bprintf].
+ In case of multiple and related calls to [bprintf] to output material on the
+ same buffer [b], you should consider using [fprintf] with a
+ formatter writing to the buffer [b] (as obtained by
+ [formatter_of_buffer b]), otherwise the repeated flushes of the
+ pretty-printer queue would result in badly formatted output. *)