summaryrefslogtreecommitdiffstats
path: root/ocamldoc/odoc_info.mli
diff options
context:
space:
mode:
Diffstat (limited to 'ocamldoc/odoc_info.mli')
-rw-r--r--ocamldoc/odoc_info.mli113
1 files changed, 102 insertions, 11 deletions
diff --git a/ocamldoc/odoc_info.mli b/ocamldoc/odoc_info.mli
index 76e28df64..d1b98e224 100644
--- a/ocamldoc/odoc_info.mli
+++ b/ocamldoc/odoc_info.mli
@@ -20,6 +20,7 @@ type ref_kind = Odoc_types.ref_kind =
| RK_class_type
| RK_value
| RK_type
+ | RK_extension
| RK_exception
| RK_attribute
| RK_method
@@ -169,6 +170,47 @@ module Parameter :
val type_by_name : parameter -> string -> Types.type_expr
end
+(** Representation and manipulation of extensions. *)
+module Extension :
+ sig
+ type private_flag = Odoc_extension.private_flag =
+ Private | Public
+
+ (** Used when the extension is a rebind of another extension,
+ when we have [extension Xt = Target_xt].*)
+ type extension_alias = Odoc_extension.extension_alias =
+ {
+ xa_name : Name.t ; (** The complete name of the target extension. *)
+ mutable xa_xt : t_extension_constructor option ; (** The target extension, if we found it.*)
+ }
+
+ and t_extension_constructor = Odoc_extension.t_extension_constructor =
+ {
+ xt_name : Name.t ;
+ xt_args: Odoc_type.constructor_args;
+ xt_ret: Types.type_expr option ; (** the optional return type of the extension *)
+ xt_type_extension: t_type_extension ; (** the type extension containing this constructor *)
+ xt_alias: extension_alias option ; (** [None] when the extension is not a rebind. *)
+ mutable xt_loc: Odoc_types.location ;
+ mutable xt_text: Odoc_types.info option ; (** optional user description *)
+ }
+
+ and t_type_extension = Odoc_extension.t_type_extension =
+ {
+ mutable te_info : info option ; (** Information found in the optional associated comment. *)
+ te_type_name : Name.t ; (** The type of the extension *)
+ te_type_parameters : Types.type_expr list;
+ te_private : private_flag ;
+ mutable te_constructors: t_extension_constructor list;
+ mutable te_loc : location ;
+ mutable te_code : string option ;
+ }
+
+ (** Access to the extensions in a group. *)
+ val extension_constructors : t_type_extension -> t_extension_constructor list
+
+ end
+
(** Representation and manipulation of exceptions. *)
module Exception :
sig
@@ -184,7 +226,8 @@ module Exception :
{
ex_name : Name.t ;
mutable ex_info : info option ; (** Information found in the optional associated comment. *)
- ex_args : Types.type_expr list ; (** The types of the parameters. *)
+ ex_args : Odoc_type.constructor_args;
+ ex_ret : Types.type_expr option ; (** The the optional return type of the exception. *)
ex_alias : exception_alias option ; (** [None] when the exception is not a rebind. *)
mutable ex_loc : location ;
mutable ex_code : string option ;
@@ -197,15 +240,6 @@ module Type :
type private_flag = Odoc_type.private_flag =
Private | Public
- (** Description of a variant type constructor. *)
- type variant_constructor = Odoc_type.variant_constructor =
- {
- vc_name : string ; (** Name of the constructor. *)
- vc_args : Types.type_expr list ; (** Arguments of the constructor. *)
- vc_ret : Types.type_expr option ;
- mutable vc_text : info option ; (** Optional description in the associated comment. *)
- }
-
(** Description of a record type field. *)
type record_field = Odoc_type.record_field =
{
@@ -215,6 +249,19 @@ module Type :
mutable rf_text : info option ; (** Optional description in the associated comment.*)
}
+ (** Description of a variant type constructor. *)
+ type constructor_args = Odoc_type.constructor_args =
+ | Cstr_record of record_field list
+ | Cstr_tuple of Types.type_expr list
+
+ type variant_constructor = Odoc_type.variant_constructor =
+ {
+ vc_name : string ; (** Name of the constructor. *)
+ vc_args : constructor_args;
+ vc_ret : Types.type_expr option ;
+ mutable vc_text : info option ; (** Optional description in the associated comment. *)
+ }
+
(** The various kinds of a type. *)
type type_kind = Odoc_type.type_kind =
Type_abstract (** Type is abstract, for example [type t]. *)
@@ -222,6 +269,17 @@ module Type :
(** constructors *)
| Type_record of record_field list
(** fields *)
+ | Type_open (** Type is open *)
+
+ type object_field = Odoc_type.object_field = {
+ of_name : string ;
+ of_type : Types.type_expr ;
+ mutable of_text : Odoc_types.info option ; (** optional user description *)
+ }
+
+ type type_manifest = Odoc_type.type_manifest =
+ | Other of Types.type_expr (** Type manifest directly taken from Typedtre. *)
+ | Object_type of object_field list
(** Representation of a type. *)
type t_type = Odoc_type.t_type =
@@ -232,7 +290,7 @@ module Type :
(** type parameters: (type, covariant, contravariant) *)
ty_kind : type_kind; (** Type kind. *)
ty_private : private_flag; (** Private or public type. *)
- ty_manifest : Types.type_expr option; (** Type manifest. *)
+ ty_manifest : type_manifest option ;
mutable ty_loc : location ;
mutable ty_code : string option;
}
@@ -410,6 +468,7 @@ module Module :
| Element_class of Class.t_class
| Element_class_type of Class.t_class_type
| Element_value of Value.t_value
+ | Element_type_extension of Extension.t_type_extension
| Element_exception of Exception.t_exception
| Element_type of Type.t_type
| Element_module_comment of text
@@ -518,6 +577,9 @@ module Module :
(** Access to the included modules of a module. *)
val module_included_modules : ?trans:bool-> t_module -> included_module list
+ (** Access to the type extensions of a module. *)
+ val module_type_extensions : ?trans:bool-> t_module -> Extension.t_type_extension list
+
(** Access to the exceptions of a module. *)
val module_exceptions : ?trans:bool-> t_module -> Exception.t_exception list
@@ -630,6 +692,10 @@ val string_of_type_list : ?par: bool -> string -> Types.type_expr list -> string
for the given type. *)
val string_of_type_param_list : Type.t_type -> string
+(** This function returns a string to represent the list of type parameters
+ for the given type extension. *)
+val string_of_type_extension_param_list : Extension.t_type_extension -> string
+
(** This function returns a string to represent the given list of
type parameters of a class or class type,
with a given separator. *)
@@ -659,6 +725,11 @@ val string_of_info : info -> string
(** @return a string to describe the given type. *)
val string_of_type : Type.t_type -> string
+val string_of_record : Type.record_field list -> string
+
+(** @return a string to describe the given type extension. *)
+val string_of_type_extension : Extension.t_type_extension -> string
+
(** @return a string to describe the given exception. *)
val string_of_exception : Exception.t_exception -> string
@@ -789,6 +860,7 @@ module Search :
| Res_class_type of Class.t_class_type
| Res_value of Value.t_value
| Res_type of Type.t_type
+ | Res_extension of Extension.t_extension_constructor
| Res_exception of Exception.t_exception
| Res_attribute of Value.t_attribute
| Res_method of Value.t_method
@@ -805,6 +877,9 @@ module Search :
(** A function to search all the values in a list of modules. *)
val values : Module.t_module list -> Value.t_value list
+ (** A function to search all the extensions in a list of modules. *)
+ val extensions : Module.t_module list -> Extension.t_extension_constructor list
+
(** A function to search all the exceptions in a list of modules. *)
val exceptions : Module.t_module list -> Exception.t_exception list
@@ -844,11 +919,27 @@ module Scan :
method scan_type_const : Type.t_type -> Type.variant_constructor -> unit
method scan_type_recfield : Type.t_type -> Type.record_field -> unit
method scan_type : Type.t_type -> unit
+ method scan_extension_constructor : Extension.t_extension_constructor -> unit
method scan_exception : Exception.t_exception -> unit
method scan_attribute : Value.t_attribute -> unit
method scan_method : Value.t_method -> unit
method scan_included_module : Module.included_module -> unit
+ (** Scan of a type extension *)
+
+ (** Overide this method to perform controls on the extension's type,
+ private and info. This method is called before scanning the
+ extension's constructors.
+ @return true if the extension's constructors must be scanned.*)
+ method scan_type_extension_pre : Extension.t_type_extension -> bool
+
+ (** This method scans the constructors of the given type extension. *)
+ method scan_type_extension_constructors : Extension.t_type_extension -> unit
+
+ (** Scan of a type extension. Should not be overridden. It calls [scan_type_extension_pre]
+ and if [scan_type_extension_pre] returns [true], then it calls scan_type_extension_constructors.*)
+ method scan_type_extension : Extension.t_type_extension -> unit
+
(** Scan of a class. *)
(** Scan of a comment inside a class. *)