Adapt ocamldoc for -ppx. Also reuse some code from Pparse instead of duplicating it.

git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@12598 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
master
Alain Frisch 2012-06-13 08:32:57 +00:00
parent 60d0694e9f
commit d70eff6a1f
7 changed files with 18 additions and 63 deletions

View File

@ -185,7 +185,8 @@ OCAMLCMOFILES=$(OCAMLSRCDIR)/parsing/printast.cmo \
$(OCAMLSRCDIR)/bytecomp/translobj.cmo \
$(OCAMLSRCDIR)/bytecomp/translcore.cmo \
$(OCAMLSRCDIR)/bytecomp/translclass.cmo \
$(OCAMLSRCDIR)/tools/depend.cmo
$(OCAMLSRCDIR)/tools/depend.cmo \
$(OCAMLSRCDIR)/driver/pparse.cmo
OCAMLCMXFILES=$(OCAMLCMOFILES:.cmo=.cmx)

View File

@ -174,7 +174,8 @@ OCAMLCMOFILES=$(OCAMLSRCDIR)/parsing/printast.cmo \
$(OCAMLSRCDIR)/bytecomp/translobj.cmo \
$(OCAMLSRCDIR)/bytecomp/translcore.cmo \
$(OCAMLSRCDIR)/bytecomp/translclass.cmo \
$(OCAMLSRCDIR)/tools/depend.cmo
$(OCAMLSRCDIR)/tools/depend.cmo \
$(OCAMLSRCDIR)/driver/pparse.cmo
OCAMLCMXFILES=$(OCAMLCMOFILES:.cmo=.cmx)

View File

@ -43,62 +43,11 @@ let initial_env () =
(** Optionally preprocess a source file *)
let preprocess sourcefile =
match !Clflags.preprocessor with
None -> sourcefile
| Some pp ->
let tmpfile = Filename.temp_file "camlpp" "" in
let comm = Printf.sprintf "%s %s > %s" pp sourcefile tmpfile in
if Ccomp.command comm <> 0 then begin
remove_file tmpfile;
Printf.eprintf "Preprocessing error\n";
exit 2
end;
tmpfile
(** Remove the input file if this file was the result of a preprocessing.*)
let remove_preprocessed inputfile =
match !Clflags.preprocessor with
None -> ()
| Some _ -> remove_file inputfile
let remove_preprocessed_if_ast inputfile =
match !Clflags.preprocessor with
None -> ()
| Some _ -> if inputfile <> !Location.input_name then remove_file inputfile
exception Outdated_version
(** Parse a file or get a dumped syntax tree in it *)
let parse_file inputfile parse_fun ast_magic =
let ic = open_in_bin inputfile in
let is_ast_file =
try
let buffer = Misc.input_bytes ic (String.length ast_magic) in
if buffer = ast_magic then true
else if String.sub buffer 0 9 = String.sub ast_magic 0 9 then
raise Outdated_version
else false
with
Outdated_version ->
fatal_error "OCaml and preprocessor have incompatible versions"
| _ -> false
in
let ast =
try
if is_ast_file then begin
Location.input_name := input_value ic;
input_value ic
end else begin
seek_in ic 0;
Location.input_name := inputfile;
let lexbuf = Lexing.from_channel ic in
Location.init lexbuf inputfile;
parse_fun lexbuf
end
with x -> close_in ic; raise x
in
close_in ic;
ast
try
Pparse.preprocess sourcefile
with Pparse.Error ->
Printf.eprintf "Preprocessing error\n";
exit 2
let (++) x f = f x
@ -112,7 +61,7 @@ let process_implementation_file ppf sourcefile =
let inputfile = preprocess sourcefile in
let env = initial_env () in
try
let parsetree = parse_file inputfile Parse.implementation ast_impl_magic_number in
let parsetree = Pparse.file Format.err_formatter inputfile Parse.implementation ast_impl_magic_number in
let typedtree =
Typemod.type_implementation
sourcefile prefixname modulename env parsetree
@ -140,7 +89,7 @@ let process_interface_file ppf sourcefile =
let modulename = String.capitalize(Filename.basename prefixname) in
Env.set_unit_name modulename;
let inputfile = preprocess sourcefile in
let ast = parse_file inputfile Parse.interface ast_intf_magic_number in
let ast = Pparse.file Format.err_formatter inputfile Parse.interface ast_intf_magic_number in
let sg = Typemod.transl_signature (initial_env()) ast in
Warnings.check_fatal ();
(ast, sg, inputfile)
@ -238,7 +187,7 @@ let process_file ppf sourcefile =
print_string Odoc_messages.ok;
print_newline ()
);
remove_preprocessed input_file;
Pparse.remove_preprocessed input_file;
Some file_module
with
| Sys_error s
@ -267,7 +216,7 @@ let process_file ppf sourcefile =
print_string Odoc_messages.ok;
print_newline ()
);
remove_preprocessed input_file;
Pparse.remove_preprocessed input_file;
Some file_module
with
| Sys_error s

View File

@ -94,6 +94,7 @@ let default_options = [
(Misc.expand_directory Config.standard_library s) :: !Odoc_global.include_dirs),
M.include_dirs ;
"-pp", Arg.String (fun s -> Odoc_global.preprocessor := Some s), M.preprocess ;
"-ppx", Arg.String (fun s -> Odoc_global.ppx := s :: !Odoc_global.ppx), M.ppx ;
"-impl", Arg.String (fun s ->
Odoc_global.files := !Odoc_global.files @ [Odoc_global.Impl_file s]),
M.option_impl ;

View File

@ -46,6 +46,7 @@ let recursive_types = Clflags.recursive_types
(** Optional preprocessor command. *)
let preprocessor = Clflags.preprocessor
let ppx = Clflags.ppx
let sort_modules = ref false

View File

@ -23,7 +23,8 @@ type source_file =
val include_dirs : string list ref
(** Optional preprocessor command to pass to ocaml compiler. *)
val preprocessor : string option ref
val preprocessor : string option ref (* -pp *)
val ppx : string list ref (* -ppx *)
(** Recursive types flag to passe to ocaml compiler. *)
val recursive_types : bool ref

View File

@ -35,6 +35,7 @@ let verbose_mode = "\t\tverbose mode"
let include_dirs = "<dir>\tAdd <dir> to the list of include directories"
let rectypes = "\tAllow arbitrary recursive types"
let preprocess = "<command>\tPipe sources through preprocessor <command>"
let ppx = "<command>\n\t\tPipe abstract syntax tree through preprocessor <command>"
let option_impl ="<file>\tConsider <file> as a .ml file"
let option_intf ="<file>\tConsider <file> as a .mli file"
let option_text ="<file>\tConsider <file> as a .txt file"