summaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
authorDamien Doligez <damien.doligez-inria.fr>2012-06-27 13:14:47 +0000
committerDamien Doligez <damien.doligez-inria.fr>2012-06-27 13:14:47 +0000
commitec0cb70b4d14ca9b9f79b95d3533bbdcd3283ca1 (patch)
tree110f002daef5716f9fa25c27d48439fda6bf4a89
parentec0422aa3333200cb1b7fdf3a2a34fc3ca993c51 (diff)
update test file following commit 10652 in ocamldoc
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@12652 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
-rw-r--r--testsuite/tests/tool-ocamldoc/odoc_test.ml100
1 files changed, 50 insertions, 50 deletions
diff --git a/testsuite/tests/tool-ocamldoc/odoc_test.ml b/testsuite/tests/tool-ocamldoc/odoc_test.ml
index b5cc55626..019647905 100644
--- a/testsuite/tests/tool-ocamldoc/odoc_test.ml
+++ b/testsuite/tests/tool-ocamldoc/odoc_test.ml
@@ -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))