]> rtime.felk.cvut.cz Git - l4.git/blob - l4/pkg/ocaml/contrib/ocamldoc/odoc_args.ml
update
[l4.git] / l4 / pkg / ocaml / contrib / ocamldoc / odoc_args.ml
1 (***********************************************************************)
2 (*                             OCamldoc                                *)
3 (*                                                                     *)
4 (*            Maxence Guesdon, projet Cristal, INRIA Rocquencourt      *)
5 (*                                                                     *)
6 (*  Copyright 2001 Institut National de Recherche en Informatique et   *)
7 (*  en Automatique.  All rights reserved.  This file is distributed    *)
8 (*  under the terms of the Q Public License version 1.0.               *)
9 (*                                                                     *)
10 (***********************************************************************)
11
12 (* cvsid $Id: odoc_args.ml 9229 2009-04-09 13:56:38Z guesdon $ *)
13
14 (** Command-line arguments. *)
15
16 open Clflags
17
18 module M = Odoc_messages
19
20 type source_file =
21     Impl_file of string
22   | Intf_file of string
23   | Text_file of string
24
25 let include_dirs = Clflags.include_dirs
26
27 class type doc_generator =
28     object
29       method generate : Odoc_module.t_module list -> unit
30     end
31
32 let doc_generator = ref (None : doc_generator option)
33
34 let merge_options = ref ([] : Odoc_types.merge_option list)
35
36 let out_file = ref M.default_out_file
37
38 let dot_include_all = ref false
39
40 let dot_types = ref false
41
42 let dot_reduce = ref false
43
44 let dot_colors  = ref (List.flatten M.default_dot_colors)
45
46 let man_suffix = ref M.default_man_suffix
47 let man_section = ref M.default_man_section
48
49 let man_mini = ref false
50
51 (** Analysis of a string defining options. Return the list of
52    options according to the list giving associations between
53    [(character, _)] and a list of options. *)
54 let analyse_option_string l s =
55   List.fold_left
56     (fun acc -> fun ((c,_), v) ->
57       if String.contains s c then
58         acc @ v
59       else
60         acc)
61     []
62     l
63
64 (** Analysis of a string defining the merge options to be used.
65    Returns the list of options specified.*)
66 let analyse_merge_options s =
67   let l = [
68     (M.merge_description, [Odoc_types.Merge_description]) ;
69     (M.merge_author, [Odoc_types.Merge_author]) ;
70     (M.merge_version, [Odoc_types.Merge_version]) ;
71     (M.merge_see, [Odoc_types.Merge_see]) ;
72     (M.merge_since, [Odoc_types.Merge_since]) ;
73     (M.merge_deprecated, [Odoc_types.Merge_deprecated]) ;
74     (M.merge_param, [Odoc_types.Merge_param]) ;
75     (M.merge_raised_exception, [Odoc_types.Merge_raised_exception]) ;
76     (M.merge_return_value, [Odoc_types.Merge_return_value]) ;
77     (M.merge_custom, [Odoc_types.Merge_custom]) ;
78     (M.merge_all, Odoc_types.all_merge_options)
79   ]
80   in
81   analyse_option_string l s
82
83 let classic = Clflags.classic
84
85 let dump = ref (None : string option)
86
87 let load = ref ([] : string list)
88
89 (** Allow arbitrary recursive types. *)
90 let recursive_types = Clflags.recursive_types
91
92 let verbose = ref false
93
94 (** Optional preprocessor command. *)
95 let preprocessor = Clflags.preprocessor
96
97 let sort_modules = ref false
98
99 let no_custom_tags = ref false
100
101 let no_stop = ref false
102
103 let remove_stars = ref false
104
105 let keep_code = ref false
106
107 let inverse_merge_ml_mli = ref false
108
109 let filter_with_module_constraints = ref true
110
111 let title = ref (None : string option)
112
113 let intro_file = ref (None : string option)
114
115 let with_parameter_list = ref false
116
117 let hidden_modules = ref ([] : string list)
118
119 let target_dir = ref Filename.current_dir_name
120
121 let css_style = ref None
122
123 let index_only = ref false
124
125 let colorize_code = ref false
126
127 let html_short_functors = ref false
128
129 let with_header = ref true
130
131 let with_trailer = ref true
132
133 let separate_files = ref false
134
135 let latex_titles = ref [
136   1, "section" ;
137   2, "subsection" ;
138   3, "subsubsection" ;
139   4, "paragraph" ;
140   5, "subparagraph" ;
141 ]
142
143 let with_toc = ref true
144
145 let with_index = ref true
146
147 let esc_8bits = ref false
148
149 let info_section = ref "Objective Caml"
150
151 let info_entry = ref []
152
153 let files = ref []
154
155 let f_latex_title s =
156   try
157     let pos = String.index s ',' in
158     let n = int_of_string (String.sub s 0 pos) in
159     let len = String.length s in
160     let command = String.sub s (pos + 1) (len - pos - 1) in
161     latex_titles := List.remove_assoc n !latex_titles ;
162     latex_titles := (n, command) :: !latex_titles
163   with
164     Not_found
165   | Invalid_argument _ ->
166       incr Odoc_global.errors ;
167       prerr_endline (M.wrong_format s)
168
169 let add_hidden_modules s =
170   let l = Str.split (Str.regexp ",") s in
171   List.iter
172     (fun n ->
173       let name = Str.global_replace (Str.regexp "[ \n\r\t]+") "" n in
174       match name with
175         "" -> ()
176       | _ ->
177           match name.[0] with
178             'A'..'Z' -> hidden_modules := name :: !hidden_modules
179           | _ ->
180               incr Odoc_global.errors;
181               prerr_endline (M.not_a_module_name name)
182     )
183     l
184
185 let latex_value_prefix = ref M.default_latex_value_prefix
186 let latex_type_prefix = ref M.default_latex_type_prefix
187 let latex_exception_prefix = ref M.default_latex_exception_prefix
188 let latex_module_prefix = ref M.default_latex_module_prefix
189 let latex_module_type_prefix = ref M.default_latex_module_type_prefix
190 let latex_class_prefix = ref M.default_latex_class_prefix
191 let latex_class_type_prefix = ref M.default_latex_class_type_prefix
192 let latex_attribute_prefix = ref M.default_latex_attribute_prefix
193 let latex_method_prefix = ref M.default_latex_method_prefix
194
195 let set_doc_generator (dg_opt : doc_generator option) = doc_generator := dg_opt
196
197 (** The default html generator. Initialized in the parse function, to be used during the command line analysis.*)
198 let default_html_generator = ref (None : doc_generator option)
199
200 (** The default latex generator. Initialized in the parse function, to be used during the command line analysis.*)
201 let default_latex_generator = ref (None : doc_generator option)
202
203 (** The default texinfo generator. Initialized in the parse function, to be used during the command line analysis.*)
204 let default_texi_generator = ref (None : doc_generator option)
205
206 (** The default man pages generator. Initialized in the parse function, to be used during the command line analysis.*)
207 let default_man_generator = ref (None : doc_generator option)
208
209 (** The default dot generator. Initialized in the parse function, to be used during  the command line analysis.*)
210 let default_dot_generator = ref (None : doc_generator option)
211
212 (** The default option list *)
213 let options = ref [
214   "-version", Arg.Unit (fun () -> print_string M.message_version ; print_newline () ; exit 0) , M.option_version ;
215   "-v", Arg.Unit (fun () -> verbose := true), M.verbose_mode ;
216   "-I", Arg.String (fun s -> include_dirs := (Misc.expand_directory Config.standard_library s) :: !include_dirs), M.include_dirs ;
217   "-pp", Arg.String (fun s -> preprocessor := Some s), M.preprocess ;
218   "-impl", Arg.String (fun s -> files := !files @ [Impl_file s]), M.option_impl ;
219   "-intf", Arg.String (fun s -> files := !files @ [Intf_file s]), M.option_intf ;
220   "-text", Arg.String (fun s -> files := !files @ [Text_file s]), M.option_text ;
221   "-rectypes", Arg.Set recursive_types, M.rectypes ;
222   "-nolabels", Arg.Unit (fun () -> classic := true), M.nolabels ;
223   "-warn-error", Arg.Set Odoc_global.warn_error, M.werr ;
224   "-hide-warnings", Arg.Clear Odoc_config.print_warnings, M.hide_warnings ;
225   "-o", Arg.String (fun s -> out_file := s), M.out_file ;
226   "-d", Arg.String (fun s -> target_dir := s), M.target_dir ;
227   "-sort", Arg.Unit (fun () -> sort_modules := true), M.sort_modules ;
228   "-no-stop", Arg.Set no_stop, M.no_stop ;
229   "-no-custom-tags", Arg.Set no_custom_tags, M.no_custom_tags ;
230   "-stars", Arg.Set remove_stars, M.remove_stars ;
231   "-inv-merge-ml-mli", Arg.Set inverse_merge_ml_mli, M.inverse_merge_ml_mli ;
232   "-no-module-constraint-filter", Arg.Clear filter_with_module_constraints,
233   M.no_filter_with_module_constraints ;
234
235   "-keep-code", Arg.Set keep_code, M.keep_code^"\n" ;
236
237   "-dump", Arg.String (fun s -> dump := Some s), M.dump ;
238   "-load", Arg.String (fun s -> load := !load @ [s]), M.load^"\n" ;
239
240   "-t", Arg.String (fun s -> title := Some s), M.option_title ;
241   "-intro", Arg.String (fun s -> intro_file := Some s), M.option_intro ;
242   "-hide", Arg.String add_hidden_modules, M.hide_modules ;
243   "-m", Arg.String (fun s -> merge_options := !merge_options @ (analyse_merge_options s)),
244   M.merge_options ^
245   "\n\n *** choosing a generator ***\n";
246
247 (* generators *)
248   "-html", Arg.Unit (fun () -> set_doc_generator !default_html_generator), M.generate_html ;
249   "-latex", Arg.Unit (fun () -> set_doc_generator !default_latex_generator), M.generate_latex ;
250   "-texi", Arg.Unit (fun () -> set_doc_generator !default_texi_generator), M.generate_texinfo ;
251   "-man", Arg.Unit (fun () -> set_doc_generator !default_man_generator), M.generate_man ;
252   "-dot", Arg.Unit (fun () -> set_doc_generator !default_dot_generator), M.generate_dot ;
253   "-customdir", Arg.Unit (fun () -> Printf.printf "%s\n" Odoc_config.custom_generators_path; exit 0),
254   M.display_custom_generators_dir ;
255   "-i", Arg.String (fun s -> ()), M.add_load_dir ;
256   "-g", Arg.String (fun s -> ()), M.load_file ^
257   "\n\n *** HTML options ***\n";
258
259 (* html only options *)
260   "-all-params", Arg.Set with_parameter_list, M.with_parameter_list ;
261   "-css-style", Arg.String (fun s -> css_style := Some s), M.css_style ;
262   "-index-only", Arg.Set index_only, M.index_only ;
263   "-colorize-code", Arg.Set colorize_code, M.colorize_code ;
264   "-short-functors", Arg.Set html_short_functors, M.html_short_functors ^
265   "\n\n *** LaTeX options ***\n";
266
267 (* latex only options *)
268   "-noheader", Arg.Unit (fun () -> with_header := false), M.no_header ;
269   "-notrailer", Arg.Unit (fun () -> with_trailer := false), M.no_trailer ;
270   "-sepfiles", Arg.Set separate_files, M.separate_files ;
271   "-latextitle", Arg.String f_latex_title, M.latex_title latex_titles ;
272   "-latex-value-prefix", Arg.String (fun s -> latex_value_prefix := s), M.latex_value_prefix ;
273   "-latex-type-prefix", Arg.String (fun s -> latex_type_prefix := s), M.latex_type_prefix ;
274   "-latex-exception-prefix", Arg.String (fun s -> latex_exception_prefix := s), M.latex_exception_prefix ;
275   "-latex-attribute-prefix", Arg.String (fun s -> latex_attribute_prefix := s), M.latex_attribute_prefix ;
276   "-latex-method-prefix", Arg.String (fun s -> latex_method_prefix := s), M.latex_method_prefix ;
277   "-latex-module-prefix", Arg.String (fun s -> latex_module_prefix := s), M.latex_module_prefix ;
278   "-latex-module-type-prefix", Arg.String (fun s -> latex_module_type_prefix := s), M.latex_module_type_prefix ;
279   "-latex-class-prefix", Arg.String (fun s -> latex_class_prefix := s), M.latex_class_prefix ;
280   "-latex-class-type-prefix", Arg.String (fun s -> latex_class_type_prefix := s), M.latex_class_type_prefix ;
281   "-notoc", Arg.Unit (fun () -> with_toc := false),
282   M.no_toc ^
283   "\n\n *** texinfo options ***\n";
284
285 (* tex only options *)
286   "-noindex", Arg.Clear with_index, M.no_index ;
287   "-esc8", Arg.Set esc_8bits, M.esc_8bits ;
288   "-info-section", Arg.String ((:=) info_section), M.info_section ;
289   "-info-entry", Arg.String (fun s -> info_entry := !info_entry @ [ s ]),
290   M.info_entry ^
291   "\n\n *** dot options ***\n";
292
293 (* dot only options *)
294   "-dot-colors", Arg.String (fun s -> dot_colors := Str.split (Str.regexp_string ",") s), M.dot_colors ;
295   "-dot-include-all", Arg.Set dot_include_all, M.dot_include_all ;
296   "-dot-types", Arg.Set dot_types, M.dot_types ;
297   "-dot-reduce", Arg.Set dot_reduce, M.dot_reduce^
298   "\n\n *** man pages options ***\n";
299
300 (* man only options *)
301   "-man-mini", Arg.Set man_mini, M.man_mini ;
302   "-man-suffix", Arg.String (fun s -> man_suffix := s), M.man_suffix ;
303   "-man-section", Arg.String (fun s -> man_section := s), M.man_section ;
304
305 ]
306
307 let add_option o =
308   let (s,_,_) = o in
309   let rec iter = function
310       [] -> [o]
311     | (s2,f,m) :: q ->
312         if s = s2 then
313           o :: q
314         else
315           (s2,f,m) :: (iter q)
316   in
317   options := iter !options
318
319 let parse ~html_generator ~latex_generator ~texi_generator ~man_generator ~dot_generator =
320   let anonymous f =
321     let sf =
322       if Filename.check_suffix f "ml" then
323         Impl_file f
324       else
325         if Filename.check_suffix f "mli" then
326           Intf_file f
327         else
328           if Filename.check_suffix f "txt" then
329             Text_file f
330           else
331             failwith (Odoc_messages.unknown_extension f)
332     in
333     files := !files @ [sf]
334   in
335   default_html_generator := Some html_generator ;
336   default_latex_generator := Some latex_generator ;
337   default_texi_generator := Some texi_generator ;
338   default_man_generator := Some man_generator ;
339   default_dot_generator := Some dot_generator ;
340   let _ = Arg.parse !options
341       anonymous
342       (M.usage^M.options_are)
343   in
344   (* we sort the hidden modules by name, to be sure that for example,
345      A.B is before A, so we will match against A.B before A in
346      Odoc_name.hide_modules.*)
347   hidden_modules := List.sort (fun a -> fun b -> - (compare a b)) !hidden_modules