summaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
authorMaxence Guesdon <maxence.guesdon@inria.fr>2009-03-11 07:04:39 +0000
committerMaxence Guesdon <maxence.guesdon@inria.fr>2009-03-11 07:04:39 +0000
commite93f6dd12bd3dae4c4eb6525563ae967ce48fbce (patch)
tree4538cb98bb99da63f9f372ba94528c943c2da8d1
parent89154947c2bcbfabfb31fc75c2cf47b273dcd449 (diff)
option -g also for native code version (loading custom generators)
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@9184 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
-rw-r--r--ocamldoc/Changes.txt4
-rw-r--r--ocamldoc/Makefile29
-rw-r--r--ocamldoc/odoc.ml18
-rw-r--r--ocamldoc/odoc_args.ml8
-rw-r--r--ocamldoc/odoc_args.mli4
-rw-r--r--ocamldoc/odoc_messages.ml5
-rw-r--r--ocamldoc/odoc_opt.ml81
7 files changed, 32 insertions, 117 deletions
diff --git a/ocamldoc/Changes.txt b/ocamldoc/Changes.txt
index 77f100de4..3707d265b 100644
--- a/ocamldoc/Changes.txt
+++ b/ocamldoc/Changes.txt
@@ -11,6 +11,10 @@ TODO:
- xml generator
=====
+Release > 3.11.0:
+- option -g also for native code version (loading custom generators)
+
+=====
Release 3.09.3:
- mod: PR#4017 new option -short-functors to use a short form to display
functors in html generator
diff --git a/ocamldoc/Makefile b/ocamldoc/Makefile
index 14a596763..a9ce89591 100644
--- a/ocamldoc/Makefile
+++ b/ocamldoc/Makefile
@@ -111,16 +111,17 @@ CMOFILES= odoc_config.cmo \
CMXFILES= $(CMOFILES:.cmo=.cmx)
CMIFILES= $(CMOFILES:.cmo=.cmi)
-EXECMOFILES=$(CMOFILES)\
- odoc_dag2html.cmo\
- odoc_to_text.cmo\
- odoc_ocamlhtml.cmo\
- odoc_html.cmo\
- odoc_man.cmo\
+EXECMOFILES=$(CMOFILES) \
+ odoc_dag2html.cmo \
+ odoc_to_text.cmo \
+ odoc_ocamlhtml.cmo \
+ odoc_html.cmo \
+ odoc_man.cmo \
odoc_latex_style.cmo \
- odoc_latex.cmo\
- odoc_texi.cmo\
- odoc_dot.cmo
+ odoc_latex.cmo \
+ odoc_texi.cmo \
+ odoc_dot.cmo \
+ odoc.cmo
EXECMXFILES= $(EXECMOFILES:.cmo=.cmx)
EXECMIFILES= $(EXECMOFILES:.cmo=.cmi)
@@ -199,10 +200,10 @@ libopt: $(OCAMLDOC_LIBCMXA) $(OCAMLDOC_LIBCMI)
debug:
make OCAMLPP=""
-$(OCAMLDOC): $(EXECMOFILES) odoc.cmo
- $(OCAMLC) -o $@ -linkall unix.cma str.cma dynlink.cma $(LINKFLAGS) $(OCAMLCMOFILES) $(EXECMOFILES) odoc.cmo
-$(OCAMLDOC_OPT): $(EXECMXFILES) odoc_opt.cmx
- $(OCAMLOPT) -o $@ unix.cmxa str.cmxa $(LINKFLAGS) $(OCAMLCMXFILES) $(EXECMXFILES) odoc_opt.cmx
+$(OCAMLDOC): $(EXECMOFILES)
+ $(OCAMLC) -o $@ -linkall unix.cma str.cma dynlink.cma $(LINKFLAGS) $(OCAMLCMOFILES) $(EXECMOFILES)
+$(OCAMLDOC_OPT): $(EXECMXFILES)
+ $(OCAMLOPT) -o $@ unix.cmxa str.cmxa dynlink.cmxa $(LINKFLAGS) $(OCAMLCMXFILES) $(EXECMXFILES)
$(OCAMLDOC_LIBCMA): $(LIBCMOFILES)
$(OCAMLC) -a -o $@ $(LINKFLAGS) $(OCAMLCMOFILES) $(LIBCMOFILES)
@@ -211,7 +212,7 @@ $(OCAMLDOC_LIBCMXA): $(LIBCMXFILES)
manpages: stdlib_man/Pervasives.3o
-dot: $(EXECMOFILES) odoc.cmo
+dot: $(EXECMOFILES)
$(OCAMLDOC_RUN) -dot -dot-reduce -o ocamldoc.dot $(INCLUDES) \
odoc*.ml
diff --git a/ocamldoc/odoc.ml b/ocamldoc/odoc.ml
index e66ce3754..1709694ee 100644
--- a/ocamldoc/odoc.ml
+++ b/ocamldoc/odoc.ml
@@ -25,17 +25,18 @@ let print_DEBUG s = print_string s ; print_newline ()
(* we check if we must load a module given on the command line *)
let arg_list = Array.to_list Sys.argv
-let (cmo_or_cma_opt, paths) =
+let (cm_opt, paths) =
let rec iter (f_opt, inc) = function
[] | _ :: [] -> (f_opt, inc)
| "-g" :: file :: q when
((Filename.check_suffix file "cmo") or
- (Filename.check_suffix file "cma")) &
+ (Filename.check_suffix file "cma") or
+ (Filename.check_suffix file "cmxs")) &
(f_opt = None) ->
- iter (Some file, inc) q
- | "-i" :: dir :: q ->
- iter (f_opt, inc @ [dir]) q
- | _ :: q ->
+ iter (Some file, inc) q
+ | "-i" :: dir :: q ->
+ iter (f_opt, inc @ [dir]) q
+ | _ :: q ->
iter (f_opt, inc) q
in
iter (None, []) arg_list
@@ -63,12 +64,11 @@ let get_real_filename name =
)
let _ =
- match cmo_or_cma_opt with
+ match cm_opt with
None ->
()
| Some file ->
- (* initializations for dynamic loading *)
- Dynlink.init ();
+ let file = Dynlink.adapt_filename file in
Dynlink.allow_unsafe_modules true;
try
let real_file = get_real_filename file in
diff --git a/ocamldoc/odoc_args.ml b/ocamldoc/odoc_args.ml
index 82e1f83db..3ed7039f0 100644
--- a/ocamldoc/odoc_args.ml
+++ b/ocamldoc/odoc_args.ml
@@ -24,8 +24,6 @@ type source_file =
let include_dirs = Clflags.include_dirs
-let bytecode_mode = ref true
-
class type doc_generator =
object
method generate : Odoc_module.t_module list -> unit
@@ -254,10 +252,8 @@ let options = ref [
"-dot", Arg.Unit (fun () -> set_doc_generator !default_dot_generator), M.generate_dot ;
"-customdir", Arg.Unit (fun () -> Printf.printf "%s\n" Odoc_config.custom_generators_path; exit 0),
M.display_custom_generators_dir ;
- "-i", Arg.String (fun s -> if !bytecode_mode then () else (prerr_endline (M.option_not_in_native_code "-i"); exit 1)),
- M.add_load_dir ;
- "-g", Arg.String (fun s -> if !bytecode_mode then () else (prerr_endline (M.option_not_in_native_code "-g"); exit 1)),
- M.load_file ^
+ "-i", Arg.String (fun s -> ()), M.add_load_dir ;
+ "-g", Arg.String (fun s -> ()), M.load_file ^
"\n\n *** HTML options ***\n";
(* html only options *)
diff --git a/ocamldoc/odoc_args.mli b/ocamldoc/odoc_args.mli
index 898da800e..2e096ac36 100644
--- a/ocamldoc/odoc_args.mli
+++ b/ocamldoc/odoc_args.mli
@@ -22,10 +22,6 @@ type source_file =
(** 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
diff --git a/ocamldoc/odoc_messages.ml b/ocamldoc/odoc_messages.ml
index 073187cc5..078f2d649 100644
--- a/ocamldoc/odoc_messages.ml
+++ b/ocamldoc/odoc_messages.ml
@@ -24,7 +24,6 @@ let message_version = software^" "^config_version
let usage = "Usage : "^(Sys.argv.(0))^" [options] <files>\n"
let options_are = "Options are :"
let option_version = "\tPrint version and exit"
-let bytecode_only = "(bytecode version only)"
let latex_only = "(LaTeX only)"
let texi_only = "(TeXinfo only)"
let latex_texi_only = "(LaTeX and TeXinfo only)"
@@ -41,8 +40,8 @@ let option_intf ="<file>\tConsider <file> as a .mli file"
let option_text ="<file>\tConsider <file> as a .txt file"
let display_custom_generators_dir = "\tDisplay custom generators standard directory and exit"
let add_load_dir = "<dir>\tAdd the given directory to the search path for custom\n"^
- "\t\tgenerators "^bytecode_only
-let load_file = "<file.cm[o|a]>\n\t\tLoad file defining a new documentation generator\n\t\t"^bytecode_only
+ "\t\tgenerators"
+let load_file = "<file.cm[o|a|xs]>\n\t\tLoad file defining a new documentation generator"
let nolabels = "\tIgnore non-optional labels in types"
let werr = "\tTreat ocamldoc warnings as errors"
let hide_warnings = "\n\t\tdo not print ocamldoc warnings"
diff --git a/ocamldoc/odoc_opt.ml b/ocamldoc/odoc_opt.ml
deleted file mode 100644
index ff9959971..000000000
--- a/ocamldoc/odoc_opt.ml
+++ /dev/null
@@ -1,81 +0,0 @@
-(***********************************************************************)
-(* OCamldoc *)
-(* *)
-(* Maxence Guesdon, projet Cristal, INRIA Rocquencourt *)
-(* *)
-(* Copyright 2001 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. *)
-(* *)
-(***********************************************************************)
-
-(* $Id$ *)
-
-(** Main module for native version.*)
-
-open Config
-open Clflags
-open Misc
-open Format
-open Typedtree
-
-let _ = Odoc_args.bytecode_mode := false
-
-
-let html_generator = new Odoc_html.html
-let default_latex_generator = new Odoc_latex.latex
-let default_texi_generator = new Odoc_texi.texi
-let default_man_generator = new Odoc_man.man
-let default_dot_generator = new Odoc_dot.dot
-let _ = Odoc_args.parse
- (html_generator :> Odoc_args.doc_generator)
- (default_latex_generator :> Odoc_args.doc_generator)
- (default_texi_generator :> Odoc_args.doc_generator)
- (default_man_generator :> Odoc_args.doc_generator)
- (default_dot_generator :> Odoc_args.doc_generator)
-
-let loaded_modules =
- List.flatten
- (List.map
- (fun f ->
- Odoc_info.verbose (Odoc_messages.loading f);
- try
- let l = Odoc_analyse.load_modules f in
- Odoc_info.verbose Odoc_messages.ok;
- l
- with Failure s ->
- prerr_endline s ;
- incr Odoc_global.errors ;
- []
- )
- !Odoc_args.load
- )
-
-let modules = Odoc_analyse.analyse_files ~init: loaded_modules !Odoc_args.files
-
-let _ =
- match !Odoc_args.dump with
- None -> ()
- | Some f ->
- try Odoc_analyse.dump_modules f modules
- with Failure s ->
- prerr_endline s ;
- incr Odoc_global.errors
-
-let _ =
- match !Odoc_args.doc_generator with
- None ->
- ()
- | Some gen ->
- Odoc_info.verbose Odoc_messages.generating_doc;
- gen#generate modules;
- Odoc_info.verbose Odoc_messages.ok
-
-let _ =
- if !Odoc_global.errors > 0 then
- (
- prerr_endline (Odoc_messages.errors_occured !Odoc_global.errors) ;
- exit 1
- )
- else
- exit 0