summaryrefslogtreecommitdiffstats
path: root/driver/compile.ml
diff options
context:
space:
mode:
Diffstat (limited to 'driver/compile.ml')
-rw-r--r--driver/compile.ml79
1 files changed, 9 insertions, 70 deletions
diff --git a/driver/compile.ml b/driver/compile.ml
index c58483e5e..0699c531c 100644
--- a/driver/compile.ml
+++ b/driver/compile.ml
@@ -44,86 +44,25 @@ let initial_env () =
with Not_found ->
fatal_error "cannot open pervasives.cmi"
-(* 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
-
-let remove_preprocessed inputfile =
- match !Clflags.preprocessor with
- None -> ()
- | Some _ -> remove_file inputfile
-
-(* Parse a file or get a dumped syntax tree in it *)
-
-exception Outdated_version
-
-let parse_file ppf inputfile parse_fun ast_magic =
- let ic = open_in_bin inputfile in
- let is_ast_file =
- try
- let buffer = String.create (String.length ast_magic) in
- really_input ic buffer 0 (String.length ast_magic);
- 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
- if !Clflags.fast then
- fprintf ppf "@[Warning: %s@]@."
- "option -unsafe used with a preprocessor returning a syntax tree";
- Location.input_name := input_value ic;
- input_value ic
- end else begin
- seek_in ic 0;
- Location.input_name := inputfile;
- parse_fun (Lexing.from_channel ic)
- end
- with x -> close_in ic; raise x
- in
- close_in ic;
- ast
-
-let remove_preprocessed_if_ast inputfile =
- match !Clflags.preprocessor with
- None -> ()
- | Some _ -> if inputfile <> !Location.input_name then remove_file inputfile
-
(* Compile a .mli file *)
let interface ppf sourcefile =
init_path();
let prefixname = chop_extension_if_any sourcefile in
let modulename = String.capitalize(Filename.basename prefixname) in
- let inputfile = preprocess sourcefile in
+ let inputfile = Pparse.preprocess sourcefile in
try
- let ast = parse_file ppf inputfile Parse.interface ast_intf_magic_number in
+ let ast =
+ Pparse.file ppf inputfile Parse.interface ast_intf_magic_number in
if !Clflags.dump_parsetree then fprintf ppf "%a@." Printast.interface ast;
let sg = Typemod.transl_signature (initial_env()) ast in
if !Clflags.print_types
then fprintf std_formatter "%a@." Printtyp.signature sg;
Warnings.check_fatal ();
Env.save_signature sg modulename (prefixname ^ ".cmi");
- remove_preprocessed inputfile
+ Pparse.remove_preprocessed inputfile
with e ->
- remove_preprocessed_if_ast inputfile;
+ Pparse.remove_preprocessed_if_ast inputfile;
raise e
(* Compile a .ml file *)
@@ -138,12 +77,12 @@ let implementation ppf sourcefile =
init_path();
let prefixname = chop_extension_if_any sourcefile in
let modulename = String.capitalize(Filename.basename prefixname) in
- let inputfile = preprocess sourcefile in
+ let inputfile = Pparse.preprocess sourcefile in
let objfile = prefixname ^ ".cmo" in
let oc = open_out_bin objfile in
let env = initial_env() in
try
- parse_file ppf inputfile Parse.implementation ast_impl_magic_number
+ Pparse.file ppf inputfile Parse.implementation ast_impl_magic_number
++ print_if ppf Clflags.dump_parsetree Printast.implementation
++ Typemod.type_implementation sourcefile prefixname modulename env
++ Translmod.transl_implementation modulename
@@ -154,12 +93,12 @@ let implementation ppf sourcefile =
++ print_if ppf Clflags.dump_instr Printinstr.instrlist
++ Emitcode.to_file oc modulename;
Warnings.check_fatal ();
- remove_preprocessed inputfile;
+ Pparse.remove_preprocessed inputfile;
close_out oc;
with x ->
close_out oc;
remove_file objfile;
- remove_preprocessed_if_ast inputfile;
+ Pparse.remove_preprocessed_if_ast inputfile;
raise x
let c_file name =