Skip to content

Commit

Permalink
Extend -o to work when compiling C files
Browse files Browse the repository at this point in the history
When using ocamlc/ocamlopt to compile C files, it was not possible
so far to control where the resulting object file should be written.

In other words, before this commit a command like

ocamlopt -c foo.c -o /tmp/foo.o

produced the following error message:

Options -c and -o are incompatible when compiling C files

This commit removes this restriction and lets the compiler accept
that the command-line options -c and -o are given simultaneously
also when compiling one C file, so that the previous command now works.

The -o command-line option remains forbidden when compiling several C files.
  • Loading branch information
shindere committed Oct 6, 2020
1 parent 9522819 commit f0b63a3
Show file tree
Hide file tree
Showing 11 changed files with 91 additions and 9 deletions.
19 changes: 12 additions & 7 deletions driver/compenv.ml
Expand Up @@ -608,8 +608,13 @@ let process_action
| ProcessCFile name ->
readenv ppf (Before_compile name);
Location.input_name := name;
if Ccomp.compile_file name <> 0 then raise (Exit_with_status 2);
ccobjs := c_object_of_filename name :: !ccobjs
let obj_name = match !output_name with
| None -> c_object_of_filename name
| Some n -> n
in
if Ccomp.compile_file ~output:obj_name name <> 0
then raise (Exit_with_status 2);
ccobjs := obj_name :: !ccobjs
| ProcessObjects names ->
ccobjs := names @ !ccobjs
| ProcessDLLs names ->
Expand Down Expand Up @@ -656,12 +661,12 @@ let process_deferred_actions env =
begin
match final_output_name with
| None -> ()
| Some output_name ->
| Some _output_name ->
if !compile_only then begin
if List.filter (function
| ProcessCFile name -> c_object_of_filename name <> output_name
| _ -> false) !deferred_actions <> [] then
fatal "Options -c and -o are incompatible when compiling C files";
if List.length (List.filter (function
| ProcessCFile _ -> true
| _ -> false) !deferred_actions) > 1 then
fatal "Option -o makes no sense when compiling several C files";

if List.length (List.filter (function
| ProcessImplementation _
Expand Down
26 changes: 25 additions & 1 deletion ocamltest/builtin_actions.ml
Expand Up @@ -221,6 +221,29 @@ let check_program_output = make
Builtin_variables.output
Builtin_variables.reference)

let file_exists_action _log env =
match Environments.lookup Builtin_variables.file env with
| None ->
let reason = reason_with_fallback env "the file variable is undefined" in
let result = Result.fail_with_reason reason in
(result, env)
| Some filename ->
if Sys.file_exists filename
then begin
let default_reason = Printf.sprintf "File %s exists" filename in
let reason = reason_with_fallback env default_reason in
let result = Result.pass_with_reason reason in
(result, env)
end else begin
let default_reason =
Printf.sprintf "File %s does not exist" filename
in
let reason = reason_with_fallback env default_reason in
let result = Result.fail_with_reason reason in
(result, env)
end
let file_exists = make "file-exists" file_exists_action

let initialize_test_exit_status_variables _log env =
Environments.add_bindings
[
Expand Down Expand Up @@ -263,5 +286,6 @@ let _ =
arch_i386;
arch_power;
function_sections;
naked_pointers
naked_pointers;
file_exists;
]
2 changes: 2 additions & 0 deletions ocamltest/builtin_actions.mli
Expand Up @@ -47,3 +47,5 @@ val run : Actions.t
val script : Actions.t

val check_program_output : Actions.t

val file_exists : Actions.t
4 changes: 4 additions & 0 deletions ocamltest/builtin_variables.ml
Expand Up @@ -34,6 +34,9 @@ let commandline = Variables.make ("commandline",
let exit_status = Variables.make ("exit_status",
"Expected program exit status")

let file = Variables.make ("file",
"File whose existence should be tested")

let files = Variables.make ("files",
"Files used by the tests")

Expand Down Expand Up @@ -109,6 +112,7 @@ let _ = List.iter Variables.register_variable
cwd;
commandline;
exit_status;
file;
files;
make;
ocamltest_response;
Expand Down
2 changes: 2 additions & 0 deletions ocamltest/builtin_variables.mli
Expand Up @@ -25,6 +25,8 @@ val commandline : Variables.t

val exit_status : Variables.t

val file : Variables.t

val files : Variables.t

val make : Variables.t
Expand Down
8 changes: 8 additions & 0 deletions testsuite/tests/tool-command-line/hello.c
@@ -0,0 +1,8 @@
#include <stdio.h>
#include <stdlib.h>

int main()
{
printf("Hello, world!\n");
return 0;
}
18 changes: 18 additions & 0 deletions testsuite/tests/tool-command-line/test-o-one-c-file.ml
@@ -0,0 +1,18 @@
(* TEST
files = "hello.c"
* setup-ocamlopt.opt-build-env
** script
script = "mkdir outputdir"
*** ocamlopt.opt
all_modules = "hello.c"
compile_only = "true"
flags = "-o outputdir/hello.${objext}"
**** file-exists
file = "outputdir/hello.${objext}"
*)

(*
This test makes sure it is possible to specify the name of the output
object file when compiling a C file with the OCaml compiler.
The test does not need to contain any OCaml code.
*)
@@ -0,0 +1 @@
Option -o makes no sense when compiling several C files
15 changes: 15 additions & 0 deletions testsuite/tests/tool-command-line/test-o-several-c-files.ml
@@ -0,0 +1,15 @@
(* TEST
* setup-ocamlopt.opt-build-env
** ocamlopt.opt
all_modules = "foo.c bar.c"
compile_only = "true"
flags = "-o outputdir/baz.${objext}"
ocamlopt_opt_exit_status = "2"
*** check-ocamlopt.opt-output
*)

(*
This test makes sure that the -o option is rejected when trying to
compile several C files during the same invocatin of the OCaml compiler.
The test does not need to contain any OCaml code.
*)
Expand Up @@ -28,4 +28,7 @@ compiler_output = "compiler-output"
*)

(* this file is just a test driver, the test does not contain real OCamlcode *)
(*
This file is just a test driver, the test does not contain any
real OCaml code
*)

0 comments on commit f0b63a3

Please sign in to comment.