blob: 9e34bb2a1c1a53b032435e76ebf65d9c31627ddb (
plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
|
(***********************************************************************)
(* *)
(* OCamldoc *)
(* *)
(* Maxence Guesdon, projet Cristal, INRIA Rocquencourt *)
(* *)
(* Copyright 2004 Institut National de Recherche en Informatique et *)
(* en Automatique. All rights reserved. This file is distributed *)
(* under the terms of the Q Public License version 1.0. *)
(* *)
(***********************************************************************)
(** Custom generator to perform test on ocamldoc. *)
open Odoc_info
open Odoc_info.Module
open Odoc_info.Type
type test_kind =
Types_display
let p = Format.fprintf
class string_gen =
object(self)
inherit Odoc_info.Scan.scanner
val mutable test_kinds = []
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
)
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 (Other e) -> Odoc_info.string_of_type_expr e
| Some (Object_type fields) ->
let b = Buffer.create 256 in
Buffer.add_string b "<";
List.iter
(fun fd ->
Printf.bprintf b " %s: %s ;"
fd.of_name
(Odoc_info.string_of_type_expr fd.of_type)
)
fields;
Buffer.add_string b " >";
Buffer.contents b
);
);
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);
);
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
);
);
true
method generate (module_list: Odoc_info.Module.t_module list) =
let oc = open_out !Odoc_info.Global.out_file in
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
with
e ->
prerr_endline (Printexc.to_string e)
);
Format.pp_print_flush fmt ();
close_out oc
end
let _ =
let module My_generator = struct
class generator =
let inst = new string_gen in
object
method generate = inst#generate
end
end in
Odoc_args.set_generator (Odoc_gen.Base (module My_generator : Odoc_gen.Base))
|