Use Filename.quote_command (#9476)

master
Nicolás Ojeda Bär 2020-04-20 14:38:10 +02:00 committed by GitHub
parent c5a1f91900
commit 15b08d2fdf
No known key found for this signature in database
GPG Key ID: 4AEE18F83AFDEB23
4 changed files with 15 additions and 14 deletions

View File

@ -166,13 +166,12 @@ let check_file ?(tool = default_comparison_tool) files =
let diff files = let diff files =
let temporary_file = Filename.temp_file "ocamltest" "diff" in let temporary_file = Filename.temp_file "ocamltest" "diff" in
let diff_commandline = String.concat " " let diff_commandline =
[ Filename.quote_command "diff" ~stdout:temporary_file
"diff -u"; [ "-u";
files.reference_filename; files.reference_filename;
files.output_filename; files.output_filename ]
"> " ^ temporary_file in
] in
let result = let result =
if (Sys.command diff_commandline) = 2 then Stdlib.Error "diff" if (Sys.command diff_commandline) = 2 then Stdlib.Error "diff"
else Ok (Sys.string_of_file temporary_file) else Ok (Sys.string_of_file temporary_file)

View File

@ -155,7 +155,10 @@ let test_file test_filename =
let test_build_directory_prefix = let test_build_directory_prefix =
get_test_build_directory_prefix test_directory in get_test_build_directory_prefix test_directory in
let clean_test_build_directory () = let clean_test_build_directory () =
ignore (Sys.command ("rm -rf " ^ test_build_directory_prefix)) in ignore
(Sys.command
(Filename.quote_command "rm" ["-rf"; test_build_directory_prefix]))
in
clean_test_build_directory (); clean_test_build_directory ();
Sys.make_directory test_build_directory_prefix; Sys.make_directory test_build_directory_prefix;
let summary = Sys.with_chdir test_build_directory_prefix let summary = Sys.with_chdir test_build_directory_prefix

View File

@ -102,8 +102,7 @@ module Sys = struct
let mkdir dir = let mkdir dir =
if not (Sys.file_exists dir) then if not (Sys.file_exists dir) then
let quoted_dir = "\"" ^ dir ^ "\"" in run_system_command (Filename.quote_command "mkdir" [dir])
run_system_command ("mkdir " ^ quoted_dir)
let rec make_directory dir = let rec make_directory dir =
if Sys.file_exists dir then () if Sys.file_exists dir then ()

View File

@ -250,10 +250,10 @@ let find_dyn_offset filename =
Fun.protect Fun.protect
~finally:(fun () -> remove_file tempfile) ~finally:(fun () -> remove_file tempfile)
(fun () -> (fun () ->
let rc = Sys.command (sprintf "%s %s > %s" let rc =
(Filename.quote helper) Sys.command
(Filename.quote filename) (Filename.quote_command helper ~stdout:tempfile [filename])
tempfile) in in
if rc <> 0 then failwith "cannot read"; if rc <> 0 then failwith "cannot read";
let tc = Scanf.Scanning.from_file tempfile in let tc = Scanf.Scanning.from_file tempfile in
Fun.protect Fun.protect