Nettoyage gestion option -o

git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@4920 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
master
Xavier Leroy 2002-06-11 14:15:12 +00:00
parent 8ab1afe7b1
commit ed4fe78854
9 changed files with 61 additions and 28 deletions

View File

@ -209,7 +209,7 @@ let make_startup_file ppf filename units_list =
Emit.end_assembly();
close_out oc
let call_linker file_list startup_file =
let call_linker file_list startup_file output_name =
let libname =
if !Clflags.gprofile
then "libasmrunp" ^ ext_lib
@ -220,14 +220,15 @@ let call_linker file_list startup_file =
else find_in_path !load_path libname
with Not_found ->
raise(Error(File_not_found libname)) in
let c_lib = if !Clflags.nopervasives then "" else Config.native_c_libraries in
let c_lib =
if !Clflags.nopervasives then "" else Config.native_c_libraries in
let cmd =
match Config.system with
"win32" ->
if not !Clflags.output_c_object then
Printf.sprintf "%s /Fe%s %s %s %s %s %s %s %s"
!Clflags.c_linker
(Filename.quote !Clflags.exec_name)
(Filename.quote output_name)
(Clflags.std_include_flag "-I")
(String.concat " " (List.rev !Clflags.ccopts))
(Filename.quote startup_file)
@ -239,7 +240,7 @@ let call_linker file_list startup_file =
else
Printf.sprintf "%s /out:%s %s %s"
Config.native_partial_linker
(Filename.quote !Clflags.object_name)
(Filename.quote output_name)
(Filename.quote startup_file)
(Ccomp.quote_files (List.rev file_list))
| _ ->
@ -247,7 +248,7 @@ let call_linker file_list startup_file =
Printf.sprintf "%s %s -o %s %s %s %s %s %s %s %s %s"
!Clflags.c_linker
(if !Clflags.gprofile then "-pg" else "")
(Filename.quote !Clflags.exec_name)
(Filename.quote output_name)
(Clflags.std_include_flag "-I")
(String.concat " " (List.rev !Clflags.ccopts))
(Filename.quote startup_file)
@ -261,7 +262,7 @@ let call_linker file_list startup_file =
else
Printf.sprintf "%s -o %s %s %s"
Config.native_partial_linker
(Filename.quote !Clflags.object_name)
(Filename.quote output_name)
(Filename.quote startup_file)
(Ccomp.quote_files (List.rev file_list))
in if Ccomp.command cmd <> 0 then raise(Error Linking_error)
@ -281,7 +282,7 @@ let object_file_name name =
(* Main entry point *)
let link ppf objfiles =
let link ppf objfiles output_name =
let stdlib =
if !Clflags.gprofile then "stdlib.p.cmxa" else "stdlib.cmxa" in
let stdexit =
@ -307,7 +308,7 @@ let link ppf objfiles =
if Proc.assemble_file startup startup_obj <> 0 then
raise(Error(Assembler_error startup));
try
call_linker (List.map object_file_name objfiles) startup_obj;
call_linker (List.map object_file_name objfiles) startup_obj output_name;
if not !Clflags.keep_startup_file then remove_file startup;
remove_file startup_obj
with x ->

View File

@ -16,7 +16,7 @@
open Format
val link: formatter -> string list -> unit
val link: formatter -> string list -> string -> unit
val check_consistency: string -> Compilenv.unit_infos -> Digest.t -> unit
val extract_crc_interfaces: unit -> (string * Digest.t) list

View File

