diff options
author | Alain Frisch <alain@frisch.fr> | 2012-07-24 16:24:44 +0000 |
---|---|---|
committer | Alain Frisch <alain@frisch.fr> | 2012-07-24 16:24:44 +0000 |
commit | 936914100b0250a932750d51e67a9e01f3184149 (patch) | |
tree | fbf3f378a4e99fd7a41031ea197de58a156d349a | |
parent | aebeab4caebea0f6664896b800d5529fece68ad2 (diff) |
Add support for -ppx in ocamldep (and reuse preprocessing code in Pparse).
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@12769 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
-rw-r--r-- | .depend | 12 | ||||
-rw-r--r-- | tools/Makefile.shared | 3 | ||||
-rw-r--r-- | tools/depend.ml | 3 | ||||
-rw-r--r-- | tools/depend.mli | 2 | ||||
-rw-r--r-- | tools/ocamldep.ml | 81 |
5 files changed, 26 insertions, 75 deletions
@@ -39,6 +39,8 @@ parsing/lexer.cmo : utils/warnings.cmi parsing/parser.cmi utils/misc.cmi \ parsing/location.cmi parsing/lexer.cmi parsing/lexer.cmx : utils/warnings.cmx parsing/parser.cmx utils/misc.cmx \ parsing/location.cmx parsing/lexer.cmi +parsing/linenum.cmo : utils/misc.cmi +parsing/linenum.cmx : utils/misc.cmx parsing/location.cmo : utils/warnings.cmi utils/terminfo.cmi \ parsing/location.cmi parsing/location.cmx : utils/warnings.cmx utils/terminfo.cmx \ @@ -111,7 +113,7 @@ typing/typedtree.cmi : typing/types.cmi typing/primitive.cmi typing/path.cmi \ parsing/longident.cmi parsing/location.cmi typing/ident.cmi \ typing/env.cmi parsing/asttypes.cmi typing/typedtreeIter.cmi : typing/typedtree.cmi parsing/asttypes.cmi -typing/typedtreeMap.cmi : typing/typedtree.cmi parsing/asttypes.cmi +typing/typedtreeMap.cmi : typing/typedtree.cmi typing/typemod.cmi : typing/types.cmi typing/typedtree.cmi \ parsing/parsetree.cmi parsing/longident.cmi parsing/location.cmi \ typing/includemod.cmi typing/ident.cmi typing/env.cmi @@ -301,10 +303,10 @@ typing/typedtree.cmo : typing/types.cmi typing/primitive.cmi typing/path.cmi \ typing/typedtree.cmx : typing/types.cmx typing/primitive.cmx typing/path.cmx \ utils/misc.cmx parsing/longident.cmx parsing/location.cmx \ typing/ident.cmx typing/env.cmx parsing/asttypes.cmi typing/typedtree.cmi -typing/typedtreeIter.cmo : typing/typedtree.cmi utils/misc.cmi \ - parsing/asttypes.cmi typing/typedtreeIter.cmi -typing/typedtreeIter.cmx : typing/typedtree.cmx utils/misc.cmx \ - parsing/asttypes.cmi typing/typedtreeIter.cmi +typing/typedtreeIter.cmo : typing/typedtree.cmi parsing/asttypes.cmi \ + typing/typedtreeIter.cmi +typing/typedtreeIter.cmx : typing/typedtree.cmx parsing/asttypes.cmi \ + typing/typedtreeIter.cmi typing/typedtreeMap.cmo : typing/typedtree.cmi utils/misc.cmi \ parsing/asttypes.cmi typing/typedtreeMap.cmi typing/typedtreeMap.cmx : typing/typedtree.cmx utils/misc.cmx \ diff --git a/tools/Makefile.shared b/tools/Makefile.shared index bddcfdb98..4729fef31 100644 --- a/tools/Makefile.shared +++ b/tools/Makefile.shared @@ -37,7 +37,8 @@ opt.opt: ocamldep.opt CAMLDEP_OBJ=depend.cmo ocamldep.cmo CAMLDEP_IMPORTS=misc.cmo config.cmo clflags.cmo terminfo.cmo \ warnings.cmo location.cmo longident.cmo \ - syntaxerr.cmo parser.cmo lexer.cmo parse.cmo + syntaxerr.cmo parser.cmo lexer.cmo parse.cmo \ + ccomp.cmo pparse.cmo ocamldep: depend.cmi $(CAMLDEP_OBJ) $(CAMLC) $(LINKFLAGS) -o ocamldep $(CAMLDEP_IMPORTS) $(CAMLDEP_OBJ) diff --git a/tools/depend.ml b/tools/depend.ml index 2015f937e..7bf1d55b4 100644 --- a/tools/depend.ml +++ b/tools/depend.ml @@ -279,6 +279,9 @@ and add_struct_item bv item = and add_use_file bv top_phrs = ignore (List.fold_left add_top_phrase bv top_phrs) +and add_implementation bv l = + ignore (add_structure bv l) + and add_top_phrase bv = function | Ptop_def str -> add_structure bv str | Ptop_dir (_, _) -> bv diff --git a/tools/depend.mli b/tools/depend.mli index 7c6d0c01d..de7663335 100644 --- a/tools/depend.mli +++ b/tools/depend.mli @@ -21,3 +21,5 @@ val free_structure_names : StringSet.t ref val add_use_file : StringSet.t -> Parsetree.toplevel_phrase list -> unit val add_signature : StringSet.t -> Parsetree.signature -> unit + +val add_implementation : StringSet.t -> Parsetree.structure -> unit diff --git a/tools/ocamldep.ml b/tools/ocamldep.ml index 46449037a..eee0ae5b7 100644 --- a/tools/ocamldep.ml +++ b/tools/ocamldep.ml @@ -185,62 +185,6 @@ let print_raw_dependencies source_file deps = deps; print_char '\n' -(* Optionally preprocess a source file *) - -let preprocessor = ref None - -exception Preprocessing_error - -let preprocess sourcefile = - match !preprocessor with - None -> sourcefile - | Some pp -> - flush Pervasives.stdout; - let tmpfile = Filename.temp_file "camlpp" "" in - let comm = Printf.sprintf "%s %s > %s" pp sourcefile tmpfile in - if Sys.command comm <> 0 then begin - Misc.remove_file tmpfile; - raise Preprocessing_error - end; - tmpfile - -let remove_preprocessed inputfile = - match !preprocessor with - None -> () - | Some _ -> Misc.remove_file inputfile - -(* Parse a file or get a dumped syntax tree in it *) - -let is_ast_file ic ast_magic = - 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 - failwith "OCaml and preprocessor have incompatible versions" - else false - with End_of_file -> false - -let parse_use_file ic = - if is_ast_file ic Config.ast_impl_magic_number then - let _source_file = input_value ic in - [Ptop_def (input_value ic : Parsetree.structure)] - else begin - seek_in ic 0; - let lb = Lexing.from_channel ic in - Location.init lb !Location.input_name; - Parse.use_file lb - end - -let parse_interface ic = - if is_ast_file ic Config.ast_intf_magic_number then - let _source_file = input_value ic in - (input_value ic : Parsetree.signature) - else begin - seek_in ic 0; - let lb = Lexing.from_channel ic in - Location.init lb !Location.input_name; - Parse.interface lb - end (* Process one file *) @@ -255,29 +199,25 @@ let report_err source_file exn = Syntaxerr.report_error err | Sys_error msg -> Format.fprintf Format.err_formatter "@[I/O error:@ %s@]@." msg - | Preprocessing_error -> + | Pparse.Error -> Format.fprintf Format.err_formatter "@[Preprocessing error on file %s@]@." source_file | x -> raise x -let read_parse_and_extract parse_function extract_function source_file = +let read_parse_and_extract parse_function extract_function magic source_file = Depend.free_structure_names := Depend.StringSet.empty; try - let input_file = preprocess source_file in - let ic = open_in_bin input_file in - try - let ast = parse_function ic in - extract_function Depend.StringSet.empty ast; - !Depend.free_structure_names - with x -> - close_in ic; remove_preprocessed input_file; raise x + let input_file = Pparse.preprocess source_file in + let ast = Pparse.file Format.err_formatter input_file parse_function magic in + extract_function Depend.StringSet.empty ast; + !Depend.free_structure_names with x -> report_err source_file x; Depend.StringSet.empty let ml_file_dependencies source_file = let extracted_deps = read_parse_and_extract - parse_use_file Depend.add_use_file source_file + Parse.implementation Depend.add_implementation Config.ast_impl_magic_number source_file in if !sort_files then files := (source_file, ML, !Depend.free_structure_names) :: !files @@ -307,7 +247,8 @@ let ml_file_dependencies source_file = let mli_file_dependencies source_file = let extracted_deps = read_parse_and_extract - parse_interface Depend.add_signature source_file in + Parse.interface Depend.add_signature Config.ast_intf_magic_number source_file + in if !sort_files then files := (source_file, MLI, extracted_deps) :: !files else @@ -449,8 +390,10 @@ let _ = " Generate dependencies on all files (not accommodating for make shortcomings)"; "-one-line", Arg.Set one_line, " Output one line per file, regardless of the length"; - "-pp", Arg.String(fun s -> preprocessor := Some s), + "-pp", Arg.String(fun s -> Clflags.preprocessor := Some s), "<cmd> Pipe sources through preprocessor <cmd>"; + "-ppx", Arg.String(fun s -> Clflags.ppx := s :: !Clflags.ppx), + "<cmd> Pipe abstract syntax trees through preprocessor <cmd>"; "-slash", Arg.Set force_slash, " (Windows) Use forward slash / instead of backslash \\ in file paths"; "-version", Arg.Unit print_version, |