]> rtime.felk.cvut.cz Git - l4.git/blob - l4/pkg/ocaml/contrib/ocamldoc/odoc_args.mli
update
[l4.git] / l4 / pkg / ocaml / contrib / ocamldoc / odoc_args.mli
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 (* $Id: odoc_args.mli 9229 2009-04-09 13:56:38Z guesdon $ *)
13
14 (** Analysis of the command line arguments. *)
15
16 (** The kind of source file in arguments. *)
17 type source_file =
18     Impl_file of string
19   | Intf_file of string
20   | Text_file of string
21
22 (** The include_dirs in the OCaml compiler. *)
23 val include_dirs : string list ref
24
25 (** The class type of documentation generators. *)
26 class type doc_generator =
27   object method generate : Odoc_module.t_module list -> unit end
28
29 (** The function to be used to create a generator. *)
30 val doc_generator : doc_generator option ref
31
32 (** The merge options to be used. *)
33 val merge_options : Odoc_types.merge_option list ref
34
35 (** Classic mode or not. *)
36 val classic : bool ref
37
38 (** The file used by the generators outputting only one file. *)
39 val out_file : string ref
40
41 (** The optional file name to dump the collected information into.*)
42 val dump : string option ref
43
44 (** The list of information files to load. *)
45 val load : string list ref
46
47 (** Verbose mode or not. *)
48 val verbose : bool ref
49
50 (** We must sort the list of top modules or not.*)
51 val sort_modules : bool ref
52
53 (** We must not stop at the stop special comments. Default is false (we stop).*)
54 val no_stop : bool ref
55
56 (** We must raise an exception when we find an unknown @-tag. *)
57 val no_custom_tags : bool ref
58
59 (** We must remove the the first characters of each comment line, until the first asterisk '*'. *)
60 val remove_stars : bool ref
61
62 (** To keep the code while merging, when we have both .ml and .mli files for a module. *)
63 val keep_code : bool ref
64
65 (** To inverse implementation and interface files when merging. *)
66 val inverse_merge_ml_mli : bool ref
67
68 (** To filter module elements according to module type constraints. *)
69 val filter_with_module_constraints : bool ref
70
71 (** The optional title to use in the generated documentation. *)
72 val title : string option ref
73
74 (** The optional file whose content can be used as intro text. *)
75 val intro_file : string option ref
76
77 (** Flag to indicate whether we must display the complete list of parameters
78    for functions and methods. *)
79 val with_parameter_list : bool ref
80
81 (** The list of module names to hide. *)
82 val hidden_modules : string list ref
83
84 (** The directory where files have to be generated. *)
85 val target_dir : string ref
86
87 (** An optional file to use where a CSS style is defined (for HTML). *)
88 val css_style : string option ref
89
90 (** Generate only index files. (for HTML). *)
91 val index_only : bool ref
92
93 (** To colorize code in HTML generated documentation pages, not code pages. *)
94 val colorize_code : bool ref
95
96 (** To display functors in short form rather than with "functor ... -> ",
97    in HTML generated documentation. *)
98 val html_short_functors : bool ref
99
100 (** The flag which indicates if we must generate a header (for LaTeX). *)
101 val with_header : bool ref
102
103 (** The flag which indicates if we must generate a trailer (for LaTeX). *)
104 val with_trailer : bool ref
105
106 (** The flag to indicate if we must generate one file per module (for LaTeX). *)
107 val separate_files : bool ref
108
109 (** The list of pairs (title level, sectionning style). *)
110 val latex_titles : (int * string) list ref
111
112 (** The prefix to use for value labels in LaTeX. *)
113 val latex_value_prefix : string ref
114
115 (** The prefix to use for type labels in LaTeX. *)
116 val latex_type_prefix : string ref
117
118 (** The prefix to use for exception labels in LaTeX. *)
119 val latex_exception_prefix : string ref
120
121 (** The prefix to use for module labels in LaTeX. *)
122 val latex_module_prefix : string ref
123
124 (** The prefix to use for module type labels in LaTeX. *)
125 val latex_module_type_prefix : string ref
126
127 (** The prefix to use for class labels in LaTeX. *)
128 val latex_class_prefix : string ref
129
130 (** The prefix to use for class type labels in LaTeX. *)
131 val latex_class_type_prefix : string ref
132
133 (** The prefix to use for attribute labels in LaTeX. *)
134 val latex_attribute_prefix : string ref
135
136 (** The prefix to use for method labels in LaTeX. *)
137 val latex_method_prefix : string ref
138
139 (** The flag which indicates if we must generate a table of contents (for LaTeX). *)
140 val with_toc : bool ref
141
142 (** The flag which indicates if we must generate an index (for TeXinfo). *)
143 val with_index : bool ref
144
145 (** The flag which indicates if we must escape accentuated characters (for TeXinfo).*)
146 val esc_8bits : bool ref
147
148 (** The Info directory section *)
149 val info_section : string ref
150
151 (** The Info directory entries to insert *)
152 val info_entry : string list ref
153
154 (** Include all modules or only the ones on the command line, for the dot ouput. *)
155 val dot_include_all : bool ref
156
157 (** Generate dependency graph for types. *)
158 val dot_types : bool ref
159
160 (** Perform transitive reduction before dot output. *)
161 val dot_reduce : bool ref
162
163 (** The colors used in the dot output. *)
164 val dot_colors : string list ref
165
166 (** The suffix for man pages. *)
167 val man_suffix : string ref
168
169 (** The section for man pages. *)
170 val man_section : string ref
171
172 (** The flag to generate all man pages or only for modules and classes.*)
173 val man_mini : bool ref
174
175 (** The files to be analysed. *)
176 val files : source_file list ref
177
178 (** To set the documentation generator. *)
179 val set_doc_generator : doc_generator option -> unit
180
181 (** Add an option specification. *)
182 val add_option : string * Arg.spec * string -> unit
183
184 (** Parse the args.
185    [byte] indicate if we are in bytecode mode (default is [true]).*)
186 val parse :
187     html_generator:doc_generator ->
188       latex_generator:doc_generator ->
189         texi_generator:doc_generator ->
190           man_generator:doc_generator ->
191             dot_generator:doc_generator ->
192               unit