summaryrefslogtreecommitdiffstats
path: root/ocamldoc
diff options
context:
space:
mode:
Diffstat (limited to 'ocamldoc')
-rw-r--r--ocamldoc/odoc_ast.ml17
-rw-r--r--ocamldoc/odoc_env.ml2
-rw-r--r--ocamldoc/odoc_html.ml3
-rw-r--r--ocamldoc/odoc_info.mli2
-rw-r--r--ocamldoc/odoc_man.ml2
-rw-r--r--ocamldoc/odoc_module.ml2
-rw-r--r--ocamldoc/odoc_print.ml2
-rw-r--r--ocamldoc/odoc_sig.ml33
-rw-r--r--ocamldoc/odoc_to_text.ml7
9 files changed, 47 insertions, 23 deletions
diff --git a/ocamldoc/odoc_ast.ml b/ocamldoc/odoc_ast.ml
index 6f0a8d572..18e474a79 100644
--- a/ocamldoc/odoc_ast.ml
+++ b/ocamldoc/odoc_ast.ml
@@ -1606,18 +1606,25 @@ module Analyser =
| (Parsetree.Pmod_functor (_, pmodule_type, p_module_expr2),
Typedtree.Tmod_functor (ident, _, mtyp, tt_module_expr2)) ->
- let loc_start = pmodule_type.Parsetree.pmty_loc.Location.loc_start.Lexing.pos_cnum in
- let loc_end = pmodule_type.Parsetree.pmty_loc.Location.loc_end.Lexing.pos_cnum in
+ let loc = match pmodule_type with None -> Location.none
+ | Some pmty -> pmty.Parsetree.pmty_loc in
+ let loc_start = loc.Location.loc_start.Lexing.pos_cnum in
+ let loc_end = loc.Location.loc_end.Lexing.pos_cnum in
let mp_type_code = get_string_of_file loc_start loc_end in
print_DEBUG (Printf.sprintf "mp_type_code=%s" mp_type_code);
let mp_name = Name.from_ident ident in
- let mp_kind = Sig.analyse_module_type_kind env
- current_module_name pmodule_type mtyp.mty_type
+ let mp_kind =
+ match pmodule_type, mtyp with
+ Some pmty, Some mty ->
+ Sig.analyse_module_type_kind env current_module_name pmty
+ mty.mty_type
+ | _ -> Module_type_struct []
in
let param =
{
mp_name = mp_name ;
- mp_type = Odoc_env.subst_module_type env mtyp.mty_type ;
+ mp_type = Misc.may_map
+ (fun m -> Odoc_env.subst_module_type env m.mty_type) mtyp ;
mp_type_code = mp_type_code ;
mp_kind = mp_kind ;
}
diff --git a/ocamldoc/odoc_env.ml b/ocamldoc/odoc_env.ml
index 5fd1f0508..d55ace84c 100644
--- a/ocamldoc/odoc_env.ml
+++ b/ocamldoc/odoc_env.ml
@@ -223,7 +223,7 @@ let subst_module_type env t =
| Types.Mty_signature _ ->
t
| Types.Mty_functor (id, mt1, mt2) ->
- Types.Mty_functor (id, iter mt1, iter mt2)
+ Types.Mty_functor (id, Misc.may_map iter mt1, iter mt2)
in
iter t
diff --git a/ocamldoc/odoc_html.ml b/ocamldoc/odoc_html.ml
index db7d82ce1..3bee9838b 100644
--- a/ocamldoc/odoc_html.ml
+++ b/ocamldoc/odoc_html.ml
@@ -1384,7 +1384,8 @@ class html =
(** Print html code to display the type of a module parameter.. *)
method html_of_module_parameter_type b m_name p =
- self#html_of_module_type b m_name ~code: p.mp_type_code p.mp_type
+ match p.mp_type with None -> bs b "<code>()</code>"
+ | Some mty -> self#html_of_module_type b m_name ~code: p.mp_type_code mty
(** Generate a file containing the module type in the given file name. *)
method output_module_type in_title file mtyp =
diff --git a/ocamldoc/odoc_info.mli b/ocamldoc/odoc_info.mli
index bf4d33b6f..76e28df64 100644
--- a/ocamldoc/odoc_info.mli
+++ b/ocamldoc/odoc_info.mli
@@ -434,7 +434,7 @@ module Module :
and module_parameter = Odoc_module.module_parameter = {
mp_name : string ; (** the name *)
- mp_type : Types.module_type ; (** the type *)
+ mp_type : Types.module_type option ; (** the type *)
mp_type_code : string ; (** the original code *)
mp_kind : module_type_kind ; (** the way the parameter was built *)
}
diff --git a/ocamldoc/odoc_man.ml b/ocamldoc/odoc_man.ml
index 808136968..8a252d631 100644
--- a/ocamldoc/odoc_man.ml
+++ b/ocamldoc/odoc_man.ml
@@ -637,7 +637,7 @@ class man =
(fun (p, desc_opt) ->
bs b ".sp\n";
bs b ("\""^p.mp_name^"\"\n");
- self#man_of_module_type b m_name p.mp_type;
+ Misc.may (self#man_of_module_type b m_name) p.mp_type;
bs b "\n";
(
match desc_opt with
diff --git a/ocamldoc/odoc_module.ml b/ocamldoc/odoc_module.ml
index 216f1cfb3..b1bedfa77 100644
--- a/ocamldoc/odoc_module.ml
+++ b/ocamldoc/odoc_module.ml
@@ -46,7 +46,7 @@ and module_alias = {
and module_parameter = {
mp_name : string ; (** the name *)
- mp_type : Types.module_type ; (** the type *)
+ mp_type : Types.module_type option ; (** the type *)
mp_type_code : string ; (** the original code *)
mp_kind : module_type_kind ; (** the way the parameter was built *)
}
diff --git a/ocamldoc/odoc_print.ml b/ocamldoc/odoc_print.ml
index aa6dea128..d6b56f395 100644
--- a/ocamldoc/odoc_print.ml
+++ b/ocamldoc/odoc_print.ml
@@ -62,7 +62,7 @@ let simpl_module_type ?code t =
| Some s -> raise (Use_code s)
)
| Types.Mty_functor (id, mt1, mt2) ->
- Types.Mty_functor (id, iter mt1, iter mt2)
+ Types.Mty_functor (id, Misc.may_map iter mt1, iter mt2)
in
iter t
diff --git a/ocamldoc/odoc_sig.ml b/ocamldoc/odoc_sig.ml
index 422b35507..93f0193e5 100644
--- a/ocamldoc/odoc_sig.ml
+++ b/ocamldoc/odoc_sig.ml
@@ -1076,19 +1076,26 @@ module Analyser =
| Parsetree.Pmty_functor (_, pmodule_type2, module_type2) ->
(
- let loc_start = pmodule_type2.Parsetree.pmty_loc.Location.loc_start.Lexing.pos_cnum in
- let loc_end = pmodule_type2.Parsetree.pmty_loc.Location.loc_end.Lexing.pos_cnum in
+ let loc = match pmodule_type2 with None -> Location.none
+ | Some pmty -> pmty.Parsetree.pmty_loc in
+ let loc_start = loc.Location.loc_start.Lexing.pos_cnum in
+ let loc_end = loc.Location.loc_end.Lexing.pos_cnum in
let mp_type_code = get_string_of_file loc_start loc_end in
print_DEBUG (Printf.sprintf "mp_type_code=%s" mp_type_code);
match sig_module_type with
Types.Mty_functor (ident, param_module_type, body_module_type) ->
- let mp_kind = analyse_module_type_kind env
- current_module_name pmodule_type2 param_module_type
+ let mp_kind =
+ match pmodule_type2, param_module_type with
+ Some pmty, Some mty ->
+ analyse_module_type_kind env current_module_name pmty mty
+ | _ -> Module_type_struct []
in
let param =
{
mp_name = Name.from_ident ident ;
- mp_type = Odoc_env.subst_module_type env param_module_type ;
+ mp_type =
+ Misc.may_map (Odoc_env.subst_module_type env)
+ param_module_type;
mp_type_code = mp_type_code ;
mp_kind = mp_kind ;
}
@@ -1155,17 +1162,23 @@ module Analyser =
(
match sig_module_type with
Types.Mty_functor (ident, param_module_type, body_module_type) ->
- let loc_start = pmodule_type2.Parsetree.pmty_loc.Location.loc_start.Lexing.pos_cnum in
- let loc_end = pmodule_type2.Parsetree.pmty_loc.Location.loc_end.Lexing.pos_cnum in
+ let loc = match pmodule_type2 with None -> Location.none
+ | Some pmty -> pmty.Parsetree.pmty_loc in
+ let loc_start = loc.Location.loc_start.Lexing.pos_cnum in
+ let loc_end = loc.Location.loc_end.Lexing.pos_cnum in
let mp_type_code = get_string_of_file loc_start loc_end in
print_DEBUG (Printf.sprintf "mp_type_code=%s" mp_type_code);
- let mp_kind = analyse_module_type_kind env
- current_module_name pmodule_type2 param_module_type
+ let mp_kind =
+ match pmodule_type2, param_module_type with
+ Some pmty, Some mty ->
+ analyse_module_type_kind env current_module_name pmty mty
+ | _ -> Module_type_struct []
in
let param =
{
mp_name = Name.from_ident ident ;
- mp_type = Odoc_env.subst_module_type env param_module_type ;
+ mp_type = Misc.may_map
+ (Odoc_env.subst_module_type env) param_module_type ;
mp_type_code = mp_type_code ;
mp_kind = mp_kind ;
}
diff --git a/ocamldoc/odoc_to_text.ml b/ocamldoc/odoc_to_text.ml
index 7b08417e7..c91387570 100644
--- a/ocamldoc/odoc_to_text.ml
+++ b/ocamldoc/odoc_to_text.ml
@@ -428,8 +428,11 @@ class virtual to_text =
List
(List.map
(fun (p, desc_opt) ->
- [Code (p.mp_name^" : ")] @
- (self#text_of_module_type p.mp_type) @
+ begin match p.mp_type with None -> [Raw ""]
+ | Some mty ->
+ [Code (p.mp_name^" : ")] @
+ (self#text_of_module_type mty)
+ end @
(match desc_opt with
None -> []
| Some t -> (Raw " ") :: t)