summaryrefslogtreecommitdiffstats
path: root/stdlib
diff options
context:
space:
mode:
authorPierre Weis <Pierre.Weis@inria.fr>2010-05-03 07:09:33 +0000
committerPierre Weis <Pierre.Weis@inria.fr>2010-05-03 07:09:33 +0000
commite9de1fb06b1f1a5aa62fa0d16d38d977545ff08a (patch)
treea6ab80a6f01b8480d824d4b1c7d942c8e4e7e5be /stdlib
parent5abbfde92c7beb6b184a7b2f15ca7a1bcf33bca9 (diff)
PR#5023. Adding some documentation words for function set_formatter_output_channel.
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@10346 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
Diffstat (limited to 'stdlib')
-rw-r--r--stdlib/format.ml32
-rw-r--r--stdlib/format.mli9
2 files changed, 23 insertions, 18 deletions
diff --git a/stdlib/format.ml b/stdlib/format.ml
index 429bf7dd6..90bcea728 100644
--- a/stdlib/format.ml
+++ b/stdlib/format.ml
@@ -817,9 +817,25 @@ let pp_get_all_formatter_output_functions state () =
state.pp_output_newline, state.pp_output_spaces)
;;
+(* Default function to output new lines. *)
+let display_newline state () = state.pp_output_function "\n" 0 1;;
+
+(* Default function to output spaces. *)
+let blank_line = String.make 80 ' ';;
+let rec display_blanks state n =
+ if n > 0 then
+ if n <= 80 then state.pp_output_function blank_line 0 n else
+ begin
+ state.pp_output_function blank_line 0 80;
+ display_blanks state (n - 80)
+ end
+;;
+
let pp_set_formatter_out_channel state os =
state.pp_output_function <- output os;
- state.pp_flush_function <- (fun () -> flush os)
+ state.pp_flush_function <- (fun () -> flush os);
+ state.pp_output_newline <- display_newline state;
+ state.pp_output_spaces <- display_blanks state;
;;
(**************************************************************
@@ -873,20 +889,6 @@ let pp_make_formatter f g h i =
}
;;
-(* Default function to output spaces. *)
-let blank_line = String.make 80 ' ';;
-let rec display_blanks state n =
- if n > 0 then
- if n <= 80 then state.pp_output_function blank_line 0 n else
- begin
- state.pp_output_function blank_line 0 80;
- display_blanks state (n - 80)
- end
-;;
-
-(* Default function to output new lines. *)
-let display_newline state () = state.pp_output_function "\n" 0 1;;
-
(* Make a formatter with default functions to output spaces and new lines. *)
let make_formatter output flush =
let ppf = pp_make_formatter output flush ignore ignore in
diff --git a/stdlib/format.mli b/stdlib/format.mli
index 2998a0b28..10c6efa7b 100644
--- a/stdlib/format.mli
+++ b/stdlib/format.mli
@@ -341,12 +341,15 @@ val get_mark_tags : unit -> bool;;
(** {6 Redirecting the standard formatter output} *)
val set_formatter_out_channel : Pervasives.out_channel -> unit;;
-(** Redirect the pretty-printer output to the given channel. *)
+(** Redirect the pretty-printer output to the given channel.
+ (All the output functions of the standard formatter are set to the
+ default output functions printing to the given channel.) *)
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].
+ relevant pretty-printer output functions to the functions [out] and
+ [flush].
The [out] function performs the pretty-printer string output. It is called
with a string [s], a start position [p], and a number of characters
@@ -371,7 +374,7 @@ val set_all_formatter_output_functions :
flush:(unit -> unit) ->
newline:(unit -> unit) ->
spaces:(int -> unit) ->
- 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 [set_formatter_output_functions]. In