summaryrefslogtreecommitdiffstats
path: root/stdlib
diff options
context:
space:
mode:
authorXavier Leroy <xavier.leroy@inria.fr>1995-07-07 12:09:01 +0000
committerXavier Leroy <xavier.leroy@inria.fr>1995-07-07 12:09:01 +0000
commitcd93956a7ba58b079b8b793beccad593ccd08943 (patch)
treed0a69a59f962d0dd7c1cfcbda65cfade28c0a563 /stdlib
parent7d761dd6dfe2f119131592deba0d9f9b30231de4 (diff)
Curryfication de Format.print_break.
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@67 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
Diffstat (limited to 'stdlib')
-rw-r--r--stdlib/format.ml10
-rw-r--r--stdlib/format.mli12
2 files changed, 11 insertions, 11 deletions
diff --git a/stdlib/format.ml b/stdlib/format.ml
index 6ac6c247c..34d3cb12f 100644
--- a/stdlib/format.ml
+++ b/stdlib/format.ml
@@ -392,14 +392,14 @@ let print_if_newline () =
If line is broken then offset is added to the indentation of the current
block else (the value of) width blanks are printed.
To do (?) : add a maximum width and offset value *)
-let print_break (width, offset) =
+let print_break width offset =
if !pp_curr_depth < !pp_max_boxes then
scan_push true
{elem_size = (- !pp_right_total); token = Pp_break (width,offset);
length = width}
-let print_space () = print_break (1,0)
-and print_cut () = print_break (0,0)
+let print_space () = print_break 1 0
+and print_cut () = print_break 0 0
let open_tbox () =
incr pp_curr_depth;
@@ -416,13 +416,13 @@ let close_tbox () =
decr pp_curr_depth end
(* Print a tabulation break *)
-let print_tbreak (width, offset) =
+let print_tbreak width offset =
if !pp_curr_depth < !pp_max_boxes then
scan_push true
{elem_size = (- !pp_right_total); token = Pp_tbreak (width,offset);
length = width}
-let print_tab () = print_tbreak (0,0)
+let print_tab () = print_tbreak 0 0
let set_tab () =
if !pp_curr_depth < !pp_max_boxes
diff --git a/stdlib/format.mli b/stdlib/format.mli
index 5d9a9ac3e..f2efe77c7 100644
--- a/stdlib/format.mli
+++ b/stdlib/format.mli
@@ -56,20 +56,20 @@ val print_bool : bool -> unit
(* Print an boolean in the current box. *)
(*** Break hints *)
-val print_break : int * int -> 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
+ [print_break nspaces offset] indicates that the line may
be List.split (a newline character is printed) at this point,
if the contents of the current box does not fit on one line.
If the line is List.split at that point, [offset] is added to
the current indentation. If the line is not List.split,
[nspaces] spaces are printed. *)
val print_cut : unit -> unit
- (* [print_cut ()] is equivalent to [print_break (0,0)].
+ (* [print_cut ()] is equivalent to [print_break 0 0].
This allows line splitting at the current point, without printing
spaces or adding indentation. *)
val print_space : unit -> unit
- (* [print_space ()] is equivalent to [print_break (1,0)].
+ (* [print_space ()] is equivalent to [print_break 1 0].
This either prints one space or splits the line at that point. *)
val force_newline : unit -> unit
(* Force a newline in the current box. *)
@@ -89,9 +89,9 @@ val open_tbox : unit -> unit
(* Open a tabulation box. *)
val close_tbox : unit -> unit
(* Close the most recently opened tabulation box. *)
-val print_tbreak : int * int -> unit
+val print_tbreak : int -> int -> unit
(* Break hint in a tabulation box.
- [print_tbreak (spaces, offset)] moves the insertion point to
+ [print_tbreak spaces offset] moves the insertion point to
the next tabulation ([spaces] being added to this position).
Nothing occurs if insertion point is already on a
tabulation mark.