summaryrefslogtreecommitdiffstats
path: root/ocamldoc
diff options
context:
space:
mode:
Diffstat (limited to 'ocamldoc')
-rw-r--r--ocamldoc/Makefile.nt1
-rw-r--r--ocamldoc/odoc_ast.ml4
-rw-r--r--ocamldoc/odoc_env.ml4
-rw-r--r--ocamldoc/odoc_print.ml8
-rw-r--r--ocamldoc/odoc_sig.ml10
5 files changed, 14 insertions, 13 deletions
diff --git a/ocamldoc/Makefile.nt b/ocamldoc/Makefile.nt
index ee155e793..e03bb6b19 100644
--- a/ocamldoc/Makefile.nt
+++ b/ocamldoc/Makefile.nt
@@ -143,6 +143,7 @@ OCAMLCMOFILES=$(OCAMLSRCDIR)/parsing/printast.cmo \
$(OCAMLSRCDIR)/parsing/parser.cmo \
$(OCAMLSRCDIR)/parsing/lexer.cmo \
$(OCAMLSRCDIR)/parsing/parse.cmo \
+ $(OCAMLSRCDIR)/parsing/ast_mapper.cmo \
$(OCAMLSRCDIR)/typing/types.cmo \
$(OCAMLSRCDIR)/typing/path.cmo \
$(OCAMLSRCDIR)/typing/btype.cmo \
diff --git a/ocamldoc/odoc_ast.ml b/ocamldoc/odoc_ast.ml
index a4da0f73a..dd106b4f0 100644
--- a/ocamldoc/odoc_ast.ml
+++ b/ocamldoc/odoc_ast.ml
@@ -944,12 +944,12 @@ module Analyser =
let f = match ele with
Element_module m ->
(function
- Types.Sig_module (ident,t,_) ->
+ Types.Sig_module (ident,md,_) ->
let n1 = Name.simple m.m_name
and n2 = Ident.name ident in
(
match n1 = n2 with
- true -> filter_module_with_module_type_constraint m t; true
+ true -> filter_module_with_module_type_constraint m md.md_type; true
| false -> false
)
| _ -> false)
diff --git a/ocamldoc/odoc_env.ml b/ocamldoc/odoc_env.ml
index d6a595bd7..7a9c86edd 100644
--- a/ocamldoc/odoc_env.ml
+++ b/ocamldoc/odoc_env.ml
@@ -53,9 +53,9 @@ let rec add_signature env root ?rel signat =
Types.Sig_value (ident, _) -> { env with env_values = (rel_name ident, qualify ident) :: env.env_values }
| Types.Sig_type (ident,_,_) -> { env with env_types = (rel_name ident, qualify ident) :: env.env_types }
| Types.Sig_exception (ident, _) -> { env with env_exceptions = (rel_name ident, qualify ident) :: env.env_exceptions }
- | Types.Sig_module (ident, modtype, _) ->
+ | Types.Sig_module (ident, md, _) ->
let env2 =
- match modtype with (* A VOIR : le cas ou c'est un identificateur, dans ce cas on n'a pas de signature *)
+ match md.Types.md_type with (* A VOIR : le cas ou c'est un identificateur, dans ce cas on n'a pas de signature *)
Types.Mty_signature s -> add_signature env (qualify ident) ~rel: (rel_name ident) s
| _ -> env
in
diff --git a/ocamldoc/odoc_print.ml b/ocamldoc/odoc_print.ml
index d09bc9324..aa6dea128 100644
--- a/ocamldoc/odoc_print.ml
+++ b/ocamldoc/odoc_print.ml
@@ -84,11 +84,11 @@ let simpl_class_type t =
(* on vire les vals et methods pour ne pas qu'elles soient imprimees
quand on affichera le type *)
let tnil = { Types.desc = Types.Tnil ; Types.level = 0; Types.id = 0 } in
- Types.Cty_signature { Types.cty_self = { cs.Types.cty_self with
+ Types.Cty_signature { Types.csig_self = { cs.Types.csig_self with
Types.desc = Types.Tobject (tnil, ref None) };
- Types.cty_vars = Types.Vars.empty ;
- Types.cty_concr = Types.Concr.empty ;
- Types.cty_inher = []
+ csig_vars = Types.Vars.empty ;
+ csig_concr = Types.Concr.empty ;
+ csig_inher = []
}
| Types.Cty_arrow (l, texp, ct) ->
let new_ct = iter ct in
diff --git a/ocamldoc/odoc_sig.ml b/ocamldoc/odoc_sig.ml
index da70778c4..4ea352174 100644
--- a/ocamldoc/odoc_sig.ml
+++ b/ocamldoc/odoc_sig.ml
@@ -94,7 +94,7 @@ module Signature_search =
let search_module table name =
match Hashtbl.find table (M name) with
- | (Types.Sig_module (ident, module_type, _)) -> module_type
+ | (Types.Sig_module (ident, md, _)) -> md.Types.md_type
| _ -> assert false
let search_module_type table name =
@@ -106,11 +106,11 @@ module Signature_search =
| _ -> assert false
let search_attribute_type name class_sig =
- let (_, _, type_expr) = Types.Vars.find name class_sig.Types.cty_vars in
+ let (_, _, type_expr) = Types.Vars.find name class_sig.Types.csig_vars in
type_expr
let search_method_type name class_sig =
- let fields = Odoc_misc.get_fields class_sig.Types.cty_self in
+ let fields = Odoc_misc.get_fields class_sig.Types.csig_self in
List.assoc name fields
end
@@ -219,7 +219,7 @@ module Analyser =
Types.Type_abstract ->
Odoc_type.Type_abstract
| Types.Type_variant l ->
- let f (constructor_name, type_expr_list, ret_type) =
+ let f {Types.cd_id=constructor_name;cd_args=type_expr_list;cd_res=ret_type} =
let constructor_name = Ident.name constructor_name in
let comment_opt =
try
@@ -238,7 +238,7 @@ module Analyser =
Odoc_type.Type_variant (List.map f l)
| Types.Type_record (l, _) ->
- let f (field_name, mutable_flag, type_expr) =
+ let f {Types.ld_id=field_name;ld_mutable=mutable_flag;ld_type=type_expr} =
let field_name = Ident.name field_name in
let comment_opt =
try