1(**************************************************************************)
2(*                                                                        *)
3(*                                 OCaml                                  *)
4(*                                                                        *)
5(*             Maxence Guesdon, projet Cristal, INRIA Rocquencourt        *)
6(*                                                                        *)
7(*   Copyright 2001 Institut National de Recherche en Informatique et     *)
8(*     en Automatique.                                                    *)
9(*                                                                        *)
10(*   All rights reserved.  This file is distributed under the terms of    *)
11(*   the GNU Lesser General Public License version 2.1, with the          *)
12(*   special exception on linking described in the file LICENSE.          *)
13(*                                                                        *)
14(**************************************************************************)
15
16(** The messages of the application. *)
17
18let ok = "Ok"
19let software = "OCamldoc"
20let config_version = Config.version
21let magic = config_version^""
22
23(** Messages for command line *)
24
25let usage = "Usage: "^(Sys.argv.(0))^" [options] <files>\n"
26let options_are = "Options are:"
27let latex_only = "(LaTeX only)"
28let texi_only = "(TeXinfo only)"
29let latex_texi_only = "(LaTeX and TeXinfo only)"
30let html_only = "(HTML only)"
31let html_latex_only = "(HTML and LaTeX only)"
32let html_latex_texi_only = "(HTML, LaTeX and TeXinfo only)"
33let man_only = "(man only)"
34let option_impl ="<file> Consider <file> as a .ml file"
35let option_intf ="<file> Consider <file> as a .mli file"
36let option_text ="<file> Consider <file> as a .txt file"
37let display_custom_generators_dir = "Display custom generators standard directory and exit"
38let add_load_dir = "<dir> Add the given directory to the search path for custom\n"^
39  "\t\tgenerators"
40let load_file = "<file.cm[o|a|xs]> Load file defining a new documentation generator"
41let werr = " Treat ocamldoc warnings as errors"
42let show_missed_crossref = " Show missed cross-reference opportunities"
43let hide_warnings = " do not print ocamldoc warnings"
44let target_dir = "<dir> Generate files in directory <dir>, rather than in current\n"^
45  "\t\tdirectory (for man and HTML generators)"
46let dump = "<file> Dump collected information into <file>"
47let load = "<file> Load information from <file> ; may be used several times"
48let css_style = "<file> Use content of <file> as CSS style definition "^html_only
49let index_only = " Generate index files only "^html_only
50let colorize_code = " Colorize code even in documentation pages "^html_only
51let html_short_functors = " Use short form to display functor types "^html_only
52let charset c = Printf.sprintf
53  "<s> Add information about character encoding being s\n\t\t(default is %s)"
54  c
55let generate_html = " Generate HTML documentation"
56let generate_latex = " Generate LaTeX documentation"
57let generate_texinfo = " Generate TeXinfo documentation"
58let generate_man = " Generate man pages"
59let generate_dot = " Generate dot code of top modules dependencies"
60
61let option_not_in_native_code op = "Option "^op^" not available in native code version."
62
63let default_out_file = "ocamldoc.out"
64let out_file =
65  "<file> Set the output file name, used by texi, latex and dot generators\n"^
66  "\t\t(default is "^default_out_file^")\n"^
67  "\t\tor the prefix of index files for the HTML generator\n"^
68  "\t\t(default is index)"
69
70let dot_include_all =
71  " Include all modules in the dot output, not only the\n"^
72  "\t\tmodules given on the command line"
73let dot_types = " Generate dependency graph for types instead of modules"
74let default_dot_colors =
75  [ [ "darkturquoise" ; "darkgoldenrod2" ; "cyan" ; "green" ; ] ;
76    [ "magenta" ; "yellow" ; "burlywood1" ; "aquamarine" ; "floralwhite" ; "lightpink" ] ;
77    [ "lightblue" ; "mediumturquoise" ; "salmon" ; "slategray3"] ;
78  ]
79
80let dot_colors =
81  " <c1,c2,...,cn>\n"^
82  "\t\tUse colors c1,c1,...,cn in the dot output\n"^
83  "\t\t(default list is "^
84  (String.concat ",\n\t\t" (List.map (String.concat ",") default_dot_colors))^")"
85
86let dot_reduce =
87  " Perform a transitive reduction on the selected dependency graph\n"^
88  "\t\tbefore the dot output"
89
90let man_mini = " Generate man pages only for modules, module types, classes\n"^
91  "\t\tand class types "^man_only
92let default_man_section = "3"
93let man_section = "<section> Use <section> in man page files "^
94  "(default is "^default_man_section^") "^man_only^"\n"
95
96let default_man_suffix = default_man_section^"o"
97let man_suffix = "<suffix> Use <suffix> for man page files "^
98  "(default is "^default_man_suffix^") "^man_only^"\n"
99
100let option_title = "<title> Use <title> as title for the generated documentation"
101let option_intro =
102  "<file> Use content of <file> as ocamldoc text to use as introduction\n"^
103  "\t\t"^(html_latex_texi_only)
104let with_parameter_list = " Display the complete list of parameters for functions and\n"^
105  "\t\tmethods "^html_only
106let hide_modules = "<M1,M2.M3,...> Hide the given complete module names in generated doc"
107let no_header = " Suppress header in generated documentation\n\t\t"^latex_texi_only
108let no_trailer = " Suppress trailer in generated documentation\n\t\t"^latex_texi_only
109let separate_files = " Generate one file per toplevel module "^latex_only
110let latex_title ref_titles =
111  "n,style Associate {n } to the given sectionning style\n"^
112  "\t\t(e.g. 'section') in the latex output "^latex_only^"\n"^
113  "\t\tDefault sectionning is:\n\t\t"^
114  (String.concat "\n\t\t"
115     (List.map (fun (n,t) -> Printf.sprintf " %d -> %s" n t) !ref_titles))
116
117let default_latex_value_prefix = "val:"
118let latex_value_prefix =
119  "<string>\n"^
120  "\t\tUse <string> as prefix for the LaTeX labels of values.\n"^
121  "\t\t(default is \""^default_latex_value_prefix^"\")"
122
123let default_latex_type_prefix = "type:"
124let latex_type_prefix =
125  "<string>\n"^
126  "\t\tUse <string> as prefix for the LaTeX labels of types.\n"^
127  "\t\t(default is \""^default_latex_type_prefix^"\")"
128
129let default_latex_type_elt_prefix = "typeelt:"
130let latex_type_elt_prefix =
131  "<string>\n"^
132  "\t\tUse <string> as prefix for the LaTeX labels of type elements.\n"^
133  "\t\t(default is \""^default_latex_type_elt_prefix^"\")"
134
135let default_latex_extension_prefix = "extension:"
136let latex_extension_prefix =
137  "<string>\n"^
138  "\t\tUse <string> as prefix for the LaTeX labels of extensions.\n"^
139  "\t\t(default is \""^default_latex_extension_prefix^"\")"
140
141let default_latex_exception_prefix = "exception:"
142let latex_exception_prefix =
143  "<string>\n"^
144  "\t\tUse <string> as prefix for the LaTeX labels of exceptions.\n"^
145  "\t\t(default is \""^default_latex_exception_prefix^"\")"
146
147let default_latex_module_prefix = "module:"
148let latex_module_prefix =
149  "<string>\n"^
150  "\t\tUse <string> as prefix for the LaTeX labels of modules.\n"^
151  "\t\t(default is \""^default_latex_module_prefix^"\")"
152
153let default_latex_module_type_prefix = "moduletype:"
154let latex_module_type_prefix =
155  "<string>\n"^
156  "\t\tUse <string> as prefix for the LaTeX labels of module types.\n"^
157  "\t\t(default is \""^default_latex_module_type_prefix^"\")"
158
159let default_latex_class_prefix = "class:"
160let latex_class_prefix =
161  "<string>\n"^
162  "\t\tUse <string> as prefix for the LaTeX labels of classes.\n"^
163  "\t\t(default is \""^default_latex_class_prefix^"\")"
164
165let default_latex_class_type_prefix = "classtype:"
166let latex_class_type_prefix =
167  "<string>\n"^
168  "\t\tUse <string> as prefix for the LaTeX labels of class types.\n"^
169  "\t\t(default is \""^default_latex_class_type_prefix^"\")"
170
171let default_latex_attribute_prefix = "val:"
172let latex_attribute_prefix =
173  "<string>\n"^
174  "\t\tUse <string> as prefix for the LaTeX labels of attributes.\n"^
175  "\t\t(default is \""^default_latex_attribute_prefix^"\")"
176
177let default_latex_method_prefix = "method:"
178let latex_method_prefix =
179  "<string>\n"^
180  "\t\tUse <string> as prefix for the LaTeX labels of methods.\n"^
181  "\t\t(default is \""^default_latex_method_prefix^"\")"
182
183let no_toc = " Do not generate table of contents "^latex_only
184let sort_modules = " Sort the list of top modules before generating the documentation"
185let no_stop = " Do not stop at (**/**) comments"
186let no_custom_tags = " Do not allow custom @-tags"
187let remove_stars = " Remove beginning blanks of comment lines, until the first '*'"
188let keep_code = " Always keep code when available"
189let inverse_merge_ml_mli = " Inverse implementations and interfaces when merging"
190let no_filter_with_module_constraints = "Do not filter module elements using module type constraints"
191let merge_description = ('d', "merge description")
192let merge_author = ('a', "merge @author")
193let merge_version = ('v', "merge @version")
194let merge_see = ('l', "merge @see")
195let merge_since = ('s', "merge @since")
196let merge_before = ('b', "merge @before")
197let merge_deprecated = ('o', "merge @deprecated")
198let merge_param = ('p', "merge @param")
199let merge_raised_exception = ('e', "merge @raise")
200let merge_return_value = ('r', "merge @return")
201let merge_custom = ('c', "merge custom @-tags")
202let merge_all = ('A', "merge all")
203
204let no_index = " Do not build index for Info files "^texi_only
205let esc_8bits = " Escape accentuated characters in Info files "^texi_only
206let info_section = " Specify section of Info directory "^texi_only
207let info_entry = " Specify Info directory entry "^texi_only
208
209let options_can_be = "<options> can be one or more of the following characters:"
210let string_of_options_list l =
211  List.fold_left (fun acc -> fun (c, m) -> acc^"\n\t\t"^(String.make 1 c)^"  "^m)
212    ""
213    l
214
215let merge_options =
216  "<options> specify merge options between .mli and .ml\n\t\t"^
217  options_can_be^
218  (string_of_options_list
219     [ merge_description ;
220       merge_author ;
221       merge_version ;
222       merge_see ;
223       merge_since ;
224       merge_before ;
225       merge_deprecated ;
226       merge_param ;
227       merge_raised_exception ;
228       merge_return_value ;
229       merge_custom ;
230       merge_all ]
231  )
232
233let help = " Display this list of options"
234
235
236(** Error and warning messages *)
237
238let warning = "Warning"
239
240let error_location file l c =
241  Printf.sprintf "File \"%s\", line %d, character %d:\n" file l c
242
243let bad_magic_number =
244  "Bad magic number for this ocamldoc dump!\n"^
245  "This dump was not created by this version of OCamldoc."
246
247let not_a_module_name s = s^" is not a valid module name"
248let load_file_error f e = "Error while loading file "^f^":\n"^e
249let wrong_format s = "Wrong format for \""^s^"\""
250let errors_occured n = (string_of_int n)^" error(s) encountered"
251let parse_error = "Parse error"
252let text_parse_error l c s =
253  let lines = Str.split (Str.regexp_string "\n") s in
254  "Error parsing text:\n"
255  ^ (List.nth lines l) ^ "\n"
256  ^ (String.make c ' ') ^ "^"
257
258let file_not_found_in_paths paths name =
259  Printf.sprintf "No file %s found in the load paths: \n%s"
260    name
261    (String.concat "\n" paths)
262
263let tag_not_handled tag = "Tag @"^tag^" not handled by this generator"
264let should_escape_at_sign = "The character @ has a special meaning in ocamldoc comments, for commands such as @raise or @since. \
265If you want to write a single @, you must escape it as \\@."
266let bad_tree = "Incorrect tree structure."
267let not_a_valid_tag s = s^" is not a valid tag."
268let fun_without_param f = "Function "^f^" has no parameter.";;
269let method_without_param f = "Method "^f^" has no parameter.";;
270let anonymous_parameters f = "Function "^f^" has anonymous parameters."
271let function_colon f = "Function "^f^": "
272let implicit_match_in_parameter = "Parameters contain implicit pattern matching."
273let unknown_extension f = "Unknown extension for file "^f^"."
274let two_implementations name = "There are two implementations of module "^name^"."
275let two_interfaces name = "There are two interfaces of module "^name^"."
276let too_many_module_objects name = "There are too many interfaces/implementation of module "^name^"."
277let extension_not_found_in_implementation ext m = "Extension "^ext^" was not found in implementation of module "^m^"."
278let exception_not_found_in_implementation exc m = "Exception "^exc^" was not found in implementation of module "^m^"."
279let type_not_found_in_implementation exc m = "Type "^exc^" was not found in implementation of module "^m^"."
280let module_not_found_in_implementation m m2 = "Module "^m^" was not found in implementation of module "^m2^"."
281let value_not_found_in_implementation v m = "Value "^v^" was not found in implementation of module "^m^"."
282let class_not_found_in_implementation c m = "Class "^c^" was not found in implementation of module "^m^"."
283let attribute_not_found_in_implementation a c = "Attribute "^a^" was not found in implementation of class "^c^"."
284let method_not_found_in_implementation m c = "Method "^m^" was not found in implementation of class "^c^"."
285let different_types t = "Definition of type "^t^" doesn't match from interface to implementation."
286let attribute_type_not_found cl att = "The type of the attribute "^att^" could not be found in the signature of class "^cl^"."
287let method_type_not_found cl met = "The type of the method "^met^" could not be found in the signature of class "^cl^"."
288let module_not_found m m2 = "The module "^m2^" could not be found in the signature of module "^m^"."
289let module_type_not_found m mt = "The module type "^mt^" could not be found in the signature of module "^m^"."
290let value_not_found m v = "The value "^v^" could not be found in the signature of module "^m^"."
291let extension_not_found m e = "The extension "^e^" could not be found in the signature of module "^m^"."
292let exception_not_found m e = "The exception "^e^" could not be found in the signature of module "^m^"."
293let type_not_found m t = "The type "^t^" could not be found in the signature of module "^m^"."
294let class_not_found m c = "The class "^c^" could not be found in the signature of module "^m^"."
295let class_type_not_found m c = "The class type "^c^" could not be found in the signature of module "^m^"."
296let type_not_found_in_typedtree t = "Type "^t^" was not found in typed tree."
297let extension_not_found_in_typedtree x = "Extension "^x^" was not found in typed tree."
298let exception_not_found_in_typedtree e = "Exception "^e^" was not found in typed tree."
299let module_type_not_found_in_typedtree mt = "Module type "^mt^" was not found in typed tree."
300let module_not_found_in_typedtree m = "Module "^m^" was not found in typed tree."
301let class_not_found_in_typedtree c = "Class "^c^" was not found in typed tree."
302let class_type_not_found_in_typedtree ct = "Class type "^ct^" was not found in typed tree."
303let inherit_classexp_not_found_in_typedtree n =
304  "Inheritance class expression number "^(string_of_int n)^" was not found in typed tree."
305let attribute_not_found_in_typedtree att = "Class attribute "^att^" was not found in typed tree."
306let method_not_found_in_typedtree met = "Class method "^met^" was not found in typed tree."
307let misplaced_comment file pos =
308  Printf.sprintf "Misplaced special comment in file %s, character %d." file pos
309
310let cross_module_not_found n = "Module "^n^" not found"
311let cross_module_type_not_found n = "Module type "^n^" not found"
312let cross_module_or_module_type_not_found n = "Module or module type "^n^" not found"
313let cross_class_not_found n = "Class "^n^" not found"
314let cross_class_type_not_found n = "class type "^n^" not found"
315let cross_class_or_class_type_not_found n = "Class or class type "^n^" not found"
316let cross_extension_not_found n = "Extension "^n^" not found"
317let cross_exception_not_found n = "Exception "^n^" not found"
318let cross_element_not_found n = "Element "^n^" not found"
319let cross_method_not_found n = "Method "^n^" not found"
320let cross_attribute_not_found n = "Attribute "^n^" not found"
321let cross_section_not_found n = "Section "^n^" not found"
322let cross_value_not_found n = "Value "^n^" not found"
323let cross_type_not_found n = "Type "^n^" not found"
324let cross_recfield_not_found n = Printf.sprintf "Record field %s not found" n
325let cross_const_not_found n = Printf.sprintf "Constructor %s not found" n
326
327let code_could_be_cross_reference n parent =
328  Printf.sprintf "Code element [%s] in %s corresponds to a known \
329                  cross-referenceable element, it might be worthwhile to replace it \
330                  with {!%s}" n parent n
331
332
333let object_end = "object ... end"
334let struct_end = "struct ... end"
335let sig_end = "sig ... end"
336
337let current_generator_is_not kind =
338  Printf.sprintf "Current generator is not a %s generator" kind
339;;
340
341(** Messages for verbose mode. *)
342
343let analysing f = "Analysing file "^f^"..."
344let merging = "Merging..."
345let cross_referencing = "Cross referencing..."
346let generating_doc = "Generating documentation..."
347let loading f = "Loading "^f^"..."
348let file_generated f = "File "^f^" generated."
349let file_exists_dont_generate f =
350  "File "^f^" exists, we don't generate it."
351
352(** Messages for documentation generation.*)
353
354let modul = "Module"
355let modules = "Modules"
356let functors = "Functors"
357let values = "Simple values"
358let types = "Types"
359let extensions = "Extensions"
360let exceptions = "Exceptions"
361let record = "Record"
362let variant = "Variant"
363let mutab = "mutable"
364let functions = "Functions"
365let parameters = "Parameters"
366let abstract = "Abstract"
367let functo = "Functor"
368let clas = "Class"
369let classes = "Classes"
370let attributes = "Attributes"
371let methods = "Methods"
372let authors = "Author(s)"
373let version = "Version"
374let since = "Since"
375let before = "Before"
376let deprecated = "Deprecated."
377let raises = "Raises"
378let returns = "Returns"
379let inherits = "Inherits"
380let inheritance = "Inheritance"
381let privat = "private"
382let module_type = "Module type"
383let class_type = "Class type"
384let description = "Description"
385let interface = "Interface"
386let type_parameters = "Type parameters"
387let class_types = "Class types"
388let module_types = "Module types"
389let see_also = "See also"
390let documentation = "Documentation"
391let index_of = "Index of"
392let top = "Top"
393let index_of_values = index_of^" values"
394let index_of_extensions = index_of^" extensions"
395let index_of_exceptions = index_of^" exceptions"
396let index_of_types = index_of^" types"
397let index_of_attributes = index_of^" class attributes"
398let index_of_methods = index_of^" class methods"
399let index_of_classes = index_of^" classes"
400let index_of_class_types = index_of^" class types"
401let index_of_modules = index_of^" modules"
402let index_of_module_types = index_of^" module types"
403let previous = "Previous"
404let next = "Next"
405let up = "Up"
406