From 06f3bdbab5826b4b73de7b4bba703b2e81085aba Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Ulysse=20G=C3=A9rard?= Date: Tue, 20 Oct 2020 15:46:22 +0200 Subject: [PATCH 01/24] Add test illustrating desired change MIME-Version: 1.0 Content-Type: text/plain; charset=UTF-8 Content-Transfer-Encoding: 8bit Signed-off-by: Ulysse Gérard --- .../variables/var-cc.t/dune28/dune-project | 1 + .../test-cases/variables/var-cc.t/run.t | 38 +++++++++++++++++-- 2 files changed, 36 insertions(+), 3 deletions(-) create mode 100644 test/blackbox-tests/test-cases/variables/var-cc.t/dune28/dune-project diff --git a/test/blackbox-tests/test-cases/variables/var-cc.t/dune28/dune-project b/test/blackbox-tests/test-cases/variables/var-cc.t/dune28/dune-project new file mode 100644 index 00000000000..c2e46604eed --- /dev/null +++ b/test/blackbox-tests/test-cases/variables/var-cc.t/dune28/dune-project @@ -0,0 +1 @@ +(lang dune 2.8) diff --git a/test/blackbox-tests/test-cases/variables/var-cc.t/run.t b/test/blackbox-tests/test-cases/variables/var-cc.t/run.t index 3810bb2096b..8608a88b892 100644 --- a/test/blackbox-tests/test-cases/variables/var-cc.t/run.t +++ b/test/blackbox-tests/test-cases/variables/var-cc.t/run.t @@ -2,12 +2,14 @@ According to the doc: CC is the C compiler command line (list made of the compiler name followed by its flags) that was used to compile OCaml in the current build context. -In practice it consists in the concatenation of OCaml's `c_compiler` and flags -The flags are made of the :standard (= ocamlc_cflags) set of ocamlc_flags -merged with (and sometimes replaced by) the flags in the env stanza. +In practice, in dune < 2.8 it consists in the concatenation of OCaml's +`c_compiler` and flags The flags are made of the :standard (= ocamlc_cflags) set +of ocamlc_flags merged with (and sometimes replaced by) the flags in the env +stanza. $ O_CC=$(ocamlc -config-var c_compiler) $ O_CCF=$(ocamlc -config-var ocamlc_cflags) + $ O_CCPPF=$(ocamlc -config-var ocamlc_cppflags) $ O_CC=${O_CC%% } $ O_CCF=${O_CCF%% } @@ -34,3 +36,33 @@ With redefining env flags $ dune build @cc | sed "s,${O_CC} -fPIC,OK," OK + +Since dune 2.8 the :standard set of flag and thus the %{cc} variable contain +both the cflags and cppflags from ocaml config. These flags are not added +systematically anymore to the compiler command line. + + $ cd dune28 + +No env + $ cat > dune <<'EOF' + > (rule + > (alias cc28) + > (action (echo %{cc}))) + > EOF + + $ dune build @cc28 | sed "s,${O_CC} ${O_CCF} ${O_CCPPF},OK," + OK + +With added env flags + $ cat >> dune <<'EOF' + > (env (_ (c_flags :standard -fPIC))) + > EOF + + $ dune build @cc28 | sed "s,${O_CC} ${O_CCF} ${O_CCPPF} -fPIC,OK," + OK + +With redefining env flags + $ sed -i.bak "s/:standard //g" dune + + $ dune build @cc28 | sed "s,${O_CC} -fPIC,OK," + OK From 855a2135ec22c693b7549d1a0935f7872b3d6775 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Ulysse=20G=C3=A9rard?= Date: Tue, 20 Oct 2020 15:47:31 +0200 Subject: [PATCH 02/24] Add cppflags to :standard flags for dune >= 2.8 MIME-Version: 1.0 Content-Type: text/plain; charset=UTF-8 Content-Transfer-Encoding: 8bit Signed-off-by: Ulysse Gérard --- src/dune_rules/super_context.ml | 25 +++++++++++++++++-------- 1 file changed, 17 insertions(+), 8 deletions(-) diff --git a/src/dune_rules/super_context.ml b/src/dune_rules/super_context.ml index 5d1fbf618df..f7500be2e99 100644 --- a/src/dune_rules/super_context.ml +++ b/src/dune_rules/super_context.ml @@ -2,13 +2,16 @@ open! Dune_engine open! Stdune open Import -let default_context_flags (ctx : Context.t) = - (* 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 default_context_flags (ctx : Context.t) ~dune_version = + let cflags = Ocaml_config.ocamlc_cflags ctx.ocaml_config in let cxx = - List.filter c ~f:(fun s -> not (String.is_prefix s ~prefix:"-std=")) + List.filter cflags ~f:(fun s -> not (String.is_prefix s ~prefix:"-std=")) + in + let c = + if Dune_lang.Syntax.Version.Infix.(dune_version >= (2, 8)) then + cflags @ Ocaml_config.ocamlc_cppflags ctx.ocaml_config + else + cflags in Foreign_language.Dict.make ~c ~cxx @@ -115,7 +118,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 project = Scope.project scope in + let dune_version = Dune_project.dune_version project in + let default_context_flags = default_context_flags t.context ~dune_version in let expander_for_artifacts = Memo.lazy_ (fun () -> expander_for_artifacts ~scope ~root_expander:t.root_expander @@ -580,7 +585,11 @@ 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 project = Scope.project scope in + let dune_version = Dune_project.dune_version project in + let default_context_flags = + default_context_flags context ~dune_version + in let expander_for_artifacts = Memo.lazy_ (fun () -> Code_error.raise From 50571aef84116448923ae34f0048a90aa78b47ed Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Ulysse=20G=C3=A9rard?= Date: Tue, 20 Oct 2020 16:54:18 +0200 Subject: [PATCH 03/24] Add test illustrating the new flag behavior MIME-Version: 1.0 Content-Type: text/plain; charset=UTF-8 Content-Transfer-Encoding: 8bit Signed-off-by: Ulysse Gérard --- .../blackbox-tests/test-cases/c-flags.t/bar.c | 0 test/blackbox-tests/test-cases/c-flags.t/dune | 4 ++ .../blackbox-tests/test-cases/c-flags.t/foo.c | 0 .../blackbox-tests/test-cases/c-flags.t/run.t | 65 +++++++++++++++++++ 4 files changed, 69 insertions(+) create mode 100644 test/blackbox-tests/test-cases/c-flags.t/bar.c create mode 100644 test/blackbox-tests/test-cases/c-flags.t/dune create mode 100644 test/blackbox-tests/test-cases/c-flags.t/foo.c create mode 100644 test/blackbox-tests/test-cases/c-flags.t/run.t diff --git a/test/blackbox-tests/test-cases/c-flags.t/bar.c b/test/blackbox-tests/test-cases/c-flags.t/bar.c new file mode 100644 index 00000000000..e69de29bb2d diff --git a/test/blackbox-tests/test-cases/c-flags.t/dune b/test/blackbox-tests/test-cases/c-flags.t/dune new file mode 100644 index 00000000000..05c4ef05bb6 --- /dev/null +++ b/test/blackbox-tests/test-cases/c-flags.t/dune @@ -0,0 +1,4 @@ +(library + (name test) + (foreign_stubs (language c) (names foo)) + (foreign_stubs (language c) (names bar) (flags))) diff --git a/test/blackbox-tests/test-cases/c-flags.t/foo.c b/test/blackbox-tests/test-cases/c-flags.t/foo.c new file mode 100644 index 00000000000..e69de29bb2d diff --git a/test/blackbox-tests/test-cases/c-flags.t/run.t b/test/blackbox-tests/test-cases/c-flags.t/run.t new file mode 100644 index 00000000000..dc419ca94dd --- /dev/null +++ b/test/blackbox-tests/test-cases/c-flags.t/run.t @@ -0,0 +1,65 @@ +Prior to dune 2.8 ocamlc_cflags and ocamlc_cppflags where +always prepended to the C compiler command line + +In the following tests, foo.c is built with the :standard set of flags while +bar.c is built with an empty set of flags. + + $ O_CC=$(ocamlc -config-var c_compiler) + $ O_CCF=$(ocamlc -config-var ocamlc_cflags) + $ O_CCPPF=$(ocamlc -config-var ocamlc_cppflags) + $ O_CC=${O_CC%% } + $ O_CCF=${O_CCF%% } + $ O_CCPPF=${O_CCPPF%% } + +########## +Dune < 2.8 +########## + + $ cat >dune-project < (lang dune 2.7) + + $ dune rules -m foo.o | tr -s '\t\n\\' ' ' > out_foo + $ dune rules -m bar.o | sed "s,bar,foo," | tr -s '\t\n\\' ' ' > out_bar + +Ocamlc_cflags are duplicated if the :standard set is kept: + $ cat out_foo | grep -ce "${O_CCF} ${O_CCPPF} ${O_CCF}" + 1 + +Whether or not the :standard flags is overridden, both ocamlc_cflags and +ocamlc_cpp flags appear in the compiler command line: + + $ cat out_foo | grep -ce "${O_CCF} ${O_CCPPF}" + 1 + + + $ cat out_bar | grep -ce "${O_CCF} ${O_CCPPF}" + 1 + +########### +Dune >= 2.8 +########### + + $ cat >dune-project < (lang dune 2.8) + + $ dune rules -m foo.o | tr -s '\t\n\\' ' ' > out_foo + $ dune rules -m bar.o | sed "s,bar,foo," | tr -s '\t\n\\' ' ' > out_bar + +Ocamlc_cflags are not duplicated anymore: + $ cat out_foo | grep -ce "${O_CCF} ${O_CCPPF} ${O_CCF}" + 0 + [1] + +When the :standard flags is overridden, ocamlc_cflags and +ocamlc_cpp are effectively removed from the compiler command line + + $ cat out_foo | grep -ce "${O_CCF} ${O_CCPPF}" + 1 + + $ cat out_bar | grep -ce "${O_CCF}" + 0 + [1] + + $ cat out_bar | grep -ce "${O_CCPPF}" + 0 + [1] From c870b21b8747ac2662514c752b8f7ee1aa5eb517 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Ulysse=20G=C3=A9rard?= Date: Tue, 20 Oct 2020 17:04:51 +0200 Subject: [PATCH 04/24] Do not prepend flags systematically in Dune >= 2.8 MIME-Version: 1.0 Content-Type: text/plain; charset=UTF-8 Content-Transfer-Encoding: 8bit Signed-off-by: Ulysse Gérard --- src/dune_rules/foreign_rules.ml | 18 +++++++++++++----- 1 file changed, 13 insertions(+), 5 deletions(-) diff --git a/src/dune_rules/foreign_rules.ml b/src/dune_rules/foreign_rules.ml index d5852c52462..2c6f201384d 100644 --- a/src/dune_rules/foreign_rules.ml +++ b/src/dune_rules/foreign_rules.ml @@ -75,16 +75,24 @@ 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 dune_version = + Super_context.find_scope_by_dir sctx dir + |> Scope.project |> Dune_project.dune_version + 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 - ] + if Dune_lang.Syntax.Version.Infix.(dune_version >= (2, 8)) then + Fdo.c_flags ctx + else + (* In dune < 2.8 flags from ocamlc_config are always added *) + 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 flags = Foreign.Source.flags src in From bd5235d067deb50b50235e8abdd3d28dfe1f48a0 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Ulysse=20G=C3=A9rard?= Date: Wed, 21 Oct 2020 17:02:32 +0200 Subject: [PATCH 05/24] Restrict new behavior with `new_foreign_flags_handling` option MIME-Version: 1.0 Content-Type: text/plain; charset=UTF-8 Content-Transfer-Encoding: 8bit Signed-off-by: Ulysse Gérard --- src/dune_engine/dune_project.ml | 13 +++++++++++++ src/dune_engine/dune_project.mli | 2 ++ src/dune_rules/foreign_rules.ml | 7 ++----- src/dune_rules/super_context.ml | 12 ++++-------- 4 files changed, 21 insertions(+), 13 deletions(-) diff --git a/src/dune_engine/dune_project.ml b/src/dune_engine/dune_project.ml index 915088d6c48..aeaf4b4c002 100644 --- a/src/dune_engine/dune_project.ml +++ b/src/dune_engine/dune_project.ml @@ -162,6 +162,7 @@ type t = ; dune_version : Dune_lang.Syntax.Version.t ; allow_approx_merlin : bool ; generate_opam_files : bool + ; new_foreign_flags_handling : bool ; file_key : File_key.t ; dialects : Dialect.DB.t ; explicit_js_mode : bool @@ -194,6 +195,8 @@ let allow_approx_merlin t = t.allow_approx_merlin let generate_opam_files t = t.generate_opam_files +let new_foreign_flags_handling t = t.new_foreign_flags_handling + let dialects t = t.dialects let explicit_js_mode t = t.explicit_js_mode @@ -213,6 +216,7 @@ let to_dyn ; dune_version ; allow_approx_merlin ; generate_opam_files + ; new_foreign_flags_handling ; file_key ; dialects ; explicit_js_mode @@ -235,6 +239,7 @@ let to_dyn ; ("dune_version", Dune_lang.Syntax.Version.to_dyn dune_version) ; ("allow_approx_merlin", bool allow_approx_merlin) ; ("generate_opam_files", bool generate_opam_files) + ; ("new_foreign_flags_handling", bool new_foreign_flags_handling) ; ("file_key", string file_key) ; ("dialects", Dialect.DB.to_dyn dialects) ; ("explicit_js_mode", bool explicit_js_mode) @@ -610,6 +615,7 @@ let infer ~dir packages = ; dune_version = lang.version ; allow_approx_merlin = true ; generate_opam_files = false + ; new_foreign_flags_handling = false ; file_key ; dialects = Dialect.DB.builtin ; explicit_js_mode @@ -675,6 +681,9 @@ let parse ~dir ~lang ~opam_packages ~file = and+ generate_opam_files = field_o_b "generate_opam_files" ~check:(Dune_lang.Syntax.since Stanza.syntax (1, 10)) + and+ new_foreign_flags_handling = + field_o_b "new_foreign_flags_handling" + ~check:(Dune_lang.Syntax.since Stanza.syntax (2, 8)) and+ dialects = multi_field "dialect" ( Dune_lang.Syntax.since Stanza.syntax (1, 11) @@ -792,6 +801,9 @@ let parse ~dir ~lang ~opam_packages ~file = let generate_opam_files = Option.value ~default:false generate_opam_files in + let new_foreign_flags_handling = + Option.value ~default:false new_foreign_flags_handling + in let cram = match cram with | None -> false @@ -820,6 +832,7 @@ let parse ~dir ~lang ~opam_packages ~file = ; dune_version ; allow_approx_merlin ; generate_opam_files + ; new_foreign_flags_handling ; dialects ; explicit_js_mode ; format_config diff --git a/src/dune_engine/dune_project.mli b/src/dune_engine/dune_project.mli index 9d069ab0ace..4a7341a619a 100644 --- a/src/dune_engine/dune_project.mli +++ b/src/dune_engine/dune_project.mli @@ -67,6 +67,8 @@ val allow_approx_merlin : t -> bool val generate_opam_files : t -> bool +val new_foreign_flags_handling : t -> bool + val dialects : t -> Dialect.DB.t val explicit_js_mode : t -> bool diff --git a/src/dune_rules/foreign_rules.ml b/src/dune_rules/foreign_rules.ml index 2c6f201384d..929b54d0a8b 100644 --- a/src/dune_rules/foreign_rules.ml +++ b/src/dune_rules/foreign_rules.ml @@ -75,16 +75,13 @@ 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 dune_version = - Super_context.find_scope_by_dir sctx dir - |> Scope.project |> Dune_project.dune_version - in + let project = Super_context.find_scope_by_dir sctx dir |> Scope.project in let flags = let ctx_flags = match kind with | Foreign_language.C -> let cfg = ctx.ocaml_config in - if Dune_lang.Syntax.Version.Infix.(dune_version >= (2, 8)) then + if Dune_project.new_foreign_flags_handling project then Fdo.c_flags ctx else (* In dune < 2.8 flags from ocamlc_config are always added *) diff --git a/src/dune_rules/super_context.ml b/src/dune_rules/super_context.ml index f7500be2e99..430ee510e01 100644 --- a/src/dune_rules/super_context.ml +++ b/src/dune_rules/super_context.ml @@ -2,13 +2,13 @@ open! Dune_engine open! Stdune open Import -let default_context_flags (ctx : Context.t) ~dune_version = +let default_context_flags (ctx : Context.t) ~project = let cflags = Ocaml_config.ocamlc_cflags ctx.ocaml_config in let cxx = List.filter cflags ~f:(fun s -> not (String.is_prefix s ~prefix:"-std=")) in let c = - if Dune_lang.Syntax.Version.Infix.(dune_version >= (2, 8)) then + if Dune_project.new_foreign_flags_handling project then cflags @ Ocaml_config.ocamlc_cppflags ctx.ocaml_config else cflags @@ -119,8 +119,7 @@ end = struct in let config_stanza = get_env_stanza t ~dir in let project = Scope.project scope in - let dune_version = Dune_project.dune_version project in - let default_context_flags = default_context_flags t.context ~dune_version in + let default_context_flags = default_context_flags t.context ~project in let expander_for_artifacts = Memo.lazy_ (fun () -> expander_for_artifacts ~scope ~root_expander:t.root_expander @@ -586,10 +585,7 @@ let create ~(context : Context.t) ?host ~projects ~packages ~stanzas = let dir = context.build_dir in let scope = Scope.DB.find_by_dir scopes dir in let project = Scope.project scope in - let dune_version = Dune_project.dune_version project in - let default_context_flags = - default_context_flags context ~dune_version - in + let default_context_flags = default_context_flags context ~project in let expander_for_artifacts = Memo.lazy_ (fun () -> Code_error.raise From 098389473e3843f188316c917a8379b2f40cf698 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Ulysse=20G=C3=A9rard?= Date: Wed, 21 Oct 2020 17:02:42 +0200 Subject: [PATCH 06/24] Update tests MIME-Version: 1.0 Content-Type: text/plain; charset=UTF-8 Content-Transfer-Encoding: 8bit Signed-off-by: Ulysse Gérard --- .../blackbox-tests/test-cases/c-flags.t/run.t | 32 ++++++++++++++----- .../variables/var-cc.t/dune-project | 2 +- .../variables/var-cc.t/dune28/dune-project | 1 - .../var-cc.t/new_ff_handling/dune-project | 2 ++ .../test-cases/variables/var-cc.t/run.t | 9 +++--- 5 files changed, 32 insertions(+), 14 deletions(-) delete mode 100644 test/blackbox-tests/test-cases/variables/var-cc.t/dune28/dune-project create mode 100644 test/blackbox-tests/test-cases/variables/var-cc.t/new_ff_handling/dune-project diff --git a/test/blackbox-tests/test-cases/c-flags.t/run.t b/test/blackbox-tests/test-cases/c-flags.t/run.t index dc419ca94dd..ecb3d9eb1ea 100644 --- a/test/blackbox-tests/test-cases/c-flags.t/run.t +++ b/test/blackbox-tests/test-cases/c-flags.t/run.t @@ -2,7 +2,7 @@ Prior to dune 2.8 ocamlc_cflags and ocamlc_cppflags where always prepended to the C compiler command line In the following tests, foo.c is built with the :standard set of flags while -bar.c is built with an empty set of flags. +bar.c is built with an "empty" set of flags. $ O_CC=$(ocamlc -config-var c_compiler) $ O_CCF=$(ocamlc -config-var ocamlc_cflags) @@ -11,12 +11,12 @@ bar.c is built with an empty set of flags. $ O_CCF=${O_CCF%% } $ O_CCPPF=${O_CCPPF%% } -########## -Dune < 2.8 -########## + +new_foreign_flags_handling = false +================================== $ cat >dune-project < (lang dune 2.7) + > (lang dune 2.8) $ dune rules -m foo.o | tr -s '\t\n\\' ' ' > out_foo $ dune rules -m bar.o | sed "s,bar,foo," | tr -s '\t\n\\' ' ' > out_bar @@ -35,12 +35,12 @@ ocamlc_cpp flags appear in the compiler command line: $ cat out_bar | grep -ce "${O_CCF} ${O_CCPPF}" 1 -########### -Dune >= 2.8 -########### +new_foreign_flags_handling = true +================================= $ cat >dune-project < (lang dune 2.8) + > (new_foreign_flags_handling true) $ dune rules -m foo.o | tr -s '\t\n\\' ' ' > out_foo $ dune rules -m bar.o | sed "s,bar,foo," | tr -s '\t\n\\' ' ' > out_bar @@ -63,3 +63,19 @@ ocamlc_cpp are effectively removed from the compiler command line $ cat out_bar | grep -ce "${O_CCPPF}" 0 [1] + +new_foreign_flags_handling = true but dune < 2.8 +================================================ + + $ cat >dune-project < (lang dune 2.7) + > (new_foreign_flags_handling true) + + $ dune rules + File "dune-project", line 2, characters 0-33: + 2 | (new_foreign_flags_handling true) + ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ + Error: 'new_foreign_flags_handling' is only available since version 2.8 of + the dune language. Please update your dune-project file to have (lang dune + 2.8). + [1] diff --git a/test/blackbox-tests/test-cases/variables/var-cc.t/dune-project b/test/blackbox-tests/test-cases/variables/var-cc.t/dune-project index 929c696e561..c2e46604eed 100644 --- a/test/blackbox-tests/test-cases/variables/var-cc.t/dune-project +++ b/test/blackbox-tests/test-cases/variables/var-cc.t/dune-project @@ -1 +1 @@ -(lang dune 2.0) +(lang dune 2.8) diff --git a/test/blackbox-tests/test-cases/variables/var-cc.t/dune28/dune-project b/test/blackbox-tests/test-cases/variables/var-cc.t/dune28/dune-project deleted file mode 100644 index c2e46604eed..00000000000 --- a/test/blackbox-tests/test-cases/variables/var-cc.t/dune28/dune-project +++ /dev/null @@ -1 +0,0 @@ -(lang dune 2.8) diff --git a/test/blackbox-tests/test-cases/variables/var-cc.t/new_ff_handling/dune-project b/test/blackbox-tests/test-cases/variables/var-cc.t/new_ff_handling/dune-project new file mode 100644 index 00000000000..89773116548 --- /dev/null +++ b/test/blackbox-tests/test-cases/variables/var-cc.t/new_ff_handling/dune-project @@ -0,0 +1,2 @@ +(lang dune 2.8) +(new_foreign_flags_handling true) \ No newline at end of file diff --git a/test/blackbox-tests/test-cases/variables/var-cc.t/run.t b/test/blackbox-tests/test-cases/variables/var-cc.t/run.t index 8608a88b892..0eaf3e3c79e 100644 --- a/test/blackbox-tests/test-cases/variables/var-cc.t/run.t +++ b/test/blackbox-tests/test-cases/variables/var-cc.t/run.t @@ -37,11 +37,12 @@ With redefining env flags $ dune build @cc | sed "s,${O_CC} -fPIC,OK," OK -Since dune 2.8 the :standard set of flag and thus the %{cc} variable contain -both the cflags and cppflags from ocaml config. These flags are not added -systematically anymore to the compiler command line. +Since dune 2.8, when using the new_foreign_flags_handling option the :standard +set of flag and thus the %{cc} variable contain both the cflags and cppflags +from ocaml config. These flags are not added systematically anymore to the +compiler command line. - $ cd dune28 + $ cd new_ff_handling No env $ cat > dune <<'EOF' From 85e00d6b3d29f46287eee97a4d7e327b71e19a58 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Ulysse=20G=C3=A9rard?= Date: Fri, 23 Oct 2020 11:22:29 +0200 Subject: [PATCH 07/24] Add some documentation for the new option MIME-Version: 1.0 Content-Type: text/plain; charset=UTF-8 Content-Transfer-Encoding: 8bit Signed-off-by: Ulysse Gérard --- doc/concepts.rst | 4 ++++ doc/dune-files.rst | 17 +++++++++++++++++ 2 files changed, 21 insertions(+) diff --git a/doc/concepts.rst b/doc/concepts.rst index 70745182a92..0acf9467aaf 100644 --- a/doc/concepts.rst +++ b/doc/concepts.rst @@ -1177,6 +1177,10 @@ Here is a complete list of supported subfields: - ``flags`` are passed when compiling source files. This field is specified using the :ref:`ordered-set-language`, where the ``:standard`` value comes from the environment settings ``c_flags`` and ``cxx_flags``, respectively. + Note that, for C subs, Dune unconditionally adds the flags present in the + fields ``ocamlc_cflags`` and ``ocamlc_cppflags`` of the OCaml config to the + compiler command line. This behavior can be disabled since Dune 2.8 via the + ``dune-project`` option :ref:`new-foreign-flags-handling`. - ``include_dirs`` are tracked as dependencies and passed to the compiler via the ``-I`` flag. You can use :ref:`variables` in this field, and refer to a library source directory using the ``(lib library-name)`` syntax. diff --git a/doc/dune-files.rst b/doc/dune-files.rst index bab0333c09c..8da6b748b06 100644 --- a/doc/dune-files.rst +++ b/doc/dune-files.rst @@ -285,6 +285,23 @@ language: The syntax is as a list of the following elements: dep-specification = dep+ +.. _new-foreign-flags-handling: + +new_foreign_flags_handling +-------------------------- + +Since Dune 2.8, it is possible to deactivate +the systematic prepending of flags coming from ``ocamlc -config`` to the C +compiler command line. This is done adding the following field to the ``dune-project`` file: + +.. code:: scheme + + (new_foreign_flags_handling true) + +In this mode, dune will populate the ``:standard`` set of C flags with the +content of ``ocamlc_cflags`` and ``ocamlc_cppflags``. These flags can be +completed or overridden using the :ref:`ordered-set-language`. + dune ==== From 9ae82275c7d3f09b94f54820bd70e684b165960d Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Ulysse=20G=C3=A9rard?= Date: Fri, 23 Oct 2020 11:34:56 +0200 Subject: [PATCH 08/24] Change CHANGES MIME-Version: 1.0 Content-Type: text/plain; charset=UTF-8 Content-Transfer-Encoding: 8bit Signed-off-by: Ulysse Gérard --- CHANGES.md | 5 +++++ 1 file changed, 5 insertions(+) diff --git a/CHANGES.md b/CHANGES.md index a2b687c1861..03e0390b8b2 100644 --- a/CHANGES.md +++ b/CHANGES.md @@ -78,6 +78,11 @@ Unreleased - Avoid pager when running `$ git diff` (#3912, @AltGr) +- Add the option `new_foreign_flags_handling` to `dune-project` that disables + the unconditional use of the `ocamlc_cflags` and `ocamlc_cppflags` from + `ocamlc -config` in C compiler calls. These flags are present in the + `:standard` set instead. (#3875, fix #3718, @voodoos) + 2.7.1 (2/09/2020) ----------------- From 0a7352310f2ce4ba584a951c1ce359e98b820b87 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Ulysse=20G=C3=A9rard?= Date: Fri, 23 Oct 2020 14:15:31 +0200 Subject: [PATCH 09/24] Comments tweak MIME-Version: 1.0 Content-Type: text/plain; charset=UTF-8 Content-Transfer-Encoding: 8bit Signed-off-by: Ulysse Gérard --- src/dune_rules/super_context.ml | 1 + test/blackbox-tests/test-cases/variables/var-cc.t/run.t | 5 ++--- 2 files changed, 3 insertions(+), 3 deletions(-) diff --git a/src/dune_rules/super_context.ml b/src/dune_rules/super_context.ml index 430ee510e01..58493fe69a9 100644 --- a/src/dune_rules/super_context.ml +++ b/src/dune_rules/super_context.ml @@ -9,6 +9,7 @@ let default_context_flags (ctx : Context.t) ~project = in let c = if Dune_project.new_foreign_flags_handling project then + (* TODO DUNE3 make this the default behavior *) cflags @ Ocaml_config.ocamlc_cppflags ctx.ocaml_config else cflags diff --git a/test/blackbox-tests/test-cases/variables/var-cc.t/run.t b/test/blackbox-tests/test-cases/variables/var-cc.t/run.t index 0eaf3e3c79e..f9ff8ed9f7a 100644 --- a/test/blackbox-tests/test-cases/variables/var-cc.t/run.t +++ b/test/blackbox-tests/test-cases/variables/var-cc.t/run.t @@ -3,9 +3,8 @@ compiler name followed by its flags) that was used to compile OCaml in the current build context. In practice, in dune < 2.8 it consists in the concatenation of OCaml's -`c_compiler` and flags The flags are made of the :standard (= ocamlc_cflags) set -of ocamlc_flags merged with (and sometimes replaced by) the flags in the env -stanza. +`c_compiler` and flags. Theses flags are made of the :standard set of flags +merged with (and sometimes replaced by) the flags in the env stanza. $ O_CC=$(ocamlc -config-var c_compiler) $ O_CCF=$(ocamlc -config-var ocamlc_cflags) From 4cf9d62ba618b89deb62eb404d2ff06771eeec60 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Ulysse=20G=C3=A9rard?= Date: Fri, 23 Oct 2020 14:33:25 +0200 Subject: [PATCH 10/24] Rename option to `always_add_cflags` MIME-Version: 1.0 Content-Type: text/plain; charset=UTF-8 Content-Transfer-Encoding: 8bit Signed-off-by: Ulysse Gérard --- CHANGES.md | 1 + doc/concepts.rst | 2 +- doc/dune-files.rst | 14 ++++++------- src/dune_engine/dune_project.ml | 20 ++++++++---------- src/dune_engine/dune_project.mli | 2 +- src/dune_rules/foreign_rules.ml | 7 ++++--- src/dune_rules/super_context.ml | 2 +- .../blackbox-tests/test-cases/c-flags.t/run.t | 21 +++++++++---------- .../var-cc.t/new_ff_handling/dune-project | 2 +- .../test-cases/variables/var-cc.t/run.t | 2 +- 10 files changed, 36 insertions(+), 37 deletions(-) diff --git a/CHANGES.md b/CHANGES.md index 03e0390b8b2..54228a1aa50 100644 --- a/CHANGES.md +++ b/CHANGES.md @@ -79,6 +79,7 @@ Unreleased - Avoid pager when running `$ git diff` (#3912, @AltGr) - Add the option `new_foreign_flags_handling` to `dune-project` that disables +- Add the option `always_add_cflags` to `dune-project` that disables the unconditional use of the `ocamlc_cflags` and `ocamlc_cppflags` from `ocamlc -config` in C compiler calls. These flags are present in the `:standard` set instead. (#3875, fix #3718, @voodoos) diff --git a/doc/concepts.rst b/doc/concepts.rst index 0acf9467aaf..b9e458a6574 100644 --- a/doc/concepts.rst +++ b/doc/concepts.rst @@ -1180,7 +1180,7 @@ Here is a complete list of supported subfields: Note that, for C subs, Dune unconditionally adds the flags present in the fields ``ocamlc_cflags`` and ``ocamlc_cppflags`` of the OCaml config to the compiler command line. This behavior can be disabled since Dune 2.8 via the - ``dune-project`` option :ref:`new-foreign-flags-handling`. + ``dune-project`` option :ref:`always-add-cflags`. - ``include_dirs`` are tracked as dependencies and passed to the compiler via the ``-I`` flag. You can use :ref:`variables` in this field, and refer to a library source directory using the ``(lib library-name)`` syntax. diff --git a/doc/dune-files.rst b/doc/dune-files.rst index 8da6b748b06..530eec37b2e 100644 --- a/doc/dune-files.rst +++ b/doc/dune-files.rst @@ -285,18 +285,18 @@ language: The syntax is as a list of the following elements: dep-specification = dep+ -.. _new-foreign-flags-handling: +.. _always-add-cflags: -new_foreign_flags_handling --------------------------- +always_add_cflags +----------------- -Since Dune 2.8, it is possible to deactivate -the systematic prepending of flags coming from ``ocamlc -config`` to the C -compiler command line. This is done adding the following field to the ``dune-project`` file: +Since Dune 2.8, it is possible to deactivate the systematic prepending of flags +coming from ``ocamlc -config`` to the C compiler command line. This is done +adding the following field to the ``dune-project`` file: .. code:: scheme - (new_foreign_flags_handling true) + (always_add_cflags false) In this mode, dune will populate the ``:standard`` set of C flags with the content of ``ocamlc_cflags`` and ``ocamlc_cppflags``. These flags can be diff --git a/src/dune_engine/dune_project.ml b/src/dune_engine/dune_project.ml index aeaf4b4c002..a3a974f70e3 100644 --- a/src/dune_engine/dune_project.ml +++ b/src/dune_engine/dune_project.ml @@ -162,7 +162,7 @@ type t = ; dune_version : Dune_lang.Syntax.Version.t ; allow_approx_merlin : bool ; generate_opam_files : bool - ; new_foreign_flags_handling : bool + ; always_add_cflags : bool ; file_key : File_key.t ; dialects : Dialect.DB.t ; explicit_js_mode : bool @@ -195,7 +195,7 @@ let allow_approx_merlin t = t.allow_approx_merlin let generate_opam_files t = t.generate_opam_files -let new_foreign_flags_handling t = t.new_foreign_flags_handling +let always_add_cflags t = t.always_add_cflags let dialects t = t.dialects @@ -216,7 +216,7 @@ let to_dyn ; dune_version ; allow_approx_merlin ; generate_opam_files - ; new_foreign_flags_handling + ; always_add_cflags ; file_key ; dialects ; explicit_js_mode @@ -239,7 +239,7 @@ let to_dyn ; ("dune_version", Dune_lang.Syntax.Version.to_dyn dune_version) ; ("allow_approx_merlin", bool allow_approx_merlin) ; ("generate_opam_files", bool generate_opam_files) - ; ("new_foreign_flags_handling", bool new_foreign_flags_handling) + ; ("always_add_cflags", bool always_add_cflags) ; ("file_key", string file_key) ; ("dialects", Dialect.DB.to_dyn dialects) ; ("explicit_js_mode", bool explicit_js_mode) @@ -615,7 +615,7 @@ let infer ~dir packages = ; dune_version = lang.version ; allow_approx_merlin = true ; generate_opam_files = false - ; new_foreign_flags_handling = false + ; always_add_cflags = true ; file_key ; dialects = Dialect.DB.builtin ; explicit_js_mode @@ -681,8 +681,8 @@ let parse ~dir ~lang ~opam_packages ~file = and+ generate_opam_files = field_o_b "generate_opam_files" ~check:(Dune_lang.Syntax.since Stanza.syntax (1, 10)) - and+ new_foreign_flags_handling = - field_o_b "new_foreign_flags_handling" + and+ always_add_cflags = + field_o_b "always_add_cflags" ~check:(Dune_lang.Syntax.since Stanza.syntax (2, 8)) and+ dialects = multi_field "dialect" @@ -801,9 +801,7 @@ let parse ~dir ~lang ~opam_packages ~file = let generate_opam_files = Option.value ~default:false generate_opam_files in - let new_foreign_flags_handling = - Option.value ~default:false new_foreign_flags_handling - in + let always_add_cflags = Option.value ~default:true always_add_cflags in let cram = match cram with | None -> false @@ -832,7 +830,7 @@ let parse ~dir ~lang ~opam_packages ~file = ; dune_version ; allow_approx_merlin ; generate_opam_files - ; new_foreign_flags_handling + ; always_add_cflags ; dialects ; explicit_js_mode ; format_config diff --git a/src/dune_engine/dune_project.mli b/src/dune_engine/dune_project.mli index 4a7341a619a..8b0d13ff59d 100644 --- a/src/dune_engine/dune_project.mli +++ b/src/dune_engine/dune_project.mli @@ -67,7 +67,7 @@ val allow_approx_merlin : t -> bool val generate_opam_files : t -> bool -val new_foreign_flags_handling : t -> bool +val always_add_cflags : t -> bool val dialects : t -> Dialect.DB.t diff --git a/src/dune_rules/foreign_rules.ml b/src/dune_rules/foreign_rules.ml index 929b54d0a8b..ad8bec93d94 100644 --- a/src/dune_rules/foreign_rules.ml +++ b/src/dune_rules/foreign_rules.ml @@ -81,15 +81,16 @@ let build_c ~kind ~sctx ~dir ~expander ~include_flags (loc, src, dst) = match kind with | Foreign_language.C -> let cfg = ctx.ocaml_config in - if Dune_project.new_foreign_flags_handling project then - Fdo.c_flags ctx - else + if Dune_project.always_add_cflags project then (* In dune < 2.8 flags from ocamlc_config are always added *) List.concat [ Ocaml_config.ocamlc_cflags cfg ; Ocaml_config.ocamlc_cppflags cfg ; Fdo.c_flags ctx ] + else + (* TODO DUNE3 make this the default behavior *) + Fdo.c_flags ctx | Foreign_language.Cxx -> Fdo.cxx_flags ctx in let flags = Foreign.Source.flags src in diff --git a/src/dune_rules/super_context.ml b/src/dune_rules/super_context.ml index 58493fe69a9..7fb1ca975f4 100644 --- a/src/dune_rules/super_context.ml +++ b/src/dune_rules/super_context.ml @@ -8,7 +8,7 @@ let default_context_flags (ctx : Context.t) ~project = List.filter cflags ~f:(fun s -> not (String.is_prefix s ~prefix:"-std=")) in let c = - if Dune_project.new_foreign_flags_handling project then + if not (Dune_project.always_add_cflags project) then (* TODO DUNE3 make this the default behavior *) cflags @ Ocaml_config.ocamlc_cppflags ctx.ocaml_config else diff --git a/test/blackbox-tests/test-cases/c-flags.t/run.t b/test/blackbox-tests/test-cases/c-flags.t/run.t index ecb3d9eb1ea..117168d012a 100644 --- a/test/blackbox-tests/test-cases/c-flags.t/run.t +++ b/test/blackbox-tests/test-cases/c-flags.t/run.t @@ -12,7 +12,7 @@ bar.c is built with an "empty" set of flags. $ O_CCPPF=${O_CCPPF%% } -new_foreign_flags_handling = false +always_add_cflags = false ================================== $ cat >dune-project <dune-project < (lang dune 2.8) - > (new_foreign_flags_handling true) + > (always_add_cflags false) $ dune rules -m foo.o | tr -s '\t\n\\' ' ' > out_foo $ dune rules -m bar.o | sed "s,bar,foo," | tr -s '\t\n\\' ' ' > out_bar @@ -64,18 +64,17 @@ ocamlc_cpp are effectively removed from the compiler command line 0 [1] -new_foreign_flags_handling = true but dune < 2.8 +always_add_cflags = true but dune < 2.8 ================================================ $ cat >dune-project < (lang dune 2.7) - > (new_foreign_flags_handling true) + > (always_add_cflags false) $ dune rules - File "dune-project", line 2, characters 0-33: - 2 | (new_foreign_flags_handling true) - ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ - Error: 'new_foreign_flags_handling' is only available since version 2.8 of - the dune language. Please update your dune-project file to have (lang dune - 2.8). + File "dune-project", line 2, characters 0-25: + 2 | (always_add_cflags false) + ^^^^^^^^^^^^^^^^^^^^^^^^^ + Error: 'always_add_cflags' is only available since version 2.8 of the dune + language. Please update your dune-project file to have (lang dune 2.8). [1] diff --git a/test/blackbox-tests/test-cases/variables/var-cc.t/new_ff_handling/dune-project b/test/blackbox-tests/test-cases/variables/var-cc.t/new_ff_handling/dune-project index 89773116548..c9ed3b53bf9 100644 --- a/test/blackbox-tests/test-cases/variables/var-cc.t/new_ff_handling/dune-project +++ b/test/blackbox-tests/test-cases/variables/var-cc.t/new_ff_handling/dune-project @@ -1,2 +1,2 @@ (lang dune 2.8) -(new_foreign_flags_handling true) \ No newline at end of file +(always_add_cflags false) \ No newline at end of file diff --git a/test/blackbox-tests/test-cases/variables/var-cc.t/run.t b/test/blackbox-tests/test-cases/variables/var-cc.t/run.t index f9ff8ed9f7a..a14c6e837ed 100644 --- a/test/blackbox-tests/test-cases/variables/var-cc.t/run.t +++ b/test/blackbox-tests/test-cases/variables/var-cc.t/run.t @@ -36,7 +36,7 @@ With redefining env flags $ dune build @cc | sed "s,${O_CC} -fPIC,OK," OK -Since dune 2.8, when using the new_foreign_flags_handling option the :standard +Since dune 2.8, when using the always_add_cflags option the :standard set of flag and thus the %{cc} variable contain both the cflags and cppflags from ocaml config. These flags are not added systematically anymore to the compiler command line. From 10a0c1450df59c3cc39c9587e152679f1716991d Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Ulysse=20G=C3=A9rard?= Date: Fri, 23 Oct 2020 15:04:04 +0200 Subject: [PATCH 11/24] Add doc about flags-flow MIME-Version: 1.0 Content-Type: text/plain; charset=UTF-8 Content-Transfer-Encoding: 8bit Signed-off-by: Ulysse Gérard --- doc/concepts.rst | 24 ++++++++++++++++++++++-- 1 file changed, 22 insertions(+), 2 deletions(-) diff --git a/doc/concepts.rst b/doc/concepts.rst index b9e458a6574..a45e2df7ae6 100644 --- a/doc/concepts.rst +++ b/doc/concepts.rst @@ -140,8 +140,7 @@ Dune supports the following variables: the value of ``workspace_root`` is not constant and depends on whether your project is vendored or not - ``CC`` is the C compiler command line (list made of the compiler - name followed by its flags) that was used to compile OCaml in the - current build context + name followed by its flags) that will be used to compile foreign code. For more details about its content see :ref:`this section `. - ``CXX`` is the C++ compiler command line being used in the current build context - ``ocaml_bin`` is the path where ``ocamlc`` lives @@ -1243,3 +1242,24 @@ foreign archive is a bit like a foreign library, hence the name of the stanza. Foreign archives are particularly useful when embedding a library written in a foreign language and/or built with another build system. See :ref:`foreign-sandboxing` for more details. + +.. _flags-flow: + +Flags +----- + +Depending on the :ref:`always-add-cflags` option, the base `:standard` set of +flags for C will contain only ``ocamlc_cflags`` or both ``ocamlc_cflags`` and +`ocamlc_cflags`. + +There are multiple levels where one can declare custom flags (using the +:ref:`ordered-set-language`), and each level inherits the flags of the previous +one in its `:standard` set: + +- In the global `env` definition of a `dune-workspace` file +- In the per-context `env` definitions in a `dune-workspace` file +- In the env definition of a `dune` file +- In a `foreign_` field of an executable or a library + +The ``%{cc}`` :ref:`variable ` will contain the flags from the first +three levels only. From 003b4dedd44b5326cf001727fd95f1d75794e3ae Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Ulysse=20G=C3=A9rard?= Date: Sat, 24 Oct 2020 13:04:15 +0200 Subject: [PATCH 12/24] Auto enable on Dune >= 3.0 MIME-Version: 1.0 Content-Type: text/plain; charset=UTF-8 Content-Transfer-Encoding: 8bit Signed-off-by: Ulysse Gérard --- src/dune_engine/dune_project.ml | 6 ++++-- src/dune_rules/foreign_rules.ml | 1 - src/dune_rules/super_context.ml | 1 - 3 files changed, 4 insertions(+), 4 deletions(-) diff --git a/src/dune_engine/dune_project.ml b/src/dune_engine/dune_project.ml index a3a974f70e3..21554c39b03 100644 --- a/src/dune_engine/dune_project.ml +++ b/src/dune_engine/dune_project.ml @@ -615,7 +615,7 @@ let infer ~dir packages = ; dune_version = lang.version ; allow_approx_merlin = true ; generate_opam_files = false - ; always_add_cflags = true + ; always_add_cflags = lang.version < (3, 0) ; file_key ; dialects = Dialect.DB.builtin ; explicit_js_mode @@ -801,7 +801,9 @@ let parse ~dir ~lang ~opam_packages ~file = let generate_opam_files = Option.value ~default:false generate_opam_files in - let always_add_cflags = Option.value ~default:true always_add_cflags in + let always_add_cflags = + Option.value ~default:(dune_version < (3, 0)) always_add_cflags + in let cram = match cram with | None -> false diff --git a/src/dune_rules/foreign_rules.ml b/src/dune_rules/foreign_rules.ml index ad8bec93d94..6951e409bee 100644 --- a/src/dune_rules/foreign_rules.ml +++ b/src/dune_rules/foreign_rules.ml @@ -89,7 +89,6 @@ let build_c ~kind ~sctx ~dir ~expander ~include_flags (loc, src, dst) = ; Fdo.c_flags ctx ] else - (* TODO DUNE3 make this the default behavior *) Fdo.c_flags ctx | Foreign_language.Cxx -> Fdo.cxx_flags ctx in diff --git a/src/dune_rules/super_context.ml b/src/dune_rules/super_context.ml index 7fb1ca975f4..dde51c23e74 100644 --- a/src/dune_rules/super_context.ml +++ b/src/dune_rules/super_context.ml @@ -9,7 +9,6 @@ let default_context_flags (ctx : Context.t) ~project = in let c = if not (Dune_project.always_add_cflags project) then - (* TODO DUNE3 make this the default behavior *) cflags @ Ocaml_config.ocamlc_cppflags ctx.ocaml_config else cflags From 7abd6ac619e6c0f720761575c462084839e4df95 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Ulysse=20G=C3=A9rard?= Date: Wed, 4 Nov 2020 15:18:07 +0100 Subject: [PATCH 13/24] Distinguish between default and `true` values of the new option MIME-Version: 1.0 Content-Type: text/plain; charset=UTF-8 Content-Transfer-Encoding: 8bit Signed-off-by: Ulysse Gérard --- src/dune_engine/dune_project.ml | 15 +++++++++++---- src/dune_engine/dune_project.mli | 2 +- src/dune_rules/foreign_rules.ml | 9 +++++---- src/dune_rules/super_context.ml | 7 ++++--- 4 files changed, 21 insertions(+), 12 deletions(-) diff --git a/src/dune_engine/dune_project.ml b/src/dune_engine/dune_project.ml index 21554c39b03..add3f6c2e56 100644 --- a/src/dune_engine/dune_project.ml +++ b/src/dune_engine/dune_project.ml @@ -162,7 +162,7 @@ type t = ; dune_version : Dune_lang.Syntax.Version.t ; allow_approx_merlin : bool ; generate_opam_files : bool - ; always_add_cflags : bool + ; always_add_cflags : bool option ; file_key : File_key.t ; dialects : Dialect.DB.t ; explicit_js_mode : bool @@ -239,7 +239,7 @@ let to_dyn ; ("dune_version", Dune_lang.Syntax.Version.to_dyn dune_version) ; ("allow_approx_merlin", bool allow_approx_merlin) ; ("generate_opam_files", bool generate_opam_files) - ; ("always_add_cflags", bool always_add_cflags) + ; ("always_add_cflags", option bool always_add_cflags) ; ("file_key", string file_key) ; ("dialects", Dialect.DB.to_dyn dialects) ; ("explicit_js_mode", bool explicit_js_mode) @@ -615,7 +615,11 @@ let infer ~dir packages = ; dune_version = lang.version ; allow_approx_merlin = true ; generate_opam_files = false - ; always_add_cflags = lang.version < (3, 0) + ; always_add_cflags = + ( if lang.version < (3, 0) then + None + else + Some false ) ; file_key ; dialects = Dialect.DB.builtin ; explicit_js_mode @@ -802,7 +806,10 @@ let parse ~dir ~lang ~opam_packages ~file = Option.value ~default:false generate_opam_files in let always_add_cflags = - Option.value ~default:(dune_version < (3, 0)) always_add_cflags + match always_add_cflags with + | None when dune_version >= (3, 0) -> Some false + | None -> None + | some -> some in let cram = match cram with diff --git a/src/dune_engine/dune_project.mli b/src/dune_engine/dune_project.mli index 8b0d13ff59d..770b21c0707 100644 --- a/src/dune_engine/dune_project.mli +++ b/src/dune_engine/dune_project.mli @@ -67,7 +67,7 @@ val allow_approx_merlin : t -> bool val generate_opam_files : t -> bool -val always_add_cflags : t -> bool +val always_add_cflags : t -> bool option val dialects : t -> Dialect.DB.t diff --git a/src/dune_rules/foreign_rules.ml b/src/dune_rules/foreign_rules.ml index 6951e409bee..c253d89526e 100644 --- a/src/dune_rules/foreign_rules.ml +++ b/src/dune_rules/foreign_rules.ml @@ -79,17 +79,18 @@ let build_c ~kind ~sctx ~dir ~expander ~include_flags (loc, src, dst) = let flags = let ctx_flags = match kind with - | Foreign_language.C -> + | Foreign_language.C -> ( let cfg = ctx.ocaml_config in - if Dune_project.always_add_cflags project then + match Dune_project.always_add_cflags project with + | None + | Some true -> (* In dune < 2.8 flags from ocamlc_config are always added *) List.concat [ Ocaml_config.ocamlc_cflags cfg ; Ocaml_config.ocamlc_cppflags cfg ; Fdo.c_flags ctx ] - else - Fdo.c_flags ctx + | Some false -> Fdo.c_flags ctx ) | Foreign_language.Cxx -> Fdo.cxx_flags ctx in let flags = Foreign.Source.flags src in diff --git a/src/dune_rules/super_context.ml b/src/dune_rules/super_context.ml index dde51c23e74..4e60e7bace0 100644 --- a/src/dune_rules/super_context.ml +++ b/src/dune_rules/super_context.ml @@ -8,10 +8,11 @@ let default_context_flags (ctx : Context.t) ~project = List.filter cflags ~f:(fun s -> not (String.is_prefix s ~prefix:"-std=")) in let c = - if not (Dune_project.always_add_cflags project) then - cflags @ Ocaml_config.ocamlc_cppflags ctx.ocaml_config - else + match Dune_project.always_add_cflags project with + | None + | Some true -> cflags + | Some false -> cflags @ Ocaml_config.ocamlc_cppflags ctx.ocaml_config in Foreign_language.Dict.make ~c ~cxx From 96bf5b4deeef4db29a23b178a6649d5ca7af49d0 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Ulysse=20G=C3=A9rard?= Date: Wed, 4 Nov 2020 15:19:06 +0100 Subject: [PATCH 14/24] Add a warning when lang >= 2.8, new option is missing and :standard sert overriden MIME-Version: 1.0 Content-Type: text/plain; charset=UTF-8 Content-Transfer-Encoding: 8bit Signed-off-by: Ulysse Gérard --- src/dune_rules/foreign_rules.ml | 25 +++++++++++++++++++++++++ 1 file changed, 25 insertions(+) diff --git a/src/dune_rules/foreign_rules.ml b/src/dune_rules/foreign_rules.ml index c253d89526e..c5c74694d0d 100644 --- a/src/dune_rules/foreign_rules.ml +++ b/src/dune_rules/foreign_rules.ml @@ -94,6 +94,31 @@ let build_c ~kind ~sctx ~dir ~expander ~include_flags (loc, src, dst) = | Foreign_language.Cxx -> Fdo.cxx_flags ctx in let flags = Foreign.Source.flags src in + (* DUNE3 will have [always_add_cflags] disabled by default. To guide users + toward this change we emit a warning when dune_lang is >= 1.8, + [always_add_cflags] is not specified in the [dune-project] file (thus + defaulting to [true]) and the [:standard] set of flags has been overriden *) + let has_standard = + Ordered_set_lang.Unexpanded.encode flags + |> List.map ~f:Dune_lang.to_string + |> List.exists ~f:(String.equal ":standard") + in + if + Dune_project.dune_version project >= (2, 8) + && Option.is_none (Dune_project.always_add_cflags project) + && not has_standard + then + User_warning.emit ~loc + [ Pp.text + "The flag set for these foreign sources overrides the `:standard` \ + set of flags. However the flags in this standard set are still \ + added to the compiler arguments by Dune. This might cause \ + unexpected issues. You can disable this warning by defining the \ + option `(always_add_cflags )` in your `dune-project` file. \ + Setting this option to `false` will effectively prevent Dune from \ + silently adding c-flags to the compiler arguments which is the \ + new recommended behaviour." + ]; Super_context.foreign_flags sctx ~dir ~expander ~flags ~language:kind |> Build.map ~f:(List.append ctx_flags) in From c7b47ddfae9d166e4eb7abd73506bd7d92c2cb87 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Ulysse=20G=C3=A9rard?= Date: Wed, 4 Nov 2020 15:19:25 +0100 Subject: [PATCH 15/24] Update test MIME-Version: 1.0 Content-Type: text/plain; charset=UTF-8 Content-Transfer-Encoding: 8bit Signed-off-by: Ulysse Gérard --- .../blackbox-tests/test-cases/c-flags.t/run.t | 26 ++++++++++++++++--- 1 file changed, 23 insertions(+), 3 deletions(-) diff --git a/test/blackbox-tests/test-cases/c-flags.t/run.t b/test/blackbox-tests/test-cases/c-flags.t/run.t index 117168d012a..b4ca49f033e 100644 --- a/test/blackbox-tests/test-cases/c-flags.t/run.t +++ b/test/blackbox-tests/test-cases/c-flags.t/run.t @@ -19,7 +19,28 @@ always_add_cflags = false > (lang dune 2.8) $ dune rules -m foo.o | tr -s '\t\n\\' ' ' > out_foo - $ dune rules -m bar.o | sed "s,bar,foo," | tr -s '\t\n\\' ' ' > out_bar + File "dune", line 4, characters 36-39: + 4 | (foreign_stubs (language c) (names bar) (flags))) + ^^^ + Warning: The flag set for these foreign sources overrides the `:standard` set + of flags. However the flags in this standard set are still added to the + compiler arguments by Dune. This might cause unexpected issues. You can + disable this warning by defining the option `(always_add_cflags )` in + your `dune-project` file. Setting this option to `false` will effectively + prevent Dune from silently adding c-flags to the compiler arguments which is + the new recommended behaviour. + + $ dune rules -m bar.o | tr -s '\t\n\\' ' ' > out_bar + File "dune", line 4, characters 36-39: + 4 | (foreign_stubs (language c) (names bar) (flags))) + ^^^ + Warning: The flag set for these foreign sources overrides the `:standard` set + of flags. However the flags in this standard set are still added to the + compiler arguments by Dune. This might cause unexpected issues. You can + disable this warning by defining the option `(always_add_cflags )` in + your `dune-project` file. Setting this option to `false` will effectively + prevent Dune from silently adding c-flags to the compiler arguments which is + the new recommended behaviour. Ocamlc_cflags are duplicated if the :standard set is kept: $ cat out_foo | grep -ce "${O_CCF} ${O_CCPPF} ${O_CCF}" @@ -31,7 +52,6 @@ ocamlc_cpp flags appear in the compiler command line: $ cat out_foo | grep -ce "${O_CCF} ${O_CCPPF}" 1 - $ cat out_bar | grep -ce "${O_CCF} ${O_CCPPF}" 1 @@ -43,7 +63,7 @@ always_add_cflags = true > (always_add_cflags false) $ dune rules -m foo.o | tr -s '\t\n\\' ' ' > out_foo - $ dune rules -m bar.o | sed "s,bar,foo," | tr -s '\t\n\\' ' ' > out_bar + $ dune rules -m bar.o | tr -s '\t\n\\' ' ' > out_bar Ocamlc_cflags are not duplicated anymore: $ cat out_foo | grep -ce "${O_CCF} ${O_CCPPF} ${O_CCF}" From 3ce2e0d815e09738089b303b445face408a680f2 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Ulysse=20G=C3=A9rard?= Date: Tue, 10 Nov 2020 14:04:12 +0100 Subject: [PATCH 16/24] Rename option to `future_c_and_cxx_flags_handling` MIME-Version: 1.0 Content-Type: text/plain; charset=UTF-8 Content-Transfer-Encoding: 8bit Signed-off-by: Ulysse Gérard --- CHANGES.md | 7 ++-- doc/dune-files.rst | 6 +-- src/dune_engine/dune_project.ml | 23 ++++++------ src/dune_engine/dune_project.mli | 2 +- src/dune_rules/foreign_rules.ml | 25 +++++++------ src/dune_rules/super_context.ml | 6 +-- .../blackbox-tests/test-cases/c-flags.t/run.t | 37 ++++++++++--------- .../var-cc.t/new_ff_handling/dune-project | 2 +- .../test-cases/variables/var-cc.t/run.t | 2 +- 9 files changed, 57 insertions(+), 53 deletions(-) diff --git a/CHANGES.md b/CHANGES.md index 54228a1aa50..3b57fee7066 100644 --- a/CHANGES.md +++ b/CHANGES.md @@ -79,9 +79,10 @@ Unreleased - Avoid pager when running `$ git diff` (#3912, @AltGr) - Add the option `new_foreign_flags_handling` to `dune-project` that disables -- Add the option `always_add_cflags` to `dune-project` that disables - the unconditional use of the `ocamlc_cflags` and `ocamlc_cppflags` from - `ocamlc -config` in C compiler calls. These flags are present in the + +- Add the option `future_c_and_cxx_flags_handling` to `dune-project` that + disables the unconditional use of the `ocamlc_cflags` and `ocamlc_cppflags` + from `ocamlc -config` in C compiler calls. These flags are present in the `:standard` set instead. (#3875, fix #3718, @voodoos) 2.7.1 (2/09/2020) diff --git a/doc/dune-files.rst b/doc/dune-files.rst index 530eec37b2e..db1c9abefc2 100644 --- a/doc/dune-files.rst +++ b/doc/dune-files.rst @@ -287,7 +287,7 @@ language: The syntax is as a list of the following elements: .. _always-add-cflags: -always_add_cflags +future_c_and_cxx_flags_handling ----------------- Since Dune 2.8, it is possible to deactivate the systematic prepending of flags @@ -296,11 +296,11 @@ adding the following field to the ``dune-project`` file: .. code:: scheme - (always_add_cflags false) + (future_c_and_cxx_flags_handling true) In this mode, dune will populate the ``:standard`` set of C flags with the content of ``ocamlc_cflags`` and ``ocamlc_cppflags``. These flags can be -completed or overridden using the :ref:`ordered-set-language`. +completed or overridden using the :ref:`ordered-set-language`. dune ==== diff --git a/src/dune_engine/dune_project.ml b/src/dune_engine/dune_project.ml index add3f6c2e56..c66a8ce057f 100644 --- a/src/dune_engine/dune_project.ml +++ b/src/dune_engine/dune_project.ml @@ -162,7 +162,7 @@ type t = ; dune_version : Dune_lang.Syntax.Version.t ; allow_approx_merlin : bool ; generate_opam_files : bool - ; always_add_cflags : bool option + ; future_c_and_cxx_flags_handling : bool option ; file_key : File_key.t ; dialects : Dialect.DB.t ; explicit_js_mode : bool @@ -195,7 +195,7 @@ let allow_approx_merlin t = t.allow_approx_merlin let generate_opam_files t = t.generate_opam_files -let always_add_cflags t = t.always_add_cflags +let future_c_and_cxx_flags_handling t = t.future_c_and_cxx_flags_handling let dialects t = t.dialects @@ -216,7 +216,7 @@ let to_dyn ; dune_version ; allow_approx_merlin ; generate_opam_files - ; always_add_cflags + ; future_c_and_cxx_flags_handling ; file_key ; dialects ; explicit_js_mode @@ -239,7 +239,8 @@ let to_dyn ; ("dune_version", Dune_lang.Syntax.Version.to_dyn dune_version) ; ("allow_approx_merlin", bool allow_approx_merlin) ; ("generate_opam_files", bool generate_opam_files) - ; ("always_add_cflags", option bool always_add_cflags) + ; ( "future_c_and_cxx_flags_handling" + , option bool future_c_and_cxx_flags_handling ) ; ("file_key", string file_key) ; ("dialects", Dialect.DB.to_dyn dialects) ; ("explicit_js_mode", bool explicit_js_mode) @@ -615,11 +616,11 @@ let infer ~dir packages = ; dune_version = lang.version ; allow_approx_merlin = true ; generate_opam_files = false - ; always_add_cflags = + ; future_c_and_cxx_flags_handling = ( if lang.version < (3, 0) then None else - Some false ) + Some true ) ; file_key ; dialects = Dialect.DB.builtin ; explicit_js_mode @@ -685,8 +686,8 @@ let parse ~dir ~lang ~opam_packages ~file = and+ generate_opam_files = field_o_b "generate_opam_files" ~check:(Dune_lang.Syntax.since Stanza.syntax (1, 10)) - and+ always_add_cflags = - field_o_b "always_add_cflags" + and+ future_c_and_cxx_flags_handling = + field_o_b "future_c_and_cxx_flags_handling" ~check:(Dune_lang.Syntax.since Stanza.syntax (2, 8)) and+ dialects = multi_field "dialect" @@ -805,8 +806,8 @@ let parse ~dir ~lang ~opam_packages ~file = let generate_opam_files = Option.value ~default:false generate_opam_files in - let always_add_cflags = - match always_add_cflags with + let future_c_and_cxx_flags_handling = + match future_c_and_cxx_flags_handling with | None when dune_version >= (3, 0) -> Some false | None -> None | some -> some @@ -839,7 +840,7 @@ let parse ~dir ~lang ~opam_packages ~file = ; dune_version ; allow_approx_merlin ; generate_opam_files - ; always_add_cflags + ; future_c_and_cxx_flags_handling ; dialects ; explicit_js_mode ; format_config diff --git a/src/dune_engine/dune_project.mli b/src/dune_engine/dune_project.mli index 770b21c0707..a5a52a7e692 100644 --- a/src/dune_engine/dune_project.mli +++ b/src/dune_engine/dune_project.mli @@ -67,7 +67,7 @@ val allow_approx_merlin : t -> bool val generate_opam_files : t -> bool -val always_add_cflags : t -> bool option +val future_c_and_cxx_flags_handling : t -> bool option val dialects : t -> Dialect.DB.t diff --git a/src/dune_rules/foreign_rules.ml b/src/dune_rules/foreign_rules.ml index c5c74694d0d..64e707240e9 100644 --- a/src/dune_rules/foreign_rules.ml +++ b/src/dune_rules/foreign_rules.ml @@ -81,23 +81,24 @@ let build_c ~kind ~sctx ~dir ~expander ~include_flags (loc, src, dst) = match kind with | Foreign_language.C -> ( let cfg = ctx.ocaml_config in - match Dune_project.always_add_cflags project with + match Dune_project.future_c_and_cxx_flags_handling project with | None - | Some true -> + | Some false -> (* In dune < 2.8 flags from ocamlc_config are always added *) List.concat [ Ocaml_config.ocamlc_cflags cfg ; Ocaml_config.ocamlc_cppflags cfg ; Fdo.c_flags ctx ] - | Some false -> Fdo.c_flags ctx ) + | Some true -> Fdo.c_flags ctx ) | Foreign_language.Cxx -> Fdo.cxx_flags ctx in let flags = Foreign.Source.flags src in - (* DUNE3 will have [always_add_cflags] disabled by default. To guide users - toward this change we emit a warning when dune_lang is >= 1.8, - [always_add_cflags] is not specified in the [dune-project] file (thus - defaulting to [true]) and the [:standard] set of flags has been overriden *) + (* DUNE3 will have [future_c_and_cxx_flags_handling] disabled by default. To + guide users toward this change we emit a warning when dune_lang is >= + 1.8, [future_c_and_cxx_flags_handling] is not specified in the + [dune-project] file (thus defaulting to [true]) and the [:standard] set + of flags has been overriden *) let has_standard = Ordered_set_lang.Unexpanded.encode flags |> List.map ~f:Dune_lang.to_string @@ -105,7 +106,7 @@ let build_c ~kind ~sctx ~dir ~expander ~include_flags (loc, src, dst) = in if Dune_project.dune_version project >= (2, 8) - && Option.is_none (Dune_project.always_add_cflags project) + && Option.is_none (Dune_project.future_c_and_cxx_flags_handling project) && not has_standard then User_warning.emit ~loc @@ -114,10 +115,10 @@ let build_c ~kind ~sctx ~dir ~expander ~include_flags (loc, src, dst) = set of flags. However the flags in this standard set are still \ added to the compiler arguments by Dune. This might cause \ unexpected issues. You can disable this warning by defining the \ - option `(always_add_cflags )` in your `dune-project` file. \ - Setting this option to `false` will effectively prevent Dune from \ - silently adding c-flags to the compiler arguments which is the \ - new recommended behaviour." + option `(future_c_and_cxx_flags_handling )` in your \ + `dune-project` file. Setting this option to `true` will \ + effectively prevent Dune from silently adding c-flags to the \ + compiler arguments which is the new recommended behaviour." ]; Super_context.foreign_flags sctx ~dir ~expander ~flags ~language:kind |> Build.map ~f:(List.append ctx_flags) diff --git a/src/dune_rules/super_context.ml b/src/dune_rules/super_context.ml index 4e60e7bace0..c6339feacbe 100644 --- a/src/dune_rules/super_context.ml +++ b/src/dune_rules/super_context.ml @@ -8,11 +8,11 @@ let default_context_flags (ctx : Context.t) ~project = List.filter cflags ~f:(fun s -> not (String.is_prefix s ~prefix:"-std=")) in let c = - match Dune_project.always_add_cflags project with + match Dune_project.future_c_and_cxx_flags_handling project with | None - | Some true -> + | Some false -> cflags - | Some false -> cflags @ Ocaml_config.ocamlc_cppflags ctx.ocaml_config + | Some true -> cflags @ Ocaml_config.ocamlc_cppflags ctx.ocaml_config in Foreign_language.Dict.make ~c ~cxx diff --git a/test/blackbox-tests/test-cases/c-flags.t/run.t b/test/blackbox-tests/test-cases/c-flags.t/run.t index b4ca49f033e..a91a465e112 100644 --- a/test/blackbox-tests/test-cases/c-flags.t/run.t +++ b/test/blackbox-tests/test-cases/c-flags.t/run.t @@ -12,7 +12,7 @@ bar.c is built with an "empty" set of flags. $ O_CCPPF=${O_CCPPF%% } -always_add_cflags = false +future_c_and_cxx_flags_handling = default (false) ================================== $ cat >dune-project <)` in - your `dune-project` file. Setting this option to `false` will effectively - prevent Dune from silently adding c-flags to the compiler arguments which is - the new recommended behaviour. + disable this warning by defining the option `(future_c_and_cxx_flags_handling + )` in your `dune-project` file. Setting this option to `true` will + effectively prevent Dune from silently adding c-flags to the compiler + arguments which is the new recommended behaviour. $ dune rules -m bar.o | tr -s '\t\n\\' ' ' > out_bar File "dune", line 4, characters 36-39: @@ -37,10 +37,10 @@ always_add_cflags = false Warning: The flag set for these foreign sources overrides the `:standard` set of flags. However the flags in this standard set are still added to the compiler arguments by Dune. This might cause unexpected issues. You can - disable this warning by defining the option `(always_add_cflags )` in - your `dune-project` file. Setting this option to `false` will effectively - prevent Dune from silently adding c-flags to the compiler arguments which is - the new recommended behaviour. + disable this warning by defining the option `(future_c_and_cxx_flags_handling + )` in your `dune-project` file. Setting this option to `true` will + effectively prevent Dune from silently adding c-flags to the compiler + arguments which is the new recommended behaviour. Ocamlc_cflags are duplicated if the :standard set is kept: $ cat out_foo | grep -ce "${O_CCF} ${O_CCPPF} ${O_CCF}" @@ -55,12 +55,12 @@ ocamlc_cpp flags appear in the compiler command line: $ cat out_bar | grep -ce "${O_CCF} ${O_CCPPF}" 1 -always_add_cflags = true +future_c_and_cxx_flags_handling = true ================================= $ cat >dune-project < (lang dune 2.8) - > (always_add_cflags false) + > (future_c_and_cxx_flags_handling true) $ dune rules -m foo.o | tr -s '\t\n\\' ' ' > out_foo $ dune rules -m bar.o | tr -s '\t\n\\' ' ' > out_bar @@ -84,17 +84,18 @@ ocamlc_cpp are effectively removed from the compiler command line 0 [1] -always_add_cflags = true but dune < 2.8 +future_c_and_cxx_flags_handling = true but dune < 2.8 ================================================ $ cat >dune-project < (lang dune 2.7) - > (always_add_cflags false) + > (future_c_and_cxx_flags_handling true) $ dune rules - File "dune-project", line 2, characters 0-25: - 2 | (always_add_cflags false) - ^^^^^^^^^^^^^^^^^^^^^^^^^ - Error: 'always_add_cflags' is only available since version 2.8 of the dune - language. Please update your dune-project file to have (lang dune 2.8). + File "dune-project", line 2, characters 0-38: + 2 | (future_c_and_cxx_flags_handling true) + ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ + Error: 'future_c_and_cxx_flags_handling' is only available since version 2.8 + of the dune language. Please update your dune-project file to have (lang dune + 2.8). [1] diff --git a/test/blackbox-tests/test-cases/variables/var-cc.t/new_ff_handling/dune-project b/test/blackbox-tests/test-cases/variables/var-cc.t/new_ff_handling/dune-project index c9ed3b53bf9..03e9ffc4d9e 100644 --- a/test/blackbox-tests/test-cases/variables/var-cc.t/new_ff_handling/dune-project +++ b/test/blackbox-tests/test-cases/variables/var-cc.t/new_ff_handling/dune-project @@ -1,2 +1,2 @@ (lang dune 2.8) -(always_add_cflags false) \ No newline at end of file +(future_c_and_cxx_flags_handling true) diff --git a/test/blackbox-tests/test-cases/variables/var-cc.t/run.t b/test/blackbox-tests/test-cases/variables/var-cc.t/run.t index a14c6e837ed..1d01524db48 100644 --- a/test/blackbox-tests/test-cases/variables/var-cc.t/run.t +++ b/test/blackbox-tests/test-cases/variables/var-cc.t/run.t @@ -36,7 +36,7 @@ With redefining env flags $ dune build @cc | sed "s,${O_CC} -fPIC,OK," OK -Since dune 2.8, when using the always_add_cflags option the :standard +Since dune 2.8, when using the future_c_and_cxx_flags_handling option the :standard set of flag and thus the %{cc} variable contain both the cflags and cppflags from ocaml config. These flags are not added systematically anymore to the compiler command line. From a91f10505ab894bf0276f350b4af5b9a4b79ca01 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Ulysse=20G=C3=A9rard?= Date: Mon, 16 Nov 2020 18:25:27 +0100 Subject: [PATCH 17/24] Add has_standard function to Orderd_set_lang MIME-Version: 1.0 Content-Type: text/plain; charset=UTF-8 Content-Transfer-Encoding: 8bit Signed-off-by: Ulysse Gérard --- src/dune_rules/foreign_rules.ml | 6 +----- src/dune_rules/ordered_set_lang.ml | 11 +++++++++++ src/dune_rules/ordered_set_lang.mli | 2 ++ 3 files changed, 14 insertions(+), 5 deletions(-) diff --git a/src/dune_rules/foreign_rules.ml b/src/dune_rules/foreign_rules.ml index 64e707240e9..8e5917d1603 100644 --- a/src/dune_rules/foreign_rules.ml +++ b/src/dune_rules/foreign_rules.ml @@ -99,11 +99,7 @@ let build_c ~kind ~sctx ~dir ~expander ~include_flags (loc, src, dst) = 1.8, [future_c_and_cxx_flags_handling] is not specified in the [dune-project] file (thus defaulting to [true]) and the [:standard] set of flags has been overriden *) - let has_standard = - Ordered_set_lang.Unexpanded.encode flags - |> List.map ~f:Dune_lang.to_string - |> List.exists ~f:(String.equal ":standard") - in + let has_standard = Ordered_set_lang.Unexpanded.has_standard flags in if Dune_project.dune_version project >= (2, 8) && Option.is_none (Dune_project.future_c_and_cxx_flags_handling project) diff --git a/src/dune_rules/ordered_set_lang.ml b/src/dune_rules/ordered_set_lang.ml index 10af9380680..91e7917db26 100644 --- a/src/dune_rules/ordered_set_lang.ml +++ b/src/dune_rules/ordered_set_lang.ml @@ -299,6 +299,17 @@ module Unexpanded = struct in loop t.ast + let has_standard t = + let rec loop ast = + match ast with + | Ast.Standard -> true + | Ast.Element _ -> false + | Ast.Union l -> List.exists ~f:loop l + | Ast.Diff (l, r) -> loop l || loop r + | Ast.Include _ -> false + in + loop t.ast + type position = | Pos | Neg diff --git a/src/dune_rules/ordered_set_lang.mli b/src/dune_rules/ordered_set_lang.mli index 68c5a6ec9ab..d12258bb6c0 100644 --- a/src/dune_rules/ordered_set_lang.mli +++ b/src/dune_rules/ordered_set_lang.mli @@ -62,6 +62,8 @@ module Unexpanded : sig val has_special_forms : t -> bool + val has_standard : t -> bool + (** List of files needed to expand this set *) val files : t -> f:(String_with_vars.t -> Path.t) -> Path.Set.t From 1684848e923d0e729622661c2e1bd6f844be0e17 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Ulysse=20G=C3=A9rard?= Date: Mon, 16 Nov 2020 18:53:32 +0100 Subject: [PATCH 18/24] Add vendoring test function to File_tree MIME-Version: 1.0 Content-Type: text/plain; charset=UTF-8 Content-Transfer-Encoding: 8bit Signed-off-by: Ulysse Gérard --- bin/import.ml | 7 +------ bin/install_uninstall.ml | 7 +------ src/dune_engine/file_tree.ml | 5 +++++ src/dune_engine/file_tree.mli | 3 +++ src/dune_rules/super_context.ml | 10 +++------- 5 files changed, 13 insertions(+), 19 deletions(-) diff --git a/bin/import.ml b/bin/import.ml index 3680e49f129..38847f055d1 100644 --- a/bin/import.ml +++ b/bin/import.ml @@ -105,12 +105,7 @@ module Main = struct Package.Name.Map.filter workspace.conf.packages ~f:(fun pkg -> let vendored = let dir = Package.dir pkg in - match Dune_engine.File_tree.find_dir dir with - | None -> assert false - | Some d -> ( - match Dune_engine.File_tree.Dir.status d with - | Vendored -> true - | _ -> false ) + Dune_engine.File_tree.is_vendored dir in let name = Package.name pkg in let included = Package.Name.Set.mem names name in diff --git a/bin/install_uninstall.ml b/bin/install_uninstall.ml index 9e8df80e74e..908fe246e9e 100644 --- a/bin/install_uninstall.ml +++ b/bin/install_uninstall.ml @@ -314,12 +314,7 @@ let file_operations ~dry_run ~workspace : (module File_operations) = let package_is_vendored (pkg : Dune_engine.Package.t) = let dir = Package.dir pkg in - match Dune_engine.File_tree.find_dir dir with - | None -> assert false - | Some d -> ( - match Dune_engine.File_tree.Dir.status d with - | Vendored -> true - | _ -> false ) + Dune_engine.File_tree.is_vendored dir let install_uninstall ~what = let doc = sprintf "%s packages." (String.capitalize what) in diff --git a/src/dune_engine/file_tree.ml b/src/dune_engine/file_tree.ml index 2c2bb41dc0a..1c483732518 100644 --- a/src/dune_engine/file_tree.ml +++ b/src/dune_engine/file_tree.ml @@ -781,3 +781,8 @@ let find_dir_specified_on_command_line ~dir = [ Pp.textf "Don't know about directory %s specified on the command line!" (Path.Source.to_string_maybe_quoted dir) ] + +let is_vendored dir = + match find_dir dir with + | None -> false + | Some d -> Dir.status d = Vendored diff --git a/src/dune_engine/file_tree.mli b/src/dune_engine/file_tree.mli index 7663864d17f..6c5d36bc825 100644 --- a/src/dune_engine/file_tree.mli +++ b/src/dune_engine/file_tree.mli @@ -93,6 +93,9 @@ val files_of : Path.Source.t -> Path.Source.Set.t (** [true] iff the path is a directory *) val dir_exists : Path.Source.t -> bool +(** [true] iff the path is a vendored directory *) +val is_vendored : Path.Source.t -> bool + (** [true] iff the path is a file *) val file_exists : Path.Source.t -> bool diff --git a/src/dune_rules/super_context.ml b/src/dune_rules/super_context.ml index c6339feacbe..b2895115bed 100644 --- a/src/dune_rules/super_context.ml +++ b/src/dune_rules/super_context.ml @@ -313,13 +313,9 @@ let add_alias_action t alias ~dir ~loc ?locks ~stamp action = ~env alias ~loc ?locks ~stamp action let build_dir_is_vendored build_dir = - let opt = - let open Option.O in - let* src_dir = Path.Build.drop_build_context build_dir in - let+ src_dir = File_tree.find_dir src_dir in - Sub_dirs.Status.Vendored = File_tree.Dir.status src_dir - in - Option.value ~default:false opt + match Path.Build.drop_build_context build_dir with + | Some src_dir -> Dune_engine.File_tree.is_vendored src_dir + | None -> false let ocaml_flags t ~dir (spec : Ocaml_flags.Spec.t) = let expander = Env_tree.expander t.env_tree ~dir in From 1e2a703f7a3021d065ef98271d530d0c39885fd4 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Ulysse=20G=C3=A9rard?= Date: Mon, 16 Nov 2020 19:03:35 +0100 Subject: [PATCH 19/24] No warning for vendor dirs MIME-Version: 1.0 Content-Type: text/plain; charset=UTF-8 Content-Transfer-Encoding: 8bit Signed-off-by: Ulysse Gérard --- src/dune_rules/foreign_rules.ml | 7 ++++++- 1 file changed, 6 insertions(+), 1 deletion(-) diff --git a/src/dune_rules/foreign_rules.ml b/src/dune_rules/foreign_rules.ml index 8e5917d1603..1fa574b68a1 100644 --- a/src/dune_rules/foreign_rules.ml +++ b/src/dune_rules/foreign_rules.ml @@ -100,10 +100,15 @@ let build_c ~kind ~sctx ~dir ~expander ~include_flags (loc, src, dst) = [dune-project] file (thus defaulting to [true]) and the [:standard] set of flags has been overriden *) let has_standard = Ordered_set_lang.Unexpanded.has_standard flags in + let is_vendored = + match Path.Build.drop_build_context dir with + | Some src_dir -> Dune_engine.File_tree.is_vendored src_dir + | None -> false + in if Dune_project.dune_version project >= (2, 8) && Option.is_none (Dune_project.future_c_and_cxx_flags_handling project) - && not has_standard + && (not is_vendored) && not has_standard then User_warning.emit ~loc [ Pp.text From 7219c29cd23054411d059467c18b5bfbb43ceee3 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Ulysse=20G=C3=A9rard?= Date: Mon, 16 Nov 2020 19:04:55 +0100 Subject: [PATCH 20/24] Add test for no warning vendor MIME-Version: 1.0 Content-Type: text/plain; charset=UTF-8 Content-Transfer-Encoding: 8bit Signed-off-by: Ulysse Gérard --- test/blackbox-tests/test-cases/c-flags.t/dune | 2 ++ test/blackbox-tests/test-cases/c-flags.t/run.t | 5 +++++ test/blackbox-tests/test-cases/c-flags.t/vendor/barv.c | 0 test/blackbox-tests/test-cases/c-flags.t/vendor/dune | 3 +++ 4 files changed, 10 insertions(+) create mode 100644 test/blackbox-tests/test-cases/c-flags.t/vendor/barv.c create mode 100644 test/blackbox-tests/test-cases/c-flags.t/vendor/dune diff --git a/test/blackbox-tests/test-cases/c-flags.t/dune b/test/blackbox-tests/test-cases/c-flags.t/dune index 05c4ef05bb6..655b699921b 100644 --- a/test/blackbox-tests/test-cases/c-flags.t/dune +++ b/test/blackbox-tests/test-cases/c-flags.t/dune @@ -2,3 +2,5 @@ (name test) (foreign_stubs (language c) (names foo)) (foreign_stubs (language c) (names bar) (flags))) + +(vendored_dirs vendor) \ No newline at end of file diff --git a/test/blackbox-tests/test-cases/c-flags.t/run.t b/test/blackbox-tests/test-cases/c-flags.t/run.t index a91a465e112..195cee9bad6 100644 --- a/test/blackbox-tests/test-cases/c-flags.t/run.t +++ b/test/blackbox-tests/test-cases/c-flags.t/run.t @@ -42,6 +42,10 @@ future_c_and_cxx_flags_handling = default (false) effectively prevent Dune from silently adding c-flags to the compiler arguments which is the new recommended behaviour. +No warning in vendored subfolder + + $ dune build vendor/barv.o + Ocamlc_cflags are duplicated if the :standard set is kept: $ cat out_foo | grep -ce "${O_CCF} ${O_CCPPF} ${O_CCF}" 1 @@ -99,3 +103,4 @@ future_c_and_cxx_flags_handling = true but dune < 2.8 of the dune language. Please update your dune-project file to have (lang dune 2.8). [1] + diff --git a/test/blackbox-tests/test-cases/c-flags.t/vendor/barv.c b/test/blackbox-tests/test-cases/c-flags.t/vendor/barv.c new file mode 100644 index 00000000000..e69de29bb2d diff --git a/test/blackbox-tests/test-cases/c-flags.t/vendor/dune b/test/blackbox-tests/test-cases/c-flags.t/vendor/dune new file mode 100644 index 00000000000..5c45502bdc6 --- /dev/null +++ b/test/blackbox-tests/test-cases/c-flags.t/vendor/dune @@ -0,0 +1,3 @@ +(library + (name testv) +(foreign_stubs (language c) (names barv) (flags))) From ba0189796f97874b18d19f089f0737b7ea3b7249 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Ulysse=20G=C3=A9rard?= Date: Thu, 19 Nov 2020 12:57:10 +0100 Subject: [PATCH 21/24] Rename option to 'use_standard_c_and_cxx_flags' MIME-Version: 1.0 Content-Type: text/plain; charset=UTF-8 Content-Transfer-Encoding: 8bit Signed-off-by: Ulysse Gérard --- CHANGES.md | 4 +--- doc/dune-files.rst | 6 ++--- src/dune_engine/dune_project.ml | 22 ++++++++--------- src/dune_engine/dune_project.mli | 2 +- src/dune_rules/foreign_rules.ml | 10 ++++---- src/dune_rules/super_context.ml | 2 +- .../blackbox-tests/test-cases/c-flags.t/run.t | 24 +++++++++---------- .../var-cc.t/new_ff_handling/dune-project | 2 +- .../test-cases/variables/var-cc.t/run.t | 2 +- 9 files changed, 36 insertions(+), 38 deletions(-) diff --git a/CHANGES.md b/CHANGES.md index 3b57fee7066..a91f849fe79 100644 --- a/CHANGES.md +++ b/CHANGES.md @@ -78,9 +78,7 @@ Unreleased - Avoid pager when running `$ git diff` (#3912, @AltGr) -- Add the option `new_foreign_flags_handling` to `dune-project` that disables - -- Add the option `future_c_and_cxx_flags_handling` to `dune-project` that +- Add the option `use_standard_c_and_cxx_flags` to `dune-project` that disables the unconditional use of the `ocamlc_cflags` and `ocamlc_cppflags` from `ocamlc -config` in C compiler calls. These flags are present in the `:standard` set instead. (#3875, fix #3718, @voodoos) diff --git a/doc/dune-files.rst b/doc/dune-files.rst index db1c9abefc2..00874c48e39 100644 --- a/doc/dune-files.rst +++ b/doc/dune-files.rst @@ -287,8 +287,8 @@ language: The syntax is as a list of the following elements: .. _always-add-cflags: -future_c_and_cxx_flags_handling ------------------ +use_standard_c_and_cxx_flags +---------------------------- Since Dune 2.8, it is possible to deactivate the systematic prepending of flags coming from ``ocamlc -config`` to the C compiler command line. This is done @@ -296,7 +296,7 @@ adding the following field to the ``dune-project`` file: .. code:: scheme - (future_c_and_cxx_flags_handling true) + (use_standard_c_and_cxx_flags true) In this mode, dune will populate the ``:standard`` set of C flags with the content of ``ocamlc_cflags`` and ``ocamlc_cppflags``. These flags can be diff --git a/src/dune_engine/dune_project.ml b/src/dune_engine/dune_project.ml index c66a8ce057f..e20f9bc8021 100644 --- a/src/dune_engine/dune_project.ml +++ b/src/dune_engine/dune_project.ml @@ -162,7 +162,7 @@ type t = ; dune_version : Dune_lang.Syntax.Version.t ; allow_approx_merlin : bool ; generate_opam_files : bool - ; future_c_and_cxx_flags_handling : bool option + ; use_standard_c_and_cxx_flags : bool option ; file_key : File_key.t ; dialects : Dialect.DB.t ; explicit_js_mode : bool @@ -195,7 +195,7 @@ let allow_approx_merlin t = t.allow_approx_merlin let generate_opam_files t = t.generate_opam_files -let future_c_and_cxx_flags_handling t = t.future_c_and_cxx_flags_handling +let use_standard_c_and_cxx_flags t = t.use_standard_c_and_cxx_flags let dialects t = t.dialects @@ -216,7 +216,7 @@ let to_dyn ; dune_version ; allow_approx_merlin ; generate_opam_files - ; future_c_and_cxx_flags_handling + ; use_standard_c_and_cxx_flags ; file_key ; dialects ; explicit_js_mode @@ -239,8 +239,8 @@ let to_dyn ; ("dune_version", Dune_lang.Syntax.Version.to_dyn dune_version) ; ("allow_approx_merlin", bool allow_approx_merlin) ; ("generate_opam_files", bool generate_opam_files) - ; ( "future_c_and_cxx_flags_handling" - , option bool future_c_and_cxx_flags_handling ) + ; ( "use_standard_c_and_cxx_flags" + , option bool use_standard_c_and_cxx_flags ) ; ("file_key", string file_key) ; ("dialects", Dialect.DB.to_dyn dialects) ; ("explicit_js_mode", bool explicit_js_mode) @@ -616,7 +616,7 @@ let infer ~dir packages = ; dune_version = lang.version ; allow_approx_merlin = true ; generate_opam_files = false - ; future_c_and_cxx_flags_handling = + ; use_standard_c_and_cxx_flags = ( if lang.version < (3, 0) then None else @@ -686,8 +686,8 @@ let parse ~dir ~lang ~opam_packages ~file = and+ generate_opam_files = field_o_b "generate_opam_files" ~check:(Dune_lang.Syntax.since Stanza.syntax (1, 10)) - and+ future_c_and_cxx_flags_handling = - field_o_b "future_c_and_cxx_flags_handling" + 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+ dialects = multi_field "dialect" @@ -806,8 +806,8 @@ let parse ~dir ~lang ~opam_packages ~file = let generate_opam_files = Option.value ~default:false generate_opam_files in - let future_c_and_cxx_flags_handling = - match future_c_and_cxx_flags_handling with + let use_standard_c_and_cxx_flags = + match use_standard_c_and_cxx_flags with | None when dune_version >= (3, 0) -> Some false | None -> None | some -> some @@ -840,7 +840,7 @@ let parse ~dir ~lang ~opam_packages ~file = ; dune_version ; allow_approx_merlin ; generate_opam_files - ; future_c_and_cxx_flags_handling + ; use_standard_c_and_cxx_flags ; dialects ; explicit_js_mode ; format_config diff --git a/src/dune_engine/dune_project.mli b/src/dune_engine/dune_project.mli index a5a52a7e692..26053cd5d24 100644 --- a/src/dune_engine/dune_project.mli +++ b/src/dune_engine/dune_project.mli @@ -67,7 +67,7 @@ val allow_approx_merlin : t -> bool val generate_opam_files : t -> bool -val future_c_and_cxx_flags_handling : t -> bool option +val use_standard_c_and_cxx_flags : t -> bool option val dialects : t -> Dialect.DB.t diff --git a/src/dune_rules/foreign_rules.ml b/src/dune_rules/foreign_rules.ml index 1fa574b68a1..11445dd4bd2 100644 --- a/src/dune_rules/foreign_rules.ml +++ b/src/dune_rules/foreign_rules.ml @@ -81,7 +81,7 @@ let build_c ~kind ~sctx ~dir ~expander ~include_flags (loc, src, dst) = match kind with | Foreign_language.C -> ( let cfg = ctx.ocaml_config in - match Dune_project.future_c_and_cxx_flags_handling project with + match Dune_project.use_standard_c_and_cxx_flags project with | None | Some false -> (* In dune < 2.8 flags from ocamlc_config are always added *) @@ -94,9 +94,9 @@ let build_c ~kind ~sctx ~dir ~expander ~include_flags (loc, src, dst) = | Foreign_language.Cxx -> Fdo.cxx_flags ctx in let flags = Foreign.Source.flags src in - (* DUNE3 will have [future_c_and_cxx_flags_handling] disabled by default. To + (* DUNE3 will have [use_standard_c_and_cxx_flags] disabled by default. To guide users toward this change we emit a warning when dune_lang is >= - 1.8, [future_c_and_cxx_flags_handling] is not specified in the + 1.8, [use_standard_c_and_cxx_flags] is not specified in the [dune-project] file (thus defaulting to [true]) and the [:standard] set of flags has been overriden *) let has_standard = Ordered_set_lang.Unexpanded.has_standard flags in @@ -107,7 +107,7 @@ let build_c ~kind ~sctx ~dir ~expander ~include_flags (loc, src, dst) = in if Dune_project.dune_version project >= (2, 8) - && Option.is_none (Dune_project.future_c_and_cxx_flags_handling project) + && Option.is_none (Dune_project.use_standard_c_and_cxx_flags project) && (not is_vendored) && not has_standard then User_warning.emit ~loc @@ -116,7 +116,7 @@ let build_c ~kind ~sctx ~dir ~expander ~include_flags (loc, src, dst) = set of flags. However the flags in this standard set are still \ added to the compiler arguments by Dune. This might cause \ unexpected issues. You can disable this warning by defining the \ - option `(future_c_and_cxx_flags_handling )` in your \ + option `(use_standard_c_and_cxx_flags )` in your \ `dune-project` file. Setting this option to `true` will \ effectively prevent Dune from silently adding c-flags to the \ compiler arguments which is the new recommended behaviour." diff --git a/src/dune_rules/super_context.ml b/src/dune_rules/super_context.ml index b2895115bed..4c25476509e 100644 --- a/src/dune_rules/super_context.ml +++ b/src/dune_rules/super_context.ml @@ -8,7 +8,7 @@ let default_context_flags (ctx : Context.t) ~project = List.filter cflags ~f:(fun s -> not (String.is_prefix s ~prefix:"-std=")) in let c = - match Dune_project.future_c_and_cxx_flags_handling project with + match Dune_project.use_standard_c_and_cxx_flags project with | None | Some false -> cflags diff --git a/test/blackbox-tests/test-cases/c-flags.t/run.t b/test/blackbox-tests/test-cases/c-flags.t/run.t index 195cee9bad6..6c8cb426d94 100644 --- a/test/blackbox-tests/test-cases/c-flags.t/run.t +++ b/test/blackbox-tests/test-cases/c-flags.t/run.t @@ -12,7 +12,7 @@ bar.c is built with an "empty" set of flags. $ O_CCPPF=${O_CCPPF%% } -future_c_and_cxx_flags_handling = default (false) +use_standard_c_and_cxx_flags = default (false) ================================== $ cat >dune-project <)` in your `dune-project` file. Setting this option to `true` will effectively prevent Dune from silently adding c-flags to the compiler arguments which is the new recommended behaviour. @@ -37,7 +37,7 @@ future_c_and_cxx_flags_handling = default (false) Warning: The flag set for these foreign sources overrides the `:standard` set of flags. However the flags in this standard set are still added to the compiler arguments by Dune. This might cause unexpected issues. You can - disable this warning by defining the option `(future_c_and_cxx_flags_handling + disable this warning by defining the option `(use_standard_c_and_cxx_flags )` in your `dune-project` file. Setting this option to `true` will effectively prevent Dune from silently adding c-flags to the compiler arguments which is the new recommended behaviour. @@ -59,12 +59,12 @@ ocamlc_cpp flags appear in the compiler command line: $ cat out_bar | grep -ce "${O_CCF} ${O_CCPPF}" 1 -future_c_and_cxx_flags_handling = true +use_standard_c_and_cxx_flags = true ================================= $ cat >dune-project < (lang dune 2.8) - > (future_c_and_cxx_flags_handling true) + > (use_standard_c_and_cxx_flags true) $ dune rules -m foo.o | tr -s '\t\n\\' ' ' > out_foo $ dune rules -m bar.o | tr -s '\t\n\\' ' ' > out_bar @@ -88,19 +88,19 @@ ocamlc_cpp are effectively removed from the compiler command line 0 [1] -future_c_and_cxx_flags_handling = true but dune < 2.8 +use_standard_c_and_cxx_flags = true but dune < 2.8 ================================================ $ cat >dune-project < (lang dune 2.7) - > (future_c_and_cxx_flags_handling true) + > (use_standard_c_and_cxx_flags true) $ dune rules - File "dune-project", line 2, characters 0-38: - 2 | (future_c_and_cxx_flags_handling true) - ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ - Error: 'future_c_and_cxx_flags_handling' is only available since version 2.8 - of the dune language. Please update your dune-project file to have (lang dune + File "dune-project", line 2, characters 0-35: + 2 | (use_standard_c_and_cxx_flags true) + ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ + Error: 'use_standard_c_and_cxx_flags' is only available since version 2.8 of + the dune language. Please update your dune-project file to have (lang dune 2.8). [1] diff --git a/test/blackbox-tests/test-cases/variables/var-cc.t/new_ff_handling/dune-project b/test/blackbox-tests/test-cases/variables/var-cc.t/new_ff_handling/dune-project index 03e9ffc4d9e..d362119f69c 100644 --- a/test/blackbox-tests/test-cases/variables/var-cc.t/new_ff_handling/dune-project +++ b/test/blackbox-tests/test-cases/variables/var-cc.t/new_ff_handling/dune-project @@ -1,2 +1,2 @@ (lang dune 2.8) -(future_c_and_cxx_flags_handling true) +(use_standard_c_and_cxx_flags true) diff --git a/test/blackbox-tests/test-cases/variables/var-cc.t/run.t b/test/blackbox-tests/test-cases/variables/var-cc.t/run.t index 1d01524db48..eca8555fb0a 100644 --- a/test/blackbox-tests/test-cases/variables/var-cc.t/run.t +++ b/test/blackbox-tests/test-cases/variables/var-cc.t/run.t @@ -36,7 +36,7 @@ With redefining env flags $ dune build @cc | sed "s,${O_CC} -fPIC,OK," OK -Since dune 2.8, when using the future_c_and_cxx_flags_handling option the :standard +Since dune 2.8, when using the use_standard_c_and_cxx_flags option the :standard set of flag and thus the %{cc} variable contain both the cflags and cppflags from ocaml config. These flags are not added systematically anymore to the compiler command line. From 153a1e228e89f68712992554d1204bf5fa56fd49 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Ulysse=20G=C3=A9rard?= Date: Thu, 19 Nov 2020 13:44:47 +0100 Subject: [PATCH 22/24] Fmt MIME-Version: 1.0 Content-Type: text/plain; charset=UTF-8 Content-Transfer-Encoding: 8bit Signed-off-by: Ulysse Gérard --- src/dune_engine/dune_project.ml | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/src/dune_engine/dune_project.ml b/src/dune_engine/dune_project.ml index e20f9bc8021..658f48f13fe 100644 --- a/src/dune_engine/dune_project.ml +++ b/src/dune_engine/dune_project.ml @@ -239,8 +239,7 @@ let to_dyn ; ("dune_version", Dune_lang.Syntax.Version.to_dyn dune_version) ; ("allow_approx_merlin", bool allow_approx_merlin) ; ("generate_opam_files", bool generate_opam_files) - ; ( "use_standard_c_and_cxx_flags" - , option bool use_standard_c_and_cxx_flags ) + ; ("use_standard_c_and_cxx_flags", option bool use_standard_c_and_cxx_flags) ; ("file_key", string file_key) ; ("dialects", Dialect.DB.to_dyn dialects) ; ("explicit_js_mode", bool explicit_js_mode) From 329cea0a8c08ad0d0fce498894d4276ee1be82d3 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Ulysse=20G=C3=A9rard?= Date: Wed, 13 Jan 2021 16:05:31 +0100 Subject: [PATCH 23/24] Remove duplicate fields MIME-Version: 1.0 Content-Type: text/plain; charset=UTF-8 Content-Transfer-Encoding: 8bit Signed-off-by: Ulysse Gérard --- src/dune_engine/dune_project.ml | 13 ------------- src/dune_engine/dune_project.mli | 6 ++---- 2 files changed, 2 insertions(+), 17 deletions(-) diff --git a/src/dune_engine/dune_project.ml b/src/dune_engine/dune_project.ml index 95f242c69dc..823a2e54153 100644 --- a/src/dune_engine/dune_project.ml +++ b/src/dune_engine/dune_project.ml @@ -160,7 +160,6 @@ 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 ; use_standard_c_and_cxx_flags : bool option ; file_key : File_key.t @@ -191,8 +190,6 @@ 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 use_standard_c_and_cxx_flags t = t.use_standard_c_and_cxx_flags @@ -214,7 +211,6 @@ let to_dyn ; implicit_transitive_deps ; wrapped_executables ; dune_version - ; use_standard_c_and_cxx_flags ; generate_opam_files ; use_standard_c_and_cxx_flags ; file_key @@ -237,7 +233,6 @@ 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) ; ("use_standard_c_and_cxx_flags", option bool use_standard_c_and_cxx_flags) ; ("file_key", string file_key) @@ -614,7 +609,6 @@ let infer ~dir packages = ; extension_args ; parsing_context ; dune_version = lang.version - ; use_standard_c_and_cxx_flags = false ; generate_opam_files = false ; use_standard_c_and_cxx_flags = ( if lang.version < (3, 0) then @@ -701,9 +695,6 @@ 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" @@ -819,9 +810,6 @@ 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 @@ -877,7 +865,6 @@ 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 ; use_standard_c_and_cxx_flags ; dialects diff --git a/src/dune_engine/dune_project.mli b/src/dune_engine/dune_project.mli index 2ae3f389e79..3cb70487edf 100644 --- a/src/dune_engine/dune_project.mli +++ b/src/dune_engine/dune_project.mli @@ -63,14 +63,12 @@ val root : t -> Path.Source.t val stanza_parser : t -> Stanza.t list Dune_lang.Decoder.t +val generate_opam_files : 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 - val use_standard_c_and_cxx_flags : t -> bool option val dialects : t -> Dialect.DB.t From 68f2bd4b110909cc61c35c628d383ab09dc2e03c Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Ulysse=20G=C3=A9rard?= Date: Wed, 13 Jan 2021 16:05:53 +0100 Subject: [PATCH 24/24] Formating MIME-Version: 1.0 Content-Type: text/plain; charset=UTF-8 Content-Transfer-Encoding: 8bit Signed-off-by: Ulysse Gérard --- src/dune_rules/foreign_rules.ml | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/src/dune_rules/foreign_rules.ml b/src/dune_rules/foreign_rules.ml index 6db0df47460..95a7200a53b 100644 --- a/src/dune_rules/foreign_rules.ml +++ b/src/dune_rules/foreign_rules.ml @@ -98,8 +98,8 @@ let build_c ~kind ~sctx ~dir ~expander ~include_flags (loc, src, dst) = (* DUNE3 will have [use_standard_c_and_cxx_flags] enabled by default. To guide users toward this change we emit a warning when dune_lang is >= 1.8, [use_standard_c_and_cxx_flags] is not specified in the - [dune-project] file (thus defaulting to [true]), the [:standard] set - of flags has been overriden and we are not in a vendored project *) + [dune-project] file (thus defaulting to [true]), the [:standard] set of + flags has been overriden and we are not in a vendored project *) let has_standard = Ordered_set_lang.Unexpanded.has_standard flags in let is_vendored = match Path.Build.drop_build_context dir with