summaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
authorXavier Leroy <xavier.leroy@inria.fr>1996-04-29 13:19:07 +0000
committerXavier Leroy <xavier.leroy@inria.fr>1996-04-29 13:19:07 +0000
commit8c3bf593c4790c47cf6dbf51a9e4b79e3e88710d (patch)
tree54bab66da56dc8a877271e3686fee5181ecb1064
parenta7b871dfafdd23b6fb07173bd67a78249d95a694 (diff)
Option preprocessing mise dans Clflags.
optmain: ajout de -linkall. git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@764 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
-rw-r--r--driver/compile.ml18
-rw-r--r--driver/compile.mli2
-rw-r--r--driver/main.ml2
-rw-r--r--driver/optcompile.ml18
-rw-r--r--driver/optcompile.mli2
-rw-r--r--driver/optmain.ml3
6 files changed, 19 insertions, 26 deletions
diff --git a/driver/compile.ml b/driver/compile.ml
index 7c7cf40c5..bf896c3fb 100644
--- a/driver/compile.ml
+++ b/driver/compile.ml
@@ -40,10 +40,8 @@ let initial_env () =
(* Optionally preprocess a source file *)
-let pproc = ref None
-
let preprocess sourcefile tmpfile =
- match !pproc with
+ match !Clflags.preprocessor with
None -> sourcefile
| Some pp ->
let comm = pp ^ " " ^ sourcefile ^ " > " ^ tmpfile in
@@ -54,6 +52,11 @@ let preprocess sourcefile tmpfile =
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 *)
let parse_file inputfile parse_fun ast_magic =
@@ -91,9 +94,7 @@ let interface sourcefile =
let sg = Typemod.transl_signature (initial_env()) ast in
if !Clflags.print_types then (Printtyp.signature sg; print_flush());
Env.save_signature sg modulename (prefixname ^ ".cmi");
- match !pproc with
- None -> ()
- | Some _ -> remove_file inputfile
+ remove_preprocessed inputfile
(* Compile a .ml file *)
@@ -132,10 +133,7 @@ let implementation sourcefile =
(Simplif.simplify_lambda
(print_if Clflags.dump_rawlambda Printlambda.lambda
(Translmod.transl_implementation modulename str coercion))))));
- begin match !pproc with
- None -> ()
- | Some _ -> remove_file inputfile
- end;
+ remove_preprocessed inputfile;
close_out oc
with x ->
close_out oc;
diff --git a/driver/compile.mli b/driver/compile.mli
index 25c32784a..5dc85f270 100644
--- a/driver/compile.mli
+++ b/driver/compile.mli
@@ -19,5 +19,3 @@ val c_file: string -> unit
val initial_env: unit -> Env.t
val init_path: unit -> unit
-
-val pproc : string option ref
diff --git a/driver/main.ml b/driver/main.ml
index 869bea768..83afaa4d6 100644
--- a/driver/main.ml
+++ b/driver/main.ml
@@ -49,7 +49,7 @@ let main () =
"-o", Arg.String(fun s -> exec_name := s; archive_name := s);
"-i", Arg.Set print_types;
"-a", Arg.Set make_archive;
- "-pp", Arg.String(fun s -> Compile.pproc := Some s);
+ "-pp", Arg.String(fun s -> preprocessor := Some s);
"-unsafe", Arg.Set fast;
"-nopervasives", Arg.Set nopervasives;
"-custom", Arg.Set custom_runtime;
diff --git a/driver/optcompile.ml b/driver/optcompile.ml
index 57c96370d..3a40ca31e 100644
--- a/driver/optcompile.ml
+++ b/driver/optcompile.ml
@@ -41,10 +41,8 @@ let initial_env () =
(* Optionally preprocess a source file *)
-let pproc = ref None
-
let preprocess sourcefile tmpfile =
- match !pproc with
+ match !Clflags.preprocessor with
None -> sourcefile
| Some pp ->
let comm = pp ^ " " ^ sourcefile ^ " > " ^ tmpfile in
@@ -55,6 +53,11 @@ let preprocess sourcefile tmpfile =
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 *)
let parse_file inputfile parse_fun ast_magic =
@@ -91,9 +94,7 @@ let interface sourcefile =
let sg = Typemod.transl_signature (initial_env()) ast in
if !Clflags.print_types then (Printtyp.signature sg; print_flush());
Env.save_signature sg modulename (prefixname ^ ".cmi");
- match !pproc with
- None -> ()
- | Some _ -> remove_file inputfile
+ remove_preprocessed inputfile
(* Compile a .ml file *)
@@ -128,10 +129,7 @@ let implementation sourcefile =
(Simplif.simplify_lambda
(print_if Clflags.dump_rawlambda Printlambda.lambda lam)));
Compilenv.save_unit_info (prefixname ^ ".cmx");
- begin match !pproc with
- None -> ()
- | Some _ -> remove_file inputfile
- end
+ remove_preprocessed inputfile
let c_file name =
if Sys.command
diff --git a/driver/optcompile.mli b/driver/optcompile.mli
index 25c32784a..5dc85f270 100644
--- a/driver/optcompile.mli
+++ b/driver/optcompile.mli
@@ -19,5 +19,3 @@ val c_file: string -> unit
val initial_env: unit -> Env.t
val init_path: unit -> unit
-
-val pproc : string option ref
diff --git a/driver/optmain.ml b/driver/optmain.ml
index 0e306ad56..415b7a9e0 100644
--- a/driver/optmain.ml
+++ b/driver/optmain.ml
@@ -50,12 +50,13 @@ let main () =
"-o", Arg.String(fun s -> exec_name := s; archive_name := s);
"-i", Arg.Set print_types;
"-a", Arg.Set make_archive;
- "-pp", Arg.String(fun s -> Optcompile.pproc := Some s);
+ "-pp", Arg.String(fun s -> preprocessor := Some s);
"-unsafe", Arg.Set fast;
"-compact", Arg.Clear optimize_for_speed;
"-nopervasives", Arg.Set nopervasives;
"-ccopt", Arg.String(fun s -> ccopts := s :: !ccopts);
"-cclib", Arg.String(fun s -> ccobjs := s :: !ccobjs);
+ "-linkall", Arg.Set link_everything;
"-drawlambda", Arg.Set dump_rawlambda;
"-dlambda", Arg.Set dump_lambda;
"-dcmm", Arg.Set dump_cmm;