@ -510,7 +510,7 @@ let fix_exec_name name =
(* Main entry point (build a custom runtime if needed) *)
let link objfiles =
let link objfiles output_name =
let objfiles =
if !Clflags.nopervasives then objfiles
else if !Clflags.output_c_object then "stdlib.cma" :: objfiles
@ -520,7 +520,7 @@ let link objfiles =
Clflags.ccopts := !lib_ccopts @ !Clflags.ccopts; (* put user's opts first *)
Clflags.dllibs := !lib_dllibs @ !Clflags.dllibs; (* put user's DLLs first *)
if not !Clflags.custom_runtime then
link_bytecode tolink !Clflags.exec_name true
link_bytecode tolink output_name true
else if not !Clflags.output_c_object then begin
let bytecode_name = Filename.temp_file "camlcode" "" in
let prim_name = Filename.temp_file "camlprim" ".c" in
@ -529,7 +529,7 @@ let link objfiles =
let poc = open_out prim_name in
Symtable.output_primitive_table poc;
close_out poc;
let exec_name = fix_exec_name !Clflags.exec_name in
let exec_name = fix_exec_name output_name in
if build_custom_runtime prim_name exec_name <> 0
then raise(Error Custom_runtime);
if !Clflags.make_runtime
@ -541,7 +541,7 @@ let link objfiles =
raise x
end else begin
let c_file =
Filename.chop_suffix !Clflags.object_name Config.ext_obj ^ ".c" in
Filename.chop_suffix output_name Config.ext_obj ^ ".c" in
if Sys.file_exists c_file then raise(Error(File_exists c_file));
try
link_bytecode_as_c tolink c_file;
@ -550,7 +550,7 @@ let link objfiles =
remove_file c_file
with x ->
remove_file c_file;
remove_file !Clflags.object_name;
remove_file output_name;
raise x
end

View File

@ -14,7 +14,7 @@
(* Link .cmo files and produce a bytecode executable. *)
val link: string list -> unit
val link: string list -> string -> unit
val check_consistency: string -> Emitcode.compilation_unit -> unit

View File

@ -91,7 +91,7 @@ module Options = Main_args.Make_options (struct
let _nolabels = set classic
let _noautolink = set no_auto_link
let _nostdlib = set no_std_include
let _o s = exec_name := s; archive_name := s; object_name := s
let _o s = output_name := Some s
let _output_obj () = output_c_object := true; custom_runtime := true
let _pack = set make_package
let _pp s = preprocessor := Some s
@ -114,20 +114,33 @@ module Options = Main_args.Make_options (struct
let anonymous = anonymous
end)
let extract_output = function
| Some s -> s
| None ->
prerr_endline
"Please specify the name of the output file, using option -o";
exit 2
let default_output = function
| Some s -> s
| None -> Config.default_executable_name
let main () =
try
Arg.parse Options.list anonymous usage;
if !make_archive then begin
Compile.init_path();
Bytelibrarian.create_archive (List.rev !objfiles) !archive_name
Bytelibrarian.create_archive (List.rev !objfiles)
(extract_output !output_name)
end
else if !make_package then begin
Compile.init_path();
Bytepackager.package_files (List.rev !objfiles) !object_name
Bytepackager.package_files (List.rev !objfiles)
(extract_output !output_name)
end
else if not !compile_only && !objfiles <> [] then begin
Compile.init_path();
Bytelink.link (List.rev !objfiles)
Bytelink.link (List.rev !objfiles) (default_output !output_name)
end;
exit 0
with x ->

View File

@ -54,6 +54,17 @@ let print_version_number () =
let print_standard_library () =
print_string Config.standard_library; print_newline(); exit 0
let extract_output = function
| Some s -> s
| None ->
prerr_endline
"Please specify the name of the output file, using option -o";
exit 2
let default_output = function
| Some s -> s
| None -> Config.default_executable_name
let usage = "Usage: ocamlopt <options> <files>\nOptions are:"
let main () =
@ -96,9 +107,7 @@ let main () =
"-nolabels", Arg.Set classic, " Ignore non-optional labels in types";
"-nostdlib", Arg.Set no_std_include,
" do not add standard directory to the list of include directories";
"-o", Arg.String(fun s -> exec_name := s;
archive_name := s;
object_name := s),
"-o", Arg.String(fun s -> output_name := Some s),
"<file> Set output file name to <file>";
"-output-obj", Arg.Unit(fun () -> output_c_object := true),
" Output a C object file instead of an executable";
@ -164,15 +173,17 @@ let main () =
] (process_file ppf) usage;
if !make_archive then begin
Optcompile.init_path();
Asmlibrarian.create_archive (List.rev !objfiles) !archive_name
Asmlibrarian.create_archive (List.rev !objfiles)
(extract_output !output_name)
end
else if !make_package then begin
Optcompile.init_path();
Asmpackager.package_files ppf (List.rev !objfiles) !object_name
Asmpackager.package_files ppf (List.rev !objfiles)
(extract_output !output_name)
end
else if not !compile_only && !objfiles <> [] then begin
Optcompile.init_path();
Asmlink.link ppf (List.rev !objfiles)
Asmlink.link ppf (List.rev !objfiles) (default_output !output_name)
end;
exit 0
with x ->

View File

@ -19,9 +19,7 @@ and ccobjs = ref ([] : string list) (* .o, .a, .so and -cclib -lxxx *)
and dllibs = ref ([] : string list) (* .so and -dllib -lxxx *)
let compile_only = ref false (* -c *)
and exec_name = ref "a.out" (* -o *)
and archive_name = ref "library.cma" (* -o *)
and object_name = ref ("camlprog" ^ Config.ext_obj) (* -o *)
and output_name = ref (None : string option) (* -o *)
and include_dirs = ref ([] : string list)(* -I *)
and no_std_include = ref false (* -nostdlib *)
and print_types = ref false (* -i *)

View File

@ -98,3 +98,7 @@ val ext_lib: string
(* Extension for library files, e.g. [.a] under Unix. *)
val ext_dll: string
(* Extension for dynamically-loaded libraries, e.g. [.so] under Unix.*)
val default_executable_name: string
(* Name of executable produced by linking if none is given with -o,
e.g. [a.out] under Unix. *)

View File

@ -62,3 +62,9 @@ let ext_obj = "%%EXT_OBJ%%"
let ext_asm = "%%EXT_ASM%%"
let ext_lib = "%%EXT_LIB%%"
let ext_dll = "%%EXT_DLL%%"
let default_executable_name =
match Sys.os_type with
"Unix" -> "a.out"
| "Win32" | "Cygwin" -> "camlprog.exe"
| _ -> "camlprog"