summaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
authorMaxence Guesdon <maxence.guesdon@inria.fr>2001-12-28 23:13:52 +0000
committerMaxence Guesdon <maxence.guesdon@inria.fr>2001-12-28 23:13:52 +0000
commita1f70bfb1d3c294d345c15796bab5524cb41c8de (patch)
treecf74709ee5d5b7e31f1ad5336be2b111d66ec9ac
parentb7c2dcaa7e66058328841017bc2ef329e3d70286 (diff)
changements niveaux de titres dans les commentaires
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@4195 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
-rw-r--r--stdlib/list.mli14
-rw-r--r--stdlib/listLabels.mli14
-rw-r--r--stdlib/oo.mli12
-rw-r--r--stdlib/parsing.mli2
-rw-r--r--stdlib/pervasives.mli44
5 files changed, 43 insertions, 43 deletions
diff --git a/stdlib/list.mli b/stdlib/list.mli
index 87bb1c3b8..3a3312534 100644
--- a/stdlib/list.mli
+++ b/stdlib/list.mli
@@ -64,7 +64,7 @@ val flatten : 'a list list -> 'a list
(length of the argument + length of the longest sub-list). *)
-(** {2 Iterators} *)
+(** {6 Iterators} *)
val iter : ('a -> unit) -> 'a list -> unit
@@ -91,7 +91,7 @@ val fold_right : ('a -> 'b -> 'b) -> 'a list -> 'b -> 'b
[f a1 (f a2 (... (f an b) ...))]. Not tail-recursive. *)
-(** {2 Iterators on two lists} *)
+(** {6 Iterators on two lists} *)
val iter2 : ('a -> 'b -> unit) -> 'a list -> 'b list -> unit
@@ -124,7 +124,7 @@ val fold_right2 : ('a -> 'b -> 'c -> 'c) -> 'a list -> 'b list -> 'c -> 'c
different lengths. Not tail-recursive. *)
-(** {2 List scanning} *)
+(** {6 List scanning} *)
val for_all : ('a -> bool) -> 'a list -> bool
@@ -156,7 +156,7 @@ val memq : 'a -> 'a list -> bool
equality to compare list elements. *)
-(** {2 List searching} *)
+(** {6 List searching} *)
val find : ('a -> bool) -> 'a list -> 'a
@@ -181,7 +181,7 @@ val partition : ('a -> bool) -> 'a list -> 'a list * 'a list
The order of the elements in the input list is preserved. *)
-(** {2 Association lists} *)
+(** {6 Association lists} *)
val assoc : 'a -> ('a * 'b) list -> 'b
@@ -214,7 +214,7 @@ val remove_assq : 'a -> ('a * 'b) list -> ('a * 'b) list
of structural equality to compare keys. Not tail-recursive. *)
-(** {2 Lists of pairs} *)
+(** {6 Lists of pairs} *)
val split : ('a * 'b) list -> 'a list * 'b list
@@ -231,7 +231,7 @@ val combine : 'a list -> 'b list -> ('a * 'b) list
have different lengths. Not tail-recursive. *)
-(** {2 Sorting} *)
+(** {6 Sorting} *)
val sort : ('a -> 'a -> int) -> 'a list -> 'a list
diff --git a/stdlib/listLabels.mli b/stdlib/listLabels.mli
index 7664cf936..1f26c0c56 100644
--- a/stdlib/listLabels.mli
+++ b/stdlib/listLabels.mli
@@ -65,7 +65,7 @@ val flatten : 'a list list -> 'a list
(length of the argument + length of the longest sub-list). *)
-(** {2 Iterators} *)
+(** {6 Iterators} *)
val iter : f:('a -> unit) -> 'a list -> unit
@@ -92,7 +92,7 @@ val fold_right : f:('a -> 'b -> 'b) -> 'a list -> init:'b -> 'b
[f a1 (f a2 (... (f an b) ...))]. Not tail-recursive. *)
-(** {2 Iterators on two lists} *)
+(** {6 Iterators on two lists} *)
val iter2 : f:('a -> 'b -> unit) -> 'a list -> 'b list -> unit
@@ -129,7 +129,7 @@ val fold_right2 :
-(** {2 List scanning} *)
+(** {6 List scanning} *)
val for_all : f:('a -> bool) -> 'a list -> bool
@@ -163,7 +163,7 @@ val memq : 'a -> set:'a list -> bool
-(** {2 List searching} *)
+(** {6 List searching} *)
val find : f:('a -> bool) -> 'a list -> 'a
@@ -190,7 +190,7 @@ val partition : f:('a -> bool) -> 'a list -> 'a list * 'a list
-(** {2 Association lists} *)
+(** {6 Association lists} *)
val assoc : 'a -> ('a * 'b) list -> 'b
@@ -225,7 +225,7 @@ val remove_assq : 'a -> ('a * 'b) list -> ('a * 'b) list
-(** {2 Lists of pairs} *)
+(** {6 Lists of pairs} *)
val split : ('a * 'b) list -> 'a list * 'b list
@@ -243,7 +243,7 @@ val combine : 'a list -> 'b list -> ('a * 'b) list
-(** {2 Sorting} *)
+(** {6 Sorting} *)
val sort : cmp:('a -> 'a -> int) -> 'a list -> 'a list
diff --git a/stdlib/oo.mli b/stdlib/oo.mli
index 1ef711241..d3f2c3ed4 100644
--- a/stdlib/oo.mli
+++ b/stdlib/oo.mli
@@ -22,14 +22,14 @@ val copy : (< .. > as 'a) -> 'a
(**/**)
-(** {2 For system use only, not for the casual user} *)
+(** {6 For system use only, not for the casual user} *)
-(** {2 Methods} *)
+(** {6 Methods} *)
type label
val new_method : string -> label
-(** {2 Classes} *)
+(** {6 Classes} *)
type table
type meth
@@ -46,13 +46,13 @@ val add_initializer : table -> (obj -> unit) -> unit
val create_table : string list -> table
val init_class : table -> unit
-(** {2 Objects} *)
+(** {6 Objects} *)
val create_object : table -> obj
val run_initializers : obj -> table -> unit
val send : obj -> label -> t
-(** {2 Parameters} *)
+(** {6 Parameters} *)
type params =
{ mutable compact_table : bool;
@@ -63,7 +63,7 @@ type params =
val params : params
-(** {2 Statistics} *)
+(** {6 Statistics} *)
type stats =
{ classes : int;
diff --git a/stdlib/parsing.mli b/stdlib/parsing.mli
index 512878bff..54a247bd9 100644
--- a/stdlib/parsing.mli
+++ b/stdlib/parsing.mli
@@ -50,7 +50,7 @@ exception Parse_error
(**/**)
-(** {2 } *)
+(** {6 } *)
(** The following definitions are used by the generated parsers only.
They are not intended to be used by user programs. *)
diff --git a/stdlib/pervasives.mli b/stdlib/pervasives.mli
index 1ead63d0e..a1e8c9ccf 100644
--- a/stdlib/pervasives.mli
+++ b/stdlib/pervasives.mli
@@ -24,7 +24,7 @@
name, without prefixing them by [Pervasives].
*)
-(** {2 Predefined types}
+(** {6 Predefined types}
These are predefined types :
{[ type int]} The type of integer numbers.
{[ type char]} The type of characters.
@@ -45,7 +45,7 @@ These are predefined types :
[%a] and [%t] printing functions (see module {!Printf}).
*)
-(** {2 Exceptions} *)
+(** {6 Exceptions} *)
external raise : exn -> 'a = "%raise"
(** Raise the given exception value *)
@@ -113,7 +113,7 @@ val failwith : string -> 'a
(** Raise exception [Failure] with the given string. *)
-(** {2 Comparisons} *)
+(** {6 Comparisons} *)
external ( = ) : 'a -> 'a -> bool = "%equal"
@@ -172,7 +172,7 @@ external ( != ) : 'a -> 'a -> bool = "%noteq"
(** Negation of {!Pervasives.==}. *)
-(** {2 Boolean operations} *)
+(** {6 Boolean operations} *)
external not : bool -> bool = "%boolnot"
@@ -195,7 +195,7 @@ external ( or ) : bool -> bool -> bool = "%sequor"
[e2] is not evaluated at all. *)
-(** {2 Integer arithmetic} *)
+(** {6 Integer arithmetic} *)
(** Integers are 31 bits wide (or 63 bits on 64-bit processors).
All operations are taken modulo 2{^31} (or 2{^63}).
@@ -246,7 +246,7 @@ val min_int : int
-(** {3 Bitwise operations} *)
+(** {7 Bitwise operations} *)
external ( land ) : int -> int -> int = "%andint"
@@ -279,7 +279,7 @@ external ( asr ) : int -> int -> int = "%asrint"
The result is unspecified if [m < 0] or [m >= bitsize]. *)
-(** {2 Floating-point arithmetic}
+(** {6 Floating-point arithmetic}
Caml's floating-point numbers follow the
IEEE 754 standard, using double precision (64 bits) numbers.
@@ -433,7 +433,7 @@ external classify_float : float -> fpclass = "classify_float"
normal, subnormal, zero, infinite, or not a number. *)
-(** {2 String operations}
+(** {6 String operations}
More string operations are provided in module {!String}.
*)
@@ -442,7 +442,7 @@ val ( ^ ) : string -> string -> string
(** String concatenation. *)
-(** {2 Character operations}
+(** {6 Character operations}
More character operations are provided in module {!Char}.
*)
@@ -456,7 +456,7 @@ val char_of_int : int -> char
outside the range 0--255. *)
-(** {2 Unit operations} *)
+(** {6 Unit operations} *)
external ignore : 'a -> unit = "%ignore"
(** Discard the value of its argument and return [()].
@@ -467,7 +467,7 @@ external ignore : 'a -> unit = "%ignore"
avoids the warning. *)
-(** {2 String conversion functions} *)
+(** {6 String conversion functions} *)
val string_of_bool : bool -> string
(** Return the string representation of a boolean. *)
@@ -497,7 +497,7 @@ external float_of_string : string -> float = "float_of_string"
-(** {2 Pair operations} *)
+(** {6 Pair operations} *)
external fst : 'a * 'b -> 'a = "%field0"
(** Return the first component of a pair. *)
@@ -506,7 +506,7 @@ external snd : 'a * 'b -> 'b = "%field1"
(** Return the second component of a pair. *)
-(** {2 List operations}
+(** {6 List operations}
More list operations are provided in module {!List}.
*)
@@ -515,7 +515,7 @@ val ( @ ) : 'a list -> 'a list -> 'a list
(** List concatenation. *)
-(** {2 Input/output} *)
+(** {6 Input/output} *)
type in_channel
(** The type of input channel. *)
@@ -533,7 +533,7 @@ val stderr : out_channel
(** The standard error ouput for the process. *)
-(** {3 Output functions on standard output} *)
+(** {7 Output functions on standard output} *)
val print_char : char -> unit
(** Print a character on standard output. *)
@@ -557,7 +557,7 @@ val print_newline : unit -> unit
buffering of standard output. *)
-(** {3 Output functions on standard error} *)
+(** {7 Output functions on standard error} *)
val prerr_char : char -> unit
(** Print a character on standard error. *)
@@ -580,7 +580,7 @@ val prerr_newline : unit -> unit
standard error. *)
-(** {3 Input functions on standard input} *)
+(** {7 Input functions on standard input} *)
val read_line : unit -> string
(** Flush standard output, then read characters from standard input
@@ -598,7 +598,7 @@ val read_float : unit -> float
The result is unspecified if the line read is not a valid
representation of a floating-point number. *)
-(** {3 General output functions} *)
+(** {7 General output functions} *)
type open_flag =
@@ -703,7 +703,7 @@ val set_binary_mode_out : out_channel -> bool -> unit
do not distinguish between text mode and binary mode. *)
-(** {3 General input functions} *)
+(** {7 General input functions} *)
val open_in : string -> in_channel
(** Open the named file for reading, and return a new input channel
@@ -803,7 +803,7 @@ val set_binary_mode_in : in_channel -> bool -> unit
do not distinguish between text mode and binary mode. *)
-(** {2 References} *)
+(** {6 References} *)
type 'a ref = { mutable contents : 'a }
@@ -830,7 +830,7 @@ external decr : int ref -> unit = "%decr"
Equivalent to [fun r -> r := pred !r]. *)
-(** {2 Program termination} *)
+(** {6 Program termination} *)
val exit : int -> 'a
@@ -855,7 +855,7 @@ val at_exit : (unit -> unit) -> unit
(**/**)
-(** {2 For system use only, not for the casual user} *)
+(** {6 For system use only, not for the casual user} *)
val unsafe_really_input : in_channel -> string -> int -> int -> unit