Stdlib doc: harmonize heading levels again. (#2142)

master
Daniel Bünzli 2018-11-08 17:33:55 +01:00 committed by Alain Frisch
parent bf78bacb14
commit acb0e91ac6
23 changed files with 26 additions and 26 deletions

View File

@ -493,7 +493,7 @@ module LargeFile :
regular integers (type [int]), thus allowing operating on files
whose sizes are greater than [max_int]. *)
(** {6 Mapping files into memory} *)
(** {1 Mapping files into memory} *)
val map_file :
file_descr -> ?pos:int64 -> ('a, 'b) Stdlib.Bigarray.kind ->

View File

@ -306,7 +306,7 @@ let stable_sort cmp a =
let fast_sort = stable_sort
(** {6 Iterators} *)
(** {1 Iterators} *)
let to_seq a =
let rec aux i () =

View File

@ -259,7 +259,7 @@ val fast_sort : ('a -> 'a -> int) -> 'a array -> unit
*)
(** {6 Iterators} *)
(** {1 Iterators} *)
val to_seq : 'a array -> 'a Seq.t
(** Iterate on the array, in increasing order. Modifications of the

View File

@ -161,7 +161,7 @@ val fold_right : f:('b -> 'a -> 'a) -> 'b array -> init:'a -> 'a
where [n] is the length of the array [a]. *)
(** {6 Iterators on two arrays} *)
(** {1 Iterators on two arrays} *)
val iter2 : f:('a -> 'b -> unit) -> 'a array -> 'b array -> unit
@ -178,7 +178,7 @@ val map2 : f:('a -> 'b -> 'c) -> 'a array -> 'b array -> 'c array
@since 4.05.0 *)
(** {6 Array scanning} *)
(** {1 Array scanning} *)
val exists : f:('a -> bool) -> 'a array -> bool
@ -259,7 +259,7 @@ val fast_sort : cmp:('a -> 'a -> int) -> 'a array -> unit
*)
(** {6 Iterators} *)
(** {1 Iterators} *)
val to_seq : 'a array -> 'a Seq.t
(** Iterate on the array, in increasing order

View File

@ -273,7 +273,7 @@ let truncate b len =
else
b.position <- len
(** {6 Iterators} *)
(** {1 Iterators} *)
let to_seq b =
let rec aux i () =

View File

@ -158,7 +158,7 @@ val truncate : t -> int -> unit
Raise [Invalid_argument] if [len < 0] or [len > length b].
@since 4.05.0 *)
(** {6 Iterators} *)
(** {1 Iterators} *)
val to_seq : t -> char Seq.t
(** Iterate on the buffer, in increasing order.

View File

@ -330,7 +330,7 @@ let lowercase s = map Char.lowercase s
let capitalize s = apply1 Char.uppercase s
let uncapitalize s = apply1 Char.lowercase s
(** {6 Iterators} *)
(** {1 Iterators} *)
let to_seq s =
let rec aux i () =

View File

@ -319,7 +319,7 @@ val equal: t -> t -> bool
(** The equality function for byte sequences.
@since 4.03.0 *)
(** {3 Unsafe conversions (for advanced users)}
(** {1:unsafe Unsafe conversions (for advanced users)}
This section describes unsafe, low-level conversion functions
between [bytes] and [string]. They do not copy the internal data;
@ -448,7 +448,7 @@ let s = Bytes.of_string "hello"
[string] type for this purpose.
*)
(** {6 Iterators} *)
(** {1 Iterators} *)
val to_seq : t -> char Seq.t
(** Iterate on the string, in increasing index order. Modifications of the

View File

@ -293,7 +293,7 @@ val equal: t -> t -> bool
(** The equality function for byte sequences.
@since 4.05.0 *)
(** {6 Iterators} *)
(** {1 Iterators} *)
val to_seq : t -> char Seq.t
(** Iterate on the string, in increasing index order. Modifications of the

View File

@ -354,7 +354,7 @@ let stats h =
max_bucket_length = mbl;
bucket_histogram = histo }
(** {6 Iterators} *)
(** {1 Iterators} *)
let to_seq tbl =
(* capture current array, so that even if the table is resized we

View File

@ -216,7 +216,7 @@ val stats : ('a, 'b) t -> statistics
buckets by size.
@since 4.00.0 *)
(** {6 Iterators} *)
(** {1 Iterators} *)
val to_seq : ('a,'b) t -> ('a * 'b) Seq.t
(** Iterate on the whole table, in unspecified order.

View File

@ -494,7 +494,7 @@ let rec compare_length_with l n =
compare_length_with l (n-1)
;;
(** {6 Iterators} *)
(** {1 Iterators} *)
let to_seq l =
let rec aux l () = match l with

View File

@ -349,7 +349,7 @@ val merge : ('a -> 'a -> int) -> 'a list -> 'a list -> 'a list
Not tail-recursive (sum of the lengths of the arguments).
*)
(** {6 Iterators} *)
(** {1 Iterators} *)
val to_seq : 'a list -> 'a Seq.t
(** Iterate on the list

View File

@ -355,7 +355,7 @@ val merge : cmp:('a -> 'a -> int) -> 'a list -> 'a list -> 'a list
Not tail-recursive (sum of the lengths of the arguments).
*)
(** {6 Iterators} *)
(** {1 Iterators} *)
val to_seq : 'a list -> 'a Seq.t
(** Iterate on the list

View File

@ -306,7 +306,7 @@ module type S =
(** Same as {!Map.S.map}, but the function receives as arguments both the
key and the associated value for each binding of the map. *)
(** {6 Iterators} *)
(** {1 Iterators} *)
val to_seq : 'a t -> (key * 'a) Seq.t
(** Iterate on the whole map, in ascending order

View File

@ -147,7 +147,7 @@ let transfer q1 q2 =
q2.last <- q1.last;
clear q1
(** {6 Iterators} *)
(** {1 Iterators} *)
let to_seq q =
let rec aux c () = match c with

View File

@ -91,7 +91,7 @@ val transfer : 'a t -> 'a t -> unit
sequence [iter (fun x -> add x q2) q1; clear q1], but runs
in constant time. *)
(** {6 Iterators} *)
(** {1 Iterators} *)
val to_seq : 'a t -> 'a Seq.t
(** Iterate on the queue, in front-to-back order.

View File

@ -264,7 +264,7 @@ module type S =
except perhaps for lists with many duplicated elements.
@since 4.02.0 *)
(** {6 Iterators} *)
(** {1 Iterators} *)
val to_seq_from : elt -> t -> elt Seq.t
(** [to_seq_from x s] iterates on a subset of the elements of [s]

View File

@ -53,7 +53,7 @@ let iter f s = List.iter f s.c
let fold f acc s = List.fold_left f acc s.c
(** {6 Iterators} *)
(** {1 Iterators} *)
let to_seq s = List.to_seq s.c

View File

@ -72,7 +72,7 @@ val fold : ('b -> 'a -> 'b) -> 'b -> 'a t -> 'b
and [xn] the bottom element. The stack is unchanged.
@since 4.03 *)
(** {6 Iterators} *)
(** {1 Iterators} *)
val to_seq : 'a t -> 'a Seq.t
(** Iterate on the stack, top to bottom.

View File

@ -224,7 +224,7 @@ let capitalize s =
let uncapitalize s =
B.uncapitalize (bos s) |> bts
(** {6 Iterators} *)
(** {1 Iterators} *)
let to_seq s = bos s |> B.to_seq

View File

@ -333,7 +333,7 @@ val split_on_char: char -> string -> string list
@since 4.04.0
*)
(** {6 Iterators} *)
(** {1 Iterators} *)
val to_seq : t -> char Seq.t
(** Iterate on the string, in increasing index order. Modifications of the

View File

@ -288,7 +288,7 @@ val split_on_char: sep:char -> string -> string list
@since 4.05.0
*)
(** {6 Iterators} *)
(** {1 Iterators} *)
val to_seq : t -> char Seq.t
(** Iterate on the string, in increasing index order. Modifications of the