summaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
authorXavier Leroy <xavier.leroy@inria.fr>2004-06-13 12:46:41 +0000
committerXavier Leroy <xavier.leroy@inria.fr>2004-06-13 12:46:41 +0000
commit3dce37c1963ca174eab9f03b9636170e1ecded6e (patch)
tree532b7b7b8439a837207ad6da7b993c6e03a99f86
parent2955927a88bbd1ba882f01e35750cf068c73b16c (diff)
Generalisation de l'option -o
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@6395 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
-rw-r--r--Changes4
-rw-r--r--driver/compile.ml20
-rw-r--r--driver/compile.mli4
-rw-r--r--driver/main.ml24
-rw-r--r--driver/optcompile.ml22
-rw-r--r--driver/optcompile.mli4
-rw-r--r--driver/optmain.ml26
7 files changed, 63 insertions, 41 deletions
diff --git a/Changes b/Changes
index e4aeca2f9..0d008b350 100644
--- a/Changes
+++ b/Changes
@@ -22,6 +22,8 @@ Both compilers:
* A compile-time error is signaled if an integer literal exceeds the
range of representable integers.
- Fixed code generation error for "module rec" definitions.
+- The combination of options -c -o sets the name of the generated
+ .cm[iox] files.
Bytecode compiler:
- Option -output-obj is now compatible with Dynlink and
@@ -46,7 +48,7 @@ Standard library:
* String-to-integer conversions now fail if the result overflows
the range of integers representable in the result type.
* All array and string access functions now raise
- (Invalid_argument "index out of bounds") when a bounds check fails.
+ Invalid_argument("index out of bounds") when a bounds check fails.
In earlier releases, different exceptions were raised
in bytecode and native-code.
- Module Buffer: new functions Buffer.sub, Buffer.nth
diff --git a/driver/compile.ml b/driver/compile.ml
index 52cf87d4a..5f065ff81 100644
--- a/driver/compile.ml
+++ b/driver/compile.ml
@@ -50,10 +50,10 @@ let initial_env () =
(* Compile a .mli file *)
-let interface ppf sourcefile =
+let interface ppf sourcefile outputprefix =
init_path();
- let prefixname = chop_extension_if_any sourcefile in
- let modulename = String.capitalize(Filename.basename prefixname) in
+ let modulename =
+ String.capitalize(Filename.basename(chop_extension_if_any sourcefile)) in
let inputfile = Pparse.preprocess sourcefile in
try
let ast =
@@ -65,7 +65,7 @@ let interface ppf sourcefile =
(Typemod.simplify_signature sg);
Warnings.check_fatal ();
if not !Clflags.print_types then
- Env.save_signature sg modulename (prefixname ^ ".cmi");
+ Env.save_signature sg modulename (outputprefix ^ ".cmi");
Pparse.remove_preprocessed inputfile
with e ->
Pparse.remove_preprocessed_if_ast inputfile;
@@ -79,27 +79,27 @@ let print_if ppf flag printer arg =
let (++) x f = f x
-let implementation ppf sourcefile =
+let implementation ppf sourcefile outputprefix =
init_path();
- let prefixname = chop_extension_if_any sourcefile in
- let modulename = String.capitalize(Filename.basename prefixname) in
+ let modulename =
+ String.capitalize(Filename.basename(chop_extension_if_any sourcefile)) in
let inputfile = Pparse.preprocess sourcefile in
let env = initial_env() in
if !Clflags.print_types then begin
try ignore(
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)
+ ++ Typemod.type_implementation sourcefile outputprefix modulename env)
with x ->
Pparse.remove_preprocessed_if_ast inputfile;
raise x
end else begin
- let objfile = prefixname ^ ".cmo" in
+ let objfile = outputprefix ^ ".cmo" in
let oc = open_out_bin objfile in
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
+ ++ Typemod.type_implementation sourcefile outputprefix modulename env
++ Translmod.transl_implementation modulename
++ print_if ppf Clflags.dump_rawlambda Printlambda.lambda
++ Simplif.simplify_lambda
diff --git a/driver/compile.mli b/driver/compile.mli
index 2271d103e..507d61bbd 100644
--- a/driver/compile.mli
+++ b/driver/compile.mli
@@ -16,8 +16,8 @@
open Format
-val interface: formatter -> string -> unit
-val implementation: formatter -> string -> unit
+val interface: formatter -> string -> string -> unit
+val implementation: formatter -> string -> string -> unit
val c_file: string -> unit
val initial_env: unit -> Env.t
diff --git a/driver/main.ml b/driver/main.ml
index 16c29249c..12c5305bc 100644
--- a/driver/main.ml
+++ b/driver/main.ml
@@ -15,22 +15,32 @@
open Config
open Clflags
+let output_prefix name =
+ let oname =
+ match !output_name with
+ | None -> name
+ | Some n -> if !compile_only then (output_name := None; n) else name in
+ Misc.chop_extension_if_any oname
+
let process_interface_file ppf name =
- Compile.interface ppf name
+ Compile.interface ppf name (output_prefix name)
let process_implementation_file ppf name =
- Compile.implementation ppf name;
- objfiles := (Misc.chop_extension_if_any name ^ ".cmo") :: !objfiles
+ let opref = output_prefix name in
+ Compile.implementation ppf name opref;
+ objfiles := (opref ^ ".cmo") :: !objfiles
let process_file ppf name =
if Filename.check_suffix name ".ml"
|| Filename.check_suffix name ".mlt" then begin
- Compile.implementation ppf name;
- objfiles := (Misc.chop_extension_if_any name ^ ".cmo") :: !objfiles
+ let opref = output_prefix name in
+ Compile.implementation ppf name opref;
+ objfiles := (opref ^ ".cmo") :: !objfiles
end
else if Filename.check_suffix name !Config.interface_suffix then begin
- Compile.interface ppf name;
- if !make_package then objfiles := name :: !objfiles
+ let opref = output_prefix name in
+ Compile.interface ppf name opref;
+ if !make_package then objfiles := (opref ^ ".cmi") :: !objfiles
end
else if Filename.check_suffix name ".cmo"
|| Filename.check_suffix name ".cma" then
diff --git a/driver/optcompile.ml b/driver/optcompile.ml
index 0e52920f3..9d00bf855 100644
--- a/driver/optcompile.ml
+++ b/driver/optcompile.ml
@@ -47,10 +47,10 @@ let initial_env () =
(* Compile a .mli file *)
-let interface ppf sourcefile =
+let interface ppf sourcefile outputprefix =
init_path();
- let prefixname = Misc.chop_extension_if_any sourcefile in
- let modulename = String.capitalize(Filename.basename prefixname) in
+ let modulename =
+ String.capitalize(Filename.basename(chop_extension_if_any sourcefile)) in
let inputfile = Pparse.preprocess sourcefile in
try
let ast =
@@ -62,7 +62,7 @@ let interface ppf sourcefile =
(Typemod.simplify_signature sg);
Warnings.check_fatal ();
if not !Clflags.print_types then
- Env.save_signature sg modulename (prefixname ^ ".cmi");
+ Env.save_signature sg modulename (outputprefix ^ ".cmi");
Pparse.remove_preprocessed inputfile
with e ->
Pparse.remove_preprocessed_if_ast inputfile;
@@ -77,10 +77,10 @@ let print_if ppf flag printer arg =
let (++) x f = f x
let (+++) (x, y) f = (x, f y)
-let implementation ppf sourcefile =
+let implementation ppf sourcefile outputprefix =
init_path();
- let prefixname = Misc.chop_extension_if_any sourcefile in
- let modulename = String.capitalize(Filename.basename prefixname) in
+ let modulename =
+ String.capitalize(Filename.basename(chop_extension_if_any sourcefile)) in
let inputfile = Pparse.preprocess sourcefile in
let env = initial_env() in
Compilenv.reset modulename;
@@ -88,17 +88,17 @@ let implementation ppf sourcefile =
if !Clflags.print_types then ignore(
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)
+ ++ Typemod.type_implementation sourcefile outputprefix modulename env)
else begin
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
+ ++ Typemod.type_implementation sourcefile outputprefix 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");
+ ++ Asmgen.compile_implementation outputprefix ppf;
+ Compilenv.save_unit_info (outputprefix ^ ".cmx");
end;
Warnings.check_fatal ();
Pparse.remove_preprocessed inputfile
diff --git a/driver/optcompile.mli b/driver/optcompile.mli
index 2271d103e..507d61bbd 100644
--- a/driver/optcompile.mli
+++ b/driver/optcompile.mli
@@ -16,8 +16,8 @@
open Format
-val interface: formatter -> string -> unit
-val implementation: formatter -> string -> unit
+val interface: formatter -> string -> string -> unit
+val implementation: formatter -> string -> string -> unit
val c_file: string -> unit
val initial_env: unit -> Env.t
diff --git a/driver/optmain.ml b/driver/optmain.ml
index 2209562b1..ab4a81ecc 100644
--- a/driver/optmain.ml
+++ b/driver/optmain.ml
@@ -15,22 +15,32 @@
open Config
open Clflags
+let output_prefix name =
+ let oname =
+ match !output_name with
+ | None -> name
+ | Some n -> if !compile_only then (output_name := None; n) else name in
+ Misc.chop_extension_if_any oname
+
let process_interface_file ppf name =
- Optcompile.interface ppf name
+ Optcompile.interface ppf name (output_prefix name)
let process_implementation_file ppf name =
- Optcompile.implementation ppf name;
- objfiles := (Misc.chop_extension_if_any name ^ ".cmx") :: !objfiles
+ let opref = output_prefix name in
+ Optcompile.implementation ppf name opref;
+ objfiles := (opref ^ ".cmx") :: !objfiles
let process_file ppf name =
if Filename.check_suffix name ".ml"
|| Filename.check_suffix name ".mlt" then begin
- Optcompile.implementation ppf name;
- objfiles := (Misc.chop_extension_if_any name ^ ".cmx") :: !objfiles
+ let opref = output_prefix name in
+ Optcompile.implementation ppf name opref;
+ objfiles := (opref ^ ".cmx") :: !objfiles
end
else if Filename.check_suffix name !Config.interface_suffix then begin
- Optcompile.interface ppf name;
- if !make_package then objfiles := name :: !objfiles
+ let opref = output_prefix name in
+ Optcompile.interface ppf name opref;
+ if !make_package then objfiles := (opref ^ ".cmi") :: !objfiles
end
else if Filename.check_suffix name ".cmx"
|| Filename.check_suffix name ".cmxa" then
@@ -43,7 +53,7 @@ let process_file ppf name =
else if Filename.check_suffix name ".c" then begin
Optcompile.c_file name;
ccobjs := (Filename.chop_suffix (Filename.basename name) ".c" ^ ext_obj)
- :: !ccobjs
+ :: !ccobjs
end
else
raise(Arg.Bad("don't know what to do with " ^ name))