summaryrefslogtreecommitdiffstats
path: root/ocamldoc/odoc_sig.ml
diff options
context:
space:
mode:
Diffstat (limited to 'ocamldoc/odoc_sig.ml')
-rw-r--r--ocamldoc/odoc_sig.ml17
1 files changed, 9 insertions, 8 deletions
diff --git a/ocamldoc/odoc_sig.ml b/ocamldoc/odoc_sig.ml
index 36b3b1411..9e0fc743e 100644
--- a/ocamldoc/odoc_sig.ml
+++ b/ocamldoc/odoc_sig.ml
@@ -172,9 +172,9 @@ module Analyser =
let name_comment_from_type_kind pos_end pos_limit tk =
match tk with
- Parsetree.Ptype_abstract | Parsetree.Ptype_private ->
+ Parsetree.Ptype_abstract ->
(0, [])
- | Parsetree.Ptype_variant (cons_core_type_list_list, _) ->
+ | Parsetree.Ptype_variant cons_core_type_list_list ->
let rec f acc cons_core_type_list_list =
match cons_core_type_list_list with
[] ->
@@ -197,7 +197,7 @@ module Analyser =
in
f [] cons_core_type_list_list
- | Parsetree.Ptype_record (name_mutable_type_list, _) (* of (string * mutable_flag * core_type) list*) ->
+ | Parsetree.Ptype_record name_mutable_type_list (* of (string * mutable_flag * core_type) list*) ->
let rec f = function
[] ->
[]
@@ -220,7 +220,7 @@ module Analyser =
Types.Type_abstract ->
Odoc_type.Type_abstract
- | Types.Type_variant (l, priv) ->
+ | Types.Type_variant l ->
let f (constructor_name, type_expr_list) =
let comment_opt =
try
@@ -235,9 +235,9 @@ module Analyser =
vc_text = comment_opt
}
in
- Odoc_type.Type_variant (List.map f l, priv = Asttypes.Private)
+ Odoc_type.Type_variant (List.map f l)
- | Types.Type_record (l, _, priv) ->
+ | Types.Type_record (l, _) ->
let f (field_name, mutable_flag, type_expr) =
let comment_opt =
try
@@ -253,7 +253,7 @@ module Analyser =
rf_text = comment_opt
}
in
- Odoc_type.Type_record (List.map f l, priv = Asttypes.Private)
+ Odoc_type.Type_record (List.map f l)
(** Analysis of the elements of a class, from the information in the parsetree and in the class
signature. @return the couple (inherited_class list, elements).*)
@@ -609,7 +609,8 @@ module Analyser =
)
sig_type_decl.Types.type_params
sig_type_decl.Types.type_variance;
- ty_kind = type_kind ;
+ ty_kind = type_kind;
+ ty_private = sig_type_decl.Types.type_private;
ty_manifest =
(match sig_type_decl.Types.type_manifest with
None -> None