Skip to content

Commit

Permalink
Rename option to 'use_standard_c_and_cxx_flags'
Browse files Browse the repository at this point in the history
Signed-off-by: Ulysse Gérard <[email protected]>
  • Loading branch information
voodoos committed Nov 19, 2020
1 parent 4f50074 commit 30ffcb0
Show file tree
Hide file tree
Showing 4 changed files with 22 additions and 18 deletions.
20 changes: 11 additions & 9 deletions src/dune_engine/dune_project.ml
Original file line number Diff line number Diff line change
Expand Up @@ -161,7 +161,7 @@ type t =
; wrapped_executables : bool
; dune_version : Dune_lang.Syntax.Version.t
; allow_approx_merlin : bool
; add_cxx_flags : bool
; use_standard_c_and_cxx_flags : bool
; generate_opam_files : bool
; file_key : File_key.t
; dialects : Dialect.DB.t
Expand Down Expand Up @@ -193,7 +193,7 @@ let implicit_transitive_deps t = t.implicit_transitive_deps

let allow_approx_merlin t = t.allow_approx_merlin

let add_cxx_flags t = t.add_cxx_flags
let use_standard_c_and_cxx_flags t = t.use_standard_c_and_cxx_flags

let generate_opam_files t = t.generate_opam_files

Expand All @@ -215,7 +215,7 @@ let to_dyn
; wrapped_executables
; dune_version
; allow_approx_merlin
; add_cxx_flags
; use_standard_c_and_cxx_flags
; generate_opam_files
; file_key
; dialects
Expand All @@ -238,7 +238,7 @@ let to_dyn
; ("wrapped_executables", bool wrapped_executables)
; ("dune_version", Dune_lang.Syntax.Version.to_dyn dune_version)
; ("allow_approx_merlin", bool allow_approx_merlin)
; ("add_cxx_flags", bool add_cxx_flags)
; ("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 @@ -614,7 +614,7 @@ let infer ~dir packages =
; parsing_context
; dune_version = lang.version
; allow_approx_merlin = true
; add_cxx_flags = false
; use_standard_c_and_cxx_flags = false
; generate_opam_files = false
; file_key
; dialects = Dialect.DB.builtin
Expand Down Expand Up @@ -677,8 +677,8 @@ let parse ~dir ~lang ~opam_packages ~file =
and+ allow_approx_merlin =
field_o_b "allow_approximate_merlin"
~check:(Dune_lang.Syntax.since Stanza.syntax (1, 9))
and+ add_cxx_flags =
field_o_b "add_cxx_flags"
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 =
Expand Down Expand Up @@ -795,7 +795,9 @@ let parse ~dir ~lang ~opam_packages ~file =
let allow_approx_merlin =
Option.value ~default:(dune_version < (1, 9)) allow_approx_merlin
in
let add_cxx_flags = Option.value ~default:false add_cxx_flags 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 @@ -829,7 +831,7 @@ let parse ~dir ~lang ~opam_packages ~file =
; wrapped_executables
; dune_version
; allow_approx_merlin
; add_cxx_flags
; use_standard_c_and_cxx_flags
; generate_opam_files
; dialects
; explicit_js_mode
Expand Down
8 changes: 5 additions & 3 deletions src/dune_engine/dune_project.mli
Original file line number Diff line number Diff line change
Expand Up @@ -65,9 +65,11 @@ val stanza_parser : t -> Stanza.t list Dune_lang.Decoder.t

val allow_approx_merlin : t -> bool

(** The option [add_cxx_flags] enables the automatic addition of flags necessary
to build c++ files with the active c compiler *)
val add_cxx_flags : t -> bool
(** 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

Expand Down
2 changes: 1 addition & 1 deletion src/dune_rules/super_context.ml
Original file line number Diff line number Diff line change
Expand Up @@ -11,7 +11,7 @@ let default_context_flags (ctx : Context.t) ~project =
List.filter c ~f:(fun s -> not (String.is_prefix s ~prefix:"-std="))
in
let cxx =
if Dune_project.add_cxx_flags project then
if Dune_project.use_standard_c_and_cxx_flags project then
let ccomp_type = Ocaml_config.ccomp_type ctx.ocaml_config in
match ccomp_type with
| Ocaml_config.Ccomp_type.Other s ->
Expand Down
10 changes: 5 additions & 5 deletions test/blackbox-tests/test-cases/cxx-flags.t/run.t
Original file line number Diff line number Diff line change
Expand Up @@ -6,28 +6,28 @@
$ ClangF="-x c++"
$ MsvcF="/TP"

Default: add_cxx_flags = false
Default: use_standard_c_and_cxx_flags = false
$ dune rules baz.o | tr -s '\n' ' ' |
> grep -ce "$GCCF\|$ClangF|$MsvcF"
0
[1]


With add_cxx_flags = false
With use_standard_c_and_cxx_flags = false
$ cat >dune-project <<EOF
> (lang dune 2.8)
> (no_forced_c_flags_and_more_cxx_flags false)
> (use_standard_c_and_cxx_flags false)
> EOF

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

With add_cxx_flags = true
With use_standard_c_and_cxx_flags = true
$ cat >dune-project <<EOF
> (lang dune 2.8)
> (no_forced_c_flags_and_more_cxx_flags true)
> (use_standard_c_and_cxx_flags true)
> EOF

$ dune rules baz.o | tr -s '\n' ' ' |
Expand Down

0 comments on commit 30ffcb0

Please sign in to comment.