Skip to content

Commit

Permalink
Detect common C compilers and add default CXX flags (#3802)
Browse files Browse the repository at this point in the history
* Use C preprocessor to detect C compiler
* Add CXX flags for most common compilers.
* Add option 'use_standard_c_and_cxx_flags' to dune-project
* Emit a warning when failing to detect the C compiler

Signed-off-by: Ulysse Gérard <[email protected]>
  • Loading branch information
voodoos authored Jan 13, 2021
1 parent 4d53aad commit 1dd3d7c
Show file tree
Hide file tree
Showing 16 changed files with 235 additions and 22 deletions.
13 changes: 13 additions & 0 deletions src/dune_engine/dune_project.ml
Original file line number Diff line number Diff line change
Expand Up @@ -160,6 +160,7 @@ type t =
; implicit_transitive_deps : bool
; wrapped_executables : bool
; dune_version : Dune_lang.Syntax.Version.t
; use_standard_c_and_cxx_flags : bool
; generate_opam_files : bool
; file_key : File_key.t
; dialects : Dialect.DB.t
Expand Down Expand Up @@ -189,6 +190,8 @@ let file_key t = t.file_key

let implicit_transitive_deps t = t.implicit_transitive_deps

let use_standard_c_and_cxx_flags t = t.use_standard_c_and_cxx_flags

let generate_opam_files t = t.generate_opam_files

let dialects t = t.dialects
Expand All @@ -208,6 +211,7 @@ let to_dyn
; implicit_transitive_deps
; wrapped_executables
; dune_version
; use_standard_c_and_cxx_flags
; generate_opam_files
; file_key
; dialects
Expand All @@ -229,6 +233,7 @@ let to_dyn
; ("implicit_transitive_deps", bool implicit_transitive_deps)
; ("wrapped_executables", bool wrapped_executables)
; ("dune_version", Dune_lang.Syntax.Version.to_dyn dune_version)
; ("use_standard_c_and_cxx_flags", bool use_standard_c_and_cxx_flags)
; ("generate_opam_files", bool generate_opam_files)
; ("file_key", string file_key)
; ("dialects", Dialect.DB.to_dyn dialects)
Expand Down Expand Up @@ -604,6 +609,7 @@ let infer ~dir packages =
; extension_args
; parsing_context
; dune_version = lang.version
; use_standard_c_and_cxx_flags = false
; generate_opam_files = false
; file_key
; dialects = Dialect.DB.builtin
Expand Down Expand Up @@ -685,6 +691,9 @@ let parse ~dir ~lang ~opam_packages ~file ~dir_status =
"It is useless since the Merlin configurations are not ambiguous \
anymore."
loc lang.syntax (2, 8) ~what:"This field"
and+ use_standard_c_and_cxx_flags =
field_o_b "use_standard_c_and_cxx_flags"
~check:(Dune_lang.Syntax.since Stanza.syntax (2, 8))
and+ () = Dune_lang.Versioned_file.no_more_lang
and+ generate_opam_files =
field_o_b "generate_opam_files"
Expand Down Expand Up @@ -797,6 +806,9 @@ let parse ~dir ~lang ~opam_packages ~file ~dir_status =
~default:(strict_package_deps_default ~lang)
in
let dune_version = lang.version in
let use_standard_c_and_cxx_flags =
Option.value ~default:false use_standard_c_and_cxx_flags
in
let explicit_js_mode =
Option.value explicit_js_mode ~default:(explicit_js_mode_default ~lang)
in
Expand Down Expand Up @@ -846,6 +858,7 @@ let parse ~dir ~lang ~opam_packages ~file ~dir_status =
; implicit_transitive_deps
; wrapped_executables
; dune_version
; use_standard_c_and_cxx_flags
; generate_opam_files
; dialects
; explicit_js_mode
Expand Down
6 changes: 6 additions & 0 deletions src/dune_engine/dune_project.mli
Original file line number Diff line number Diff line change
Expand Up @@ -63,6 +63,12 @@ val root : t -> Path.Source.t

val stanza_parser : t -> Stanza.t list Dune_lang.Decoder.t

(** The option [use_standard_c_and_cxx_flags] enables the automatic addition of
flags necessary to build c++ files with the active C compiler. It also
disables the automatic addition of C flags from [ocamlc -config] to the
compiler command line when building C stubs. *)
val use_standard_c_and_cxx_flags : t -> bool

val generate_opam_files : t -> bool

val dialects : t -> Dialect.DB.t
Expand Down
45 changes: 45 additions & 0 deletions src/dune_rules/cxx_flags.ml
Original file line number Diff line number Diff line change
@@ -0,0 +1,45 @@
open! Stdune
open Dune_engine

type ccomp_type =
| Gcc
| Msvc
| Clang
| Other of string

let base_cxx_flags = function
| Gcc -> [ "-x"; "c++"; "-lstdc++"; "-shared-libgcc" ]
| Clang -> [ "-x"; "c++" ]
| Msvc -> [ "/TP" ]
| _ -> []

let preprocessed_filename = "ccomp"

let ccomp_type dir =
let open Build.O in
let filepath =
Path.Build.(relative (relative dir ".dune") preprocessed_filename)
in
let+ ccomp = Build.contents (Path.build filepath) in
match String.trim ccomp with
| "clang" -> Clang
| "gcc" -> Gcc
| "msvc" -> Msvc
| s -> Other s

let check_warn = function
| Other s ->
User_warning.emit
[ Pp.textf
"Dune was not able to automatically infer the C compiler in use: \
\"%s\". Please open an issue on github to help us improve this \
feature."
s
]
| _ -> ()

let get_flags dir =
let open Build.O in
let+ ccomp_type = ccomp_type dir in
check_warn ccomp_type;
base_cxx_flags ccomp_type
13 changes: 13 additions & 0 deletions src/dune_rules/cxx_flags.mli
Original file line number Diff line number Diff line change
@@ -0,0 +1,13 @@
(** This module contains a small database of flags that is used when compiling C
and C++ stubs. *)
open! Stdune

open Dune_engine

(** The name of the file created in the .dune folder after calling the C
preprocessor *)
val preprocessed_filename : string

(** [get_flags c_compiler] returns the necessary flags to turn this compiler
into a c++ compiler for some of the most common compilers *)
val get_flags : Path.Build.t -> string list Build.t
44 changes: 44 additions & 0 deletions src/dune_rules/cxx_rules.ml
Original file line number Diff line number Diff line change
@@ -0,0 +1,44 @@
open! Stdune
open! Dune_engine

let header_file_content =
{|
#if defined( __clang__ )
#define CCOMP clang
#elif defined( _MSC_VER )
#define CCOMP msvc
#elif defined( __GNUC__ )
#define CCOMP gcc
#else
#define CCOMP other
#endif

CCOMP
|}

let rules ~sctx ~dir =
let file = Path.Build.relative dir Cxx_flags.preprocessed_filename in
let ocfg = (Super_context.context sctx).ocaml_config in
let prog =
Super_context.resolve_program sctx ~dir ~loc:None
(Ocaml_config.c_compiler ocfg)
in
(* let tmp = Path.External.of_string (Filename.get_temp_dir_name ()) in *)
let header_file = Path.Build.relative dir "header_check.h" in
let write_test_file = Action.write_file header_file header_file_content in
let args =
let open Command.Args in
[ ( match Ocaml_config.ccomp_type ocfg with
| Msvc -> A "/EP"
| Other _ -> As [ "-E"; "-P" ] )
; A Path.(to_absolute_filename (build header_file))
]
in
let action =
let open Build.With_targets.O in
let+ run_preprocessor =
Command.run ~dir:(Path.build dir) ~stdout_to:file prog args
in
Action.progn [ write_test_file; run_preprocessor ]
in
Super_context.add_rule sctx ~dir action
3 changes: 3 additions & 0 deletions src/dune_rules/cxx_rules.mli
Original file line number Diff line number Diff line change
@@ -0,0 +1,3 @@
(** Preprocessing-based C compiler detection *)

val rules : sctx:Super_context.t -> dir:Stdune.Path.Build.t -> unit
4 changes: 1 addition & 3 deletions src/dune_rules/env_node.ml
Original file line number Diff line number Diff line change
Expand Up @@ -123,9 +123,7 @@ let make ~dir ~inherit_from ~scope ~config_stanza ~profile ~expander
Disabled )
in
let foreign_flags =
inherited ~field:foreign_flags
~root:(Foreign_language.Dict.map ~f:Build.return default_context_flags)
(fun flags ->
inherited ~field:foreign_flags ~root:default_context_flags (fun flags ->
let expander = Expander.set_dir (Memo.Lazy.force expander) ~dir in
Foreign_language.Dict.mapi config.foreign_flags ~f:(fun ~language f ->
let standard = Foreign_language.Dict.get flags language in
Expand Down
2 changes: 1 addition & 1 deletion src/dune_rules/env_node.mli
Original file line number Diff line number Diff line change
Expand Up @@ -25,7 +25,7 @@ val make :
-> profile:Profile.t
-> expander:Expander.t Memo.Lazy.t
-> expander_for_artifacts:Expander.t Memo.Lazy.t
-> default_context_flags:string list Foreign_language.Dict.t
-> default_context_flags:string list Build.t Foreign_language.Dict.t
-> default_env:Env.t
-> default_bin_artifacts:Artifacts.Bin.t
-> t
Expand Down
28 changes: 14 additions & 14 deletions src/dune_rules/foreign_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -75,21 +75,21 @@ let include_dir_flags ~expander ~dir (stubs : Foreign.Stubs.t) =

let build_c ~kind ~sctx ~dir ~expander ~include_flags (loc, src, dst) =
let ctx = Super_context.context sctx in
let flags =
let ctx_flags =
match kind with
| Foreign_language.C ->
let cfg = ctx.ocaml_config in
List.concat
[ Ocaml_config.ocamlc_cflags cfg
; Ocaml_config.ocamlc_cppflags cfg
; Fdo.c_flags ctx
]
| Foreign_language.Cxx -> Fdo.cxx_flags ctx
in
let base_flags =
let cfg = ctx.ocaml_config in
match kind with
| Foreign_language.C ->
List.concat
[ Ocaml_config.ocamlc_cflags cfg
; Ocaml_config.ocamlc_cppflags cfg
; Fdo.c_flags ctx
]
| Foreign_language.Cxx -> Fdo.cxx_flags ctx
in
let with_user_and_std_flags =
let flags = Foreign.Source.flags src in
Super_context.foreign_flags sctx ~dir ~expander ~flags ~language:kind
|> Build.map ~f:(List.append ctx_flags)
|> Build.map ~f:(List.append base_flags)
in
let output_param =
match ctx.lib_config.ccomp_type with
Expand All @@ -108,7 +108,7 @@ let build_c ~kind ~sctx ~dir ~expander ~include_flags (loc, src, dst) =
produced in the current directory *)
Command.run ~dir:(Path.build dir)
(Super_context.resolve_program ~loc:None ~dir sctx c_compiler)
( [ Command.Args.dyn flags
( [ Command.Args.dyn with_user_and_std_flags
; S [ A "-I"; Path ctx.stdlib_dir ]
; include_flags
]
Expand Down
2 changes: 2 additions & 0 deletions src/dune_rules/gen_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -301,6 +301,8 @@ let gen_rules ~sctx ~dir components : Build_system.extra_sub_directories_to_keep
attached to [write_dot_dune_dir] in context.ml *)
Super_context.add_rule sctx ~dir
(Build.write_file (Path.Build.relative dir "configurator") "");
(* Add rules for C compiler detection *)
Cxx_rules.rules ~sctx ~dir;
These String.Set.empty
| ".js" :: rest -> (
Jsoo_rules.setup_separate_compilation_rules sctx rest;
Expand Down
20 changes: 16 additions & 4 deletions src/dune_rules/super_context.ml
Original file line number Diff line number Diff line change
Expand Up @@ -2,15 +2,23 @@ open! Dune_engine
open! Stdune
open Import

let default_context_flags (ctx : Context.t) =
let default_context_flags (ctx : Context.t) ~project =
(* TODO DUNE3 To ensure full backward compatibility, ocaml_cflags are still
present in the :standard set of flags. However these should not as they are
already prepended when calling the compiler, causing flag duplication. *)
let c = Ocaml_config.ocamlc_cflags ctx.ocaml_config in
let cxx =
List.filter c ~f:(fun s -> not (String.is_prefix s ~prefix:"-std="))
in
Foreign_language.Dict.make ~c ~cxx
let cxx =
if Dune_project.use_standard_c_and_cxx_flags project then
let open Build.O in
let+ db_flags = Cxx_flags.get_flags ctx.build_dir in
db_flags @ cxx
else
Build.return cxx
in
Foreign_language.Dict.make ~c:(Build.return c) ~cxx

module Env_tree : sig
type t
Expand Down Expand Up @@ -118,7 +126,9 @@ end = struct
| Some parent -> Memo.lazy_ (fun () -> get_node t ~dir:parent)
in
let config_stanza = get_env_stanza t ~dir in
let default_context_flags = default_context_flags t.context in
let default_context_flags =
default_context_flags t.context ~project:(Scope.project scope)
in
let expander_for_artifacts =
Memo.lazy_ (fun () ->
expander_for_artifacts ~scope ~root_expander:t.root_expander
Expand Down Expand Up @@ -619,7 +629,9 @@ let create ~(context : Context.t) ?host ~projects ~packages ~stanzas () =
let make ~inherit_from ~config_stanza =
let dir = context.build_dir in
let scope = Scope.DB.find_by_dir scopes dir in
let default_context_flags = default_context_flags context in
let default_context_flags =
default_context_flags context ~project:(Scope.project scope)
in
let expander_for_artifacts =
Memo.lazy_ (fun () ->
Code_error.raise
Expand Down
2 changes: 2 additions & 0 deletions test/blackbox-tests/test-cases/cxx-flags.t/baz.cpp
Original file line number Diff line number Diff line change
@@ -0,0 +1,2 @@
#include <caml/mlvalues.h>
extern "C" value baz(value unit) { return Val_int(2046); }
10 changes: 10 additions & 0 deletions test/blackbox-tests/test-cases/cxx-flags.t/dune
Original file line number Diff line number Diff line change
@@ -0,0 +1,10 @@
(library
(name quad)
(modules quad)
(foreign_stubs (language cxx) (names baz)))

(executable
(name main)
(libraries quad)
(modules main))

1 change: 1 addition & 0 deletions test/blackbox-tests/test-cases/cxx-flags.t/main.ml
Original file line number Diff line number Diff line change
@@ -0,0 +1 @@
let () = Printf.printf "%d" (Quad.quad ())
2 changes: 2 additions & 0 deletions test/blackbox-tests/test-cases/cxx-flags.t/quad.ml
Original file line number Diff line number Diff line change
@@ -0,0 +1,2 @@
external baz : unit -> int = "baz"
let quad x = baz x
62 changes: 62 additions & 0 deletions test/blackbox-tests/test-cases/cxx-flags.t/run.t
Original file line number Diff line number Diff line change
@@ -0,0 +1,62 @@
Default: use_standard_c_and_cxx_flags = false
=============================================

$ cat >dune-project <<EOF
> (lang dune 2.8)
> EOF

> The flags that Dune should use
$ GCCF="-x c++ -lstdc++ -shared-libgcc"
$ ClangF="-x c++"
$ MsvcF="/TP"

> Check that compiler detection is done
$ dune build .dune/ccomp

$ cat _build/default/.dune/ccomp |
> grep -ce "clang\|gcc\|msvc"
1

> No specific flags added
$ dune rules baz.o | tr -s '\n' ' ' |
> grep -ce "$GCCF\|$ClangF|$MsvcF"
0
[1]


With use_standard_c_and_cxx_flags = false
=========================================

$ cat >dune-project <<EOF
> (lang dune 2.8)
> (use_standard_c_and_cxx_flags false)
> EOF

> No specific flags added
$ dune rules baz.o | tr -s '\n' ' ' |
> grep -ce "$GCCF\|$ClangF|$MsvcF"
0
[1]

With use_standard_c_and_cxx_flags = true
========================================

$ cat >dune-project <<EOF
> (lang dune 2.8)
> (use_standard_c_and_cxx_flags true)
> EOF

> Check that compiler detection is done
$ dune build .dune/ccomp

$ cat _build/default/.dune/ccomp |
> grep -ce "clang\|gcc\|msvc"
1

> Specific flags added
$ dune rules baz.o | tr -s '\n' ' ' |
> grep -ce "$GCCF\|$ClangF\|$MsvcF"
1

$ dune exec ./main.exe
2046

0 comments on commit 1dd3d7c

Please sign in to comment.