Skip to content

Commit 903ab4c

Browse files
committed
PR#7363: start documentation headers at {1
1 parent 8ca16f7 commit 903ab4c

Some content is hidden

Large Commits have some content hidden by default. Use the searchbox below for content that may be hidden.

43 files changed

+273
-272
lines changed

manual/tools/caml_tex2.ml

+4-4
Original file line numberDiff line numberDiff line change
@@ -87,13 +87,13 @@ module Output = struct
8787
| Ok -> Printf.fprintf ppf "an ok"
8888
| Warning n -> Printf.fprintf ppf "a warning %d" n
8989

90-
(** {2 Related latex environment } *)
90+
(** {1 Related latex environment } *)
9191
let env = function
9292
| Error -> error
9393
| Warning _ -> warning
9494
| Ok -> ok_output
9595

96-
(** {2 Exceptions } *)
96+
(** {1 Exceptions } *)
9797
exception Parsing_error of kind * string
9898

9999
type source = { file:string; lines:int * int; phrase:string; output:string }
@@ -141,7 +141,7 @@ module Output = struct
141141
and [@@expect warning n] (with n a warning number).\n" s
142142

143143

144-
(** {2 Output analysis} *)
144+
(** {1 Output analysis} *)
145145
let catch_error s =
146146
if string_match ~!{|Error:|} s 0 then Some Error else None
147147

@@ -156,7 +156,7 @@ module Output = struct
156156
| None, Some e -> e
157157
| None, None -> Ok
158158

159-
(** {2 Parsing caml_example options } *)
159+
(** {1 Parsing caml_example options } *)
160160

161161
(** Parse [warning=n] options for caml_example options *)
162162
let parse_warning s =

ocamldoc/odoc_class.ml

+1-1
Original file line numberDiff line numberDiff line change
@@ -94,7 +94,7 @@ and t_class_type = {
9494
}
9595

9696

97-
(** {2 Functions} *)
97+
(** {1 Functions} *)
9898

9999
(** Returns the text associated to the given parameter label
100100
in the given class, or None. *)

ocamldoc/odoc_info.mli

+10-10
Original file line numberDiff line numberDiff line change
@@ -135,7 +135,7 @@ module Name :
135135
(** Representation and manipulation of method / function / class / module parameters.*)
136136
module Parameter :
137137
sig
138-
(** {3 Types} *)
138+
(** {2 Types} *)
139139

140140
(** Representation of a simple parameter name *)
141141
type simple_name = Odoc_parameter.simple_name =
@@ -154,7 +154,7 @@ module Parameter :
154154
(** A parameter is just a param_info.*)
155155
type parameter = param_info
156156

157-
(** {3 Functions} *)
157+
(** {2 Functions} *)
158158

159159
(** Access to the name as a string. For tuples, parentheses and commas are added. *)
160160
val complete_name : parameter -> string
@@ -343,7 +343,7 @@ module Value :
343343
(** Representation and manipulation of classes and class types.*)
344344
module Class :
345345
sig
346-
(** {3 Types} *)
346+
(** {2 Types} *)
347347

348348
(** To keep the order of elements in a class. *)
349349
type class_element = Odoc_class.class_element =
@@ -429,7 +429,7 @@ module Class :
429429
mutable clt_loc : location ;
430430
}
431431

432-
(** {3 Functions} *)
432+
(** {2 Functions} *)
433433

434434
(** Access to the elements of a class. *)
435435
val class_elements : ?trans:bool -> t_class -> class_element list
@@ -465,7 +465,7 @@ module Class :
465465
(** Representation and manipulation of modules and module types. *)
466466
module Module :
467467
sig
468-
(** {3 Types} *)
468+
(** {2 Types} *)
469469

470470
(** To keep the order of elements in a module. *)
471471
type module_element = Odoc_module.module_element =
@@ -570,7 +570,7 @@ module Module :
570570
mutable mt_loc : location ;
571571
}
572572

573-
(** {3 Functions for modules} *)
573+
(** {2 Functions for modules} *)
574574

575575
(** Access to the elements of a module. *)
576576
val module_elements : ?trans:bool -> t_module -> module_element list
@@ -620,7 +620,7 @@ module Module :
620620
(** The list of module comments. *)
621621
val module_comments : ?trans:bool-> t_module -> text list
622622

623-
(** {3 Functions for module types} *)
623+
(** {2 Functions for module types} *)
624624

625625
(** Access to the elements of a module type. *)
626626
val module_type_elements : ?trans:bool-> t_module_type -> module_element list
@@ -669,7 +669,7 @@ module Module :
669669
end
670670

671671

672-
(** {3 Getting strings from values} *)
672+
(** {2 Getting strings from values} *)
673673

