summaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
-rw-r--r--.depend111
-rw-r--r--Makefile9
-rw-r--r--driver/compile.ml79
-rw-r--r--driver/errors.ml2
-rw-r--r--driver/optcompile.ml108
-rw-r--r--driver/opterrors.ml2
-rw-r--r--driver/pparse.ml79
-rw-r--r--driver/pparse.mli22
8 files changed, 208 insertions, 204 deletions
diff --git a/.depend b/.depend
index bc9e29e14..5524d2842 100644
--- a/.depend
+++ b/.depend
@@ -76,7 +76,7 @@ typing/typeclass.cmi: parsing/asttypes.cmi typing/ctype.cmi typing/env.cmi \
parsing/parsetree.cmi typing/typedtree.cmi typing/types.cmi
typing/typecore.cmi: parsing/asttypes.cmi typing/env.cmi typing/ident.cmi \
parsing/location.cmi parsing/longident.cmi parsing/parsetree.cmi \
- typing/typedtree.cmi typing/types.cmi
+ typing/path.cmi typing/typedtree.cmi typing/types.cmi
typing/typedecl.cmi: typing/env.cmi typing/ident.cmi parsing/location.cmi \
parsing/longident.cmi parsing/parsetree.cmi typing/path.cmi \
typing/types.cmi
@@ -89,7 +89,8 @@ typing/typemod.cmi: typing/env.cmi typing/ident.cmi typing/includemod.cmi \
typing/types.cmi: parsing/asttypes.cmi typing/ident.cmi typing/path.cmi \
typing/primitive.cmi
typing/typetexp.cmi: typing/env.cmi parsing/location.cmi \
- parsing/longident.cmi parsing/parsetree.cmi typing/types.cmi
+ parsing/longident.cmi parsing/parsetree.cmi typing/path.cmi \
+ typing/types.cmi
typing/btype.cmo: utils/misc.cmi typing/path.cmi typing/types.cmi \
typing/btype.cmi
typing/btype.cmx: utils/misc.cmx typing/path.cmx typing/types.cmx \
@@ -232,12 +233,12 @@ typing/types.cmx: parsing/asttypes.cmi typing/ident.cmx utils/misc.cmx \
typing/path.cmx typing/primitive.cmx typing/types.cmi
typing/typetexp.cmo: typing/btype.cmi typing/ctype.cmi typing/env.cmi \
parsing/location.cmi parsing/longident.cmi utils/misc.cmi \
- parsing/parsetree.cmi typing/printtyp.cmi utils/tbl.cmi typing/types.cmi \
- utils/warnings.cmi typing/typetexp.cmi
+ parsing/parsetree.cmi typing/path.cmi typing/printtyp.cmi utils/tbl.cmi \
+ typing/types.cmi utils/warnings.cmi typing/typetexp.cmi
typing/typetexp.cmx: typing/btype.cmx typing/ctype.cmx typing/env.cmx \
parsing/location.cmx parsing/longident.cmx utils/misc.cmx \
- parsing/parsetree.cmi typing/printtyp.cmx utils/tbl.cmx typing/types.cmx \
- utils/warnings.cmx typing/typetexp.cmi
+ parsing/parsetree.cmi typing/path.cmx typing/printtyp.cmx utils/tbl.cmx \
+ typing/types.cmx utils/warnings.cmx typing/typetexp.cmi
bytecomp/bytegen.cmi: bytecomp/instruct.cmi bytecomp/lambda.cmi
bytecomp/bytelink.cmi: bytecomp/emitcode.cmi bytecomp/symtable.cmi
bytecomp/emitcode.cmi: typing/ident.cmi bytecomp/instruct.cmi \
@@ -569,73 +570,77 @@ asmcomp/split.cmx: asmcomp/mach.cmx utils/misc.cmx asmcomp/reg.cmx \
driver/compile.cmi: typing/env.cmi
driver/optcompile.cmi: typing/env.cmi
driver/compile.cmo: bytecomp/bytegen.cmi utils/ccomp.cmi utils/clflags.cmo \
- utils/config.cmi bytecomp/emitcode.cmi typing/env.cmi \
- parsing/location.cmi utils/misc.cmi parsing/parse.cmi \
- parsing/printast.cmi bytecomp/printinstr.cmi bytecomp/printlambda.cmi \
- typing/printtyp.cmi bytecomp/simplif.cmi bytecomp/translmod.cmi \
- typing/typedtree.cmi typing/typemod.cmi utils/warnings.cmi \
- driver/compile.cmi
+ utils/config.cmi bytecomp/emitcode.cmi typing/env.cmi utils/misc.cmi \
+ parsing/parse.cmi driver/pparse.cmi parsing/printast.cmi \
+ bytecomp/printinstr.cmi bytecomp/printlambda.cmi typing/printtyp.cmi \
+ bytecomp/simplif.cmi bytecomp/translmod.cmi typing/typedtree.cmi \
+ typing/typemod.cmi utils/warnings.cmi driver/compile.cmi
driver/compile.cmx: bytecomp/bytegen.cmx utils/ccomp.cmx utils/clflags.cmx \
- utils/config.cmx bytecomp/emitcode.cmx typing/env.cmx \
- parsing/location.cmx utils/misc.cmx parsing/parse.cmx \
- parsing/printast.cmx bytecomp/printinstr.cmx bytecomp/printlambda.cmx \
- typing/printtyp.cmx bytecomp/simplif.cmx bytecomp/translmod.cmx \
- typing/typedtree.cmx typing/typemod.cmx utils/warnings.cmx \
- driver/compile.cmi
+ utils/config.cmx bytecomp/emitcode.cmx typing/env.cmx utils/misc.cmx \
+ parsing/parse.cmx driver/pparse.cmx parsing/printast.cmx \
+ bytecomp/printinstr.cmx bytecomp/printlambda.cmx typing/printtyp.cmx \
+ bytecomp/simplif.cmx bytecomp/translmod.cmx typing/typedtree.cmx \
+ typing/typemod.cmx utils/warnings.cmx driver/compile.cmi
driver/errors.cmo: bytecomp/bytelibrarian.cmi bytecomp/bytelink.cmi \
typing/ctype.cmi typing/env.cmi typing/includemod.cmi parsing/lexer.cmi \
- parsing/location.cmi bytecomp/symtable.cmi parsing/syntaxerr.cmi \
- bytecomp/translclass.cmi bytecomp/translcore.cmi typing/typeclass.cmi \
- typing/typecore.cmi typing/typedecl.cmi typing/typemod.cmi \
- typing/typetexp.cmi utils/warnings.cmi driver/errors.cmi
+ parsing/location.cmi driver/pparse.cmi bytecomp/symtable.cmi \
+ parsing/syntaxerr.cmi bytecomp/translclass.cmi bytecomp/translcore.cmi \
+ typing/typeclass.cmi typing/typecore.cmi typing/typedecl.cmi \
+ typing/typemod.cmi typing/typetexp.cmi utils/warnings.cmi \
+ driver/errors.cmi
driver/errors.cmx: bytecomp/bytelibrarian.cmx bytecomp/bytelink.cmx \
typing/ctype.cmx typing/env.cmx typing/includemod.cmx parsing/lexer.cmx \
- parsing/location.cmx bytecomp/symtable.cmx parsing/syntaxerr.cmx \
- bytecomp/translclass.cmx bytecomp/translcore.cmx typing/typeclass.cmx \
- typing/typecore.cmx typing/typedecl.cmx typing/typemod.cmx \
- typing/typetexp.cmx utils/warnings.cmx driver/errors.cmi
+ parsing/location.cmx driver/pparse.cmx bytecomp/symtable.cmx \
+ parsing/syntaxerr.cmx bytecomp/translclass.cmx bytecomp/translcore.cmx \
+ typing/typeclass.cmx typing/typecore.cmx typing/typedecl.cmx \
+ typing/typemod.cmx typing/typetexp.cmx utils/warnings.cmx \
+ driver/errors.cmi
driver/main_args.cmo: driver/main_args.cmi
driver/main_args.cmx: driver/main_args.cmi
driver/main.cmo: bytecomp/bytelibrarian.cmi bytecomp/bytelink.cmi \
utils/clflags.cmo driver/compile.cmi utils/config.cmi driver/errors.cmi \
- driver/main_args.cmi utils/warnings.cmi driver/main.cmi
+ driver/main_args.cmi utils/misc.cmi utils/warnings.cmi driver/main.cmi
driver/main.cmx: bytecomp/bytelibrarian.cmx bytecomp/bytelink.cmx \
utils/clflags.cmx driver/compile.cmx utils/config.cmx driver/errors.cmx \
- driver/main_args.cmx utils/warnings.cmx driver/main.cmi
+ driver/main_args.cmx utils/misc.cmx utils/warnings.cmx driver/main.cmi
driver/optcompile.cmo: asmcomp/asmgen.cmi utils/ccomp.cmi utils/clflags.cmo \
- asmcomp/compilenv.cmi utils/config.cmi typing/env.cmi \
- parsing/location.cmi utils/misc.cmi parsing/parse.cmi \
- parsing/printast.cmi bytecomp/printlambda.cmi typing/printtyp.cmi \
- bytecomp/simplif.cmi bytecomp/translmod.cmi typing/typedtree.cmi \
- typing/typemod.cmi utils/warnings.cmi driver/optcompile.cmi
+ asmcomp/compilenv.cmi utils/config.cmi typing/env.cmi utils/misc.cmi \
+ parsing/parse.cmi driver/pparse.cmi parsing/printast.cmi \
+ bytecomp/printlambda.cmi typing/printtyp.cmi bytecomp/simplif.cmi \
+ bytecomp/translmod.cmi typing/typedtree.cmi typing/typemod.cmi \
+ utils/warnings.cmi driver/optcompile.cmi
driver/optcompile.cmx: asmcomp/asmgen.cmx utils/ccomp.cmx utils/clflags.cmx \
- asmcomp/compilenv.cmx utils/config.cmx typing/env.cmx \
- parsing/location.cmx utils/misc.cmx parsing/parse.cmx \
- parsing/printast.cmx bytecomp/printlambda.cmx typing/printtyp.cmx \
- bytecomp/simplif.cmx bytecomp/translmod.cmx typing/typedtree.cmx \
- typing/typemod.cmx utils/warnings.cmx driver/optcompile.cmi
+ asmcomp/compilenv.cmx utils/config.cmx typing/env.cmx utils/misc.cmx \
+ parsing/parse.cmx driver/pparse.cmx parsing/printast.cmx \
+ bytecomp/printlambda.cmx typing/printtyp.cmx bytecomp/simplif.cmx \
+ bytecomp/translmod.cmx typing/typedtree.cmx typing/typemod.cmx \
+ utils/warnings.cmx driver/optcompile.cmi
driver/opterrors.cmo: asmcomp/asmgen.cmi asmcomp/asmlibrarian.cmi \
asmcomp/asmlink.cmi asmcomp/compilenv.cmi typing/ctype.cmi typing/env.cmi \
typing/includemod.cmi parsing/lexer.cmi parsing/location.cmi \
- parsing/syntaxerr.cmi bytecomp/translclass.cmi bytecomp/translcore.cmi \
- typing/typeclass.cmi typing/typecore.cmi typing/typedecl.cmi \
- typing/typemod.cmi typing/typetexp.cmi utils/warnings.cmi \
- driver/opterrors.cmi
+ driver/pparse.cmi parsing/syntaxerr.cmi bytecomp/translclass.cmi \
+ bytecomp/translcore.cmi typing/typeclass.cmi typing/typecore.cmi \
+ typing/typedecl.cmi typing/typemod.cmi typing/typetexp.cmi \
+ utils/warnings.cmi driver/opterrors.cmi
driver/opterrors.cmx: asmcomp/asmgen.cmx asmcomp/asmlibrarian.cmx \
asmcomp/asmlink.cmx asmcomp/compilenv.cmx typing/ctype.cmx typing/env.cmx \
typing/includemod.cmx parsing/lexer.cmx parsing/location.cmx \
- parsing/syntaxerr.cmx bytecomp/translclass.cmx bytecomp/translcore.cmx \
- typing/typeclass.cmx typing/typecore.cmx typing/typedecl.cmx \
- typing/typemod.cmx typing/typetexp.cmx utils/warnings.cmx \
- driver/opterrors.cmi
+ driver/pparse.cmx parsing/syntaxerr.cmx bytecomp/translclass.cmx \
+ bytecomp/translcore.cmx typing/typeclass.cmx typing/typecore.cmx \
+ typing/typedecl.cmx typing/typemod.cmx typing/typetexp.cmx \
+ utils/warnings.cmx driver/opterrors.cmi
driver/optmain.cmo: asmcomp/asmlibrarian.cmi asmcomp/asmlink.cmi \
- utils/clflags.cmo utils/config.cmi driver/optcompile.cmi \
+ utils/clflags.cmo utils/config.cmi utils/misc.cmi driver/optcompile.cmi \
driver/opterrors.cmi asmcomp/printmach.cmi utils/warnings.cmi \
driver/optmain.cmi
driver/optmain.cmx: asmcomp/asmlibrarian.cmx asmcomp/asmlink.cmx \
- utils/clflags.cmx utils/config.cmx driver/optcompile.cmx \
+ utils/clflags.cmx utils/config.cmx utils/misc.cmx driver/optcompile.cmx \
driver/opterrors.cmx asmcomp/printmach.cmx utils/warnings.cmx \
driver/optmain.cmi
+driver/pparse.cmo: utils/ccomp.cmi utils/clflags.cmo parsing/location.cmi \
+ utils/misc.cmi driver/pparse.cmi
+driver/pparse.cmx: utils/ccomp.cmx utils/clflags.cmx parsing/location.cmx \
+ utils/misc.cmx driver/pparse.cmi
toplevel/genprintval.cmi: typing/env.cmi typing/outcometree.cmi \
typing/path.cmi typing/types.cmi
toplevel/topdirs.cmi: parsing/longident.cmi
@@ -690,10 +695,12 @@ toplevel/toploop.cmx: bytecomp/bytegen.cmx utils/clflags.cmx \
typing/printtyp.cmx bytecomp/simplif.cmx bytecomp/symtable.cmx \
bytecomp/translmod.cmx typing/typedtree.cmx typing/typemod.cmx \
typing/types.cmx utils/warnings.cmx toplevel/toploop.cmi
-toplevel/topmain.cmo: utils/clflags.cmo utils/config.cmi utils/misc.cmi \
- toplevel/topdirs.cmi toplevel/toploop.cmi utils/warnings.cmi
-toplevel/topmain.cmx: utils/clflags.cmx utils/config.cmx utils/misc.cmx \
- toplevel/topdirs.cmx toplevel/toploop.cmx utils/warnings.cmx
+toplevel/topmain.cmo: utils/clflags.cmo utils/config.cmi driver/errors.cmi \
+ utils/misc.cmi toplevel/topdirs.cmi toplevel/toploop.cmi \
+ utils/warnings.cmi
+toplevel/topmain.cmx: utils/clflags.cmx utils/config.cmx driver/errors.cmx \
+ utils/misc.cmx toplevel/topdirs.cmx toplevel/toploop.cmx \
+ utils/warnings.cmx
toplevel/trace.cmo: typing/ctype.cmi parsing/longident.cmi bytecomp/meta.cmi \
utils/misc.cmi typing/path.cmi typing/predef.cmi typing/printtyp.cmi \
toplevel/toploop.cmi typing/types.cmi toplevel/trace.cmi
diff --git a/Makefile b/Makefile
index 0fcdff3e6..ad9ba5aad 100644
--- a/Makefile
+++ b/Makefile
@@ -78,12 +78,13 @@ ASMCOMP=asmcomp/arch.cmo asmcomp/cmm.cmo asmcomp/printcmm.cmo \
asmcomp/emitaux.cmo asmcomp/emit.cmo asmcomp/asmgen.cmo \
asmcomp/asmlink.cmo asmcomp/asmlibrarian.cmo
-DRIVER=driver/errors.cmo driver/compile.cmo driver/main_args.cmo \
- driver/main.cmo
+DRIVER=driver/pparse.cmo driver/errors.cmo driver/compile.cmo \
+ driver/main_args.cmo driver/main.cmo
-OPTDRIVER=driver/opterrors.cmo driver/optcompile.cmo driver/optmain.cmo
+OPTDRIVER= driver/pparse.cmo driver/opterrors.cmo driver/optcompile.cmo \
+ driver/optmain.cmo
-TOPLEVEL=driver/errors.cmo driver/compile.cmo \
+TOPLEVEL=driver/pparse.cmo driver/errors.cmo driver/compile.cmo \
toplevel/genprintval.cmo toplevel/toploop.cmo \
toplevel/trace.cmo toplevel/topdirs.cmo
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 =
diff --git a/driver/errors.ml b/driver/errors.ml
index 3d0b19774..73e7caf9b 100644
--- a/driver/errors.ml
+++ b/driver/errors.ml
@@ -29,6 +29,8 @@ let report_error ppf exn =
Lexer.report_error ppf err
| Syntaxerr.Error err ->
Syntaxerr.report_error ppf err
+ | Pparse.Error ->
+ fprintf ppf "Preprocessor error"
| Env.Error err ->
Env.report_error ppf err
| Ctype.Tags(l, l') -> fprintf ppf
diff --git a/driver/optcompile.ml b/driver/optcompile.ml
index 5c1d3da17..b3302a182 100644
--- a/driver/optcompile.ml
+++ b/driver/optcompile.ml
@@ -45,77 +45,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
-
(* Compile a .mli file *)
let interface ppf sourcefile =
let prefixname = Misc.chop_extension_if_any sourcefile in
let modulename = String.capitalize(Filename.basename prefixname) in
- let inputfile = preprocess sourcefile in
- let ast = parse_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
+ let inputfile = Pparse.preprocess sourcefile in
+ try
+ 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");
+ Pparse.remove_preprocessed inputfile
+ with e ->
+ Pparse.remove_preprocessed_if_ast inputfile;
+ raise e
(* Compile a .ml file *)
@@ -129,20 +77,24 @@ let (+++) (x, y) f = (x, f y)
let implementation ppf sourcefile =
let prefixname = Misc.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 env = initial_env() in
Compilenv.reset modulename;
- parse_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_store_implementation modulename
- +++ print_if ppf Clflags.dump_rawlambda Printlambda.lambda
- +++ Simplif.simplify_lambda
- +++ print_if ppf Clflags.dump_lambda Printlambda.lambda
- ++ Asmgen.compile_implementation prefixname ppf;
- Compilenv.save_unit_info (prefixname ^ ".cmx");
- Warnings.check_fatal ();
- remove_preprocessed inputfile
+ try
+ 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_store_implementation modulename
+ +++ print_if ppf Clflags.dump_rawlambda Printlambda.lambda
+ +++ Simplif.simplify_lambda
+ +++ print_if ppf Clflags.dump_lambda Printlambda.lambda
+ ++ Asmgen.compile_implementation prefixname ppf;
+ Compilenv.save_unit_info (prefixname ^ ".cmx");
+ Warnings.check_fatal ();
+ Pparse.remove_preprocessed inputfile
+ with x ->
+ Pparse.remove_preprocessed_if_ast inputfile;
+ raise x
let c_file name =
if Ccomp.compile_file name <> 0 then exit 2
diff --git a/driver/opterrors.ml b/driver/opterrors.ml
index 847d6dc95..c452dd9f7 100644
--- a/driver/opterrors.ml
+++ b/driver/opterrors.ml
@@ -29,6 +29,8 @@ let report_error ppf exn =
Lexer.report_error ppf err
| Syntaxerr.Error err ->
Syntaxerr.report_error ppf err
+ | Pparse.Error ->
+ fprintf ppf "Preprocessor error"
| Env.Error err ->
Env.report_error ppf err
| Ctype.Tags(l, l') -> fprintf ppf
diff --git a/driver/pparse.ml b/driver/pparse.ml
new file mode 100644
index 000000000..bcec36e7e
--- /dev/null
+++ b/driver/pparse.ml
@@ -0,0 +1,79 @@
+(***********************************************************************)
+(* *)
+(* Objective Caml *)
+(* *)
+(* Daniel de Rauglaudre, projet Cristal, INRIA Rocquencourt *)
+(* *)
+(* Copyright 2002 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$ *)
+
+open Format
+
+exception Error
+
+(* 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
+ Misc.remove_file tmpfile;
+ raise Error;
+ end;
+ tmpfile
+
+let remove_preprocessed inputfile =
+ match !Clflags.preprocessor with
+ None -> ()
+ | Some _ -> Misc.remove_file inputfile
+
+let remove_preprocessed_if_ast inputfile =
+ match !Clflags.preprocessor with
+ None -> ()
+ | Some _ ->
+ if inputfile <> !Location.input_name then Misc.remove_file inputfile
+
+(* Parse a file or get a dumped syntax tree in it *)
+
+exception Outdated_version
+
+let 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 ->
+ Misc.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
diff --git a/driver/pparse.mli b/driver/pparse.mli
new file mode 100644
index 000000000..0ed039136
--- /dev/null
+++ b/driver/pparse.mli
@@ -0,0 +1,22 @@
+(***********************************************************************)
+(* *)
+(* Objective Caml *)
+(* *)
+(* Daniel de Rauglaudre, projet Cristal, INRIA Rocquencourt *)
+(* *)
+(* Copyright 2002 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$ *)
+
+open Format
+
+exception Error
+
+val preprocess : string -> string
+val remove_preprocessed : string -> unit
+val remove_preprocessed_if_ast : string -> unit
+val file : formatter -> string -> (Lexing.lexbuf -> 'a) -> string -> 'a