Initial snarf.
[shack.git] / libmojave / stdlib / lm_rformat.mli
blob6fb956866e459d9b501b19475072ac7009d1e3a5
1 (*
2 * Formatter like in the standard library.
3 * Output is organized into boxes, each of which has an indentation.
5 * Commands:
6 * format_sbreak str str': soft break is taken if necessary
7 * if taken, str is printed after the current line
8 * if not, str' is printed
9 * format_hbreak str str': hard breaks are taken in groups
10 * if taken, str is printed
11 * if not, str' is printed
13 * format_lzone: begin a zone with no breaks
14 * format_szone: soft break zone (all or no hard breaks are taken)
15 * format_hzone: all hard breaks are taken.
16 * format_ezone: end the current zone.
18 * format_pushm i: push left margin from here by i more spaces
19 * format_popm: pop last pushm
21 * format_char: add a single char
22 * format_int: print a number
23 * format_string: add a string to the buffer
25 * ----------------------------------------------------------------
27 * This file is part of MetaPRL, a modular, higher order
28 * logical framework that provides a logical programming
29 * environment for OCaml and other languages.
31 * See the file doc/htmlman/default.html or visit http://metaprl.org/
32 * for more information.
34 * Copyright (C) 1998-2005 PRL Group, Cornell University and Caltech
36 * This library is free software; you can redistribute it and/or
37 * modify it under the terms of the GNU Lesser General Public
38 * License as published by the Free Software Foundation,
39 * version 2.1 of the License.
41 * This library is distributed in the hope that it will be useful,
42 * but WITHOUT ANY WARRANTY; without even the implied warranty of
43 * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU
44 * Lesser General Public License for more details.
46 * You should have received a copy of the GNU Lesser General Public
47 * License along with this library; if not, write to the Free Software
48 * Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301 USA
50 * Additional permission is given to link this library with the
51 * OpenSSL project's "OpenSSL" library, and with the OCaml runtime,
52 * and you may distribute the linked executables. See the file
53 * LICENSE.libmojave for more details.
55 * Author: Jason Hickey <jyh@cs.cornell.edu>
56 * Modified by: Aleksey Nogin <nogin@cs.cornell.edu>
60 (************************************************************************
61 * TYPES *
62 ************************************************************************)
65 * Abstract type of buffers containing formatted text.
67 type buffer
70 * The BufferOverflow exception is raised when too much visible text is
71 * put in the buffer. You can control how much visible text is allowed
72 * by using the format_bound function below.
74 exception RFormatOverflow
77 * A printer contains:
78 * print_string s : print string s to the buffer
79 * print_atomic s : print the buffer to the buffer
80 * print_invis s : print string s in invisible mode
81 * print_tab lmargin tags : tab to the specified left margin
82 * print_begin_tag : start tagging a value
83 * print_end_tag : finish tagging the value
85 type printer =
86 { print_string : string -> unit;
87 print_invis : string -> unit;
88 print_atomic : string -> unit;
89 print_tab : int * string -> string list -> unit;
90 print_begin_tag : string -> unit;
91 print_end_tag : string -> unit
94 (************************************************************************
95 * INTERFACE *
96 ************************************************************************)
99 * Buffer creation.
101 val new_buffer : unit -> buffer
102 val clone_buffer : buffer -> buffer
103 val clear_buffer : buffer -> unit
104 val buffer_is_empty : buffer -> bool
107 * Marshaling.
108 * This will raise Failure if the marshal
109 * version changes.
111 val marshal_buffers : buffer list -> string
112 val unmarshal_buffers : string -> buffer list
115 * Specify the max number of characters in the buffer.
116 * This will not raise an exception even if the buffer
117 * is already too large. You will get the exception
118 * the next time you insert visible text.
120 val format_bound : buffer -> int -> unit
123 * Breaks.
125 val format_cbreak : buffer -> string -> string -> unit
126 val format_sbreak : buffer -> string -> string -> unit
127 val format_hbreak : buffer -> string -> string -> unit
128 val format_space : buffer -> unit
129 val format_hspace : buffer -> unit
130 val format_newline : buffer -> unit
133 * Break zones.
135 val zone_depth : buffer -> int
136 val format_lzone : buffer -> unit
137 val format_szone : buffer -> unit
138 val format_hzone : buffer -> unit
139 val format_ezone : buffer -> unit
140 val format_izone : buffer -> unit
141 val format_azone : buffer -> unit
143 (* TeX boxes *)
144 val format_tzone : buffer -> string -> unit
147 * Margins.
149 val format_pushm : buffer -> int -> unit
150 val format_pushm_str : buffer -> string -> unit
151 val format_popm : buffer -> unit
154 * Printers.
156 val format_char : buffer -> char -> unit
157 val format_string : buffer -> string -> unit
158 val format_raw_string : buffer -> string -> unit
159 val format_quoted_string : buffer -> string -> unit
160 val format_int : buffer -> int -> unit
161 val format_num : buffer -> Lm_num.num -> unit
162 val format_buffer : buffer -> buffer -> unit
165 * Internals.
168 (* Get the current nesting depth *)
169 val format_depth : buffer -> int
171 (* Close all open boxes, indicriminately *)
172 val format_flush : buffer -> unit
174 (* Close all open pushm boxes *)
175 val format_flush_popm : buffer -> unit
178 * Collecting output.
180 val default_width : int (* 80 *)
183 * Final output.
185 val print_to_printer : buffer -> int -> printer -> unit
188 * -*-
189 * Local Variables:
190 * Caml-master: "manager"
191 * End:
192 * -*-