Use Sys.{win32,...} instead Sys.os_type

master
Nicolás Ojeda Bär 2020-05-24 13:03:18 +02:00 committed by Gabriel Scherer
parent 3eebf1ab8c
commit b77b13d812
7 changed files with 10 additions and 15 deletions

View File

@ -68,7 +68,7 @@ let setup_symlinks test_source_directory build_directory files =
let src = Filename.concat test_source_directory filename in let src = Filename.concat test_source_directory filename in
let dst = Filename.concat build_directory filename in let dst = Filename.concat build_directory filename in
Sys.copy_file src dst in Sys.copy_file src dst in
let f = if Sys.os_type="Win32" then copy else symlink in let f = if Sys.win32 then copy else symlink in
Sys.make_directory build_directory; Sys.make_directory build_directory;
List.iter f files List.iter f files
@ -121,7 +121,7 @@ let run_cmd
in in
let lst = List.concat (List.map String.words cmd) in let lst = List.concat (List.map String.words cmd) in
let quoted_lst = let quoted_lst =
if Sys.os_type="Win32" if Sys.win32
then List.map Filename.maybe_quote lst then List.map Filename.maybe_quote lst
else lst in else lst in
let cmd' = String.concat " " quoted_lst in let cmd' = String.concat " " quoted_lst in

View File

@ -138,11 +138,8 @@ let compare_files ?(tool = default_comparison_tool) files =
files.reference_filename; files.reference_filename;
files.output_filename files.output_filename
] in ] in
let dev_null = match Sys.os_type with
| "Win32" -> "NUL"
| _ -> "/dev/null" in
let settings = Run_command.settings_of_commandline let settings = Run_command.settings_of_commandline
~stdout_fname:dev_null ~stderr_fname:dev_null commandline in ~stdout_fname:Filename.null ~stderr_fname:Filename.null commandline in
let status = Run_command.run settings in let status = Run_command.run settings in
result_of_exitcode commandline status result_of_exitcode commandline status
| Internal ignore -> | Internal ignore ->

View File

@ -852,16 +852,14 @@ let really_compare_programs backend comparison_tool log env =
"flambda temporarily disables comparison of native programs" in "flambda temporarily disables comparison of native programs" in
(Result.pass_with_reason reason, env) (Result.pass_with_reason reason, env)
end else end else
if backend = Ocaml_backends.Native && if backend = Ocaml_backends.Native && (Sys.win32 || Sys.cygwin)
(Sys.os_type="Win32" || Sys.os_type="Cygwin")
then begin then begin
let reason = let reason =
"comparison of native programs temporarily disabled under Windows" in "comparison of native programs temporarily disabled under Windows" in
(Result.pass_with_reason reason, env) (Result.pass_with_reason reason, env)
end else begin end else begin
let comparison_tool = let comparison_tool =
if backend=Ocaml_backends.Native && if backend=Ocaml_backends.Native && (Sys.win32 || Sys.cygwin)
(Sys.os_type="Win32" || Sys.os_type="Cygwin")
then then
let bytes_to_ignore = 512 (* comparison_start_address program *) in let bytes_to_ignore = 512 (* comparison_start_address program *) in
Filecompare.(make_cmp_tool ~ignore:{bytes=bytes_to_ignore; lines=0}) Filecompare.(make_cmp_tool ~ignore:{bytes=bytes_to_ignore; lines=0})

View File

@ -24,7 +24,7 @@ let stdlib =
Filename.make_path [srcdir; "stdlib"] Filename.make_path [srcdir; "stdlib"]
let libunix = let libunix =
let subdir = if Sys.os_type="Win32" then "win32unix" else "unix" in let subdir = if Sys.win32 then "win32unix" else "unix" in
Filename.make_path [srcdir; "otherlibs"; subdir] Filename.make_path [srcdir; "otherlibs"; subdir]
let toplevel = let toplevel =

View File

@ -79,7 +79,7 @@ let testing = make_library_modifier
let tool_ocaml_lib = make_module_modifier let tool_ocaml_lib = make_module_modifier
"lib" (compiler_subdir ["testsuite"; "lib"]) "lib" (compiler_subdir ["testsuite"; "lib"])
let unixlibdir = if Sys.os_type="Win32" then "win32unix" else "unix" let unixlibdir = if Sys.win32 then "win32unix" else "unix"
let unix = make_library_modifier let unix = make_library_modifier
"unix" (compiler_subdir ["otherlibs"; unixlibdir]) "unix" (compiler_subdir ["otherlibs"; unixlibdir])

View File

@ -28,7 +28,7 @@ end
module Filename = struct module Filename = struct
include Filename include Filename
let path_sep = if Sys.os_type="Win32" then ";" else ":" let path_sep = if Sys.win32 then ";" else ":"
(* This function comes from otherlibs/win32unix/unix.ml *) (* This function comes from otherlibs/win32unix/unix.ml *)
let maybe_quote f = let maybe_quote f =
if String.contains f ' ' || if String.contains f ' ' ||
@ -43,7 +43,7 @@ module Filename = struct
let make_path components = List.fold_left Filename.concat "" components let make_path components = List.fold_left Filename.concat "" components
let mkexe = let mkexe =
if Sys.os_type="Win32" if Sys.win32
then fun name -> make_filename name "exe" then fun name -> make_filename name "exe"
else fun name -> name else fun name -> name
end end

View File

@ -32,7 +32,7 @@ type settings = {
let settings_of_commandline ?(stdout_fname="") ?(stderr_fname="") commandline = let settings_of_commandline ?(stdout_fname="") ?(stderr_fname="") commandline =
let words = String.words commandline in let words = String.words commandline in
let quoted_words = let quoted_words =
if Sys.os_type="Win32" if Sys.win32
then List.map Filename.maybe_quote words then List.map Filename.maybe_quote words
else words in else words in
{ {