1995-08-09 08:06:35 -07:00
|
|
|
(***********************************************************************)
|
|
|
|
(* *)
|
1996-04-30 07:53:58 -07:00
|
|
|
(* Objective Caml *)
|
1995-08-09 08:06:35 -07:00
|
|
|
(* *)
|
1997-11-06 06:11:06 -08:00
|
|
|
(* Pierre Weis, projet Cristal, INRIA Rocquencourt *)
|
1995-08-09 08:06:35 -07:00
|
|
|
(* *)
|
1996-04-30 07:53:58 -07:00
|
|
|
(* Copyright 1996 Institut National de Recherche en Informatique et *)
|
1999-11-17 10:59:06 -08:00
|
|
|
(* en Automatique. All rights reserved. This file is distributed *)
|
2001-12-07 05:41:02 -08:00
|
|
|
(* under the terms of the GNU Library General Public License, with *)
|
|
|
|
(* the special exception on linking described in file ../LICENSE. *)
|
1995-08-09 08:06:35 -07:00
|
|
|
(* *)
|
|
|
|
(***********************************************************************)
|
|
|
|
|
|
|
|
(* $Id$ *)
|
|
|
|
|
2002-03-05 12:56:46 -08:00
|
|
|
(**************************************************************
|
|
|
|
|
|
|
|
Data structures definitions.
|
|
|
|
|
|
|
|
**************************************************************)
|
|
|
|
|
1995-05-04 03:15:53 -07:00
|
|
|
(* Tokens are one of the following : *)
|
|
|
|
|
2002-03-05 12:56:46 -08:00
|
|
|
type pp_token =
|
1996-07-08 11:53:26 -07:00
|
|
|
| Pp_text of string (* normal text *)
|
|
|
|
| Pp_break of int * int (* complete break *)
|
2002-03-11 14:18:20 -08:00
|
|
|
| Pp_tbreak of int * int (* go to next tabulation *)
|
1996-07-08 11:53:26 -07:00
|
|
|
| Pp_stab (* set a tabulation *)
|
|
|
|
| Pp_begin of int * block_type (* beginning of a block *)
|
|
|
|
| Pp_end (* end of a block *)
|
2002-03-11 14:18:20 -08:00
|
|
|
| Pp_tbegin of tblock (* beginning of a tabulation block *)
|
1996-07-08 11:53:26 -07:00
|
|
|
| Pp_tend (* end of a tabulation block *)
|
|
|
|
| Pp_newline (* to force a newline inside a block *)
|
|
|
|
| Pp_if_newline (* to do something only if this very
|
|
|
|
line has been broken *)
|
2002-03-11 14:18:20 -08:00
|
|
|
| Pp_open_tag of string (* opening a tag name *)
|
|
|
|
| Pp_close_tag (* closing a tag *)
|
|
|
|
|
|
|
|
and tag = string
|
1995-05-04 03:15:53 -07:00
|
|
|
|
|
|
|
and block_type =
|
1996-07-08 11:53:26 -07:00
|
|
|
| Pp_hbox (* Horizontal block no line breaking *)
|
|
|
|
| Pp_vbox (* Vertical block each break leads to a new line *)
|
|
|
|
| Pp_hvbox (* Horizontal-vertical block: same as vbox, except if this block
|
|
|
|
is small enough to fit on a single line *)
|
|
|
|
| Pp_hovbox (* Horizontal or Vertical block: breaks lead to new line
|
|
|
|
only when necessary to print the content of the block *)
|
|
|
|
| Pp_box (* Horizontal or Indent block: breaks lead to new line
|
|
|
|
only when necessary to print the content of the block, or
|
|
|
|
when it leads to a new indentation of the current line *)
|
|
|
|
| Pp_fits (* Internal usage: when a block fits on a single line *)
|
1995-05-04 03:15:53 -07:00
|
|
|
|
|
|
|
and tblock = Pp_tbox of int list ref (* Tabulation box *)
|
1996-07-08 11:53:26 -07:00
|
|
|
;;
|
1995-05-04 03:15:53 -07:00
|
|
|
|
|
|
|
(* The Queue: contains all formatting elements.
|
1997-10-23 00:53:12 -07:00
|
|
|
elements are tuples (size, token, length), where
|
1995-05-04 03:15:53 -07:00
|
|
|
size is set when the size of the block is known
|
|
|
|
len is the declared length of the token *)
|
2002-03-11 14:18:20 -08:00
|
|
|
type pp_queue_elem = {mutable elem_size : int; token : pp_token; length : int};;
|
1995-05-04 03:15:53 -07:00
|
|
|
|
2002-03-05 12:56:46 -08:00
|
|
|
(* Scan stack:
|
1995-05-04 03:15:53 -07:00
|
|
|
each element is (left_total, queue element) where left_total
|
1995-05-05 03:05:18 -07:00
|
|
|
is the value of pp_left_total when the element has been enqueued *)
|
1996-07-08 11:53:26 -07:00
|
|
|
type pp_scan_elem = Scan_elem of int * pp_queue_elem;;
|
1995-05-04 03:15:53 -07:00
|
|
|
|
2002-03-05 12:56:46 -08:00
|
|
|
(* Formatting stack:
|
1995-05-04 03:15:53 -07:00
|
|
|
used to break the lines while printing tokens.
|
|
|
|
The formatting stack contains the description of
|
|
|
|
the currently active blocks. *)
|
1996-07-08 11:53:26 -07:00
|
|
|
type pp_format_elem = Format_elem of block_type * int;;
|
1996-08-27 04:57:46 -07:00
|
|
|
|
1996-07-08 11:53:26 -07:00
|
|
|
(* General purpose queues, used in the formatter *)
|
|
|
|
type 'a queue_elem = | Nil | Cons of 'a queue_cell
|
|
|
|
and 'a queue_cell = {mutable head : 'a; mutable tail : 'a queue_elem};;
|
|
|
|
|
2002-03-11 14:18:20 -08:00
|
|
|
type 'a queue = {
|
|
|
|
mutable insert : 'a queue_elem;
|
|
|
|
mutable body : 'a queue_elem
|
|
|
|
};;
|
1996-07-08 11:53:26 -07:00
|
|
|
|
2002-03-19 23:33:20 -08:00
|
|
|
type formatter_tag_functions = {
|
|
|
|
mark_open_tag : tag -> string;
|
|
|
|
mark_close_tag : tag -> string;
|
|
|
|
print_open_tag : tag -> unit;
|
|
|
|
print_close_tag : tag -> unit;
|
|
|
|
|
2002-03-19 22:51:17 -08:00
|
|
|
};;
|
|
|
|
|
2002-03-11 14:18:20 -08:00
|
|
|
type formatter = {
|
|
|
|
mutable pp_scan_stack : pp_scan_elem list;
|
1996-07-08 11:53:26 -07:00
|
|
|
mutable pp_format_stack : pp_format_elem list;
|
|
|
|
mutable pp_tbox_stack : tblock list;
|
2002-03-11 14:18:20 -08:00
|
|
|
mutable pp_tag_stack : tag list;
|
2002-03-19 23:33:20 -08:00
|
|
|
mutable pp_mark_stack : tag list;
|
1996-07-08 11:53:26 -07:00
|
|
|
(* Global variables: default initialization is
|
|
|
|
set_margin 78
|
|
|
|
set_min_space_left 0 *)
|
1997-10-23 00:53:12 -07:00
|
|
|
(* Value of right margin *)
|
1996-07-08 11:53:26 -07:00
|
|
|
mutable pp_margin : int;
|
|
|
|
(* Minimal space left before margin, when opening a block *)
|
|
|
|
mutable pp_min_space_left : int;
|
1997-10-23 00:53:12 -07:00
|
|
|
(* Maximum value of indentation:
|
1996-07-08 11:53:26 -07:00
|
|
|
no blocks can be opened further *)
|
|
|
|
mutable pp_max_indent : int;
|
1997-10-23 00:53:12 -07:00
|
|
|
(* Space remaining on the current line *)
|
|
|
|
mutable pp_space_left : int;
|
|
|
|
(* Current value of indentation *)
|
|
|
|
mutable pp_current_indent : int;
|
|
|
|
(* True when the line has been broken by the pretty-printer *)
|
|
|
|
mutable pp_is_new_line : bool;
|
|
|
|
(* Total width of tokens already printed *)
|
|
|
|
mutable pp_left_total : int;
|
|
|
|
(* Total width of tokens ever put in queue *)
|
|
|
|
mutable pp_right_total : int;
|
|
|
|
(* Current number of opened blocks *)
|
|
|
|
mutable pp_curr_depth : int;
|
|
|
|
(* Maximum number of blocks which can be simultaneously opened *)
|
|
|
|
mutable pp_max_boxes : int;
|
|
|
|
(* Ellipsis string *)
|
|
|
|
mutable pp_ellipsis : string;
|
|
|
|
(* Output function *)
|
1996-07-08 11:53:26 -07:00
|
|
|
mutable pp_output_function : string -> int -> int -> unit;
|
1997-10-23 00:53:12 -07:00
|
|
|
(* Flushing function *)
|
1996-07-08 11:53:26 -07:00
|
|
|
mutable pp_flush_function : unit -> unit;
|
1998-12-02 02:15:37 -08:00
|
|
|
(* Output of new lines *)
|
2002-03-19 22:51:17 -08:00
|
|
|
mutable pp_output_newline : unit -> unit;
|
1998-12-02 02:15:37 -08:00
|
|
|
(* Output of indentation spaces *)
|
2002-03-19 22:51:17 -08:00
|
|
|
mutable pp_output_spaces : int -> unit;
|
2002-03-11 14:18:20 -08:00
|
|
|
(* Are tags printed ? *)
|
|
|
|
mutable pp_print_tags : bool;
|
2002-03-19 23:33:20 -08:00
|
|
|
(* Are tags marked ? *)
|
|
|
|
mutable pp_mark_tags : bool;
|
2002-03-19 22:51:17 -08:00
|
|
|
(* Find opening and closing markers of tags. *)
|
2002-03-19 23:33:20 -08:00
|
|
|
mutable pp_mark_open_tag : tag -> string;
|
|
|
|
mutable pp_mark_close_tag : tag -> string;
|
|
|
|
mutable pp_print_open_tag : tag -> unit;
|
|
|
|
mutable pp_print_close_tag : tag -> unit;
|
1997-10-23 00:53:12 -07:00
|
|
|
(* The pretty-printer queue *)
|
1996-07-08 11:53:26 -07:00
|
|
|
mutable pp_queue : pp_queue_elem queue
|
|
|
|
};;
|
|
|
|
|
2002-03-05 12:56:46 -08:00
|
|
|
(**************************************************************
|
|
|
|
|
|
|
|
Auxilliaries and basic functions.
|
|
|
|
|
|
|
|
**************************************************************)
|
|
|
|
|
|
|
|
|
|
|
|
(* Qeues auxilliaries. *)
|
1996-07-08 11:53:26 -07:00
|
|
|
let make_queue () = {insert = Nil; body = Nil};;
|
|
|
|
|
|
|
|
let clear_queue q = q.insert <- Nil; q.body <- Nil;;
|
|
|
|
|
|
|
|
let add_queue x q =
|
|
|
|
let c = Cons {head = x; tail = Nil} in
|
|
|
|
match q with
|
|
|
|
| {insert = Cons cell} -> q.insert <- c; cell.tail <- c
|
|
|
|
(* Invariant: when insert is Nil body should be Nil *)
|
|
|
|
| _ -> q.insert <- c; q.body <- c;;
|
|
|
|
|
|
|
|
exception Empty_queue;;
|
|
|
|
|
|
|
|
let peek_queue = function
|
|
|
|
| {body = Cons {head = x}} -> x
|
|
|
|
| _ -> raise Empty_queue;;
|
|
|
|
|
|
|
|
let take_queue = function
|
|
|
|
| {body = Cons {head = x; tail = tl}} as q ->
|
|
|
|
q.body <- tl;
|
|
|
|
if tl = Nil then q.insert <- Nil; (* Maintain the invariant *)
|
|
|
|
x
|
|
|
|
| _ -> raise Empty_queue;;
|
1995-05-04 03:15:53 -07:00
|
|
|
|
1998-12-02 02:15:37 -08:00
|
|
|
(* Enter a token in the pretty-printer queue *)
|
|
|
|
let pp_enqueue state ({length = len} as token) =
|
|
|
|
state.pp_right_total <- state.pp_right_total + len;
|
|
|
|
add_queue token state.pp_queue;;
|
|
|
|
|
|
|
|
let pp_clear_queue state =
|
|
|
|
state.pp_left_total <- 1; state.pp_right_total <- 1;
|
|
|
|
clear_queue state.pp_queue;;
|
|
|
|
|
1995-05-05 03:05:18 -07:00
|
|
|
(* Large value for default tokens size *)
|
1996-07-08 11:53:26 -07:00
|
|
|
(* Could be 1073741823 that is 2^30 - 1, that is the minimal upper bound
|
|
|
|
of integers *)
|
|
|
|
let pp_infinity = 999999999;;
|
1995-05-04 03:15:53 -07:00
|
|
|
|
|
|
|
(* Output functions for the formatter *)
|
1996-08-27 04:57:46 -07:00
|
|
|
let pp_output_string state s = state.pp_output_function s 0 (String.length s)
|
2002-03-19 22:51:17 -08:00
|
|
|
and pp_output_newline state = state.pp_output_newline ();;
|
1995-05-04 03:15:53 -07:00
|
|
|
|
2002-03-19 22:51:17 -08:00
|
|
|
let pp_display_blanks state n = state.pp_output_spaces n;;
|
1995-05-04 03:15:53 -07:00
|
|
|
|
|
|
|
(* To format a break, indenting a new line *)
|
1996-07-08 11:53:26 -07:00
|
|
|
let break_new_line state offset width =
|
|
|
|
pp_output_newline state;
|
1997-10-23 00:53:12 -07:00
|
|
|
state.pp_is_new_line <- true;
|
1996-07-08 11:53:26 -07:00
|
|
|
let indent = state.pp_margin - width + offset in
|
1995-05-04 03:15:53 -07:00
|
|
|
(* Don't indent more than pp_max_indent *)
|
1996-07-08 11:53:26 -07:00
|
|
|
let real_indent = min state.pp_max_indent indent in
|
|
|
|
state.pp_current_indent <- real_indent;
|
|
|
|
state.pp_space_left <- state.pp_margin - state.pp_current_indent;
|
1998-12-02 02:15:37 -08:00
|
|
|
pp_display_blanks state state.pp_current_indent;;
|
1995-05-04 03:15:53 -07:00
|
|
|
|
|
|
|
(* To force a line break inside a block: no offset is added *)
|
1996-07-08 11:53:26 -07:00
|
|
|
let break_line state width = break_new_line state 0 width;;
|
1995-05-04 03:15:53 -07:00
|
|
|
|
|
|
|
(* To format a break that fits on the current line *)
|
1996-07-08 11:53:26 -07:00
|
|
|
let break_same_line state width =
|
|
|
|
state.pp_space_left <- state.pp_space_left - width;
|
1998-12-02 02:15:37 -08:00
|
|
|
pp_display_blanks state width;;
|
1995-05-04 03:15:53 -07:00
|
|
|
|
|
|
|
(* To indent no more than pp_max_indent, if one tries to open a block
|
|
|
|
beyond pp_max_indent, then the block is rejected on the left
|
|
|
|
by simulating a break. *)
|
1996-07-08 11:53:26 -07:00
|
|
|
let pp_force_break_line state =
|
|
|
|
match state.pp_format_stack with
|
1996-08-27 04:57:46 -07:00
|
|
|
| Format_elem (bl_ty, width) :: _ ->
|
1996-07-08 11:53:26 -07:00
|
|
|
if width > state.pp_space_left then
|
1995-05-04 03:15:53 -07:00
|
|
|
(match bl_ty with
|
1996-08-27 04:57:46 -07:00
|
|
|
| Pp_fits -> () | Pp_hbox -> () | _ -> break_line state width)
|
1996-07-08 11:53:26 -07:00
|
|
|
| _ -> pp_output_newline state;;
|
1995-05-04 03:15:53 -07:00
|
|
|
|
|
|
|
(* To skip a token, if the previous line has been broken *)
|
1996-07-08 11:53:26 -07:00
|
|
|
let pp_skip_token state =
|
1995-05-04 03:15:53 -07:00
|
|
|
(* When calling pp_skip_token the queue cannot be empty *)
|
1996-07-08 11:53:26 -07:00
|
|
|
match take_queue state.pp_queue with
|
1995-05-04 03:15:53 -07:00
|
|
|
{elem_size = size; length = len} ->
|
1996-07-08 11:53:26 -07:00
|
|
|
state.pp_left_total <- state.pp_left_total - len;
|
|
|
|
state.pp_space_left <- state.pp_space_left + size;;
|
1995-05-04 03:15:53 -07:00
|
|
|
|
2002-03-05 12:56:46 -08:00
|
|
|
(**************************************************************
|
|
|
|
|
|
|
|
The main pretting printing functions.
|
|
|
|
|
|
|
|
**************************************************************)
|
|
|
|
|
1995-05-04 03:15:53 -07:00
|
|
|
(* To format a token *)
|
1996-07-08 11:53:26 -07:00
|
|
|
let format_pp_token state size = function
|
1995-05-04 03:15:53 -07:00
|
|
|
|
1996-08-27 04:57:46 -07:00
|
|
|
| Pp_text s ->
|
1996-07-08 11:53:26 -07:00
|
|
|
state.pp_space_left <- state.pp_space_left - size;
|
1997-10-23 00:53:12 -07:00
|
|
|
pp_output_string state s;
|
|
|
|
state.pp_is_new_line <- false
|
1995-05-04 03:15:53 -07:00
|
|
|
|
1997-10-23 00:53:12 -07:00
|
|
|
| Pp_begin (off, ty) ->
|
1996-07-08 11:53:26 -07:00
|
|
|
let insertion_point = state.pp_margin - state.pp_space_left in
|
|
|
|
if insertion_point > state.pp_max_indent then
|
|
|
|
(* can't open a block right there *)
|
|
|
|
begin pp_force_break_line state end;
|
|
|
|
let offset = state.pp_space_left - off in
|
1995-05-04 03:15:53 -07:00
|
|
|
let bl_type =
|
|
|
|
begin match ty with
|
1996-08-27 04:57:46 -07:00
|
|
|
| Pp_vbox -> Pp_vbox
|
1996-07-08 11:53:26 -07:00
|
|
|
| _ -> if size > state.pp_space_left then ty else Pp_fits
|
1995-05-04 03:15:53 -07:00
|
|
|
end in
|
1996-07-08 11:53:26 -07:00
|
|
|
state.pp_format_stack <-
|
|
|
|
Format_elem (bl_type, offset) :: state.pp_format_stack
|
1995-05-04 03:15:53 -07:00
|
|
|
|
|
|
|
| Pp_end ->
|
1996-07-08 11:53:26 -07:00
|
|
|
begin match state.pp_format_stack with
|
1996-08-27 04:57:46 -07:00
|
|
|
| x :: (y :: l as ls) -> state.pp_format_stack <- ls
|
1995-05-04 03:15:53 -07:00
|
|
|
| _ -> () (* No more block to close *)
|
|
|
|
end
|
|
|
|
|
1996-07-08 11:53:26 -07:00
|
|
|
| Pp_tbegin (Pp_tbox _ as tbox) ->
|
|
|
|
state.pp_tbox_stack <- tbox :: state.pp_tbox_stack
|
1995-05-04 03:15:53 -07:00
|
|
|
|
|
|
|
| Pp_tend ->
|
1996-07-08 11:53:26 -07:00
|
|
|
begin match state.pp_tbox_stack with
|
1996-08-27 04:57:46 -07:00
|
|
|
| x :: ls -> state.pp_tbox_stack <- ls
|
1995-05-04 03:15:53 -07:00
|
|
|
| _ -> () (* No more tabulation block to close *)
|
|
|
|
end
|
|
|
|
|
|
|
|
| Pp_stab ->
|
1996-07-08 11:53:26 -07:00
|
|
|
begin match state.pp_tbox_stack with
|
2002-03-05 12:56:46 -08:00
|
|
|
| Pp_tbox tabs :: _ ->
|
1995-05-04 03:15:53 -07:00
|
|
|
let rec add_tab n = function
|
1996-08-27 04:57:46 -07:00
|
|
|
| [] -> [n]
|
1996-07-08 11:53:26 -07:00
|
|
|
| x :: l as ls -> if n < x then n :: ls else x :: add_tab n l in
|
|
|
|
tabs := add_tab (state.pp_margin - state.pp_space_left) !tabs
|
1995-05-04 03:15:53 -07:00
|
|
|
| _ -> () (* No opened tabulation block *)
|
|
|
|
end
|
|
|
|
|
1996-07-08 11:53:26 -07:00
|
|
|
| Pp_tbreak (n, off) ->
|
|
|
|
let insertion_point = state.pp_margin - state.pp_space_left in
|
|
|
|
begin match state.pp_tbox_stack with
|
2002-03-05 12:56:46 -08:00
|
|
|
| Pp_tbox tabs :: _ ->
|
1996-08-27 04:57:46 -07:00
|
|
|
let rec find n = function
|
|
|
|
| x :: l -> if x >= n then x else find n l
|
|
|
|
| [] -> raise Not_found in
|
|
|
|
let tab =
|
|
|
|
match !tabs with
|
|
|
|
| x :: l ->
|
|
|
|
begin try find insertion_point !tabs with Not_found -> x end
|
|
|
|
| _ -> insertion_point in
|
|
|
|
let offset = tab - insertion_point in
|
|
|
|
if offset >= 0 then break_same_line state (offset + n) else
|
|
|
|
break_new_line state (tab + off) state.pp_margin
|
|
|
|
| _ -> () (* No opened tabulation block *)
|
1995-05-04 03:15:53 -07:00
|
|
|
end
|
|
|
|
|
|
|
|
| Pp_newline ->
|
1996-07-08 11:53:26 -07:00
|
|
|
begin match state.pp_format_stack with
|
1997-10-23 00:53:12 -07:00
|
|
|
| Format_elem (_, width) :: _ -> break_line state width
|
1996-07-08 11:53:26 -07:00
|
|
|
| _ -> pp_output_newline state
|
1995-05-04 03:15:53 -07:00
|
|
|
end
|
|
|
|
|
|
|
|
| Pp_if_newline ->
|
1996-07-08 11:53:26 -07:00
|
|
|
if state.pp_current_indent != state.pp_margin - state.pp_space_left
|
1997-10-23 00:53:12 -07:00
|
|
|
then pp_skip_token state
|
1995-05-04 03:15:53 -07:00
|
|
|
|
1996-07-08 11:53:26 -07:00
|
|
|
| Pp_break (n, off) ->
|
|
|
|
begin match state.pp_format_stack with
|
1997-10-23 00:53:12 -07:00
|
|
|
| Format_elem (ty, width) :: _ ->
|
1995-05-04 03:15:53 -07:00
|
|
|
begin match ty with
|
1996-08-27 04:57:46 -07:00
|
|
|
| Pp_hovbox ->
|
2002-03-05 12:56:46 -08:00
|
|
|
if size > state.pp_space_left
|
1996-07-08 11:53:26 -07:00
|
|
|
then break_new_line state off width
|
|
|
|
else break_same_line state n
|
|
|
|
| Pp_box ->
|
1997-10-23 00:53:12 -07:00
|
|
|
(* Have the line just been broken here ? *)
|
|
|
|
if state.pp_is_new_line then break_same_line state n else
|
1996-07-08 11:53:26 -07:00
|
|
|
if size > state.pp_space_left
|
|
|
|
then break_new_line state off width else
|
1995-05-04 03:15:53 -07:00
|
|
|
(* break the line here leads to new indentation ? *)
|
1997-11-06 06:11:06 -08:00
|
|
|
if state.pp_current_indent > state.pp_margin - width + off
|
2001-11-04 13:43:01 -08:00
|
|
|
then break_new_line state off width
|
|
|
|
else break_same_line state n
|
1996-07-08 11:53:26 -07:00
|
|
|
| Pp_hvbox -> break_new_line state off width
|
|
|
|
| Pp_fits -> break_same_line state n
|
2001-11-04 13:43:01 -08:00
|
|
|
| Pp_vbox -> break_new_line state off width
|
|
|
|
| Pp_hbox -> break_same_line state n
|
1995-05-04 03:15:53 -07:00
|
|
|
end
|
|
|
|
| _ -> () (* No opened block *)
|
2002-03-11 14:18:20 -08:00
|
|
|
end
|
|
|
|
|
|
|
|
| Pp_open_tag tag_name ->
|
2002-03-19 23:33:20 -08:00
|
|
|
let marker = state.pp_mark_open_tag tag_name in
|
2002-03-19 22:51:17 -08:00
|
|
|
pp_output_string state marker;
|
2002-03-19 23:33:20 -08:00
|
|
|
state.pp_mark_stack <- tag_name :: state.pp_mark_stack
|
2002-03-11 14:18:20 -08:00
|
|
|
|
|
|
|
| Pp_close_tag ->
|
2002-03-19 23:33:20 -08:00
|
|
|
begin match state.pp_mark_stack with
|
2002-03-19 22:51:17 -08:00
|
|
|
| tag_name :: tags ->
|
2002-03-19 23:33:20 -08:00
|
|
|
let marker = state.pp_mark_close_tag tag_name in
|
2002-03-19 22:51:17 -08:00
|
|
|
pp_output_string state marker;
|
2002-03-19 23:33:20 -08:00
|
|
|
state.pp_mark_stack <- tags
|
2002-03-11 14:18:20 -08:00
|
|
|
| _ -> () (* No more tag to close *)
|
|
|
|
end;;
|
1995-05-04 03:15:53 -07:00
|
|
|
|
|
|
|
(* Print if token size is known or printing is delayed
|
|
|
|
Size is known when not negative
|
|
|
|
Printing is delayed when the text waiting in the queue requires
|
1996-07-08 11:53:26 -07:00
|
|
|
more room to format than exists on the current line *)
|
|
|
|
let rec advance_left state =
|
1995-05-04 03:15:53 -07:00
|
|
|
try
|
1996-07-08 11:53:26 -07:00
|
|
|
match peek_queue state.pp_queue with
|
1995-05-04 03:15:53 -07:00
|
|
|
{elem_size = size; token = tok; length = len} ->
|
1996-07-08 11:53:26 -07:00
|
|
|
if not
|
1996-08-27 04:57:46 -07:00
|
|
|
(size < 0 &&
|
1996-07-08 11:53:26 -07:00
|
|
|
(state.pp_right_total - state.pp_left_total < state.pp_space_left))
|
|
|
|
then begin
|
1999-02-24 07:21:50 -08:00
|
|
|
ignore(take_queue state.pp_queue);
|
1996-07-08 11:53:26 -07:00
|
|
|
format_pp_token state (if size < 0 then pp_infinity else size) tok;
|
|
|
|
state.pp_left_total <- len + state.pp_left_total;
|
|
|
|
advance_left state
|
1995-05-04 03:15:53 -07:00
|
|
|
end
|
1996-07-08 11:53:26 -07:00
|
|
|
with Empty_queue -> ();;
|
1995-05-04 03:15:53 -07:00
|
|
|
|
1996-07-08 11:53:26 -07:00
|
|
|
let enqueue_advance state tok = pp_enqueue state tok; advance_left state;;
|
1995-05-04 03:15:53 -07:00
|
|
|
|
|
|
|
(* To enqueue a string : try to advance *)
|
1996-07-08 11:53:26 -07:00
|
|
|
let enqueue_string_as state n s =
|
|
|
|
enqueue_advance state {elem_size = n; token = Pp_text s; length = n};;
|
1995-05-04 03:15:53 -07:00
|
|
|
|
1996-07-08 11:53:26 -07:00
|
|
|
let enqueue_string state s = enqueue_string_as state (String.length s) s;;
|
1995-05-04 03:15:53 -07:00
|
|
|
|
|
|
|
(* Routines for scan stack
|
|
|
|
determine sizes of blocks *)
|
1996-07-08 11:53:26 -07:00
|
|
|
|
|
|
|
(* The scan_stack is never empty *)
|
|
|
|
let scan_stack_bottom =
|
|
|
|
[Scan_elem (-1, {elem_size = (-1); token = Pp_text ""; length = 0})];;
|
1995-05-04 03:15:53 -07:00
|
|
|
|
|
|
|
(* Set size of blocks on scan stack:
|
|
|
|
if ty = true then size of break is set else size of block is set
|
|
|
|
in each case pp_scan_stack is popped *)
|
1996-07-08 11:53:26 -07:00
|
|
|
let clear_scan_stack state = state.pp_scan_stack <- scan_stack_bottom;;
|
|
|
|
|
1995-05-04 03:15:53 -07:00
|
|
|
(* Pattern matching on scan stack is exhaustive,
|
|
|
|
since scan_stack is never empty.
|
|
|
|
Pattern matching on token in scan stack is also exhaustive,
|
|
|
|
since scan_push is used on breaks and opening of boxes *)
|
1996-07-08 11:53:26 -07:00
|
|
|
let set_size state ty =
|
|
|
|
match state.pp_scan_stack with
|
1996-08-27 04:57:46 -07:00
|
|
|
| Scan_elem (left_tot,
|
1995-05-04 03:15:53 -07:00
|
|
|
({elem_size = size; token = tok} as queue_elem)) :: t ->
|
|
|
|
(* test if scan stack contains any data that is not obsolete *)
|
1996-07-08 11:53:26 -07:00
|
|
|
if left_tot < state.pp_left_total then clear_scan_stack state else
|
1995-05-04 03:15:53 -07:00
|
|
|
begin match tok with
|
1996-08-27 04:57:46 -07:00
|
|
|
| Pp_break (_, _) | Pp_tbreak (_, _) ->
|
|
|
|
if ty then
|
|
|
|
begin
|
|
|
|
queue_elem.elem_size <- state.pp_right_total + size;
|
|
|
|
state.pp_scan_stack <- t
|
|
|
|
end
|
|
|
|
| Pp_begin (_, _) ->
|
|
|
|
if not ty then
|
|
|
|
begin
|
|
|
|
queue_elem.elem_size <- state.pp_right_total + size;
|
|
|
|
state.pp_scan_stack <- t
|
|
|
|
end
|
|
|
|
| _ -> () (* scan_push is only used for breaks and boxes *)
|
1995-05-04 03:15:53 -07:00
|
|
|
end
|
1996-07-08 11:53:26 -07:00
|
|
|
| _ -> () (* scan_stack is never empty *);;
|
1995-05-04 03:15:53 -07:00
|
|
|
|
|
|
|
(* Push a token on scan stack. If b is true set_size is called *)
|
1996-07-08 11:53:26 -07:00
|
|
|
let scan_push state b tok =
|
|
|
|
pp_enqueue state tok;
|
|
|
|
if b then set_size state true;
|
|
|
|
state.pp_scan_stack <-
|
1997-10-23 00:53:12 -07:00
|
|
|
Scan_elem (state.pp_right_total, tok) :: state.pp_scan_stack;;
|
1995-05-04 03:15:53 -07:00
|
|
|
|
2001-11-04 13:43:01 -08:00
|
|
|
(* To open a new block :
|
|
|
|
the user may set the depth bound pp_max_boxes
|
|
|
|
any text nested deeper is printed as the ellipsis string *)
|
1997-09-05 11:26:53 -07:00
|
|
|
let pp_open_box_gen state indent br_ty =
|
1996-07-08 11:53:26 -07:00
|
|
|
state.pp_curr_depth <- state.pp_curr_depth + 1;
|
|
|
|
if state.pp_curr_depth < state.pp_max_boxes then
|
|
|
|
(scan_push state false
|
|
|
|
{elem_size = (- state.pp_right_total);
|
1995-05-04 03:15:53 -07:00
|
|
|
token = Pp_begin (indent, br_ty); length = 0}) else
|
1996-07-08 11:53:26 -07:00
|
|
|
if state.pp_curr_depth = state.pp_max_boxes
|
|
|
|
then enqueue_string state state.pp_ellipsis;;
|
1995-05-04 03:15:53 -07:00
|
|
|
|
|
|
|
(* The box which is always opened *)
|
1996-07-08 11:53:26 -07:00
|
|
|
let pp_open_sys_box state =
|
|
|
|
state.pp_curr_depth <- state.pp_curr_depth + 1;
|
|
|
|
scan_push state false
|
|
|
|
{elem_size = (- state.pp_right_total);
|
|
|
|
token = Pp_begin (0, Pp_hovbox); length = 0};;
|
1995-05-04 03:15:53 -07:00
|
|
|
|
1999-02-23 10:01:17 -08:00
|
|
|
(* Close a block, setting sizes of its subblocks *)
|
1996-07-08 11:53:26 -07:00
|
|
|
let pp_close_box state () =
|
|
|
|
if state.pp_curr_depth > 1 then
|
1995-05-04 03:15:53 -07:00
|
|
|
begin
|
1996-07-08 11:53:26 -07:00
|
|
|
if state.pp_curr_depth < state.pp_max_boxes then
|
1995-05-04 03:15:53 -07:00
|
|
|
begin
|
1996-07-08 11:53:26 -07:00
|
|
|
pp_enqueue state {elem_size = 0; token = Pp_end; length = 0};
|
|
|
|
set_size state true; set_size state false
|
1995-05-04 03:15:53 -07:00
|
|
|
end;
|
1997-09-05 11:26:53 -07:00
|
|
|
state.pp_curr_depth <- state.pp_curr_depth - 1;
|
1996-07-08 11:53:26 -07:00
|
|
|
end;;
|
1995-05-04 03:15:53 -07:00
|
|
|
|
2002-03-11 14:18:20 -08:00
|
|
|
(* Open a tag, pushing it on the tag stack. *)
|
2002-03-19 23:33:20 -08:00
|
|
|
let pp_open_tag state tag_name =
|
|
|
|
if state.pp_print_tags then begin
|
|
|
|
state.pp_tag_stack <- tag_name :: state.pp_tag_stack;
|
|
|
|
state.pp_print_open_tag tag_name end;
|
|
|
|
if state.pp_mark_tags then
|
|
|
|
pp_enqueue state
|
|
|
|
{elem_size = 0; token = Pp_open_tag tag_name; length = 0};;
|
2002-03-11 14:18:20 -08:00
|
|
|
|
|
|
|
(* Close a tag, popping it from the tag stack. *)
|
|
|
|
let pp_close_tag state () =
|
2002-03-19 23:33:20 -08:00
|
|
|
if state.pp_mark_tags then
|
|
|
|
pp_enqueue state {elem_size = 0; token = Pp_close_tag; length = 0};
|
2002-03-11 14:18:20 -08:00
|
|
|
if state.pp_print_tags then
|
2002-03-19 23:33:20 -08:00
|
|
|
begin match state.pp_tag_stack with
|
|
|
|
| tag_name :: tags ->
|
|
|
|
state.pp_print_close_tag tag_name;
|
|
|
|
state.pp_tag_stack <- tags
|
|
|
|
| _ -> () (* No more tag to close *)
|
|
|
|
end;;
|
2002-03-11 14:18:20 -08:00
|
|
|
|
|
|
|
let pp_set_print_tags state b = state.pp_print_tags <- b;;
|
2002-03-19 23:33:20 -08:00
|
|
|
let pp_set_mark_tags state b = state.pp_mark_tags <- b;;
|
2002-03-22 12:43:07 -08:00
|
|
|
let pp_get_print_tags state () = state.pp_print_tags;;
|
|
|
|
let pp_get_mark_tags state () = state.pp_mark_tags;;
|
2002-03-11 14:18:20 -08:00
|
|
|
|
2002-03-19 23:33:20 -08:00
|
|
|
let pp_get_formatter_tag_functions state () =
|
|
|
|
{mark_open_tag = state.pp_mark_open_tag;
|
|
|
|
mark_close_tag = state.pp_mark_close_tag;
|
|
|
|
print_open_tag = state.pp_print_open_tag;
|
|
|
|
print_close_tag = state.pp_print_close_tag;
|
|
|
|
};;
|
2002-03-11 14:18:20 -08:00
|
|
|
|
2002-03-19 23:33:20 -08:00
|
|
|
let pp_set_formatter_tag_functions state
|
|
|
|
{mark_open_tag = motag;
|
|
|
|
mark_close_tag = mctag;
|
|
|
|
print_open_tag = potag;
|
|
|
|
print_close_tag = pctag;} =
|
|
|
|
state.pp_mark_open_tag <- motag;
|
|
|
|
state.pp_mark_close_tag <- mctag;
|
|
|
|
state.pp_print_open_tag <- potag;
|
|
|
|
state.pp_print_close_tag <- pctag;;
|
2002-03-11 14:18:20 -08:00
|
|
|
|
1995-05-04 03:15:53 -07:00
|
|
|
(* Initialize pretty-printer. *)
|
1996-07-08 11:53:26 -07:00
|
|
|
let pp_rinit state =
|
|
|
|
pp_clear_queue state;
|
|
|
|
clear_scan_stack state;
|
|
|
|
state.pp_current_indent <- 0;
|
|
|
|
state.pp_curr_depth <- 0;
|
|
|
|
state.pp_space_left <- state.pp_margin;
|
|
|
|
state.pp_format_stack <- [];
|
|
|
|
state.pp_tbox_stack <- [];
|
2002-03-11 14:18:20 -08:00
|
|
|
state.pp_tag_stack <- [];
|
2002-03-19 23:33:20 -08:00
|
|
|
state.pp_mark_stack <- [];
|
1996-07-08 11:53:26 -07:00
|
|
|
pp_open_sys_box state;;
|
1995-05-04 03:15:53 -07:00
|
|
|
|
|
|
|
(* Flushing pretty-printer queue. *)
|
1999-02-16 01:07:26 -08:00
|
|
|
let pp_flush_queue state b =
|
1996-07-08 11:53:26 -07:00
|
|
|
while state.pp_curr_depth > 1 do
|
|
|
|
pp_close_box state ()
|
1995-05-04 03:15:53 -07:00
|
|
|
done;
|
1996-07-08 11:53:26 -07:00
|
|
|
state.pp_right_total <- pp_infinity; advance_left state;
|
|
|
|
if b then pp_output_newline state;
|
|
|
|
pp_rinit state;;
|
1995-05-04 03:15:53 -07:00
|
|
|
|
|
|
|
(**************************************************************
|
|
|
|
|
|
|
|
Procedures to format objects, and use boxes
|
|
|
|
|
|
|
|
**************************************************************)
|
|
|
|
|
|
|
|
(* To format a string *)
|
1996-07-08 11:53:26 -07:00
|
|
|
let pp_print_as state n s =
|
|
|
|
if state.pp_curr_depth < state.pp_max_boxes
|
|
|
|
then enqueue_string_as state n s;;
|
1995-05-04 03:15:53 -07:00
|
|
|
|
1996-07-08 11:53:26 -07:00
|
|
|
let pp_print_string state s = pp_print_as state (String.length s) s;;
|
1995-05-04 03:15:53 -07:00
|
|
|
|
|
|
|
(* To format an integer *)
|
1996-07-08 11:53:26 -07:00
|
|
|
let pp_print_int state i = pp_print_string state (string_of_int i);;
|
1995-05-04 03:15:53 -07:00
|
|
|
|
|
|
|
(* To format a float *)
|
1996-07-08 11:53:26 -07:00
|
|
|
let pp_print_float state f = pp_print_string state (string_of_float f);;
|
1995-05-04 03:15:53 -07:00
|
|
|
|
|
|
|
(* To format a boolean *)
|
1996-07-08 11:53:26 -07:00
|
|
|
let pp_print_bool state b = pp_print_string state (string_of_bool b);;
|
1995-05-04 03:15:53 -07:00
|
|
|
|
|
|
|
(* To format a char *)
|
1996-07-08 11:53:26 -07:00
|
|
|
let pp_print_char state c =
|
|
|
|
let s = String.create 1 in s.[0] <- c; pp_print_as state 1 s;;
|
1995-05-04 03:15:53 -07:00
|
|
|
|
1996-07-08 11:53:26 -07:00
|
|
|
(* Opening boxes *)
|
1997-09-05 11:26:53 -07:00
|
|
|
let pp_open_hbox state () = pp_open_box_gen state 0 Pp_hbox
|
|
|
|
and pp_open_vbox state indent = pp_open_box_gen state indent Pp_vbox
|
1995-05-04 03:15:53 -07:00
|
|
|
|
1997-09-05 11:26:53 -07:00
|
|
|
and pp_open_hvbox state indent = pp_open_box_gen state indent Pp_hvbox
|
|
|
|
and pp_open_hovbox state indent = pp_open_box_gen state indent Pp_hovbox
|
|
|
|
and pp_open_box state indent = pp_open_box_gen state indent Pp_box;;
|
1995-05-04 03:15:53 -07:00
|
|
|
|
|
|
|
(* Print a new line after printing all queued text
|
1999-02-23 10:01:17 -08:00
|
|
|
(same for print_flush but without a newline). *)
|
1999-02-16 01:07:26 -08:00
|
|
|
let pp_print_newline state () =
|
|
|
|
pp_flush_queue state true; state.pp_flush_function ()
|
|
|
|
and pp_print_flush state () =
|
|
|
|
pp_flush_queue state false; state.pp_flush_function ();;
|
1995-05-04 03:15:53 -07:00
|
|
|
|
|
|
|
(* To get a newline when one does not want to close the current block *)
|
1996-07-08 11:53:26 -07:00
|
|
|
let pp_force_newline state () =
|
|
|
|
if state.pp_curr_depth < state.pp_max_boxes then
|
|
|
|
enqueue_advance state {elem_size = 0; token = Pp_newline; length = 0};;
|
1995-05-04 03:15:53 -07:00
|
|
|
|
|
|
|
(* To format something if the line has just been broken *)
|
1996-07-08 11:53:26 -07:00
|
|
|
let pp_print_if_newline state () =
|
|
|
|
if state.pp_curr_depth < state.pp_max_boxes then
|
|
|
|
enqueue_advance state {elem_size = 0; token = Pp_if_newline; length = 0};;
|
1995-05-04 03:15:53 -07:00
|
|
|
|
|
|
|
(* Breaks: indicate where a block may be broken.
|
|
|
|
If line is broken then offset is added to the indentation of the current
|
1996-07-08 11:53:26 -07:00
|
|
|
block else (the value of) width blanks are printed.
|
1995-05-05 03:05:18 -07:00
|
|
|
To do (?) : add a maximum width and offset value *)
|
1996-07-08 11:53:26 -07:00
|
|
|
let pp_print_break state width offset =
|
2002-03-05 12:56:46 -08:00
|
|
|
if state.pp_curr_depth < state.pp_max_boxes then
|
1996-07-08 11:53:26 -07:00
|
|
|
scan_push state true
|
|
|
|
{elem_size = (- state.pp_right_total); token = Pp_break (width, offset);
|
|
|
|
length = width};;
|
|
|
|
|
|
|
|
let pp_print_space state () = pp_print_break state 1 0
|
|
|
|
and pp_print_cut state () = pp_print_break state 0 0;;
|
|
|
|
|
|
|
|
(* Tabulation boxes *)
|
|
|
|
let pp_open_tbox state () =
|
|
|
|
state.pp_curr_depth <- state.pp_curr_depth + 1;
|
|
|
|
if state.pp_curr_depth < state.pp_max_boxes then
|
|
|
|
enqueue_advance state
|
|
|
|
{elem_size = 0;
|
|
|
|
token = Pp_tbegin (Pp_tbox (ref [])); length = 0};;
|
1995-05-04 03:15:53 -07:00
|
|
|
|
|
|
|
(* Close a tabulation block *)
|
1996-07-08 11:53:26 -07:00
|
|
|
let pp_close_tbox state () =
|
|
|
|
if state.pp_curr_depth > 1 then begin
|
1996-08-27 04:57:46 -07:00
|
|
|
if state.pp_curr_depth < state.pp_max_boxes then
|
|
|
|
enqueue_advance state {elem_size = 0; token = Pp_tend; length = 0};
|
|
|
|
state.pp_curr_depth <- state.pp_curr_depth - 1 end;;
|
1995-05-04 03:15:53 -07:00
|
|
|
|
|
|
|
(* Print a tabulation break *)
|
1996-07-08 11:53:26 -07:00
|
|
|
let pp_print_tbreak state width offset =
|
|
|
|
if state.pp_curr_depth < state.pp_max_boxes then
|
|
|
|
scan_push state true
|
2002-03-05 12:56:46 -08:00
|
|
|
{elem_size = (- state.pp_right_total); token = Pp_tbreak (width, offset);
|
1996-07-08 11:53:26 -07:00
|
|
|
length = width};;
|
1995-05-04 03:15:53 -07:00
|
|
|
|
1996-07-08 11:53:26 -07:00
|
|
|
let pp_print_tab state () = pp_print_tbreak state 0 0;;
|
1995-05-04 03:15:53 -07:00
|
|
|
|
1996-07-08 11:53:26 -07:00
|
|
|
let pp_set_tab state () =
|
|
|
|
if state.pp_curr_depth < state.pp_max_boxes
|
|
|
|
then enqueue_advance state {elem_size = 0; token = Pp_stab; length=0};;
|
1995-05-04 03:15:53 -07:00
|
|
|
|
|
|
|
(**************************************************************
|
|
|
|
|
|
|
|
Procedures to control the pretty-printer
|
|
|
|
|
|
|
|
**************************************************************)
|
|
|
|
|
|
|
|
(* Fit max_boxes *)
|
1996-07-08 11:53:26 -07:00
|
|
|
let pp_set_max_boxes state n = if n > 1 then state.pp_max_boxes <- n;;
|
1995-05-04 03:15:53 -07:00
|
|
|
|
|
|
|
(* To know the current maximum number of boxes allowed *)
|
1996-07-08 11:53:26 -07:00
|
|
|
let pp_get_max_boxes state () = state.pp_max_boxes;;
|
1995-05-04 03:15:53 -07:00
|
|
|
|
1997-09-16 06:46:36 -07:00
|
|
|
let pp_over_max_boxes state () = state.pp_curr_depth = state.pp_max_boxes;;
|
|
|
|
|
1995-05-04 03:15:53 -07:00
|
|
|
(* Ellipsis *)
|
1996-07-08 11:53:26 -07:00
|
|
|
let pp_set_ellipsis_text state s = state.pp_ellipsis <- s
|
|
|
|
and pp_get_ellipsis_text state () = state.pp_ellipsis;;
|
1995-05-04 03:15:53 -07:00
|
|
|
|
2002-03-19 22:51:17 -08:00
|
|
|
(* To set the margin of pretty-printer *)
|
1996-07-08 11:53:26 -07:00
|
|
|
let pp_set_min_space_left state n =
|
|
|
|
if n >= 1 && n < pp_infinity then
|
|
|
|
begin
|
|
|
|
state.pp_min_space_left <- n;
|
|
|
|
state.pp_max_indent <- state.pp_margin - state.pp_min_space_left;
|
|
|
|
pp_rinit state end;;
|
|
|
|
|
2002-03-19 22:51:17 -08:00
|
|
|
(* Initially, we have :
|
1996-07-08 11:53:26 -07:00
|
|
|
pp_max_indent = pp_margin - pp_min_space_left, and
|
1999-02-23 10:01:17 -08:00
|
|
|
pp_space_left = pp_margin *)
|
1996-07-08 11:53:26 -07:00
|
|
|
let pp_set_max_indent state n =
|
|
|
|
pp_set_min_space_left state (state.pp_margin - 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
|
|
|
|
state.pp_margin <- n;
|
|
|
|
let new_max_indent =
|
|
|
|
(* Try to maintain max_indent to its actual value *)
|
|
|
|
if state.pp_max_indent <= state.pp_margin
|
|
|
|
then state.pp_max_indent else
|
|
|
|
(* If possible maintain pp_min_space_left to its actual value,
|
|
|
|
if this leads to a too small max_indent, take half of the
|
|
|
|
new margin, if it is greater than 1 *)
|
|
|
|
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_get_margin state () = state.pp_margin;;
|
|
|
|
|
|
|
|
let pp_set_formatter_output_functions state f g =
|
|
|
|
state.pp_output_function <- f; state.pp_flush_function <- g;;
|
2002-03-05 12:56:46 -08:00
|
|
|
let pp_get_formatter_output_functions state () =
|
1996-07-08 11:53:26 -07:00
|
|
|
(state.pp_output_function, state.pp_flush_function);;
|
|
|
|
|
2001-09-06 01:52:32 -07:00
|
|
|
let pp_set_all_formatter_output_functions state
|
|
|
|
~out:f ~flush:g ~newline:h ~spaces:i =
|
1998-12-02 02:15:37 -08:00
|
|
|
pp_set_formatter_output_functions state f g;
|
2002-03-19 22:51:17 -08:00
|
|
|
state.pp_output_newline <- (function () -> h ());
|
|
|
|
state.pp_output_spaces <- (function n -> i n);;
|
2002-03-05 12:56:46 -08:00
|
|
|
let pp_get_all_formatter_output_functions state () =
|
1998-12-02 02:15:37 -08:00
|
|
|
(state.pp_output_function, state.pp_flush_function,
|
2002-03-19 22:51:17 -08:00
|
|
|
state.pp_output_newline, state.pp_output_spaces);;
|
1998-12-02 02:15:37 -08:00
|
|
|
|
|
|
|
let pp_set_formatter_out_channel state os =
|
|
|
|
state.pp_output_function <- output os;
|
|
|
|
state.pp_flush_function <- (fun () -> flush os);;
|
|
|
|
|
2002-03-19 23:33:20 -08:00
|
|
|
let default_pp_mark_open_tag s = "<" ^ s ^ ">";;
|
|
|
|
let default_pp_mark_close_tag s = "</" ^ s ^ ">";;
|
|
|
|
|
|
|
|
let default_pp_print_open_tag s = ();;
|
|
|
|
let default_pp_print_close_tag = default_pp_print_open_tag;;
|
2002-03-11 14:18:20 -08:00
|
|
|
|
2002-03-05 12:56:46 -08:00
|
|
|
let pp_make_formatter f g h i =
|
1996-07-08 11:53:26 -07:00
|
|
|
(* The initial state of the formatter contains a dummy box *)
|
|
|
|
let pp_q = make_queue () in
|
|
|
|
let sys_tok =
|
|
|
|
{elem_size = (- 1); token = Pp_begin (0, Pp_hovbox); length = 0} in
|
|
|
|
add_queue sys_tok pp_q;
|
|
|
|
let sys_scan_stack =
|
|
|
|
(Scan_elem (1, sys_tok)) :: scan_stack_bottom in
|
|
|
|
{pp_scan_stack = sys_scan_stack;
|
|
|
|
pp_format_stack = [];
|
|
|
|
pp_tbox_stack = [];
|
2002-03-11 14:18:20 -08:00
|
|
|
pp_tag_stack = [];
|
2002-03-19 23:33:20 -08:00
|
|
|
pp_mark_stack = [];
|
1996-07-08 11:53:26 -07:00
|
|
|
pp_margin = 78;
|
|
|
|
pp_min_space_left = 10;
|
|
|
|
pp_max_indent = 78 - 10;
|
|
|
|
pp_space_left = 78;
|
|
|
|
pp_current_indent = 0;
|
1997-10-23 00:53:12 -07:00
|
|
|
pp_is_new_line = true;
|
1996-07-08 11:53:26 -07:00
|
|
|
pp_left_total = 1;
|
|
|
|
pp_right_total = 1;
|
|
|
|
pp_curr_depth = 1;
|
2001-06-18 11:14:29 -07:00
|
|
|
pp_max_boxes = max_int;
|
1996-07-08 11:53:26 -07:00
|
|
|
pp_ellipsis = ".";
|
|
|
|
pp_output_function = f;
|
|
|
|
pp_flush_function = g;
|
1998-12-02 02:15:37 -08:00
|
|
|
pp_output_newline = h;
|
|
|
|
pp_output_spaces = i;
|
2002-03-11 14:18:20 -08:00
|
|
|
pp_print_tags = true;
|
2002-03-19 23:33:20 -08:00
|
|
|
pp_mark_tags = true;
|
|
|
|
pp_mark_open_tag = default_pp_mark_open_tag;
|
|
|
|
pp_mark_close_tag = default_pp_mark_close_tag;
|
|
|
|
pp_print_open_tag = default_pp_print_open_tag;
|
|
|
|
pp_print_close_tag = default_pp_print_close_tag;
|
1996-07-08 11:53:26 -07:00
|
|
|
pp_queue = pp_q
|
|
|
|
};;
|
|
|
|
|
1998-12-02 02:15:37 -08:00
|
|
|
(* Default function to output spaces *)
|
|
|
|
let blank_line = String.make 80 ' ';;
|
1998-12-08 00:29:54 -08:00
|
|
|
let rec display_blanks state n =
|
1998-12-02 02:15:37 -08:00
|
|
|
if n > 0 then
|
1998-12-08 00:29:54 -08:00
|
|
|
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;;
|
1998-12-02 02:15:37 -08:00
|
|
|
|
|
|
|
(* Default function to output new lines *)
|
|
|
|
let display_newline state () = state.pp_output_function "\n" 0 1;;
|
1996-07-08 11:53:26 -07:00
|
|
|
|
2002-03-19 22:51:17 -08:00
|
|
|
let make_formatter f g =
|
|
|
|
let ff = pp_make_formatter f g ignore ignore in
|
|
|
|
ff.pp_output_newline <- display_newline ff;
|
|
|
|
ff.pp_output_spaces <- display_blanks ff;
|
|
|
|
ff;;
|
1998-12-02 02:15:37 -08:00
|
|
|
|
1998-12-08 00:29:54 -08:00
|
|
|
let formatter_of_out_channel oc =
|
2002-03-19 22:51:17 -08:00
|
|
|
make_formatter (output oc) (fun () -> flush oc);;
|
1998-12-02 02:15:37 -08:00
|
|
|
|
2001-11-04 13:43:01 -08:00
|
|
|
let unit_out () = ();;
|
|
|
|
|
1999-02-16 01:07:26 -08:00
|
|
|
let formatter_of_buffer b =
|
2002-03-19 22:51:17 -08:00
|
|
|
make_formatter (Buffer.add_substring b) unit_out;;
|
1999-02-16 01:07:26 -08:00
|
|
|
|
1999-02-23 10:01:17 -08:00
|
|
|
let stdbuf = Buffer.create 512;;
|
1998-12-02 02:15:37 -08:00
|
|
|
|
1999-02-23 10:01:17 -08:00
|
|
|
let str_formatter = formatter_of_buffer stdbuf;;
|
1999-02-16 01:07:26 -08:00
|
|
|
let std_formatter = formatter_of_out_channel stdout;;
|
1998-12-08 00:29:54 -08:00
|
|
|
let err_formatter = formatter_of_out_channel stderr;;
|
1997-05-15 03:41:17 -07:00
|
|
|
|
1999-02-23 10:01:17 -08:00
|
|
|
let flush_str_formatter () =
|
2002-03-19 22:51:17 -08:00
|
|
|
pp_flush_queue str_formatter false;
|
|
|
|
let s = Buffer.contents stdbuf in
|
|
|
|
Buffer.reset stdbuf;
|
|
|
|
s;;
|
1999-02-23 10:01:17 -08:00
|
|
|
|
1996-07-08 11:53:26 -07:00
|
|
|
let open_hbox = pp_open_hbox std_formatter
|
|
|
|
and open_vbox = pp_open_vbox std_formatter
|
|
|
|
and open_hvbox = pp_open_hvbox std_formatter
|
|
|
|
and open_hovbox = pp_open_hovbox std_formatter
|
|
|
|
and open_box = pp_open_box std_formatter
|
|
|
|
and close_box = pp_close_box std_formatter
|
2002-03-11 14:18:20 -08:00
|
|
|
and open_tag = pp_open_tag std_formatter
|
|
|
|
and close_tag = pp_close_tag std_formatter
|
1996-07-08 11:53:26 -07:00
|
|
|
and print_as = pp_print_as std_formatter
|
|
|
|
and print_string = pp_print_string std_formatter
|
|
|
|
and print_int = pp_print_int std_formatter
|
|
|
|
and print_float = pp_print_float std_formatter
|
|
|
|
and print_char = pp_print_char std_formatter
|
|
|
|
and print_bool = pp_print_bool std_formatter
|
|
|
|
and print_break = pp_print_break std_formatter
|
|
|
|
and print_cut = pp_print_cut std_formatter
|
|
|
|
and print_space = pp_print_space std_formatter
|
|
|
|
and force_newline = pp_force_newline std_formatter
|
|
|
|
and print_flush = pp_print_flush std_formatter
|
|
|
|
and print_newline = pp_print_newline std_formatter
|
|
|
|
and print_if_newline = pp_print_if_newline std_formatter
|
1998-12-02 02:15:37 -08:00
|
|
|
|
1996-07-08 11:53:26 -07:00
|
|
|
and open_tbox = pp_open_tbox std_formatter
|
|
|
|
and close_tbox = pp_close_tbox std_formatter
|
|
|
|
and print_tbreak = pp_print_tbreak std_formatter
|
1998-12-02 02:15:37 -08:00
|
|
|
|
1996-07-08 11:53:26 -07:00
|
|
|
and set_tab = pp_set_tab std_formatter
|
|
|
|
and print_tab = pp_print_tab std_formatter
|
1998-12-02 02:15:37 -08:00
|
|
|
|
1996-07-08 11:53:26 -07:00
|
|
|
and set_margin = pp_set_margin std_formatter
|
|
|
|
and get_margin = pp_get_margin std_formatter
|
1998-12-02 02:15:37 -08:00
|
|
|
|
1996-07-08 11:53:26 -07:00
|
|
|
and set_max_indent = pp_set_max_indent std_formatter
|
|
|
|
and get_max_indent = pp_get_max_indent std_formatter
|
1998-12-02 02:15:37 -08:00
|
|
|
|
1996-07-08 11:53:26 -07:00
|
|
|
and set_max_boxes = pp_set_max_boxes std_formatter
|
|
|
|
and get_max_boxes = pp_get_max_boxes std_formatter
|
1997-09-16 06:46:36 -07:00
|
|
|
and over_max_boxes = pp_over_max_boxes std_formatter
|
1998-12-02 02:15:37 -08:00
|
|
|
|
1996-07-08 11:53:26 -07:00
|
|
|
and set_ellipsis_text = pp_set_ellipsis_text std_formatter
|
|
|
|
and get_ellipsis_text = pp_get_ellipsis_text std_formatter
|
1998-12-02 02:15:37 -08:00
|
|
|
|
1996-07-08 11:53:26 -07:00
|
|
|
and set_formatter_out_channel =
|
|
|
|
pp_set_formatter_out_channel std_formatter
|
1998-12-02 02:15:37 -08:00
|
|
|
|
1996-07-08 11:53:26 -07:00
|
|
|
and set_formatter_output_functions =
|
|
|
|
pp_set_formatter_output_functions std_formatter
|
|
|
|
and get_formatter_output_functions =
|
1998-12-02 02:15:37 -08:00
|
|
|
pp_get_formatter_output_functions std_formatter
|
|
|
|
|
1998-12-08 00:29:54 -08:00
|
|
|
and set_all_formatter_output_functions =
|
1998-12-02 02:15:37 -08:00
|
|
|
pp_set_all_formatter_output_functions std_formatter
|
1998-12-08 00:29:54 -08:00
|
|
|
and get_all_formatter_output_functions =
|
2002-03-11 14:18:20 -08:00
|
|
|
pp_get_all_formatter_output_functions std_formatter
|
|
|
|
|
2002-03-19 23:33:20 -08:00
|
|
|
and set_formatter_tag_functions =
|
|
|
|
pp_set_formatter_tag_functions std_formatter
|
|
|
|
and get_formatter_tag_functions =
|
|
|
|
pp_get_formatter_tag_functions std_formatter
|
2002-03-11 14:18:20 -08:00
|
|
|
and set_print_tags =
|
|
|
|
pp_set_print_tags std_formatter
|
2002-03-22 12:43:07 -08:00
|
|
|
and get_print_tags =
|
|
|
|
pp_get_print_tags std_formatter
|
2002-03-19 23:33:20 -08:00
|
|
|
and set_mark_tags =
|
|
|
|
pp_set_mark_tags std_formatter
|
2002-03-22 12:43:07 -08:00
|
|
|
and get_mark_tags =
|
|
|
|
pp_get_mark_tags std_formatter
|
2002-03-11 14:18:20 -08:00
|
|
|
;;
|
1995-08-29 01:31:50 -07:00
|
|
|
|
2001-10-31 03:34:21 -08:00
|
|
|
|
2002-03-05 12:56:46 -08:00
|
|
|
(**************************************************************
|
|
|
|
|
|
|
|
Printf implementation.
|
|
|
|
|
|
|
|
**************************************************************)
|
2001-10-31 03:34:21 -08:00
|
|
|
|
2002-03-05 12:56:46 -08:00
|
|
|
(* Basic primitive functions to format int and floating point numbers. *)
|
2001-11-04 13:43:01 -08:00
|
|
|
external format_int : string -> int -> string = "format_int";;
|
|
|
|
external format_float : string -> float -> string = "format_float";;
|
1997-09-05 11:26:53 -07:00
|
|
|
|
2002-03-05 12:56:46 -08:00
|
|
|
(* Error messages when processing formats. *)
|
|
|
|
|
|
|
|
(* Trailer: giving up at character number ... *)
|
|
|
|
let giving_up mess fmt i =
|
|
|
|
"fprintf: " ^ mess ^ " ``" ^ fmt ^
|
|
|
|
"'', giving up at character number " ^ string_of_int i ^
|
|
|
|
(if i < String.length fmt
|
|
|
|
then " (" ^ String.make 1 fmt.[i] ^ ")."
|
|
|
|
else String.make 1 '.');;
|
|
|
|
|
|
|
|
(* When an invalid format deserve a special error explanation. *)
|
|
|
|
let format_invalid_arg mess fmt i = invalid_arg (giving_up mess fmt i);;
|
|
|
|
|
|
|
|
(* Standard invalid format. *)
|
|
|
|
let invalid_format fmt i = format_invalid_arg "bad format" fmt i;;
|
|
|
|
|
|
|
|
(* Cannot find a valid integer into that format. *)
|
|
|
|
let invalid_integer fmt i =
|
|
|
|
invalid_arg (giving_up "bad integer specification" fmt i);;
|
|
|
|
|
|
|
|
(* Finding an integer out of a sub-string of the format. *)
|
|
|
|
let format_int_of_string fmt i s =
|
|
|
|
try int_of_string s with
|
|
|
|
| Failure s -> invalid_integer fmt i;;
|
1998-12-23 10:57:55 -08:00
|
|
|
|
2002-03-11 14:18:20 -08:00
|
|
|
let implode_rev s0 = function
|
|
|
|
| [] -> s0
|
|
|
|
| l -> String.concat "" (s0 :: List.rev l);;
|
|
|
|
|
2001-10-31 03:34:21 -08:00
|
|
|
(* [fprintf_out] is the printf-like function generator: given the
|
|
|
|
- [str] flag that tells if we are printing into a string,
|
|
|
|
- the [out] function that has to be called at the end of formatting,
|
|
|
|
it generates a [fprintf] function that takes as arguments a [ppf]
|
|
|
|
formatter and a printing format to print the rest of arguments
|
|
|
|
according to the format.
|
|
|
|
Regular [fprintf]-like functions of this module are obtained via partial
|
|
|
|
applications of [fprintf_out]. *)
|
1999-02-23 10:01:17 -08:00
|
|
|
let fprintf_out str out ppf format =
|
1997-09-05 11:26:53 -07:00
|
|
|
let format = (Obj.magic format : string) in
|
|
|
|
let limit = String.length format in
|
|
|
|
|
1998-11-18 09:24:15 -08:00
|
|
|
let print_as = ref None in
|
|
|
|
|
2001-10-28 06:21:27 -08:00
|
|
|
let pp_print_as_char c =
|
1998-11-18 09:24:15 -08:00
|
|
|
match !print_as with
|
|
|
|
| None -> pp_print_char ppf c
|
|
|
|
| Some size ->
|
|
|
|
pp_print_as ppf size (String.make 1 c);
|
|
|
|
print_as := None
|
2001-10-28 06:21:27 -08:00
|
|
|
and pp_print_as_string s =
|
1998-11-18 09:24:15 -08:00
|
|
|
match !print_as with
|
|
|
|
| None -> pp_print_string ppf s
|
|
|
|
| Some size ->
|
|
|
|
pp_print_as ppf size s;
|
|
|
|
print_as := None in
|
|
|
|
|
1997-09-05 11:26:53 -07:00
|
|
|
let rec doprn i =
|
|
|
|
if i >= limit then
|
1999-02-16 01:07:26 -08:00
|
|
|
Obj.magic (out ())
|
1997-09-05 11:26:53 -07:00
|
|
|
else
|
|
|
|
match format.[i] with
|
2001-10-28 06:21:27 -08:00
|
|
|
| '%' ->
|
|
|
|
Printf.scan_format format i cont_s cont_a cont_t
|
1997-09-05 11:26:53 -07:00
|
|
|
| '@' ->
|
|
|
|
let j = succ i in
|
2002-03-05 12:56:46 -08:00
|
|
|
if j >= limit then invalid_format format i else
|
1997-09-05 11:26:53 -07:00
|
|
|
begin match format.[j] with
|
|
|
|
| '@' ->
|
|
|
|
pp_print_char ppf '@';
|
|
|
|
doprn (succ j)
|
|
|
|
| '[' ->
|
2002-03-11 14:18:20 -08:00
|
|
|
do_pp_open_box ppf (succ j)
|
1997-09-05 11:26:53 -07:00
|
|
|
| ']' ->
|
|
|
|
pp_close_box ppf ();
|
|
|
|
doprn (succ j)
|
2002-03-11 14:18:20 -08:00
|
|
|
| '{' ->
|
|
|
|
do_pp_open_tag ppf (succ j)
|
|
|
|
| '}' ->
|
|
|
|
pp_close_tag ppf ();
|
|
|
|
doprn (succ j)
|
1997-09-05 11:26:53 -07:00
|
|
|
| ' ' ->
|
|
|
|
pp_print_space ppf ();
|
|
|
|
doprn (succ j)
|
|
|
|
| ',' ->
|
|
|
|
pp_print_cut ppf ();
|
|
|
|
doprn (succ j)
|
1998-01-16 02:44:28 -08:00
|
|
|
| '?' ->
|
|
|
|
pp_print_flush ppf ();
|
|
|
|
doprn (succ j)
|
1997-09-05 11:26:53 -07:00
|
|
|
| '.' ->
|
|
|
|
pp_print_newline ppf ();
|
|
|
|
doprn (succ j)
|
1997-10-23 00:53:12 -07:00
|
|
|
| '\n' ->
|
1997-09-05 11:26:53 -07:00
|
|
|
pp_force_newline ppf ();
|
|
|
|
doprn (succ j)
|
1997-10-23 00:53:12 -07:00
|
|
|
| ';' ->
|
2002-03-05 12:56:46 -08:00
|
|
|
do_pp_break ppf (succ j)
|
1998-11-18 09:24:15 -08:00
|
|
|
| '<' ->
|
2002-03-05 12:56:46 -08:00
|
|
|
let got_size size j =
|
|
|
|
print_as := Some size;
|
|
|
|
doprn (skip_gt j) in
|
|
|
|
get_int (succ j) got_size
|
|
|
|
| c -> invalid_format format j
|
1997-09-05 11:26:53 -07:00
|
|
|
end
|
2001-10-28 06:21:27 -08:00
|
|
|
| c -> pp_print_as_char c; doprn (succ i)
|
1997-09-05 11:26:53 -07:00
|
|
|
|
2001-10-28 06:21:27 -08:00
|
|
|
and cont_s s i =
|
|
|
|
pp_print_as_string s; doprn i
|
|
|
|
and cont_a printer arg i =
|
|
|
|
if str then
|
|
|
|
pp_print_as_string ((Obj.magic printer) () arg)
|
|
|
|
else
|
|
|
|
printer ppf arg;
|
|
|
|
doprn i
|
|
|
|
and cont_t printer i =
|
|
|
|
if str then
|
|
|
|
pp_print_as_string ((Obj.magic printer) ())
|
|
|
|
else
|
|
|
|
printer ppf;
|
|
|
|
doprn i
|
1997-09-05 11:26:53 -07:00
|
|
|
|
2002-03-05 12:56:46 -08:00
|
|
|
and get_int i c =
|
|
|
|
if i >= limit then invalid_integer format i else
|
1997-09-05 11:26:53 -07:00
|
|
|
match format.[i] with
|
2002-03-05 12:56:46 -08:00
|
|
|
| ' ' -> get_int (succ i) c
|
|
|
|
| '%' ->
|
|
|
|
let cont_s s i = c (format_int_of_string format i s) i
|
|
|
|
and cont_a printer arg i = invalid_integer format i
|
|
|
|
and cont_t printer i = invalid_integer format i in
|
|
|
|
Printf.scan_format format i cont_s cont_a cont_t
|
|
|
|
| _ ->
|
1997-10-23 00:53:12 -07:00
|
|
|
let rec get j =
|
2002-03-05 12:56:46 -08:00
|
|
|
if j >= limit then invalid_integer format j else
|
1997-09-05 11:26:53 -07:00
|
|
|
match format.[j] with
|
1997-10-23 00:53:12 -07:00
|
|
|
| '0' .. '9' | '-' -> get (succ j)
|
2002-03-05 12:56:46 -08:00
|
|
|
| _ ->
|
|
|
|
if j = i then c 0 j else
|
|
|
|
c (format_int_of_string format j (String.sub format i (j - i))) j in
|
|
|
|
get i
|
|
|
|
|
|
|
|
and skip_gt i =
|
|
|
|
if i >= limit then invalid_format format i else
|
|
|
|
match format.[i] with
|
|
|
|
| ' ' -> skip_gt (succ i)
|
|
|
|
| '>' -> succ i
|
|
|
|
| _ -> invalid_format format i
|
|
|
|
|
|
|
|
and get_box_kind i =
|
|
|
|
if i >= limit then Pp_box, i else
|
|
|
|
match format.[i] with
|
1997-09-05 11:26:53 -07:00
|
|
|
| 'h' ->
|
2002-03-05 12:56:46 -08:00
|
|
|
let i = succ i in
|
|
|
|
if i >= limit then Pp_hbox, i else
|
|
|
|
begin match format.[i] with
|
2000-12-28 05:07:42 -08:00
|
|
|
| 'o' ->
|
2002-03-05 12:56:46 -08:00
|
|
|
let i = succ i in
|
|
|
|
if i >= limit then format_invalid_arg "bad box format" format i else
|
|
|
|
begin match format.[i] with
|
|
|
|
| 'v' -> Pp_hovbox, succ i
|
2002-03-26 09:46:09 -08:00
|
|
|
| c ->
|
|
|
|
format_invalid_arg
|
|
|
|
("bad box name ho" ^ String.make 1 c) format i end
|
2002-03-05 12:56:46 -08:00
|
|
|
| 'v' -> Pp_hvbox, succ i
|
|
|
|
| c -> Pp_hbox, i
|
1997-09-05 11:26:53 -07:00
|
|
|
end
|
2002-03-05 12:56:46 -08:00
|
|
|
| 'b' -> Pp_box, succ i
|
|
|
|
| 'v' -> Pp_vbox, succ i
|
|
|
|
| _ -> Pp_box, i
|
1997-09-05 11:26:53 -07:00
|
|
|
|
2002-03-11 14:18:20 -08:00
|
|
|
and get_tag_name i c =
|
|
|
|
let rec get accu i j =
|
|
|
|
if j >= limit
|
|
|
|
then c (implode_rev (String.sub format i (j - i)) accu) j else
|
|
|
|
match format.[j] with
|
|
|
|
| '>' -> c (implode_rev (String.sub format i (j - i)) accu) j
|
|
|
|
| '%' ->
|
|
|
|
let s0 = String.sub format i (j - i) in
|
|
|
|
let cont_s s i = get (s :: s0 :: accu) i i
|
|
|
|
and cont_a printer arg i = invalid_integer format i
|
|
|
|
and cont_t printer i = invalid_integer format i in
|
|
|
|
Printf.scan_format format i cont_s cont_a cont_t
|
|
|
|
| c -> get accu i (succ j) in
|
|
|
|
get [] i i
|
|
|
|
|
1997-10-23 00:53:12 -07:00
|
|
|
and do_pp_break ppf i =
|
2002-03-05 12:56:46 -08:00
|
|
|
if i >= limit then begin pp_print_space ppf (); doprn i end else
|
1997-10-23 00:53:12 -07:00
|
|
|
match format.[i] with
|
|
|
|
| '<' ->
|
2002-03-05 12:56:46 -08:00
|
|
|
let rec got_nspaces nspaces j =
|
|
|
|
get_int j (got_offset nspaces)
|
|
|
|
and got_offset nspaces offset j =
|
|
|
|
pp_print_break ppf nspaces offset;
|
|
|
|
doprn (skip_gt j) in
|
|
|
|
get_int (succ i) got_nspaces
|
|
|
|
| c -> pp_print_space ppf (); doprn i
|
1997-10-23 00:53:12 -07:00
|
|
|
|
2002-03-11 14:18:20 -08:00
|
|
|
and do_pp_open_box ppf i =
|
2002-03-05 12:56:46 -08:00
|
|
|
if i >= limit then begin pp_open_box_gen ppf 0 Pp_box; doprn i end else
|
1997-09-05 11:26:53 -07:00
|
|
|
match format.[i] with
|
|
|
|
| '<' ->
|
2000-12-28 05:07:42 -08:00
|
|
|
let kind, j = get_box_kind (succ i) in
|
2002-03-05 12:56:46 -08:00
|
|
|
let got_size size j =
|
|
|
|
pp_open_box_gen ppf size kind;
|
|
|
|
doprn (skip_gt j) in
|
|
|
|
get_int j got_size
|
2002-03-11 14:18:20 -08:00
|
|
|
| c -> pp_open_box_gen ppf 0 Pp_box; doprn i
|
|
|
|
|
|
|
|
and do_pp_open_tag ppf i =
|
|
|
|
if i >= limit then begin pp_open_tag ppf ""; doprn i end else
|
|
|
|
match format.[i] with
|
|
|
|
| '<' ->
|
|
|
|
let got_name tag_name j =
|
|
|
|
pp_open_tag ppf tag_name;
|
|
|
|
doprn (skip_gt j) in
|
|
|
|
get_tag_name (succ i) got_name
|
|
|
|
| c -> pp_open_tag ppf ""; doprn i in
|
1997-09-05 11:26:53 -07:00
|
|
|
|
2002-03-05 12:56:46 -08:00
|
|
|
doprn 0;;
|
1997-09-05 11:26:53 -07:00
|
|
|
|
1999-02-23 10:01:17 -08:00
|
|
|
let get_buffer_out b =
|
|
|
|
let s = Buffer.contents b in
|
|
|
|
Buffer.reset b;
|
|
|
|
s;;
|
|
|
|
|
|
|
|
let string_out b ppf () =
|
|
|
|
pp_flush_queue ppf false;
|
|
|
|
get_buffer_out b;;
|
|
|
|
|
|
|
|
let fprintf ppf = fprintf_out false unit_out ppf;;
|
|
|
|
let printf f = fprintf_out false unit_out std_formatter f;;
|
|
|
|
let eprintf f = fprintf_out false unit_out err_formatter f;;
|
2002-03-21 09:13:02 -08:00
|
|
|
let kprintf k f =
|
1999-02-23 10:01:17 -08:00
|
|
|
let b = Buffer.create 512 in
|
|
|
|
let ppf = formatter_of_buffer b in
|
2002-03-21 09:13:02 -08:00
|
|
|
fprintf_out true (fun () -> k (string_out b ppf ())) ppf f
|
|
|
|
;;
|
|
|
|
let sprintf f = kprintf (fun x -> x) f;;
|
1999-02-23 10:01:17 -08:00
|
|
|
|
|
|
|
let bprintf b =
|
|
|
|
let ppf = formatter_of_buffer b in
|
|
|
|
fprintf_out false (fun () -> pp_flush_queue ppf false) ppf;;
|
1999-02-16 01:07:26 -08:00
|
|
|
|
2001-10-31 03:34:21 -08:00
|
|
|
at_exit print_flush;;
|