674674
(** This function is used to reset the names of type variables.
675675
It must be called when printing the whole type of a function,
@@ -749,7 +749,7 @@ val string_of_attribute : Value.t_attribute -> string
749749
(** @return a string to describe the given method. *)
750750
val string_of_method : Value.t_method -> string
751751

752-
(** {3 Miscellaneous functions} *)
752+
(** {2 Miscelaneous functions} *)
753753

754754
(** Return the first sentence (until the first dot followed by a blank
755755
or the first blank line) of a text.
@@ -1036,7 +1036,7 @@ module Dep :
10361036
val deps_of_types : ?kernel: bool -> Type.t_type list -> (Type.t_type * (Name.t list)) list
10371037
end
10381038

1039-
(** {2 Some global variables} *)
1039+
(** {1 Some global variables} *)
10401040

10411041
module Global :
10421042
sig

ocamldoc/odoc_module.ml

+2-2
Original file line numberDiff line numberDiff line change
@@ -107,7 +107,7 @@ and t_module_type = {
107107
}
108108

109109

110-
(** {2 Functions} *)
110+
(** {1 Functions} *)
111111

112112
(** Returns the list of values from a list of module_element. *)
113113
let values l =
@@ -543,7 +543,7 @@ let module_type_simple_values ?(trans=true) mt =
543543
(fun v -> not (Odoc_value.is_function v))
544544
(values (module_type_elements ~trans mt))
545545

546-
(** {2 Functions for modules and module types} *)
546+
(** {1 Functions for modules and module types} *)
547547

548548
(** The list of classes defined in this module and all its modules, functors, ....
549549
@param trans indicates if, for aliased modules, we must perform a transitive search.*)

ocamldoc/odoc_texi.ml

+8-7
Original file line numberDiff line numberDiff line change
@@ -29,7 +29,7 @@ let info_section = ref "OCaml"
2929

3030
let info_entry = ref []
3131

32-
(** {2 Some small helper functions} *)
32+
(** {1 Some small helper functions} *)
3333

3434
let puts_nl chan s =
3535
output_string chan s ;
@@ -240,12 +240,13 @@ end
240240

241241

242242

243-
(** {2 Generation of Texinfo code} *)
243+
(** {1 Generation of Texinfo code} *)
244244

245245
(** This class generates Texinfo code from text structures *)
246246
class text =
247247
object(self)
248248

249+
249250
(** Associations between a title number and texinfo code. *)
250251
val titles = [
251252
0, "@chapter " ;
@@ -283,7 +284,7 @@ class text =
283284
(List.map self#texi_of_text_element t)
284285

285286

286-
(** {3 Conversion methods}
287+
(** {2 Conversion methods}
287288
[texi_of_????] converts a [text_element] to a Texinfo string. *)
288289

289290
(** Return the Texinfo code for the [text_element] in parameter. *)
@@ -401,7 +402,7 @@ class texi =
401402
inherit text
402403
inherit Odoc_to_text.to_text as to_text
403404

404-
(** {3 Small helper stuff.} *)
405+
(** {2 Small helper stuff.} *)
405406

406407
val maxdepth = 4
407408

@@ -455,7 +456,7 @@ class texi =
455456
| Raw s -> Raw (Str.global_replace re rep s)
456457
| txt -> txt) t
457458

458-
(** {3 [text] values generation}
459+
(** {2 [text] values generation}
459460
Generates [text] values out of description parts.
460461
Redefines some of methods of {! Odoc_to_text.to_text}. *)
461462

@@ -567,7 +568,7 @@ class texi =
567568
method texi_of_info i =
568569
self#texi_of_text (self#text_of_info i)
569570

570-
(** {3 Conversion of [module_elements] into Texinfo strings}
571+
(** {2 Conversion of [module_elements] into Texinfo strings}
571572
The following functions convert [module_elements] and their
572573
description to [text] values then to Texinfo strings using the
573574
functions above. *)
@@ -909,7 +910,7 @@ class texi =
909910
self#texi_of_text (Newline :: t @ [Newline])
910911
)
911912

912-
(** {3 Generating methods }
913+
(** {2 Generating methods }
913914
These methods write Texinfo code to an [out_channel] *)
914915

915916
(** Generate the Texinfo code for the given list of inherited classes.*)

otherlibs/bigarray/bigarray.mli

+9-9
Original file line numberDiff line numberDiff line change
@@ -32,7 +32,7 @@
3232
and {!Pervasives.input_value}).
3333
*)
3434

35-
(** {6 Element kinds} *)
35+
(** {1 Element kinds} *)
3636

3737
(** Big arrays can contain elements of the following kinds:
3838
- IEEE single precision (32 bits) floating-point numbers
@@ -179,7 +179,7 @@ val kind_size_in_bytes : ('a, 'b) kind -> int
179179
180180
@since 4.03.0 *)
181181

182-
(** {6 Array layouts} *)
182+
(** {1 Array layouts} *)
183183

184184
type c_layout = CamlinternalBigarray.c_layout = C_layout_typ (**)
185185
(** See {!Bigarray.fortran_layout}.*)
@@ -224,7 +224,7 @@ val c_layout : c_layout layout
224224
val fortran_layout : fortran_layout layout
225225

226226

227-
(** {6 Generic arrays (of arbitrarily many dimensions)} *)
227+
(** {1 Generic arrays (of arbitrarily many dimensions)} *)
228228

229229
module Genarray :
230230
sig
@@ -447,7 +447,7 @@ Note that Bigarray.Genarray.map_file raises Sys_error while\n\
447447
Unix.map_file raises Unix_error."]
448448
end
449449

450-
(** {6 Zero-dimensional arrays} *)
450+
(** {1 Zero-dimensional arrays} *)
451451

452452
(** Zero-dimensional arrays. The [Array0] structure provides operations
453453
similar to those of {!Bigarray.Genarray}, but specialized to the case
@@ -504,7 +504,7 @@ module Array0 : sig
504504
end
505505

506506

507-
(** {6 One-dimensional arrays} *)
507+
(** {1 One-dimensional arrays} *)
508508

509509
(** One-dimensional arrays. The [Array1] structure provides operations
510510
similar to those of
@@ -611,7 +611,7 @@ Unix.map_file raises Unix_error."]
611611
end
612612

613613

614-
(** {6 Two-dimensional arrays} *)
614+
(** {1 Two-dimensional arrays} *)
615615

616616
(** Two-dimensional arrays. The [Array2] structure provides operations
617617
similar to those of {!Bigarray.Genarray}, but specialized to the
@@ -734,7 +734,7 @@ Unix.map_file raises Unix_error."]
734734

735735
end
736736

737-
(** {6 Three-dimensional arrays} *)
737+
(** {1 Three-dimensional arrays} *)
738738

739739
(** Three-dimensional arrays. The [Array3] structure provides operations
740740
similar to those of {!Bigarray.Genarray}, but specialized to the case
@@ -882,7 +882,7 @@ Unix.map_file raises Unix_error."]
882882

883883
end
884884

885-
(** {6 Coercions between generic big arrays and fixed-dimension big arrays} *)
885+
(** {1 Coercions between generic big arrays and fixed-dimension big arrays} *)
886886

887887
external genarray_of_array0 :
888888
('a, 'b, 'c) Array0.t -> ('a, 'b, 'c) Genarray.t = "%identity"
@@ -926,7 +926,7 @@ val array3_of_genarray : ('a, 'b, 'c) Genarray.t -> ('a, 'b, 'c) Array3.t
926926
does not have exactly three dimensions. *)
927927

928928

929-
(** {6 Re-shaping big arrays} *)
929+
(** {1 Re-shaping big arrays} *)
930930

931931
val reshape : ('a, 'b, 'c) Genarray.t -> int array -> ('a, 'b, 'c) Genarray.t
932932
(** [reshape b [|d1;...;dN|]] converts the big array [b] to a

otherlibs/dynlink/dynlink.mli

+6-6
Original file line numberDiff line numberDiff line change
@@ -19,7 +19,7 @@ val is_native: bool
1919
(** [true] if the program is native,
2020
[false] if the program is bytecode. *)
2121

22-
(** {6 Dynamic loading of compiled files} *)
22+
(** {1 Dynamic loading of compiled files} *)
2323

2424
val loadfile : string -> unit
2525
(** In bytecode: load the given bytecode object file ([.cmo] file) or
@@ -42,7 +42,7 @@ val adapt_filename : string -> string
4242
(** In bytecode, the identity function. In native code, replace the last
4343
extension with [.cmxs]. *)
4444

45-
(** {6 Access control} *)
45+
(** {1 Access control} *)
4646

4747
val allow_only: string list -> unit
4848
(** [allow_only units] restricts the compilation units that
@@ -81,7 +81,7 @@ val allow_unsafe_modules : bool -> unit
8181
not allowed. In native code, this function does nothing; object files
8282
with external functions are always allowed to be dynamically linked. *)
8383

84-
(** {6 Deprecated, low-level API for access control} *)
84+
(** {1 Deprecated, low-level API for access control} *)
8585

8686
(** @deprecated The functions [add_interfaces], [add_available_units]
8787
and [clear_available_units] should not be used in new programs,
@@ -109,13 +109,13 @@ val clear_available_units : unit -> unit
109109
(** Empty the list of compilation units accessible to dynamically-linked
110110
programs. *)
111111

112-
(** {6 Deprecated, initialization} *)
112+
(** {1 Deprecated, initialization} *)
113113

114114
val init : unit -> unit
115115
(** @deprecated Initialize the [Dynlink] library. This function is called
116116
automatically when needed. *)
117117

118-
(** {6 Error reporting} *)
118+
(** {1 Error reporting} *)
119119

120120
type linking_error =
121121
Undefined_global of string
@@ -143,6 +143,6 @@ val error_message : error -> string
143143

144144
(**/**)
145145

146-
(** {6 Internal functions} *)
146+
(** {1 Internal functions} *)
147147

148148
val digest_interface : string -> string list -> Digest.t

0 commit comments

Comments
 (0)