diff options
author | Maxence Guesdon <maxence.guesdon@inria.fr> | 2002-08-13 14:09:26 +0000 |
---|---|---|
committer | Maxence Guesdon <maxence.guesdon@inria.fr> | 2002-08-13 14:09:26 +0000 |
commit | 307628e786fba0269485fb9461772747dac5311c (patch) | |
tree | 4c80ef5c1bf9f256b46277319d53fda8f6f37376 | |
parent | 9b7e6b33851e416e093ab89e7c74fa7e738a665f (diff) |
pas d'option -g en native mode + ajout du module Args dans Odoc_info et utilisation de ce module au lieu de Odoc_args dans les générateurs
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@5098 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
-rw-r--r-- | ocamldoc/odoc_args.ml | 9 | ||||
-rw-r--r-- | ocamldoc/odoc_args.mli | 13 | ||||
-rw-r--r-- | ocamldoc/odoc_dot.ml | 20 | ||||
-rw-r--r-- | ocamldoc/odoc_html.ml | 44 | ||||
-rw-r--r-- | ocamldoc/odoc_info.ml | 2 | ||||
-rw-r--r-- | ocamldoc/odoc_info.mli | 112 | ||||
-rw-r--r-- | ocamldoc/odoc_latex.ml | 40 | ||||
-rw-r--r-- | ocamldoc/odoc_man.ml | 16 | ||||
-rw-r--r-- | ocamldoc/odoc_messages.ml | 4 | ||||
-rw-r--r-- | ocamldoc/odoc_opt.ml | 1 | ||||
-rw-r--r-- | ocamldoc/odoc_texi.ml | 16 |
11 files changed, 200 insertions, 77 deletions
diff --git a/ocamldoc/odoc_args.ml b/ocamldoc/odoc_args.ml index fb3e159ec..af571c018 100644 --- a/ocamldoc/odoc_args.ml +++ b/ocamldoc/odoc_args.ml @@ -15,6 +15,8 @@ open Clflags let include_dirs = Clflags.include_dirs +let bytecode_mode = ref true + class type doc_generator = object method generate : Odoc_module.t_module list -> unit @@ -190,7 +192,7 @@ let default_man_generator = ref (None : doc_generator option) let default_dot_generator = ref (None : doc_generator option) (** The default option list *) -let options = ref [ +let options = ref [ "-version", Arg.Unit (fun () -> print_string Odoc_messages.message_version ; print_newline () ; exit 0) , Odoc_messages.option_version ; "-v", Arg.Unit (fun () -> verbose := true), Odoc_messages.verbose_mode ; "-I", Arg.String (fun s -> include_dirs := (Misc.expand_directory Config.standard_library s) :: !include_dirs), Odoc_messages.include_dirs ; @@ -218,9 +220,10 @@ let options = ref [ "-html", Arg.Unit (fun () -> set_doc_generator !default_html_generator), Odoc_messages.generate_html ; "-latex", Arg.Unit (fun () -> set_doc_generator !default_latex_generator), Odoc_messages.generate_latex ; "-texi", Arg.Unit (fun () -> set_doc_generator !default_texi_generator), Odoc_messages.generate_texinfo ; - "-man", Arg.Unit (fun () -> set_doc_generator !default_man_generator), Odoc_messages.generate_man ; + "-man", Arg.Unit (fun () -> set_doc_generator !default_man_generator), Odoc_messages.generate_man ; "-dot", Arg.Unit (fun () -> set_doc_generator !default_dot_generator), Odoc_messages.generate_dot ; - "-g", Arg.String (fun s -> ()), Odoc_messages.load_file^"\n" ; + "-g", Arg.String (fun s -> if !bytecode_mode then () else (prerr_endline (Odoc_messages.option_not_in_native_code "-g"); exit 1)), + Odoc_messages.load_file^"\n" ; (* html only options *) "-all-params", Arg.Set with_parameter_list, Odoc_messages.with_parameter_list ; diff --git a/ocamldoc/odoc_args.mli b/ocamldoc/odoc_args.mli index 4f660854c..13945f998 100644 --- a/ocamldoc/odoc_args.mli +++ b/ocamldoc/odoc_args.mli @@ -14,7 +14,11 @@ (** The include_dirs in the OCaml compiler. *) val include_dirs : string list ref - + +(** Indicate if we are in bytecode mode or not. + (For the [ocamldoc] command).*) +val bytecode_mode : bool ref + (** The class type of documentation generators. *) class type doc_generator = object method generate : Odoc_module.t_module list -> unit end @@ -155,12 +159,13 @@ val set_doc_generator : doc_generator option -> unit (** Add an option specification. *) val add_option : string * Arg.spec * string -> unit -(** Parse the args. *) +(** Parse the args. + [byte] indicate if we are in bytecode mode (default is [true]).*) val parse : html_generator:doc_generator -> latex_generator:doc_generator -> texi_generator:doc_generator -> man_generator:doc_generator -> - dot_generator:doc_generator -> - unit + dot_generator:doc_generator -> + unit diff --git a/ocamldoc/odoc_dot.ml b/ocamldoc/odoc_dot.ml index 2a5366f47..754ad4189 100644 --- a/ocamldoc/odoc_dot.ml +++ b/ocamldoc/odoc_dot.ml @@ -12,9 +12,7 @@ (** Definition of a class which outputs a dot file showing top modules dependencies.*) -module Name = Odoc_info.Name -module Module = Odoc_info.Module -module Type = Odoc_info.Type +open Odoc_info module F = Format @@ -29,7 +27,7 @@ class dot = val mutable modules = [] (** Colors to use when finding new locations of modules. *) - val mutable colors = !Odoc_args.dot_colors + val mutable colors = !Args.dot_colors (** Graph header. *) method header = @@ -73,7 +71,7 @@ class dot = method generate_for_module fmt m = let l = List.filter (fun n -> - !Odoc_args.dot_include_all or + !Args.dot_include_all or (List.exists (fun m -> m.Module.m_name = n) modules)) m.Module.m_top_deps in @@ -88,11 +86,11 @@ class dot = method generate_types types = try - let oc = open_out !Odoc_args.out_file in + let oc = open_out !Args.out_file in let fmt = F.formatter_of_out_channel oc in F.fprintf fmt "%s" self#header; let graph = Odoc_info.Dep.deps_of_types - ~kernel: !Odoc_args.dot_reduce + ~kernel: !Args.dot_reduce types in List.iter (self#generate_for_type fmt) graph; @@ -106,11 +104,11 @@ class dot = method generate_modules modules_list = try modules <- modules_list ; - let oc = open_out !Odoc_args.out_file in + let oc = open_out !Args.out_file in let fmt = F.formatter_of_out_channel oc in F.fprintf fmt "%s" self#header; - if !Odoc_args.dot_reduce then + if !Args.dot_reduce then Odoc_info.Dep.kernel_deps_of_modules modules_list; List.iter (self#generate_for_module fmt) modules_list; @@ -121,9 +119,9 @@ class dot = Sys_error s -> raise (Failure s) - (** Generate the dot code in the file {!Odoc_args.out_file}. *) + (** Generate the dot code in the file {!Args.out_file}. *) method generate (modules_list : Odoc_info.Module.t_module list) = - if !Odoc_args.dot_types then + if !Args.dot_types then self#generate_types (Odoc_info.Search.types modules_list) else self#generate_modules modules_list diff --git a/ocamldoc/odoc_html.ml b/ocamldoc/odoc_html.ml index 2a7abd843..6b7dd5197 100644 --- a/ocamldoc/odoc_html.ml +++ b/ocamldoc/odoc_html.ml @@ -192,13 +192,13 @@ class text = method html_of_Raw s = self#escape s method html_of_Code s = - if !Odoc_args.colorize_code then + if !Args.colorize_code then self#html_of_code ~with_pre: false s else "<code class=\""^Odoc_ocamlhtml.code_class^"\">"^(self#escape s)^"</code>" method html_of_CodePre s = - if !Odoc_args.colorize_code then + if !Args.colorize_code then "<pre></pre>"^(self#html_of_code s)^"<pre></pre>" else "<pre><code class=\""^Odoc_ocamlhtml.code_class^"\">"^(self#escape s)^"</code></pre>" @@ -525,12 +525,12 @@ class html = (** Init the style. *) method init_style = - (match !Odoc_args.css_style with + (match !Args.css_style with None -> let default_style = String.concat "\n" default_style_options in ( try - let chanout = open_out (Filename.concat !Odoc_args.target_dir style_file) in + let chanout = open_out (Filename.concat !Args.target_dir style_file) in output_string chanout default_style ; flush chanout ; close_out chanout @@ -545,7 +545,7 @@ class html = style <- "<link rel=\"stylesheet\" href=\""^style_file^"\" type=\"text/css\">\n" (** Get the title given by the user *) - method title = match !Odoc_args.title with None -> "" | Some t -> self#escape t + method title = match !Args.title with None -> "" | Some t -> self#escape t (** Get the title given by the user completed with the given subtitle. *) method inner_title s = @@ -805,12 +805,12 @@ class html = None -> Name.simple v.val_name | Some c -> let file = Naming.file_code_value_complete_target v in - self#output_code v.val_name (Filename.concat !Odoc_args.target_dir file) c; + self#output_code v.val_name (Filename.concat !Args.target_dir file) c; "<a href=\""^file^"\">"^(Name.simple v.val_name)^"</a>" )^" : "^ (self#html_of_type_expr (Name.father v.val_name) v.val_type)^"</pre>"^ (self#html_of_info v.val_info)^ - (if !Odoc_args.with_parameter_list then + (if !Args.with_parameter_list then self#html_of_parameter_list (Name.father v.val_name) v.val_parameters else self#html_of_described_parameter_list (Name.father v.val_name) v.val_parameters @@ -953,7 +953,7 @@ class html = None -> Name.simple a.att_value.val_name | Some c -> let file = Naming.file_code_attribute_complete_target a in - self#output_code a.att_value.val_name (Filename.concat !Odoc_args.target_dir file) c; + self#output_code a.att_value.val_name (Filename.concat !Args.target_dir file) c; "<a href=\""^file^"\">"^(Name.simple a.att_value.val_name)^"</a>" )^" : "^ (self#html_of_type_expr module_name a.att_value.val_type)^"</pre>"^ @@ -971,12 +971,12 @@ class html = None -> Name.simple m.met_value.val_name | Some c -> let file = Naming.file_code_method_complete_target m in - self#output_code m.met_value.val_name (Filename.concat !Odoc_args.target_dir file) c; + self#output_code m.met_value.val_name (Filename.concat !Args.target_dir file) c; "<a href=\""^file^"\">"^(Name.simple m.met_value.val_name)^"</a>" )^" : "^ (self#html_of_type_expr module_name m.met_value.val_type)^"</pre>"^ (self#html_of_info m.met_value.val_info)^ - (if !Odoc_args.with_parameter_list then + (if !Args.with_parameter_list then self#html_of_parameter_list module_name m.met_value.val_parameters else self#html_of_described_parameter_list module_name m.met_value.val_parameters @@ -1333,7 +1333,7 @@ class html = ('a -> string) -> string -> string -> unit = fun elements name info target title simple_file -> try - let chanout = open_out (Filename.concat !Odoc_args.target_dir simple_file) in + let chanout = open_out (Filename.concat !Args.target_dir simple_file) in output_string chanout ( "<html>\n"^ @@ -1400,7 +1400,7 @@ class html = let (html_file, _) = Naming.html_files cl.cl_name in let type_file = Naming.file_type_class_complete_target cl.cl_name in try - let chanout = open_out (Filename.concat !Odoc_args.target_dir html_file) in + let chanout = open_out (Filename.concat !Args.target_dir html_file) in let pre_name = opt (fun c -> c.cl_name) pre in let post_name = opt (fun c -> c.cl_name) post in output_string chanout @@ -1444,7 +1444,7 @@ class html = (* generate the file with the complete class type *) self#output_class_type cl.cl_name - (Filename.concat !Odoc_args.target_dir type_file) + (Filename.concat !Args.target_dir type_file) cl.cl_type with Sys_error s -> @@ -1456,7 +1456,7 @@ class html = let (html_file, _) = Naming.html_files clt.clt_name in let type_file = Naming.file_type_class_complete_target clt.clt_name in try - let chanout = open_out (Filename.concat !Odoc_args.target_dir html_file) in + let chanout = open_out (Filename.concat !Args.target_dir html_file) in let pre_name = opt (fun ct -> ct.clt_name) pre in let post_name = opt (fun ct -> ct.clt_name) post in output_string chanout @@ -1497,7 +1497,7 @@ class html = (* generate the file with the complete class type *) self#output_class_type clt.clt_name - (Filename.concat !Odoc_args.target_dir type_file) + (Filename.concat !Args.target_dir type_file) clt.clt_type with Sys_error s -> @@ -1509,7 +1509,7 @@ class html = try let (html_file, _) = Naming.html_files mt.mt_name in let type_file = Naming.file_type_module_complete_target mt.mt_name in - let chanout = open_out (Filename.concat !Odoc_args.target_dir html_file) in + let chanout = open_out (Filename.concat !Args.target_dir html_file) in let pre_name = opt (fun mt -> mt.mt_name) pre in let post_name = opt (fun mt -> mt.mt_name) post in output_string chanout @@ -1578,7 +1578,7 @@ class html = None -> () | Some mty -> self#output_module_type mt.mt_name - (Filename.concat !Odoc_args.target_dir type_file) + (Filename.concat !Args.target_dir type_file) mty ) with @@ -1592,7 +1592,7 @@ class html = Odoc_info.verbose ("Generate for module "^modu.m_name); let (html_file, _) = Naming.html_files modu.m_name in let type_file = Naming.file_type_module_complete_target modu.m_name in - let chanout = open_out (Filename.concat !Odoc_args.target_dir html_file) in + let chanout = open_out (Filename.concat !Args.target_dir html_file) in let pre_name = opt (fun m -> m.m_name) pre in let post_name = opt (fun m -> m.m_name) post in output_string chanout @@ -1656,7 +1656,7 @@ class html = (* generate the file with the complete module type *) self#output_module_type modu.m_name - (Filename.concat !Odoc_args.target_dir type_file) + (Filename.concat !Args.target_dir type_file) modu.m_type with Sys_error s -> @@ -1666,13 +1666,13 @@ class html = @raise Failure if an error occurs.*) method generate_index module_list = try - let title = match !Odoc_args.title with None -> "" | Some t -> self#escape t in + let title = match !Args.title with None -> "" | Some t -> self#escape t in let index_if_not_empty l url m = match l with [] -> "" | _ -> "<a href=\""^url^"\">"^m^"</a><br>\n" in - let chanout = open_out (Filename.concat !Odoc_args.target_dir index) in + let chanout = open_out (Filename.concat !Args.target_dir index) in output_string chanout ( "<html>\n"^ @@ -1834,7 +1834,7 @@ class html = let module_names = List.map (fun m -> m.m_name) modules in known_modules_names <- module_type_names @ module_names ; (* generate html for each module *) - if not !Odoc_args.index_only then + if not !Args.index_only then self#generate_elements self#generate_for_module module_list ; try diff --git a/ocamldoc/odoc_info.ml b/ocamldoc/odoc_info.ml index 6c1cf0353..84b365912 100644 --- a/ocamldoc/odoc_info.ml +++ b/ocamldoc/odoc_info.ml @@ -210,3 +210,5 @@ module Dep = let kernel_deps_of_modules = Odoc_dep.kernel_deps_of_modules let deps_of_types = Odoc_dep.deps_of_types end + +module Args = Odoc_args diff --git a/ocamldoc/odoc_info.mli b/ocamldoc/odoc_info.mli index 6fb5990b6..07925d644 100644 --- a/ocamldoc/odoc_info.mli +++ b/ocamldoc/odoc_info.mli @@ -848,3 +848,115 @@ module Dep : *) val deps_of_types : ?kernel: bool -> Type.t_type list -> (Type.t_type * (Name.t list)) list end + +(** Command line arguments. + You can use this module to create custom generators.*) +module Args : + sig + (** The class type of documentation generators. *) + class type doc_generator = + object method generate : Odoc_module.t_module list -> unit end + + (** The file used by the generators outputting only one file. *) + val out_file : string ref + + (** Verbose mode or not. *) + val verbose : bool ref + + (** The optional title to use in the generated documentation. *) + val title : string option ref + + (** Flag to indicate whether we must display the complete list of parameters + for functions and methods. *) + val with_parameter_list : bool ref + + (** The list of module names to hide. *) + val hidden_modules : string list ref + + (** The directory where files have to be generated. *) + val target_dir : string ref + + (** An optional file to use where a CSS style is defined (for HTML). *) + val css_style : string option ref + + (** Generate only index files. (for HTML). *) + val index_only : bool ref + + (** To colorize code in HTML generated documentation pages, not code pages. *) + val colorize_code : bool ref + + (** The flag which indicates if we must generate a header (for LaTeX). *) + val with_header : bool ref + + (** The flag which indicates if we must generate a trailer (for LaTeX). *) + val with_trailer : bool ref + + (** The flag to indicate if we must generate one file per module (for LaTeX). *) + val separate_files : bool ref + + (** The list of pairs (title level, sectionning style). *) + val latex_titles : (int * string) list ref + + (** The prefix to use for value labels in LaTeX. *) + val latex_value_prefix : string ref + + (** The prefix to use for type labels in LaTeX. *) + val latex_type_prefix : string ref + + (** The prefix to use for exception labels in LaTeX. *) + val latex_exception_prefix : string ref + + (** The prefix to use for module labels in LaTeX. *) + val latex_module_prefix : string ref + + (** The prefix to use for module type labels in LaTeX. *) + val latex_module_type_prefix : string ref + + (** The prefix to use for class labels in LaTeX. *) + val latex_class_prefix : string ref + + (** The prefix to use for class type labels in LaTeX. *) + val latex_class_type_prefix : string ref + + (** The prefix to use for attribute labels in LaTeX. *) + val latex_attribute_prefix : string ref + + (** The prefix to use for method labels in LaTeX. *) + val latex_method_prefix : string ref + + (** The flag which indicates if we must generate a table of contents (for LaTeX). *) + val with_toc : bool ref + + (** The flag which indicates if we must generate an index (for TeXinfo). *) + val with_index : bool ref + + (** The flag which indicates if we must escape accentuated characters (for TeXinfo).*) + val esc_8bits : bool ref + + (** Include all modules or only the ones on the command line, for the dot ouput. *) + val dot_include_all : bool ref + + (** Generate dependency graph for types. *) + val dot_types : bool ref + + (** Perform transitive reduction before dot output. *) + val dot_reduce : bool ref + + (** The colors used in the dot output. *) + val dot_colors : string list ref + + (** The suffix for man pages. *) + val man_suffix : string ref + + (** The flag to generate all man pages or only for modules and classes.*) + val man_mini : bool ref + + (** The files to be analysed. *) + val files : string list ref + + (** To set the documentation generator. *) + val set_doc_generator : doc_generator option -> unit + + (** Add an option specification. *) + val add_option : string * Arg.spec * string -> unit + end diff --git a/ocamldoc/odoc_latex.ml b/ocamldoc/odoc_latex.ml index d7af66828..fd6f11fac 100644 --- a/ocamldoc/odoc_latex.ml +++ b/ocamldoc/odoc_latex.ml @@ -30,7 +30,7 @@ class text = and with the given latex code. *) method section_style level s = try - let sec = List.assoc level !Odoc_args.latex_titles in + let sec = List.assoc level !Args.latex_titles in "\\"^sec^"{"^s^"}\n" with Not_found -> s @@ -131,31 +131,31 @@ class text = Buffer.contents buf (** Make a correct label from a value name. *) - method value_label ?no_ name = self#label ?no_ (!Odoc_args.latex_value_prefix^name) + method value_label ?no_ name = self#label ?no_ (!Args.latex_value_prefix^name) (** Make a correct label from an attribute name. *) - method attribute_label ?no_ name = self#label ?no_ (!Odoc_args.latex_attribute_prefix^name) + method attribute_label ?no_ name = self#label ?no_ (!Args.latex_attribute_prefix^name) (** Make a correct label from a method name. *) - method method_label ?no_ name = self#label ?no_ (!Odoc_args.latex_method_prefix^name) + method method_label ?no_ name = self#label ?no_ (!Args.latex_method_prefix^name) (** Make a correct label from a class name. *) - method class_label ?no_ name = self#label ?no_ (!Odoc_args.latex_class_prefix^name) + method class_label ?no_ name = self#label ?no_ (!Args.latex_class_prefix^name) (** Make a correct label from a class type name. *) - method class_type_label ?no_ name = self#label ?no_ (!Odoc_args.latex_class_type_prefix^name) + method class_type_label ?no_ name = self#label ?no_ (!Args.latex_class_type_prefix^name) (** Make a correct label from a module name. *) - method module_label ?no_ name = self#label ?no_ (!Odoc_args.latex_module_prefix^name) + method module_label ?no_ name = self#label ?no_ (!Args.latex_module_prefix^name) (** Make a correct label from a module type name. *) - method module_type_label ?no_ name = self#label ?no_ (!Odoc_args.latex_module_type_prefix^name) + method module_type_label ?no_ name = self#label ?no_ (!Args.latex_module_type_prefix^name) (** Make a correct label from an exception name. *) - method exception_label ?no_ name = self#label ?no_ (!Odoc_args.latex_exception_prefix^name) + method exception_label ?no_ name = self#label ?no_ (!Args.latex_exception_prefix^name) (** Make a correct label from a type name. *) - method type_label ?no_ name = self#label ?no_ (!Odoc_args.latex_type_prefix^name) + method type_label ?no_ name = self#label ?no_ (!Args.latex_type_prefix^name) (** Return latex code for the label of a given label. *) method make_label label = "\\label{"^label^"}" @@ -861,22 +861,22 @@ class latex = "\\usepackage{url} \n"^ "\\usepackage{ocamldoc}\n"^ ( - match !Odoc_args.title with + match !Args.title with None -> "" | Some s -> "\\title{"^(self#escape s)^"}\n" )^ "\\begin{document}\n"^ - (match !Odoc_args.title with None -> "" | Some _ -> "\\maketitle\n")^ - (if !Odoc_args.with_toc then "\\tableofcontents\n" else "") + (match !Args.title with None -> "" | Some _ -> "\\maketitle\n")^ + (if !Args.with_toc then "\\tableofcontents\n" else "") - (** Generate the LaTeX file from a module list, in the {!Odoc_args.out_file} file. *) + (** Generate the LaTeX file from a module list, in the {!Args.out_file} file. *) method generate module_list = - if !Odoc_args.separate_files then + if !Args.separate_files then ( let f m = try let chanout = - open_out ((Filename.concat !Odoc_args.target_dir (Name.simple m.m_name))^".tex") + open_out ((Filename.concat !Args.target_dir (Name.simple m.m_name))^".tex") in self#generate_for_module chanout m ; close_out chanout @@ -890,16 +890,16 @@ class latex = ); try - let chanout = open_out (Filename.concat !Odoc_args.target_dir !Odoc_args.out_file) in - let _ = if !Odoc_args.with_header then output_string chanout self#latex_header else () in + let chanout = open_out (Filename.concat !Args.target_dir !Args.out_file) in + let _ = if !Args.with_header then output_string chanout self#latex_header else () in List.iter - (fun m -> if !Odoc_args.separate_files then + (fun m -> if !Args.separate_files then output_string chanout ("\\input{"^((Name.simple m.m_name))^".tex}\n") else self#generate_for_module chanout m ) module_list ; - let _ = if !Odoc_args.with_trailer then output_string chanout "\\end{document}" else () in + let _ = if !Args.with_trailer then output_string chanout "\\end{document}" else () in close_out chanout with Failure s diff --git a/ocamldoc/odoc_man.ml b/ocamldoc/odoc_man.ml index 8f533ce99..936b24e85 100644 --- a/ocamldoc/odoc_man.ml +++ b/ocamldoc/odoc_man.ml @@ -145,7 +145,7 @@ class man = (** Get a file name from a complete name. *) method file_name name = - let s = Printf.sprintf "%s.%s" name !Odoc_args.man_suffix in + let s = Printf.sprintf "%s.%s" name !Args.man_suffix in Str.global_replace re_slash "slash" s (** Escape special sequences of characters in a string. *) @@ -153,7 +153,7 @@ class man = (** Open a file for output. Add the target directory.*) method open_out file = - let f = Filename.concat !Odoc_args.target_dir file in + let f = Filename.concat !Args.target_dir file in open_out f (** Return the groff string for a text, without correction of blanks. *) @@ -532,7 +532,7 @@ class man = cl.cl_name^" "^ "\""^(Odoc_misc.string_of_date ~hour: false date)^"\" "^ "OCamldoc "^ - "\""^(match !Odoc_args.title with Some t -> t | None -> "")^"\"\n"); + "\""^(match !Args.title with Some t -> t | None -> "")^"\"\n"); output_string chanout ( @@ -584,7 +584,7 @@ class man = ct.clt_name^" "^ "\""^(Odoc_misc.string_of_date ~hour: false date)^"\" "^ "OCamldoc "^ - "\""^(match !Odoc_args.title with Some t -> t | None -> "")^"\"\n"); + "\""^(match !Args.title with Some t -> t | None -> "")^"\"\n"); output_string chanout ( @@ -632,7 +632,7 @@ class man = mt.mt_name^" "^ "\""^(Odoc_misc.string_of_date ~hour: false date)^"\" "^ "OCamldoc "^ - "\""^(match !Odoc_args.title with Some t -> t | None -> "")^"\"\n"); + "\""^(match !Args.title with Some t -> t | None -> "")^"\"\n"); output_string chanout ( @@ -702,7 +702,7 @@ class man = m.m_name^" "^ "\""^(Odoc_misc.string_of_date ~hour: false date)^"\" "^ "OCamldoc "^ - "\""^(match !Odoc_args.title with Some t -> t | None -> "")^"\"\n"); + "\""^(match !Args.title with Some t -> t | None -> "")^"\"\n"); output_string chanout ( @@ -821,7 +821,7 @@ class man = "man "^ "\""^(Odoc_misc.string_of_date ~hour: false date)^"\" "^ "OCamldoc "^ - "\""^(match !Odoc_args.title with Some t -> t | None -> "")^"\"\n"); + "\""^(match !Args.title with Some t -> t | None -> "")^"\"\n"); let f ele = match ele with @@ -877,7 +877,7 @@ class man = | [Res_class cl] -> self#generate_for_class cl | [Res_class_type ct] -> self#generate_for_class_type ct | l -> - if !Odoc_args.man_mini then + if !Args.man_mini then () else self#generate_for_group l diff --git a/ocamldoc/odoc_messages.ml b/ocamldoc/odoc_messages.ml index 77a977d56..a25795d07 100644 --- a/ocamldoc/odoc_messages.ml +++ b/ocamldoc/odoc_messages.ml @@ -31,7 +31,7 @@ let verbose_mode = " verbose mode" let include_dirs = "<dir> Add <dir> to the list of include directories" let rectypes = " Allow arbitrary recursive types" let preprocess = "<command> Pipe sources through preprocessor <command>" -let load_file = "<file.cm[o|a]> Load file defining a new documentation generator" +let load_file = "<file.cm[o|a]> Load file defining a new documentation generator (bytecode version only)" let nolabels = " Ignore non-optional labels in types" let werr = "Treat ocamldoc warnings as errors" let target_dir = "<dir> Generate files in directory <dir>, rather than in current directory (for man and HTML generators)" @@ -46,6 +46,8 @@ let generate_texinfo = " Generate TeXinfo documentation" let generate_man = " Generate man pages" let generate_dot = " Generate dot code of top modules dependencies" +let option_not_in_native_code op = "Option "^op^" not available in native code version." + let default_out_file = "ocamldoc.out" let out_file = "<file> Set the ouput file name, used by texi, latex and dot generators "^ "(default is "^default_out_file^")" diff --git a/ocamldoc/odoc_opt.ml b/ocamldoc/odoc_opt.ml index a8be1963e..8eb7e6fa3 100644 --- a/ocamldoc/odoc_opt.ml +++ b/ocamldoc/odoc_opt.ml @@ -19,6 +19,7 @@ open Misc open Format open Typedtree +let _ = Odoc_args.bytecode_mode := false let html_generator = new Odoc_html.html diff --git a/ocamldoc/odoc_texi.ml b/ocamldoc/odoc_texi.ml index ec6269384..036ea213c 100644 --- a/ocamldoc/odoc_texi.ml +++ b/ocamldoc/odoc_texi.ml @@ -22,8 +22,8 @@ open Module (** {2 Command-line options} *) -let with_index = Odoc_args.with_index -let esc_8bits = Odoc_args.esc_8bits +let with_index = Args.with_index +let esc_8bits = Args.esc_8bits (** {2 Some small helper functions} *) @@ -992,7 +992,7 @@ class texi = (** Writes the header of the TeX document. *) method generate_texi_header chan m_list = let title, filename = - match !Odoc_args.title with + match !Args.title with | None -> ("", "doc.info") | Some s -> let s' = self#escape s in @@ -1056,26 +1056,26 @@ class texi = "@unnumbered " ^ longname ^ " index" ; "@printindex " ^ shortname ; ]) indices_names )) ; - if !Odoc_args.with_toc + if !Args.with_toc then puts_nl chan "@contents" ; puts_nl chan "@bye" (** Generate the Texinfo file from a module list, - in the {!Odoc_args.out_file} file. *) + in the {!Args.out_file} file. *) method generate module_list = try let chanout = open_out - (Filename.concat !Odoc_args.target_dir !Odoc_args.out_file) in - if !Odoc_args.with_header + (Filename.concat !Args.target_dir !Args.out_file) in + if !Args.with_header then self#generate_texi_header chanout module_list ; List.iter (fun modu -> Odoc_info.verbose ("Generate for module " ^ modu.m_name) ; self#generate_for_module chanout modu) module_list ; - if !Odoc_args.with_trailer + if !Args.with_trailer then self#generate_texi_trailer chanout ; close_out chanout with |