summaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
-rw-r--r--Changes3
-rw-r--r--ocamldoc/odoc_cross.ml4
-rw-r--r--ocamldoc/odoc_dep.ml4
-rw-r--r--ocamldoc/odoc_html.ml8
-rw-r--r--ocamldoc/odoc_info.mli7
-rw-r--r--ocamldoc/odoc_latex.ml16
-rw-r--r--ocamldoc/odoc_man.ml11
-rw-r--r--ocamldoc/odoc_merge.ml4
-rw-r--r--ocamldoc/odoc_sig.ml4
-rw-r--r--ocamldoc/odoc_str.ml8
-rw-r--r--ocamldoc/odoc_texi.ml66
-rw-r--r--ocamldoc/odoc_type.ml6
12 files changed, 77 insertions, 64 deletions
diff --git a/Changes b/Changes
index 961140829..1b752af23 100644
--- a/Changes
+++ b/Changes
@@ -129,6 +129,9 @@ Emacs mode:
OCamldoc:
- new ty_code field for types, to keep code of type (with option -keep-code)
+- handling recursive modules
+- handling private types
+- some fixes in html generation
Objective Caml 3.06:
diff --git a/ocamldoc/odoc_cross.ml b/ocamldoc/odoc_cross.ml
index c9231ac72..d9f99f387 100644
--- a/ocamldoc/odoc_cross.ml
+++ b/ocamldoc/odoc_cross.ml
@@ -732,11 +732,11 @@ and assoc_comments_type module_list t =
t.ty_info <- ao (assoc_comments_info module_list) t.ty_info ;
(match t.ty_kind with
Type_abstract -> ()
- | Type_variant vl ->
+ | Type_variant (vl, _) ->
List.iter
(fun vc -> vc.vc_text <- ao (assoc_comments_text module_list) vc.vc_text)
vl
- | Type_record fl ->
+ | Type_record (fl, _) ->
List.iter
(fun rf -> rf.rf_text <- ao (assoc_comments_text module_list) rf.rf_text)
fl
diff --git a/ocamldoc/odoc_dep.ml b/ocamldoc/odoc_dep.ml
index 62ca098f1..096daa86c 100644
--- a/ocamldoc/odoc_dep.ml
+++ b/ocamldoc/odoc_dep.ml
@@ -145,7 +145,7 @@ let type_deps t =
in
(match t.T.ty_kind with
T.Type_abstract -> ()
- | T.Type_variant cl ->
+ | T.Type_variant (cl, _) ->
List.iter
(fun c ->
List.iter
@@ -156,7 +156,7 @@ let type_deps t =
c.T.vc_args
)
cl
- | T.Type_record rl ->
+ | T.Type_record (rl, _) ->
List.iter
(fun r ->
let s = Odoc_misc.string_of_type_expr r.T.rf_type in
diff --git a/ocamldoc/odoc_html.ml b/ocamldoc/odoc_html.ml
index 09e6a5870..4dbe44aeb 100644
--- a/ocamldoc/odoc_html.ml
+++ b/ocamldoc/odoc_html.ml
@@ -910,8 +910,8 @@ class html =
(match t.ty_manifest with None -> "" | Some typ -> "= "^(self#html_of_type_expr father typ)^" ")^
(match t.ty_kind with
Type_abstract -> "</pre>"
- | Type_variant l ->
- "="^
+ | Type_variant (l, priv) ->
+ "= "^(if priv then "private" else "")^
"</pre><table class=\"typetable\">\n"^
(String.concat "\n"
(List.map
@@ -954,8 +954,8 @@ class html =
)^
"</table>\n"
- | Type_record l ->
- "= {"^
+ | Type_record (l, priv) ->
+ "= "^(if priv then "private " else "")^"{"^
"</pre><table class=\"typetable\">\n"^
(String.concat "\n"
(List.map
diff --git a/ocamldoc/odoc_info.mli b/ocamldoc/odoc_info.mli
index bd26000c8..a2b3615cd 100644
--- a/ocamldoc/odoc_info.mli
+++ b/ocamldoc/odoc_info.mli
@@ -203,8 +203,10 @@ module Type :
(** The various kinds of a type. *)
type type_kind = Odoc_type.type_kind =
Type_abstract (** Type is abstract, for example [type t]. *)
- | Type_variant of variant_constructor list
- | Type_record of record_field list
+ | Type_variant of variant_constructor list * bool
+ (** constructors * bool *)
+ | Type_record of record_field list * bool
+ (** fields * bool *)
(** Representation of a type. *)
type t_type = Odoc_type.t_type =
@@ -217,6 +219,7 @@ module Type :
mutable ty_loc : location ;
mutable ty_code : string option;
}
+
end
(** Representation and manipulation of values, class attributes and class methods. *)
diff --git a/ocamldoc/odoc_latex.ml b/ocamldoc/odoc_latex.ml
index 52b0b5e67..2985f89fe 100644
--- a/ocamldoc/odoc_latex.ml
+++ b/ocamldoc/odoc_latex.ml
@@ -406,17 +406,19 @@ class latex =
Format.fprintf Format.str_formatter
("%s %s")
s_type2
- (match t.ty_kind with
- Type_abstract -> ""
- | Type_variant _ -> "="
- | Type_record _ -> "= {" ) ;
+ (
+ match t.ty_kind with
+ Type_abstract -> ""
+ | Type_variant (_, priv) -> "="^(if priv then " private" else "")
+ | Type_record (_, priv) -> "= "^(if priv then "private " else "")^"{"
+ ) ;
Format.flush_str_formatter ()
in
let defs =
match t.ty_kind with
Type_abstract -> []
- | Type_variant l ->
+ | Type_variant (l, _) ->
(List.flatten
(List.map
(fun constr ->
@@ -444,7 +446,7 @@ class latex =
l
)
)
- | Type_record l ->
+ | Type_record (l, _) ->
(List.flatten
(List.map
(fun r ->
@@ -911,7 +913,7 @@ class latex =
);
try
- let chanout = open_out (Filename.concat !Args.target_dir !Args.out_file) in
+ let chanout = open_out !Args.out_file in
let _ = if !Args.with_header then output_string chanout self#latex_header else () in
List.iter
(fun m -> if !Args.separate_files then
diff --git a/ocamldoc/odoc_man.ml b/ocamldoc/odoc_man.ml
index 7f66d904b..c78654dbf 100644
--- a/ocamldoc/odoc_man.ml
+++ b/ocamldoc/odoc_man.ml
@@ -314,11 +314,12 @@ class man =
)^
(match t.ty_parameters with [] -> "" | _ -> ".I ")^(Name.simple t.ty_name)^" \n"^
(match t.ty_manifest with None -> "" | Some typ -> "= "^(self#man_of_type_expr father typ))^
- (match t.ty_kind with
+ (
+ match t.ty_kind with
Type_abstract ->
""
- | Type_variant l ->
- "=\n "^
+ | Type_variant (l, priv) ->
+ "="^(if priv then " private" else "")^"\n "^
(String.concat ""
(List.map
(fun constr ->
@@ -337,8 +338,8 @@ class man =
l
)
)
- | Type_record l ->
- "= {"^
+ | Type_record (l, priv) ->
+ "= "^(if priv then "private " else "")^"{"^
(String.concat ""
(List.map
(fun r ->
diff --git a/ocamldoc/odoc_merge.ml b/ocamldoc/odoc_merge.ml
index 1a04c2d9f..bd30da274 100644
--- a/ocamldoc/odoc_merge.ml
+++ b/ocamldoc/odoc_merge.ml
@@ -195,7 +195,7 @@ let merge_types merge_options mli ml =
Type_abstract, _ ->
()
- | Type_variant l1, Type_variant l2 ->
+ | Type_variant (l1, _), Type_variant (l2, _) ->
let f cons =
try
let cons2 = List.find
@@ -223,7 +223,7 @@ let merge_types merge_options mli ml =
in
List.iter f l1
- | Type_record l1, Type_record l2 ->
+ | Type_record (l1, _), Type_record (l2, _) ->
let f record =
try
let record2= List.find
diff --git a/ocamldoc/odoc_sig.ml b/ocamldoc/odoc_sig.ml
index a4ba06d7a..d6915e893 100644
--- a/ocamldoc/odoc_sig.ml
+++ b/ocamldoc/odoc_sig.ml
@@ -256,7 +256,7 @@ module Analyser =
vc_text = comment_opt
}
in
- Odoc_type.Type_variant (List.map f l)
+ Odoc_type.Type_variant (List.map f l, priv = Asttypes.Private)
| Types.Type_record (l, _, priv) ->
let f (field_name, mutable_flag, type_expr) =
@@ -274,7 +274,7 @@ module Analyser =
rf_text = comment_opt
}
in
- Odoc_type.Type_record (List.map f l)
+ Odoc_type.Type_record (List.map f l, priv = Asttypes.Private)
(** 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).*)
diff --git a/ocamldoc/odoc_str.ml b/ocamldoc/odoc_str.ml
index 00d12ec66..74ac8453d 100644
--- a/ocamldoc/odoc_str.ml
+++ b/ocamldoc/odoc_str.ml
@@ -31,8 +31,8 @@ let string_of_type t =
(match t.M.ty_kind with
M.Type_abstract ->
""
- | M.Type_variant l ->
- "=\n"^
+ | M.Type_variant (l, priv) ->
+ "="^(if priv then " private" else "")^"\n"^
(String.concat ""
(List.map
(fun cons ->
@@ -53,8 +53,8 @@ let string_of_type t =
l
)
)
- | M.Type_record l ->
- "= {\n"^
+ | M.Type_record (l, priv) ->
+ "= "^(if priv then "private " else "")^"{\n"^
(String.concat ""
(List.map
(fun record ->
diff --git a/ocamldoc/odoc_texi.ml b/ocamldoc/odoc_texi.ml
index e68edb521..9a309aa29 100644
--- a/ocamldoc/odoc_texi.ml
+++ b/ocamldoc/odoc_texi.ml
@@ -614,38 +614,40 @@ class texi =
| Some typ ->
(Raw " = ") :: (self#text_of_short_type_expr
(Name.father ty.ty_name) typ) ) @
- ( match ty.ty_kind with
- | Type_abstract -> [ Newline ]
- | Type_variant l ->
- (Raw " =\n") ::
- (List.flatten
- (List.map
- (fun constr ->
- (Raw (" | " ^ constr.vc_name)) ::
- (Raw (self#string_of_type_args constr.vc_args)) ::
- (match constr.vc_text with
- | None -> [ Newline ]
- | Some t ->
- ((Raw (indent 5 "\n(* ")) :: (self#soft_fix_linebreaks 8 t)) @
- [ Raw " *)" ; Newline ]
- ) ) l ) )
- | Type_record l ->
- (Raw " = {\n") ::
- (List.flatten
- (List.map
- (fun r ->
- [ Raw (" " ^ r.rf_name ^ " : ") ] @
- (self#text_of_short_type_expr
- (Name.father r.rf_name)
- r.rf_type) @
- [ Raw " ;" ] @
- (match r.rf_text with
- | None -> [ Newline ]
- | Some t ->
- ((Raw (indent 5 "\n(* ")) :: (self#soft_fix_linebreaks 8 t)) @
- [ Raw " *)" ; Newline ] ) )
- l ) )
- @ [ Raw " }" ] ) ) ;
+ (
+ match ty.ty_kind with
+ | Type_abstract -> [ Newline ]
+ | Type_variant (l, priv) ->
+ (Raw (" ="^(if priv then " private" else "")^"\n")) ::
+ (List.flatten
+ (List.map
+ (fun constr ->
+ (Raw (" | " ^ constr.vc_name)) ::
+ (Raw (self#string_of_type_args constr.vc_args)) ::
+ (match constr.vc_text with
+ | None -> [ Newline ]
+ | Some t ->
+ ((Raw (indent 5 "\n(* ")) :: (self#soft_fix_linebreaks 8 t)) @
+ [ Raw " *)" ; Newline ]
+ ) ) l ) )
+ | Type_record (l, priv) ->
+ (Raw (" = "^(if priv then "private " else "")^"{\n")) ::
+ (List.flatten
+ (List.map
+ (fun r ->
+ [ Raw (" " ^ r.rf_name ^ " : ") ] @
+ (self#text_of_short_type_expr
+ (Name.father r.rf_name)
+ r.rf_type) @
+ [ Raw " ;" ] @
+ (match r.rf_text with
+ | None -> [ Newline ]
+ | Some t ->
+ ((Raw (indent 5 "\n(* ")) :: (self#soft_fix_linebreaks 8 t)) @
+ [ Raw " *)" ; Newline ] ) )
+ l ) )
+ @ [ Raw " }" ]
+ ) ) ;
self#index `Type ty.ty_name ; Newline ] @
(self#text_of_info ty.ty_info) in
self#texi_of_text t
diff --git a/ocamldoc/odoc_type.ml b/ocamldoc/odoc_type.ml
index 9080850df..4e53fac15 100644
--- a/ocamldoc/odoc_type.ml
+++ b/ocamldoc/odoc_type.ml
@@ -32,8 +32,10 @@ type record_field = {
(** The various kinds of type. *)
type type_kind =
Type_abstract
- | Type_variant of variant_constructor list
- | Type_record of record_field list
+ | Type_variant of variant_constructor list * bool
+ (** constructors * bool *)
+ | Type_record of record_field list * bool
+ (** fields * bool *)
(** Representation of a type. *)
type t_type = {