Faire Filename.quote sur les noms de fichiers passes au compilo C, etc (PR#896)

git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@4516 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
master
Xavier Leroy 2002-03-12 16:17:53 +00:00
parent 4efb58b231
commit bae1b84692
14 changed files with 56 additions and 44 deletions

View File

@ -211,5 +211,5 @@ let assemble_file infile outfile =
then if !Clflags.gprofile then "as -O2 -nocpp -pg -o "
else "as -O2 -nocpp -o "
else "as -o " in
Ccomp.command (as_cmd ^ outfile ^ " " ^ infile)
Ccomp.command (as_cmd ^ Filename.quote outfile ^ " " ^ Filename.quote infile)

View File

@ -190,5 +190,5 @@ let contains_calls = ref false
(* Calling the assembler *)
let assemble_file infile outfile =
Sys.command ("as -o " ^ outfile ^ " " ^ infile)
Sys.command ("as -o " ^ Filename.quote outfile ^ " " ^ Filename.quote infile)

View File

@ -227,43 +227,43 @@ let call_linker file_list startup_file =
if not !Clflags.output_c_object then
Printf.sprintf "%s /Fe%s %s %s %s %s %s %s %s"
!Clflags.c_linker
!Clflags.exec_name
(Filename.quote !Clflags.exec_name)
(Clflags.std_include_flag "-I")
(String.concat " " (List.rev !Clflags.ccopts))
startup_file
(String.concat " " (List.rev file_list))
(String.concat " "
(List.rev_map Ccomp.expand_libname !Clflags.ccobjs))
runtime_lib
(Filename.quote startup_file)
(Ccomp.quote_files (List.rev file_list))
(Ccomp.quote_files
(List.rev_map Ccomp.expand_libname !Clflags.ccobjs))
(Filename.quote runtime_lib)
c_lib
else
Printf.sprintf "%s /out:%s %s %s"
Config.native_partial_linker
!Clflags.object_name
startup_file
(String.concat " " (List.rev file_list))
(Filename.quote !Clflags.object_name)
(Filename.quote startup_file)
(Ccomp.quote_files (List.rev file_list))
| _ ->
if not !Clflags.output_c_object then
Printf.sprintf "%s %s -o %s %s %s %s %s %s %s %s %s"
!Clflags.c_linker
(if !Clflags.gprofile then "-pg" else "")
!Clflags.exec_name
(Filename.quote !Clflags.exec_name)
(Clflags.std_include_flag "-I")
(String.concat " " (List.rev !Clflags.ccopts))
startup_file
(String.concat " " (List.rev file_list))
(String.concat " "
(Filename.quote startup_file)
(Ccomp.quote_files (List.rev file_list))
(Ccomp.quote_files
(List.map (fun dir -> if dir = "" then "" else "-L" ^ dir)
!load_path))
(String.concat " " (List.rev !Clflags.ccobjs))
runtime_lib
(Ccomp.quote_files (List.rev !Clflags.ccobjs))
(Filename.quote runtime_lib)
c_lib
else
Printf.sprintf "%s -o %s %s %s"
Config.native_partial_linker
!Clflags.object_name
startup_file
(String.concat " " (List.rev file_list))
(Filename.quote !Clflags.object_name)
(Filename.quote startup_file)
(Ccomp.quote_files (List.rev file_list))
in if Ccomp.command cmd <> 0 then raise(Error Linking_error)
let object_file_name name =

View File

@ -84,7 +84,9 @@ let rename_in_object_file units pref objfile =
let symbolfile = Filename.temp_file "camlsymbols" "" in
try
let nm_cmdline =
sprintf "%s %s > %s" Config.binutils_nm objfile symbolfile in
sprintf "%s %s > %s"
Config.binutils_nm
(Filename.quote objfile) (Filename.quote symbolfile) in
if Ccomp.command nm_cmdline <> 0 then raise(Error Linking_error);
let symbols_to_rename =
extract_symbols units symbolfile in
@ -95,7 +97,7 @@ let rename_in_object_file units pref objfile =
(List.map
(fun s -> sprintf "--redefine-sym '%s=%s__%s'" s pref s)
symbols_to_rename))
objfile in
(Filename.quote objfile) in
(* FIXME: what if the command line is too long? *)
if Ccomp.command objcopy_cmdline <> 0 then raise(Error Linking_error);
remove_file symbolfile;
@ -230,8 +232,10 @@ let make_package_object ppf unit_names objfiles targetobj targetname =
remove_file asmtemp;
let ld_cmd =
sprintf "%s -o %s %s %s"
Config.native_partial_linker targetobj objtemp
(String.concat " " objfiles) in
Config.native_partial_linker
(Filename.quote targetobj)
(Filename.quote objtemp)
(Ccomp.quote_files objfiles) in
let retcode = Ccomp.command ld_cmd in
remove_file objtemp;
if retcode <> 0 then raise(Error Linking_error)

View File

@ -217,5 +217,5 @@ let contains_calls = ref false
(* Calling the assembler *)
let assemble_file infile outfile =
Ccomp.command ("gas -o " ^ outfile ^ " " ^ infile)
Ccomp.command ("gas -o " ^ Filename.quote outfile ^ " " ^ Filename.quote infile)

View File

@ -170,5 +170,5 @@ let contains_calls = ref false
(* Calling the assembler *)
let assemble_file infile outfile =
Ccomp.command ("as -o " ^ outfile ^ " " ^ infile)
Ccomp.command ("as -o " ^ Filename.quote outfile ^ " " ^ Filename.quote infile)

View File

@ -170,7 +170,8 @@ let contains_calls = ref false
(* Calling the assembler *)
let assemble_file infile outfile =
Ccomp.command ("ml /nologo /coff /Cp /c /Fo" ^ outfile ^ " " ^ infile ^ ">NUL")
Ccomp.command ("ml /nologo /coff /Cp /c /Fo" ^
Filename.quote outfile ^ " " ^ Filename.quote infile ^ ">NUL")
(* /Cp preserve case of all used identifiers
/c assemble only
/Fo output file name *)

View File

@ -210,4 +210,4 @@ let contains_calls = ref false
(* Calling the assembler *)
let assemble_file infile outfile =
Ccomp.command ("as -xexplicit -o " ^ outfile ^ " " ^ infile)
Ccomp.command ("as -xexplicit -o " ^ Filename.quote outfile ^ " " ^ Filename.quote infile)

View File

@ -205,5 +205,5 @@ let contains_calls = ref false
let asm_command = "as -n32 -O2 -nocpp -g0 -o "
let assemble_file infile outfile =
Ccomp.command (asm_command ^ outfile ^ " " ^ infile)
Ccomp.command (asm_command ^ Filename.quote outfile ^ " " ^ Filename.quote infile)

View File

@ -236,6 +236,8 @@ let contains_calls = ref false
(* Calling the assembler *)
let assemble_file infile outfile =
let infile = Filename.quote infile
and outfile = Filename.quote outfile in
match Config.system with
"aix" ->
let proc = if powerpc then "ppc" else "pwr" in

View File

@ -219,5 +219,5 @@ let contains_calls = ref false
(* Calling the assembler and the archiver *)
let assemble_file infile outfile =
Ccomp.command ("as -o " ^ outfile ^ " " ^ infile)
Ccomp.command ("as -o " ^ Filename.quote outfile ^ " " ^ Filename.quote infile)

View File

@ -431,14 +431,14 @@ let build_custom_runtime prim_name exec_name =
(Printf.sprintf
"%s -o %s %s %s %s %s %s -lcamlrun %s"
!Clflags.c_linker
exec_name
(Filename.quote exec_name)
(Clflags.std_include_flag "-I")
(String.concat " " (List.rev !Clflags.ccopts))
prim_name
(String.concat " "
(Ccomp.quote_files
(List.map (fun dir -> if dir = "" then "" else "-L" ^ dir)
!load_path))
(String.concat " " (List.rev !Clflags.ccobjs))
(Ccomp.quote_files (List.rev !Clflags.ccobjs))
Config.bytecomp_c_libraries)
| "Win32" ->
let retcode =
@ -446,13 +446,13 @@ let build_custom_runtime prim_name exec_name =
(Printf.sprintf
"%s /Fe%s %s %s %s %s %s %s"
!Clflags.c_linker
exec_name
(Filename.quote exec_name)
(Clflags.std_include_flag "-I")
(String.concat " " (List.rev !Clflags.ccopts))
prim_name
(String.concat " "
(List.rev_map Ccomp.expand_libname !Clflags.ccobjs))
(Ccomp.expand_libname "-lcamlrun")
(Ccomp.quote_files
(List.rev_map Ccomp.expand_libname !Clflags.ccobjs))
(Filename.quote (Ccomp.expand_libname "-lcamlrun"))
Config.bytecomp_c_libraries) in
(* C compiler doesn't clean up after itself. Note that the .obj
file is created in the current working directory. *)

View File

@ -24,6 +24,10 @@ let command cmdline =
let run_command cmdline = ignore(command cmdline)
let quote_files lst =
String.concat " "
(List.map (fun f -> if f = "" then f else Filename.quote f) lst)
let compile_file name =
match Sys.os_type with
| "MacOS" ->
@ -44,25 +48,25 @@ let compile_file name =
"%s -c %s %s %s %s"
!Clflags.c_compiler
(String.concat " " (List.rev !Clflags.ccopts))
(String.concat " "
(List.rev_map (fun dir -> "-I" ^ dir) !Clflags.include_dirs))
(quote_files
(List.rev_map (fun dir -> "-I" ^ dir) !Clflags.include_dirs))
(Clflags.std_include_flag "-I")
name)
;;
(Filename.quote name))
let create_archive archive file_list =
Misc.remove_file archive;
let quoted_archive = Filename.quote archive in
match Config.system with
"win32" ->
command(Printf.sprintf "lib /nologo /debugtype:cv /out:%s %s"
archive (String.concat " " file_list))
quoted_archive (quote_files file_list))
| _ ->
let r1 =
command(Printf.sprintf "ar rc %s %s"
archive (String.concat " " file_list)) in
quoted_archive (quote_files file_list)) in
if r1 <> 0 || String.length Config.ranlib = 0
then r1
else command(Config.ranlib ^ " " ^ archive)
else command(Config.ranlib ^ " " ^ quoted_archive)
let expand_libname name =
if String.length name < 2 || String.sub name 0 2 <> "-l"

View File

@ -19,3 +19,4 @@ val run_command: string -> unit
val compile_file: string -> int
val create_archive: string -> string list -> int
val expand_libname: string -> string
val quote_files: string list -> string