summaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
-rw-r--r--ocamldoc/odoc_sig.ml6
-rw-r--r--ocamldoc/odoc_sig.mli20
2 files changed, 20 insertions, 6 deletions
diff --git a/ocamldoc/odoc_sig.ml b/ocamldoc/odoc_sig.ml
index 8e2756281..06d075065 100644
--- a/ocamldoc/odoc_sig.ml
+++ b/ocamldoc/odoc_sig.ml
@@ -170,10 +170,6 @@ module Analyser =
(** This function merge two optional info structures. *)
let merge_infos = Odoc_merge.merge_info_opt Odoc_types.all_merge_options
- (** This function takes a Parsetree.type_kind and returns the list of
- (name, optional comment) for the various fields/constructors of the type,
- or an empty list for an abstract type.
- [pos_start] and [pos_end] are the first and last char of the complete type definition.*)
let name_comment_from_type_kind pos_start pos_end pos_limit tk =
match tk with
Parsetree.Ptype_abstract ->
@@ -241,8 +237,6 @@ module Analyser =
in
(0, f name_mutable_type_list)
- (** This function converts a Types.type_kind into a Odoc_type.type_kind,
- by associating the comment found in the parsetree of each constructor/field, if any.*)
let get_type_kind env name_comment_list type_kind =
match type_kind with
Types.Type_abstract ->
diff --git a/ocamldoc/odoc_sig.mli b/ocamldoc/odoc_sig.mli
index d09a05697..bf29fa3d4 100644
--- a/ocamldoc/odoc_sig.mli
+++ b/ocamldoc/odoc_sig.mli
@@ -132,6 +132,26 @@ module Analyser :
val get_comments_in_module : int -> int ->
(Odoc_types.info option * Odoc_module.module_element list)
+ (** This function takes a [Parsetree.type_kind] and returns the list of
+ (name, optional comment) for the various fields/constructors of the type,
+ or an empty list for an abstract type.
+ [pos_start] and [pos_end] are the first and last char of the complete type definition.
+ [pos_limit] is the position of the last char we could use to look for a comment,
+ i.e. usually the beginning on the next element.*)
+ val name_comment_from_type_kind :
+ int -> int -> int -> Parsetree.type_kind -> int * (string * Odoc_types.info option) list
+
+ (** This function converts a [Types.type_kind] into a [Odoc_type.type_kind],
+ by associating the comment found in the parsetree of each constructor/field, if any.*)
+ val get_type_kind :
+ Odoc_env.env -> (string * Odoc_types.info option) list ->
+ Types.type_kind -> Odoc_type.type_kind
+
+ (** This function merge two optional info structures. *)
+ val merge_infos :
+ Odoc_types.info option -> Odoc_types.info option ->
+ Odoc_types.info option
+
(** Return a module_type_kind from a Parsetree.module_type and a Types.module_type *)
val analyse_module_type_kind :
Odoc_env.env -> Odoc_name.t ->