Filter out the display of .c files by MSVC
Microsoft's C Compiler displays several lines on every invocation - most of this is removed by specifying the /nologo command line option, but the compiler still displays the name of every C file it compiles. The Microsoft Macro Assembler (MASM) does the same thing, but ocamlopt by default is able to pipe the output of that command directly to NUL, as the assembler code should never produce errors. The same cannot be done for invocations of the C compiler, as obviously syntax errors must be displayed. This relative small cosmetic change pipes the output of cl to a temporary file and filters out the first line if it is exactly as expected. The most elegant solution would require pipes and process handling to be merged from the Unix module into the compilers.master
parent
7945404a4e
commit
124672aa13
9
Changes
9
Changes
|
@ -10,7 +10,7 @@ Language features:
|
|||
Namely, the redundancy checker now checks whether the uncovered pattern
|
||||
of the pattern is actually inhabited, exploding at most one wild card.
|
||||
This is also done for exhaustiveness when there is only one case.
|
||||
Additionnally, one can now write unreachable cases, of the form,
|
||||
Additionally, one can now write unreachable cases, of the form,
|
||||
"pat -> .", which are treated by the redundancy check. (Jacques Garrigue)
|
||||
- PR#6374: allow "_ t" as a short-hand for "(_, _, ..) t" for n-ary type
|
||||
constructors (Alain Frisch)
|
||||
|
@ -101,8 +101,8 @@ Compilers:
|
|||
- PR#7067: Performance regression in the native compiler for long
|
||||
nested structures (Alain Frisch, report by Daniel Bünzli, review
|
||||
by Jacques Garrigue)
|
||||
- PR#7097: Strange syntax error message around illegal packaged module signature
|
||||
constraints (Alain Frisch, report by Jun Furuse)
|
||||
- PR#7097: Strange syntax error message around illegal packaged module
|
||||
signature constraints (Alain Frisch, report by Jun Furuse)
|
||||
- GPR#17: some cmm optimizations of integer operations with constants
|
||||
(Stephen Dolan, review by Pierre Chambart)
|
||||
- GPR#109: new unboxing strategy for float and int references (Vladimir Brankov,
|
||||
|
@ -138,6 +138,9 @@ Compilers:
|
|||
(Leo White)
|
||||
- PR#6920: fix debug informations around uses of %apply or %revapply
|
||||
(Jérémie Dimino)
|
||||
- GPR#407: don't display the name of compiled .c files when calling the
|
||||
Microsoft C Compiler (same as the assembler).
|
||||
(David Allsopp)
|
||||
|
||||
Runtime system:
|
||||
- PR#3612: allow allocating custom block with finalizers in the minor heap
|
||||
|
|
|
@ -48,25 +48,59 @@ let quote_optfile = function
|
|||
| None -> ""
|
||||
| Some f -> Filename.quote f
|
||||
|
||||
let display_msvc_output file name =
|
||||
let c = open_in file in
|
||||
try
|
||||
let first = input_line c in
|
||||
if first <> name then
|
||||
print_string first;
|
||||
while true do
|
||||
print_string (input_line c)
|
||||
done
|
||||
with _ ->
|
||||
close_in c;
|
||||
Sys.remove file
|
||||
|
||||
let compile_file ~output_name name =
|
||||
command
|
||||
(Printf.sprintf
|
||||
"%s%s -c %s %s %s %s %s"
|
||||
(match !Clflags.c_compiler with
|
||||
| Some cc -> cc
|
||||
| None ->
|
||||
if !Clflags.native_code
|
||||
then Config.native_c_compiler
|
||||
else Config.bytecomp_c_compiler)
|
||||
(match output_name, Config.ccomp_type with
|
||||
| Some n, "msvc" -> " /Fo" ^ Filename.quote n
|
||||
| Some n, _ -> " -o " ^ Filename.quote n
|
||||
| None, _ -> "")
|
||||
(if !Clflags.debug && Config.ccomp_type <> "msvc" then "-g" else "")
|
||||
(String.concat " " (List.rev !Clflags.all_ccopts))
|
||||
(quote_prefixed "-I" (List.rev !Clflags.include_dirs))
|
||||
(Clflags.std_include_flag "-I")
|
||||
(Filename.quote name))
|
||||
let (pipe, file) =
|
||||
if Config.ccomp_type = "msvc" && not !Clflags.verbose then
|
||||
try
|
||||
let (t, c) = Filename.open_temp_file "msvc" "stdout" in
|
||||
close_out c;
|
||||
(Printf.sprintf " > %s" (Filename.quote t), t)
|
||||
with _ ->
|
||||
("", "")
|
||||
else
|
||||
("", "") in
|
||||
let exit =
|
||||
command
|
||||
(Printf.sprintf
|
||||
"%s%s -c %s %s %s %s %s%s"
|
||||
(match !Clflags.c_compiler with
|
||||
| Some cc -> cc
|
||||
| None ->
|
||||
if !Clflags.native_code
|
||||
then Config.native_c_compiler
|
||||
else Config.bytecomp_c_compiler)
|
||||
(match output_name, Config.ccomp_type with
|
||||
| Some n, "msvc" -> " /Fo" ^ Filename.quote n
|
||||
| Some n, _ -> " -o " ^ Filename.quote n
|
||||
| None, _ -> "")
|
||||
(if !Clflags.debug && Config.ccomp_type <> "msvc" then "-g" else "")
|
||||
(String.concat " " (List.rev !Clflags.all_ccopts))
|
||||
(quote_prefixed "-I" (List.rev !Clflags.include_dirs))
|
||||
(Clflags.std_include_flag "-I")
|
||||
(Filename.quote name)
|
||||
(* cl tediously includes the name of the C file as the first thing it
|
||||
outputs (in fairness, the tedious thing is that there's no switch to
|
||||
disable this behaviour). In the absence of the Unix module, use
|
||||
a temporary file to filter the output (cannot pipe the output to a
|
||||
filter because this removes the exit status of cl, which is wanted.
|
||||
*)
|
||||
pipe) in
|
||||
if pipe <> ""
|
||||
then display_msvc_output file name;
|
||||
exit
|
||||
|
||||
let create_archive archive file_list =
|
||||
Misc.remove_file archive;
|
||||
|
|
Loading…
Reference in New Issue