diff options
author | Maxence Guesdon <maxence.guesdon@inria.fr> | 2010-04-19 16:48:42 +0000 |
---|---|---|
committer | Maxence Guesdon <maxence.guesdon@inria.fr> | 2010-04-19 16:48:42 +0000 |
commit | f8a0a241cc43693be879c9686ad188b1b496f649 (patch) | |
tree | c1fb2f5b4b224318a5812bc6159d314a2d621515 /ocamldoc | |
parent | 0f44ce9898dd927634b90f90d0d158a44716f4ae (diff) |
handle 'module type of' in structs
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@10281 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
Diffstat (limited to 'ocamldoc')
-rw-r--r-- | ocamldoc/odoc_analyse.ml | 1 | ||||
-rw-r--r-- | ocamldoc/odoc_cross.ml | 4 | ||||
-rw-r--r-- | ocamldoc/odoc_html.ml | 4 | ||||
-rw-r--r-- | ocamldoc/odoc_info.mli | 1 | ||||
-rw-r--r-- | ocamldoc/odoc_latex.ml | 5 | ||||
-rw-r--r-- | ocamldoc/odoc_module.ml | 5 | ||||
-rw-r--r-- | ocamldoc/odoc_sig.ml | 11 | ||||
-rw-r--r-- | ocamldoc/odoc_to_text.ml | 7 |
8 files changed, 33 insertions, 5 deletions
diff --git a/ocamldoc/odoc_analyse.ml b/ocamldoc/odoc_analyse.ml index f6deb87c9..5ab371488 100644 --- a/ocamldoc/odoc_analyse.ml +++ b/ocamldoc/odoc_analyse.ml @@ -427,6 +427,7 @@ and remove_module_elements_between_stop_in_module_kind k = | Odoc_module.Module_constraint (k2, mtkind) -> Odoc_module.Module_constraint (remove_module_elements_between_stop_in_module_kind k2, remove_module_elements_between_stop_in_module_type_kind mtkind) + | Odoc_module.Module_typeof _ -> k (** Remove the module elements between the stop special comment, in the given module type kind. *) and remove_module_elements_between_stop_in_module_type_kind tk = diff --git a/ocamldoc/odoc_cross.ml b/ocamldoc/odoc_cross.ml index 5298417d8..ab59a1727 100644 --- a/ocamldoc/odoc_cross.ml +++ b/ocamldoc/odoc_cross.ml @@ -343,6 +343,9 @@ let rec associate_in_module module_list (acc_b_modif, acc_incomplete_top_module_ { mt_name = "" ; mt_info = None ; mt_type = None ; mt_is_interface = false ; mt_file = "" ; mt_kind = Some tk ; mt_loc = Odoc_types.dummy_loc } + + | Module_typeof _ -> + (acc_b, acc_inc, acc_names) in iter_kind (acc_b_modif, acc_incomplete_top_module_names, acc_names_not_found) m.m_kind @@ -799,6 +802,7 @@ and assoc_comments_module_kind parent_name module_list mk = Module_constraint (assoc_comments_module_kind parent_name module_list mk1, assoc_comments_module_type_kind parent_name module_list mtk) + | Module_typeof _ -> mk and assoc_comments_module_type_kind parent_name module_list mtk = match mtk with diff --git a/ocamldoc/odoc_html.ml b/ocamldoc/odoc_html.ml index 6dd800f28..08ab581f4 100644 --- a/ocamldoc/odoc_html.ml +++ b/ocamldoc/odoc_html.ml @@ -1225,6 +1225,10 @@ class html = | Module_constraint (k, tk) -> (* TODO: on affiche quoi ? *) self#html_of_module_kind b father ?modu k + | Module_typeof s -> + bs b "<code class=\"type\">module type of "; + bs b (self#create_fully_qualified_module_idents_links father s); + bs b "</code>" method html_of_module_parameter b father p = let (s_functor,s_arrow) = diff --git a/ocamldoc/odoc_info.mli b/ocamldoc/odoc_info.mli index ffdb2afba..73dee8406 100644 --- a/ocamldoc/odoc_info.mli +++ b/ocamldoc/odoc_info.mli @@ -447,6 +447,7 @@ module Module : Should appear in interface files only. *) | Module_constraint of module_kind * module_type_kind (** A module constraint by a module type. *) + | Module_typeof of string (** by now only the code of the module expression *) (** Representation of a module. *) and t_module = Odoc_module.t_module = diff --git a/ocamldoc/odoc_latex.ml b/ocamldoc/odoc_latex.ml index 4cfc3f9de..a9ecc5e04 100644 --- a/ocamldoc/odoc_latex.ml +++ b/ocamldoc/odoc_latex.ml @@ -659,6 +659,11 @@ class latex = | Module_constraint (k, tk) -> (* TODO: on affiche quoi ? *) self#latex_of_module_kind fmt father k + | Module_typeof s -> + self#latex_of_text fmt + [ Code "module type of "; + Code (self#relative_idents father s); + ] method latex_of_class_kind fmt father kind = match kind with diff --git a/ocamldoc/odoc_module.ml b/ocamldoc/odoc_module.ml index 44f5e9fef..d95331b25 100644 --- a/ocamldoc/odoc_module.ml +++ b/ocamldoc/odoc_module.ml @@ -60,6 +60,7 @@ and module_kind = | Module_apply of module_kind * module_kind | Module_with of module_type_kind * string | Module_constraint of module_kind * module_type_kind + | Module_typeof of string (** by now only the code of the module expression *) (** Representation of a module. *) and t_module = { @@ -244,6 +245,7 @@ let rec module_elements ?(trans=true) m = m_code_intf = None ; m_text_only = false ; } + | Module_typeof s -> [] (* module_type_elements ~trans: trans { mt_name = "" ; mt_info = None ; mt_type = None ; @@ -401,7 +403,8 @@ and module_parameters ?(trans=true) m = mt_loc = Odoc_types.dummy_loc } | Module_struct _ | Module_apply _ - | Module_with _ -> + | Module_with _ + | Module_typeof _ -> [] in iter m.m_kind diff --git a/ocamldoc/odoc_sig.ml b/ocamldoc/odoc_sig.ml index 1839e3689..96d31655d 100644 --- a/ocamldoc/odoc_sig.ml +++ b/ocamldoc/odoc_sig.ml @@ -1074,9 +1074,9 @@ module Analyser = | Parsetree.Pmty_typeof module_expr -> let loc_start = module_expr.Parsetree.pmod_loc.Location.loc_start.Lexing.pos_cnum in - let loc_end = module_expr.Parsetree.pmod_loc.Location.loc_end.Lexing.pos_cnum in - let s = get_string_of_file loc_start loc_end in - Module_type_typeof s + let loc_end = module_expr.Parsetree.pmod_loc.Location.loc_end.Lexing.pos_cnum in + let s = get_string_of_file loc_start loc_end in + Module_type_typeof s (** analyse of a Parsetree.module_type and a Types.module_type.*) and analyse_module_kind env current_module_name module_type sig_module_type = @@ -1142,7 +1142,10 @@ module Analyser = Module_with (k, s) ) | Parsetree.Pmty_typeof module_expr -> - assert false (* TODO *) + let loc_start = module_expr.Parsetree.pmod_loc.Location.loc_start.Lexing.pos_cnum in + let loc_end = module_expr.Parsetree.pmod_loc.Location.loc_end.Lexing.pos_cnum in + let s = get_string_of_file loc_start loc_end in + Module_typeof s (** Analyse of a Parsetree.class_type and a Types.class_type to return a couple (class parameters, class_kind).*) diff --git a/ocamldoc/odoc_to_text.ml b/ocamldoc/odoc_to_text.ml index e51e65f7b..e3f53383f 100644 --- a/ocamldoc/odoc_to_text.ml +++ b/ocamldoc/odoc_to_text.ml @@ -543,6 +543,13 @@ class virtual to_text = [Code " -> "] @ (self#text_of_module_kind ~with_def_syntax: false k) + | Module_typeof s -> + let code = Printf.sprintf "%smodule type of %s" + (if with_def_syntax then " : " else "") + s + in + [Code code] + (** Return html code for a [module_type_kind].*) method text_of_module_type_kind ?(with_def_syntax=true) tk = match tk with |