diff --git a/CHANGES.md b/CHANGES.md index 6d1936474c9..53d54391833 100644 --- a/CHANGES.md +++ b/CHANGES.md @@ -152,6 +152,9 @@ Unreleased - Add native support for polling mode on Windows (#7010, @yams-yams, @nojb) +- Add `(bin_annot )` to `(env ...)` to specify whether to generate + `*.cmt*` files. (#7102, @nojb) + 3.6.2 (2022-12-21) ------------------ diff --git a/doc/stanzas/env.rst b/doc/stanzas/env.rst index 877b92e9d50..8cbcaadb7c3 100644 --- a/doc/stanzas/env.rst +++ b/doc/stanzas/env.rst @@ -67,3 +67,6 @@ Fields supported in ```` are: - ``(formatting )`` allows the user to set auto-formatting in the current directory subtree (see :ref:`formatting`). + +- ``(bin_annot )`` allows the user to specify whether to generate `*.cmt` + and `*.cmti` in the current directory subtree. diff --git a/src/dune_rules/compilation_context.ml b/src/dune_rules/compilation_context.ml index 045a12b83e1..b15e984aca5 100644 --- a/src/dune_rules/compilation_context.ml +++ b/src/dune_rules/compilation_context.ml @@ -142,8 +142,8 @@ let dep_graphs t = t.modules.dep_graphs let create ~super_context ~scope ~expander ~obj_dir ~modules ~flags ~requires_compile ~requires_link ?(preprocessing = Pp_spec.dummy) ~opaque - ?stdlib ~js_of_ocaml ~package ?public_lib_name ?vimpl ?modes - ?(bin_annot = true) ?loc () = + ?stdlib ~js_of_ocaml ~package ?public_lib_name ?vimpl ?modes ?bin_annot ?loc + () = let open Memo.O in let project = Scope.project scope in let requires_compile = @@ -179,7 +179,12 @@ let create ~super_context ~scope ~expander ~obj_dir ~modules ~flags ; stdlib } in - let+ dep_graphs = Dep_rules.rules ocamldep_modules_data in + let+ dep_graphs = Dep_rules.rules ocamldep_modules_data + and+ bin_annot = + match bin_annot with + | Some b -> Memo.return b + | None -> Super_context.bin_annot super_context ~dir:(Obj_dir.dir obj_dir) + in { super_context ; scope ; expander diff --git a/src/dune_rules/dune_env.ml b/src/dune_rules/dune_env.ml index 29591888635..b2da3d241f2 100644 --- a/src/dune_rules/dune_env.ml +++ b/src/dune_rules/dune_env.ml @@ -82,6 +82,7 @@ module Stanza = struct ; format_config : Format_config.t option ; error_on_use : User_message.t option ; warn_on_load : User_message.t option + ; bin_annot : bool option } let equal_config @@ -98,6 +99,7 @@ module Stanza = struct ; format_config ; error_on_use ; warn_on_load + ; bin_annot } t = Ocaml_flags.Spec.equal flags t.flags && Foreign_language.Dict.equal Ordered_set_lang.Unexpanded.equal @@ -113,6 +115,7 @@ module Stanza = struct && Js_of_ocaml.Env.equal js_of_ocaml t.js_of_ocaml && Option.equal User_message.equal error_on_use t.error_on_use && Option.equal User_message.equal warn_on_load t.warn_on_load + && Option.equal Bool.equal bin_annot t.bin_annot let hash_config = Poly.hash @@ -131,6 +134,7 @@ module Stanza = struct ; format_config = None ; error_on_use = None ; warn_on_load = None + ; bin_annot = None } type pattern = @@ -187,6 +191,9 @@ module Stanza = struct field "coq" ~default:Ordered_set_lang.Unexpanded.standard (Dune_lang.Syntax.since Stanza.syntax (2, 7) >>> fields coq_flags) + let bin_annot = + field_o "bin_annot" (Dune_lang.Syntax.since Stanza.syntax (3, 8) >>> bool) + let config = let+ flags = Ocaml_flags.Spec.decode and+ foreign_flags = foreign_flags ~since:(Some (1, 7)) @@ -201,7 +208,8 @@ module Stanza = struct and+ odoc = odoc_field and+ js_of_ocaml = js_of_ocaml_field and+ coq = coq_field - and+ format_config = Format_config.field ~since:(2, 8) in + and+ format_config = Format_config.field ~since:(2, 8) + and+ bin_annot = bin_annot in { flags ; foreign_flags ; link_flags @@ -215,6 +223,7 @@ module Stanza = struct ; format_config ; error_on_use = None ; warn_on_load = None + ; bin_annot } let rule = diff --git a/src/dune_rules/dune_env.mli b/src/dune_rules/dune_env.mli index ff56ebb30ec..594b2d2feb3 100644 --- a/src/dune_rules/dune_env.mli +++ b/src/dune_rules/dune_env.mli @@ -38,6 +38,7 @@ module Stanza : sig ; format_config : Format_config.t option ; error_on_use : User_message.t option ; warn_on_load : User_message.t option + ; bin_annot : bool option } type pattern = diff --git a/src/dune_rules/env_node.ml b/src/dune_rules/env_node.ml index d259c84dfd8..d37e81ffaa5 100644 --- a/src/dune_rules/env_node.ml +++ b/src/dune_rules/env_node.ml @@ -26,6 +26,7 @@ type t = ; js_of_ocaml : string list Action_builder.t Js_of_ocaml.Env.t Memo.Lazy.t ; coq : Coq.t Action_builder.t Memo.Lazy.t ; format_config : Format_config.t Memo.Lazy.t + ; bin_annot : bool Memo.Lazy.t } let scope t = t.scope @@ -58,6 +59,8 @@ let odoc t = Memo.Lazy.force t.odoc let coq t = Memo.Lazy.force t.coq +let bin_annot t = Memo.Lazy.force t.bin_annot + let expand_str_lazy expander sw = match String_with_vars.text_only sw with | Some s -> Memo.return s @@ -68,7 +71,7 @@ let expand_str_lazy expander sw = let make ~dir ~inherit_from ~scope ~config_stanza ~profile ~expander ~expander_for_artifacts ~default_context_flags ~default_env - ~default_bin_artifacts ~default_cxx_link_flags = + ~default_bin_artifacts ~default_cxx_link_flags ~default_bin_annot = let open Memo.O in let config = Dune_env.Stanza.find config_stanza ~profile in let inherited ~field ~root extend = @@ -220,6 +223,10 @@ let make ~dir ~inherit_from ~scope ~config_stanza ~profile ~expander [] | Some x -> Memo.return x) in + let bin_annot = + inherited ~field:bin_annot ~root:default_bin_annot (fun default -> + Memo.return (Option.value ~default config.bin_annot)) + in { scope ; ocaml_flags ; foreign_flags @@ -233,4 +240,5 @@ let make ~dir ~inherit_from ~scope ~config_stanza ~profile ~expander ; odoc ; coq ; format_config + ; bin_annot } diff --git a/src/dune_rules/env_node.mli b/src/dune_rules/env_node.mli index b01c5d6f78f..19a878e7190 100644 --- a/src/dune_rules/env_node.mli +++ b/src/dune_rules/env_node.mli @@ -28,6 +28,7 @@ val make : -> default_env:Env.t -> default_bin_artifacts:Artifacts.Bin.t -> default_cxx_link_flags:string list Action_builder.t + -> default_bin_annot:bool -> t val scope : t -> Scope.t @@ -57,3 +58,5 @@ val menhir_flags : t -> string list Action_builder.t val format_config : t -> Format_config.t Memo.t val set_format_config : t -> Format_config.t -> t + +val bin_annot : t -> bool Memo.t diff --git a/src/dune_rules/install_rules.ml b/src/dune_rules/install_rules.ml index 9817e84a099..3fee9c9cd8e 100644 --- a/src/dune_rules/install_rules.ml +++ b/src/dune_rules/install_rules.ml @@ -161,7 +161,7 @@ end = struct let { Lib_mode.Map.ocaml = { Mode.Dict.byte; native } as ocaml; melange } = Dune_file.Mode_conf.Lib.Set.eval lib.modes ~has_native in - let module_files = + let* module_files = let inside_subdir f = match lib_subdir with | None -> f @@ -202,18 +202,21 @@ end = struct let set_dir m = List.map ~f:(fun (cm_kind, p) -> (cm_dir m cm_kind, p)) in - let modules_impl = + let+ modules_impl = + let+ bin_annot = Super_context.bin_annot sctx ~dir in List.concat_map installable_modules.impl ~f:(fun m -> let cmt_files = - List.concat_map Ml_kind.all ~f:(fun ml_kind -> - let open Lib_mode.Cm_kind in - List.concat_map - [ (native || byte, Ocaml Cmi); (melange, Melange Cmi) ] - ~f:(fun (condition, kind) -> - if_ condition - ( kind - , Obj_dir.Module.cmt_file obj_dir m ~ml_kind - ~cm_kind:kind ))) + if bin_annot then + List.concat_map Ml_kind.all ~f:(fun ml_kind -> + let open Lib_mode.Cm_kind in + List.concat_map + [ (native || byte, Ocaml Cmi); (melange, Melange Cmi) ] + ~f:(fun (condition, kind) -> + if_ condition + ( kind + , Obj_dir.Module.cmt_file obj_dir m ~ml_kind + ~cm_kind:kind ))) + else [] in common m @ cmt_files |> set_dir m) diff --git a/src/dune_rules/super_context.ml b/src/dune_rules/super_context.ml index 4ed7a69cb4d..24666119eec 100644 --- a/src/dune_rules/super_context.ml +++ b/src/dune_rules/super_context.ml @@ -161,6 +161,7 @@ end = struct ~profile:t.context.profile ~expander ~expander_for_artifacts ~default_context_flags ~default_env:t.context_env ~default_bin_artifacts:t.bin_artifacts ~default_cxx_link_flags + ~default_bin_annot:true (* Here we jump through some hoops to construct [t] as well as create a memoization table that has access to [t] and is used in [t.get_node]. @@ -345,6 +346,8 @@ let coq t ~dir = Env_tree.get_node t ~dir >>= Env_node.coq let format_config t ~dir = Env_tree.get_node t ~dir >>= Env_node.format_config +let bin_annot t ~dir = Env_tree.get_node t ~dir >>= Env_node.bin_annot + let dump_env t ~dir = let ocaml_flags = Env_tree.get_node t ~dir >>= Env_node.ocaml_flags in let foreign_flags = Env_tree.get_node t ~dir >>| Env_node.foreign_flags in @@ -494,7 +497,7 @@ let create ~(context : Context.t) ~host ~packages ~stanzas = Env_node.make ~dir ~scope ~inherit_from ~config_stanza ~profile ~expander ~expander_for_artifacts ~default_context_flags ~default_env:context_env ~default_bin_artifacts:artifacts.bin - ~default_cxx_link_flags + ~default_cxx_link_flags ~default_bin_annot:true in make ~config_stanza:context.env_nodes.context ~inherit_from: diff --git a/src/dune_rules/super_context.mli b/src/dune_rules/super_context.mli index 029636df469..b0c59bf3f74 100644 --- a/src/dune_rules/super_context.mli +++ b/src/dune_rules/super_context.mli @@ -84,6 +84,8 @@ val coq : t -> dir:Path.Build.t -> Env_node.Coq.t Action_builder.t Memo.t (** Formatting settings in the corresponding [(env)] stanza. *) val format_config : t -> dir:Path.Build.t -> Format_config.t Memo.t +val bin_annot : t -> dir:Path.Build.t -> bool Memo.t + (** Dump a directory environment in a readable form *) val dump_env : t -> dir:Path.Build.t -> Dune_lang.t list Action_builder.t diff --git a/test/blackbox-tests/test-cases/env/env-bin-annot.t/run.t b/test/blackbox-tests/test-cases/env/env-bin-annot.t/run.t new file mode 100644 index 00000000000..f95ba778920 --- /dev/null +++ b/test/blackbox-tests/test-cases/env/env-bin-annot.t/run.t @@ -0,0 +1,74 @@ +Test that we can control generation of cmt files using (cmt_annot ...) field in (env ...). + + $ cat >dune-project < (lang dune 3.8) + > (package (name pub)) + > (package (name pub2)) + > EOF + + $ mkdir -p priv/priv2 pub/pub2 priv/proj + + $ touch main.ml priv/priv.ml priv/priv2/priv2.ml pub/pub.ml pub/pub2/pub2.ml priv/proj/proj.ml + + $ cat >dune < (library (name main)) + > EOF + + $ cat >priv/dune < (env (_ (bin_annot false))) + > (library (name priv)) + > EOF + + $ cat >priv/priv2/dune < (env (_ (bin_annot true))) + > (library (name priv2)) + > EOF + +We also check that public libraries work: the first should be installed without +any cmt file... + + $ cat >pub/dune < (env (_ (bin_annot false))) + > (library (public_name pub)) + > EOF + +... and the second one _with_ cmt files. + + $ cat >pub/pub2/dune < (env (_ (bin_annot true))) + > (library (public_name pub2)) + > EOF + + $ cat >priv/proj/dune-project < (lang dune 3.8) + > EOF + + $ cat >priv/proj/dune < (library (name proj)) + > EOF + + $ dune build + +Note that "pub" does not appear in the list (as we disabled cmt files for it). + + $ find _build -name '*.cmt*' | sort + _build/default/.main.objs/byte/main.cmt + _build/default/priv/priv2/.priv2.objs/byte/priv2.cmt + _build/default/priv/proj/.proj.objs/byte/proj.cmt + _build/default/pub/pub2/.pub2.objs/byte/pub2.cmt + _build/install/default/lib/pub2/pub2.cmt + +The next test shows that workspace env settings are used as fallback if a +project does not specify the option explicitly. + + $ cat >dune-workspace < (lang dune 3.8) + > (env (_ (bin_annot false))) + > EOF + + $ dune build + + $ find _build -name '*.cmt*' | sort + _build/default/priv/priv2/.priv2.objs/byte/priv2.cmt + _build/default/pub/pub2/.pub2.objs/byte/pub2.cmt + _build/install/default/lib/pub2/pub2.cmt