[OCamlc] fixes output_complete_object

ocamlc complained that the temporary files it just created existed.
   since ed60dece81575305b5f1f7394cdda652b65b037a and
   19d3bccf48fee6e5e91e65e9f8a5d07c49d2afd4
master
François Bobot 2017-09-13 15:22:57 +02:00
parent ab7af2aa92
commit 8afe629b5f
6 changed files with 68 additions and 10 deletions

View File

@ -617,22 +617,27 @@ let link ppf objfiles output_name =
raise x
end else begin
let basename = Filename.chop_extension output_name in
let temps = ref [] in
let c_file =
if !Clflags.output_complete_object
if !Clflags.output_complete_object && not (Filename.check_suffix output_name ".c")
then Filename.temp_file "camlobj" ".c"
else basename ^ ".c"
and obj_file =
else begin
let f = basename ^ ".c" in
if Sys.file_exists f then raise(Error(File_exists f));
f
end
in
let obj_file =
if !Clflags.output_complete_object
then Filename.temp_file "camlobj" Config.ext_obj
then (Filename.chop_extension c_file) ^ Config.ext_obj
else basename ^ Config.ext_obj
in
if Sys.file_exists c_file then raise(Error(File_exists c_file));
let temps = ref [] in
try
link_bytecode_as_c ppf tolink c_file;
if not (Filename.check_suffix output_name ".c") then begin
temps := c_file :: !temps;
if Ccomp.compile_file c_file <> 0 then
(* -DCAML_INTERNALS because the .c use startup.h *)
if Ccomp.compile_file ~output:obj_file ~opt:"-DCAML_INTERNALS" c_file <> 0 then
raise(Error Custom_runtime);
if not (Filename.check_suffix output_name Config.ext_obj) ||
!Clflags.output_complete_object then begin

View File

@ -0,0 +1,40 @@
#**************************************************************************
#* *
#* OCaml *
#* *
#* Xavier Clerc, SED, INRIA Rocquencourt *
#* *
#* Copyright 2010 Institut National de Recherche en Informatique et *
#* en Automatique. *
#* *
#* All rights reserved. This file is distributed under the terms of *
#* the GNU Lesser General Public License version 2.1, with the *
#* special exception on linking described in the file LICENSE. *
#* *
#**************************************************************************
BASEDIR=../..
SHOULD_FAIL=
compile:
@for file in *.ml; do \
printf " ... testing native '$$file'"; \
( $(OCAMLOPT) -w a -output-complete-obj -o $${file}.exe.o $${file} 2>/dev/null && \
$(CC) $(CFLAGS) $(CPPFLAGS) -I$(CTOPDIR)/byterun -o $${file}_stub $${file}.exe.o -lm -ldl $${file}_stub.c 2>/dev/null && \
./$${file}_stub 1>/dev/null 2>/dev/null && \
echo " => passed" ) || echo " => failed"; \
done
@for file in *.ml; do \
printf " ... testing byte '$$file'"; \
( $(OCAMLC) -ccopt "-I$(CTOPDIR)/byterun" -w a -output-complete-obj -o $${file}.bc.o $${file} 2>/dev/null && \
$(CC) $(CFLAGS) $(CPPFLAGS) -I$(CTOPDIR)/byterun -o $${file}_bc_stub $${file}.bc.o -lm -ldl -lcurses $${file}_stub.c 2>/dev/null && \
./$${file}_bc_stub 1>/dev/null 2>/dev/null && \
echo " => passed" ) || echo " => failed"; \
done
promote:
clean: defaultclean
@rm -f ./a.out
include $(BASEDIR)/makefiles/Makefile.common

View File

@ -0,0 +1 @@
let () = Printf.printf "Test!!\n%!"

View File

@ -0,0 +1,10 @@
#include <caml/mlvalues.h>
#include <caml/alloc.h>
#include <caml/callback.h>
#include <caml/memory.h>
int main(int argc, char ** argv){
caml_startup(argv);
return 0;
}

View File

@ -64,7 +64,7 @@ let display_msvc_output file name =
close_in c;
Sys.remove file
let compile_file name =
let compile_file ?output ?(opt="") name =
let (pipe, file) =
if Config.ccomp_type = "msvc" && not !Clflags.verbose then
try
@ -78,7 +78,7 @@ let compile_file name =
let exit =
command
(Printf.sprintf
"%s -c %s %s %s %s %s%s"
"%s %s %s -c %s %s %s %s %s%s"
(match !Clflags.c_compiler with
| Some cc -> cc
| None ->
@ -87,6 +87,8 @@ let compile_file name =
then (Config.ocamlopt_cflags, Config.ocamlopt_cppflags)
else (Config.ocamlc_cflags, Config.ocamlc_cppflags) in
(String.concat " " [Config.c_compiler; cflags; cppflags]))
(match output with | None -> "" | Some o -> "-o " ^ o)
opt
(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))

View File

@ -17,7 +17,7 @@
val command: string -> int
val run_command: string -> unit
val compile_file: string -> int
val compile_file: ?output:string -> ?opt:string -> string -> int
val create_archive: string -> string list -> int
val expand_libname: string -> string
val quote_files: string list -> string