Skip to content

Commit

Permalink
Implémentation plus simple du trait précédent: pas de changement dans
Browse files Browse the repository at this point in the history
format.mli car on n'exporte rien de plus; on se contente de gérer les
fonctions de sorte que set_max_indent max_int soit équivalent à
set_max_indent pp_infinity.


git-svn-id: http://caml.inria.fr/svn/ocaml/version/3.08@6546 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
  • Loading branch information
pierreweis committed Jul 12, 2004
1 parent 6514f5a commit e7da2af
Show file tree
Hide file tree
Showing 2 changed files with 35 additions and 25 deletions.
40 changes: 28 additions & 12 deletions stdlib/format.ml
Expand Up @@ -184,10 +184,25 @@ let pp_clear_queue state =
state.pp_left_total <- 1; state.pp_right_total <- 1;
clear_queue state.pp_queue;;

(* Large value for default tokens size. *)
(* Could be 1073741823 that is 2^30 - 1, that is the minimal upper bound
of integers; now that max_int is defined, could also be max_int - 1. *)
let pp_infinity = 1000000000;;
(* Pp_infinity: large value for default tokens size.
Pp_infinity is documented as being greater than 1e10; to avoid
confusion about the word ``greater'' we shoose pp_infinity greater
than 1e10 + 1; for correct handling of tests in the algorithm
pp_infinity must be even one more than that; let's stand on the
safe side by choosing 1.e10+10.
Pp_infinity could probably be 1073741823 that is 2^30 - 1, that is
the minimal upper bound of integers; now that max_int is defined,
could also be defined as max_int - 1.
We must carefully double-check all the integer arithmetic
operations that involve pp_infinity before setting pp_infinity to
something around max_int: otherwise any overflow would wreck havoc
the pretty-printing algorithm's invariants.
Is it worth the burden ? *)

let pp_infinity = 1000000010;;

(* Output functions for the formatter. *)
let pp_output_string state s = state.pp_output_function s 0 (String.length s)
Expand Down Expand Up @@ -632,11 +647,15 @@ let pp_set_ellipsis_text state s = state.pp_ellipsis <- s
and pp_get_ellipsis_text state () = state.pp_ellipsis;;

(* To set the margin of pretty-printer. *)
let pp_limit n =
if n < pp_infinity then n else pred pp_infinity;;

let pp_set_min_space_left state n =
if n >= 1 && n < pp_infinity then begin
if n >= 1 then
let n = pp_limit n in
state.pp_min_space_left <- n;
state.pp_max_indent <- state.pp_margin - state.pp_min_space_left;
pp_rinit state end;;
pp_rinit state;;

(* Initially, we have :
pp_max_indent = pp_margin - pp_min_space_left, and
Expand All @@ -646,7 +665,8 @@ let pp_set_max_indent state n =
let pp_get_max_indent state () = state.pp_max_indent;;

let pp_set_margin state n =
if n >= 1 && n < pp_infinity then begin
if n >= 1 then
let n = pp_limit n in
state.pp_margin <- n;
let new_max_indent =
(* Try to maintain max_indent to its actual value. *)
Expand All @@ -658,10 +678,7 @@ let pp_set_margin state n =
max (max (state.pp_margin - state.pp_min_space_left)
(state.pp_margin / 2)) 1 in
(* Rebuild invariants. *)
pp_set_max_indent state new_max_indent end;;

let pp_set_margin_to_max state () =
pp_set_margin state (pp_infinity - 1);;
pp_set_max_indent state new_max_indent;;

let pp_get_margin state () = state.pp_margin;;

Expand Down Expand Up @@ -807,7 +824,6 @@ and set_tab = pp_set_tab std_formatter
and print_tab = pp_print_tab std_formatter

and set_margin = pp_set_margin std_formatter
and set_margin_to_max = pp_set_margin_to_max std_formatter
and get_margin = pp_get_margin std_formatter

and set_max_indent = pp_set_max_indent std_formatter
Expand Down
20 changes: 7 additions & 13 deletions stdlib/format.mli
Expand Up @@ -162,14 +162,9 @@ 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_to_max : unit -> unit;;

(** [set_margin_to_max ()] sets the value of the right margin to the
maximum possible value compatible with the various invariants of
the pretty printer. *)
Nothing happens if [d] is smaller than 2.
If [d] is too large, the right margin is set to the maximum
admissible value (which is greater than [10^10]). *)

val get_margin : unit -> int;;
(** Returns the position of the right margin. *)
Expand All @@ -182,13 +177,13 @@ val set_max_indent : int -> unit;;
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. *)
Nothing happens if [d] is smaller than 2.
If [d] is too large, the limit is set to the maximum
admissible value (which is greater than [10^10]). *)

val get_max_indent : unit -> int;;
(** Return the value of the maximum indentation limit (in characters). *)


(** {6 Formatting depth: maximum number of boxes allowed before ellipsis} *)

val set_max_boxes : int -> unit;;
Expand All @@ -197,7 +192,7 @@ val set_max_boxes : int -> unit;;
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. *)
Nothing happens if [max] is smaller than 2. *)

val get_max_boxes : unit -> int;;
(** Returns the maximum number of boxes allowed before ellipsis. *)
Expand Down Expand Up @@ -529,7 +524,6 @@ val pp_set_mark_tags : formatter -> bool -> unit;;
val pp_get_print_tags : formatter -> unit -> bool;;
val pp_get_mark_tags : formatter -> unit -> bool;;
val pp_set_margin : formatter -> int -> unit;;
val pp_set_margin_to_max : formatter -> unit -> unit;;
val pp_get_margin : formatter -> unit -> int;;
val pp_set_max_indent : formatter -> int -> unit;;
val pp_get_max_indent : formatter -> unit -> int;;
Expand Down

0 comments on commit e7da2af

Please sign in to comment.