summaryrefslogtreecommitdiffstats
path: root/ocamldoc/odoc_ast.ml
diff options
context:
space:
mode:
authorMaxence Guesdon <maxence.guesdon@inria.fr>2012-09-25 07:17:11 +0000
committerMaxence Guesdon <maxence.guesdon@inria.fr>2012-09-25 07:17:11 +0000
commitf071c2722e17a80d1e4741e49f1c225d267d54e9 (patch)
tree68230efbb1cbd87ec16f5abc42cf331e4a2b2b2b /ocamldoc/odoc_ast.ml
parent2932d1f4a01a0015584357401e040789a1b9c895 (diff)
PR#5744: fix pb with virtual attributes
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@12952 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
Diffstat (limited to 'ocamldoc/odoc_ast.ml')
-rw-r--r--ocamldoc/odoc_ast.ml16
1 files changed, 4 insertions, 12 deletions
diff --git a/ocamldoc/odoc_ast.ml b/ocamldoc/odoc_ast.ml
index 8745fb801..599d2c667 100644
--- a/ocamldoc/odoc_ast.ml
+++ b/ocamldoc/odoc_ast.ml
@@ -189,6 +189,9 @@ module Typedtree_search =
| { cf_desc = Typedtree.Tcf_val (_, _, _, ident, Tcfk_concrete exp, _) } :: q
when Name.from_ident ident = name ->
exp.Typedtree.exp_type
+ | { cf_desc = Typedtree.Tcf_val (_, _, _, ident, Tcfk_virtual typ, _) } :: q
+ when Name.from_ident ident = name ->
+ typ.Typedtree.ctyp_type
| _ :: q ->
iter q
in
@@ -202,12 +205,6 @@ module Typedtree_search =
in
fun ct_decl -> iter ct_decl.Types.clty_type
- let search_virtual_attribute_type table ctname name =
- let ct_decl = search_class_type_declaration table ctname in
- let cls_sig = class_sig_of_cltype_decl ct_decl.ci_type_decl in
- let (_,_,texp) = Types.Vars.find name cls_sig.cty_vars in
- texp
-
let search_method_expression cls name =
let rec iter = function
| [] ->
@@ -565,12 +562,7 @@ module Analyser =
let complete_name = Name.concat current_class_name label in
let (info_opt, ele_comments) = get_comments_in_class last_pos loc.Location.loc_start.Lexing.pos_cnum in
let type_exp =
- try
- if virt then
- Typedtree_search.search_virtual_attribute_type table
- (Name.simple current_class_name) label
- else
- Typedtree_search.search_attribute_type tt_cls label
+ try Typedtree_search.search_attribute_type tt_cls label
with Not_found ->
raise (Failure (Odoc_messages.attribute_not_found_in_typedtree complete_name))
in