Changements niveaux de titres dan les commmentaires

git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@4194 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
master
Maxence Guesdon 2001-12-28 23:13:35 +00:00
parent f0cb1b414d
commit b7c2dcaa7e
4 changed files with 23 additions and 23 deletions

View File

@ -151,7 +151,7 @@ val fold_right : f:('b -> 'a -> 'a) -> 'b array -> init:'a -> 'a
(** {2 Sorting} *)
(** {6 Sorting} *)
val sort : cmp:('a -> 'a -> int) -> 'a array -> unit
@ -180,7 +180,7 @@ val stable_sort : cmp:('a -> 'a -> int) -> 'a array -> unit
(**/**)
(** {2 Undocumented functions} *)
(** {6 Undocumented functions} *)
external unsafe_get : 'a array -> int -> 'a = "%array_unsafe_get"
external unsafe_set : 'a array -> int -> 'a -> unit = "%array_unsafe_set"

View File

@ -69,7 +69,7 @@
*)
(** {2 Boxes} *)
(** {6 Boxes} *)
val open_box : int -> unit
(** [open_box d] opens a new pretty-printing box
@ -86,7 +86,7 @@ val open_box : int -> unit
val close_box : unit -> unit
(** Close the most recently opened pretty-printing box. *)
(** {2 Formatting functions} *)
(** {6 Formatting functions} *)
val print_string : string -> unit
(** [print_string str] prints [str] in the current box. *)
@ -109,7 +109,7 @@ val print_bool : bool -> unit
(** Print a boolean in the current box. *)
(** {2 Break hints} *)
(** {6 Break hints} *)
val print_space : unit -> unit
(** [print_space ()] is used to separate items (typically to print
@ -153,7 +153,7 @@ val print_if_newline : unit -> unit
command. *)
(** {2 Margin} *)
(** {6 Margin} *)
val set_margin : int -> unit
(** [set_margin d] sets the value of the right margin
@ -166,7 +166,7 @@ val get_margin : unit -> int
(** Return the position of the right margin. *)
(** {2 Maximum indentation limit} *)
(** {6 Maximum indentation limit} *)
val set_max_indent : int -> unit
(** [set_max_indent d] sets the value of the maximum
@ -180,7 +180,7 @@ val get_max_indent : unit -> int
(** Return the value of the maximum indentation limit (in characters). *)
(** {2 Formatting depth: maximum number of boxes allowed before ellipsis} *)
(** {6 Formatting depth: maximum number of boxes allowed before ellipsis} *)
val set_max_boxes : int -> unit
(** [set_max_boxes max] sets the maximum number
@ -197,7 +197,7 @@ val over_max_boxes : unit -> bool
(** Test if the maximum number of boxes allowed have already been opened. *)
(** {2 Advanced formatting} *)
(** {6 Advanced formatting} *)
val open_hbox : unit -> unit
(** [open_hbox ()] opens a new pretty-printing box.
@ -231,7 +231,7 @@ val open_hovbox : int -> unit
current indentation. *)
(** {2 Tabulations} *)
(** {6 Tabulations} *)
val open_tbox : unit -> unit
(** Open a tabulation box. *)
@ -258,7 +258,7 @@ val print_tab : unit -> unit
(** [print_tab ()] is equivalent to [print_tbreak (0,0)]. *)
(** {2 Ellipsis} *)
(** {6 Ellipsis} *)
val set_ellipsis_text : string -> unit
(** Set the text of the ellipsis printed when too many boxes
@ -268,13 +268,13 @@ val get_ellipsis_text : unit -> string
(** Return the text of the ellipsis. *)
(** {2 Redirecting formatter output} *)
(** {6 Redirecting formatter output} *)
val set_formatter_out_channel : out_channel -> unit
(** Redirect the pretty-printer output to the given channel. *)
(** {2 Changing the meaning of printing material} *)
(** {6 Changing the meaning of printing material} *)
val set_formatter_output_functions :
(string -> int -> int -> unit) -> (unit -> unit) -> unit
@ -292,7 +292,7 @@ val get_formatter_output_functions :
(** Return the current output functions of the pretty-printer. *)
(** {2 Changing the meaning of pretty printing (indentation, line breaking, and printing material)} *)
(** {6 Changing the meaning of pretty printing (indentation, line breaking, and printing material)} *)
val set_all_formatter_output_functions :
out:(string -> int -> int -> unit) -> flush:(unit -> unit) ->
@ -321,7 +321,7 @@ val get_all_formatter_output_functions :
including line breaking and indentation functions. *)
(** {2 Multiple formatted output} *)
(** {6 Multiple formatted output} *)
type formatter
(** Abstract data type corresponding to a pretty-printer and
@ -378,7 +378,7 @@ val make_formatter :
is returned by [make_formatter (output oc) (fun () -> flush oc)]. *)
(** {2 Basic functions to use with formatters} *)
(** {6 Basic functions to use with formatters} *)
val pp_open_hbox : formatter -> unit -> unit
val pp_open_vbox : formatter -> int -> unit
@ -431,7 +431,7 @@ val pp_get_all_formatter_output_functions :
[print_string] is equal to [pp_print_string std_formatter]. *)
(** {2 [printf] like functions for pretty-printing.} *)
(** {6 [printf] like functions for pretty-printing.} *)
val fprintf : formatter -> ('a, formatter, unit) format -> 'a
(** [fprintf ff format arg1 ... argN] formats the arguments

View File

@ -19,7 +19,7 @@
*)
(** {2 Generic interface} *)
(** {6 Generic interface} *)
type ('a, 'b) t
@ -87,7 +87,7 @@ val fold : ('a -> 'b -> 'c -> 'c) -> ('a, 'b) t -> 'c -> 'c
to [f]. *)
(** {2 Functorial interface} *)
(** {6 Functorial interface} *)
module type HashedType =
@ -138,7 +138,7 @@ module Make (H : HashedType) : S with type key = H.t
equality and hashing. *)
(** {2 The polymorphic hash primitive} *)
(** {6 The polymorphic hash primitive} *)
val hash : 'a -> int

View File

@ -15,7 +15,7 @@
(** The run-time library for lexers generated by [ocamllex]. *)
(** {2 Lexer buffers} *)
(** {6 Lexer buffers} *)
type lexbuf =
@ -53,7 +53,7 @@ val from_function : (string -> int -> int) -> lexbuf
provided. A return value of 0 means end of input. *)
(** {2 Functions for lexer semantic actions} *)
(** {6 Functions for lexer semantic actions} *)
(** The following functions can be called from the semantic actions
@ -85,7 +85,7 @@ val lexeme_end : lexbuf -> int
(**/**)
(** {2 } *)
(** {6 } *)
(** The following definitions are used by the generated scanners only.
They are not intended to be used by user programs. *)