update test file following commit 10652 in ocamldoc
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@12652 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02master
parent
ec0422aa33
commit
ec0cb70b4d
|
@ -27,64 +27,64 @@ class string_gen =
|
|||
inherit Odoc_info.Scan.scanner
|
||||
|
||||
val mutable test_kinds = []
|
||||
val mutable fmt = Format.str_formatter
|
||||
val mutable fmt = Format.str_formatter
|
||||
|
||||
method must_display_types = List.mem Types_display test_kinds
|
||||
|
||||
method set_test_kinds_from_module m =
|
||||
test_kinds <- List.fold_left
|
||||
(fun acc (s, _) ->
|
||||
match s with
|
||||
"test_types_display" -> Types_display :: acc
|
||||
| _ -> acc
|
||||
)
|
||||
[]
|
||||
(
|
||||
match m.m_info with
|
||||
None -> []
|
||||
| Some i -> i.i_custom
|
||||
)
|
||||
(fun acc (s, _) ->
|
||||
match s with
|
||||
"test_types_display" -> Types_display :: acc
|
||||
| _ -> acc
|
||||
)
|
||||
[]
|
||||
(
|
||||
match m.m_info with
|
||||
None -> []
|
||||
| Some i -> i.i_custom
|
||||
)
|
||||
method! scan_type t =
|
||||
match test_kinds with
|
||||
[] -> ()
|
||||
| _ ->
|
||||
p fmt "# type %s:\n" t.ty_name;
|
||||
if self#must_display_types then
|
||||
(
|
||||
p fmt "# manifest (Odoc_info.string_of_type_expr):\n<[%s]>\n"
|
||||
(match t.ty_manifest with
|
||||
None -> "None"
|
||||
| Some e -> Odoc_info.string_of_type_expr e
|
||||
);
|
||||
);
|
||||
[] -> ()
|
||||
| _ ->
|
||||
p fmt "# type %s:\n" t.ty_name;
|
||||
if self#must_display_types then
|
||||
(
|
||||
p fmt "# manifest (Odoc_info.string_of_type_expr):\n<[%s]>\n"
|
||||
(match t.ty_manifest with
|
||||
None -> "None"
|
||||
| Some e -> Odoc_info.string_of_type_expr e
|
||||
);
|
||||
);
|
||||
|
||||
|
||||
method! scan_module_pre m =
|
||||
p fmt "#\n# module %s:\n" m.m_name ;
|
||||
if self#must_display_types then
|
||||
(
|
||||
p fmt "# Odoc_info.string_of_module_type:\n<[%s]>\n"
|
||||
(Odoc_info.string_of_module_type m.m_type);
|
||||
p fmt "# Odoc_info.string_of_module_type ~complete: true :\n<[%s]>\n"
|
||||
(Odoc_info.string_of_module_type ~complete: true m.m_type);
|
||||
);
|
||||
(
|
||||
p fmt "# Odoc_info.string_of_module_type:\n<[%s]>\n"
|
||||
(Odoc_info.string_of_module_type m.m_type);
|
||||
p fmt "# Odoc_info.string_of_module_type ~complete: true :\n<[%s]>\n"
|
||||
(Odoc_info.string_of_module_type ~complete: true m.m_type);
|
||||
);
|
||||
true
|
||||
|
||||
method! scan_module_type_pre m =
|
||||
p fmt "#\n# module type %s:\n" m.mt_name ;
|
||||
if self#must_display_types then
|
||||
(
|
||||
p fmt "# Odoc_info.string_of_module_type:\n<[%s]>\n"
|
||||
(match m.mt_type with
|
||||
None -> "None"
|
||||
| Some t -> Odoc_info.string_of_module_type t
|
||||
);
|
||||
p fmt "# Odoc_info.string_of_module_type ~complete: true :\n<[%s]>\n"
|
||||
(match m.mt_type with
|
||||
None -> "None"
|
||||
| Some t -> Odoc_info.string_of_module_type ~complete: true t
|
||||
);
|
||||
);
|
||||
(
|
||||
p fmt "# Odoc_info.string_of_module_type:\n<[%s]>\n"
|
||||
(match m.mt_type with
|
||||
None -> "None"
|
||||
| Some t -> Odoc_info.string_of_module_type t
|
||||
);
|
||||
p fmt "# Odoc_info.string_of_module_type ~complete: true :\n<[%s]>\n"
|
||||
(match m.mt_type with
|
||||
None -> "None"
|
||||
| Some t -> Odoc_info.string_of_module_type ~complete: true t
|
||||
);
|
||||
);
|
||||
true
|
||||
|
||||
method generate (module_list: Odoc_info.Module.t_module list) =
|
||||
|
@ -92,15 +92,15 @@ class string_gen =
|
|||
fmt <- Format.formatter_of_out_channel oc;
|
||||
(
|
||||
try
|
||||
List.iter
|
||||
(fun m ->
|
||||
self#set_test_kinds_from_module m;
|
||||
self#scan_module_list [m];
|
||||
)
|
||||
module_list
|
||||
List.iter
|
||||
(fun m ->
|
||||
self#set_test_kinds_from_module m;
|
||||
self#scan_module_list [m];
|
||||
)
|
||||
module_list
|
||||
with
|
||||
e ->
|
||||
prerr_endline (Printexc.to_string e)
|
||||
e ->
|
||||
prerr_endline (Printexc.to_string e)
|
||||
);
|
||||
Format.pp_print_flush fmt ();
|
||||
close_out oc
|
||||
|
@ -114,4 +114,4 @@ let _ =
|
|||
method generate = inst#generate
|
||||
end
|
||||
end in
|
||||
Odoc_args.set_generator (Odoc_gen.Base (module My_generator : Odoc_gen.Base))
|
||||
Odoc_args.set_generator (Odoc_gen.Other (module My_generator : Odoc_gen.Base))
|
||||
|
|
Loading…
Reference in New Issue