diff --git a/src/dune_rules/context.ml b/src/dune_rules/context.ml index 9dcbc39d18f..04f7df8d78d 100644 --- a/src/dune_rules/context.ml +++ b/src/dune_rules/context.ml @@ -150,7 +150,10 @@ module Builder = struct extend_paths ~env paths in { t with - merlin + merlin = + (match merlin with + | Selected -> true + | Rules_only | Nothing -> false) ; profile ; dynamically_linked_foreign_archives ; instrument_with @@ -610,7 +613,13 @@ module Group = struct | Opam opam -> Builder.set_workspace_base builder opam.base | Default default -> let builder = Builder.set_workspace_base builder default.base in - let merlin = workspace.merlin_context = Some (Workspace.Context.name context) in + let merlin = + workspace.merlin_context = Some (Workspace.Context.name context) + || + match default.base.merlin with + | Rules_only -> true + | Nothing | Selected -> false + in { builder with merlin } in match context with diff --git a/src/dune_rules/workspace.ml b/src/dune_rules/workspace.ml index ce98579da2b..6b190b1604f 100644 --- a/src/dune_rules/workspace.ml +++ b/src/dune_rules/workspace.ml @@ -266,6 +266,28 @@ module Context = struct ;; end + module Merlin = struct + type t = + | Selected + | Rules_only + | Nothing + + let equal x y = + match x, y with + | Selected, Selected | Rules_only, Rules_only | Nothing, Nothing -> true + | Selected, (Rules_only | Nothing) + | (Rules_only | Nothing), Selected + | Rules_only, Nothing + | Nothing, Rules_only -> false + ;; + + let to_dyn: t -> Dyn.t = function + | Selected -> String "selected" + | Rules_only -> String "rules_only" + | Nothing -> String "nothing" + ;; + end + module Common = struct type t = { loc : Loc.t @@ -279,7 +301,7 @@ module Context = struct ; fdo_target_exe : Path.t option ; dynamically_linked_foreign_archives : bool ; instrument_with : Lib_name.t list - ; merlin : bool + ; merlin : Merlin.t } let to_dyn { name; targets; host_context; _ } = @@ -318,7 +340,7 @@ module Context = struct dynamically_linked_foreign_archives t.dynamically_linked_foreign_archives && List.equal Lib_name.equal instrument_with t.instrument_with - && Bool.equal merlin t.merlin + && Merlin.equal merlin t.merlin ;; let fdo_suffix t = @@ -384,7 +406,8 @@ module Context = struct "instrument_with" (Dune_lang.Syntax.since syntax (2, 7) >>> repeat Lib_name.decode) and+ loc = loc - and+ merlin = field_b "merlin" in + and+ merlin = field_b "merlin" + and+ generate_merlin_rules = field_b "generate_merlin_rules" in fun ~profile_default ~instrument_with_default -> let profile = Option.value profile ~default:profile_default in let instrument_with = @@ -409,7 +432,13 @@ module Context = struct ; fdo_target_exe ; dynamically_linked_foreign_archives ; instrument_with - ; merlin + ; merlin = + (match merlin with + | true -> Selected + | false -> + (match generate_merlin_rules with + | true -> Rules_only + | false -> Nothing)) } ;; end @@ -571,7 +600,7 @@ module Context = struct ; fdo_target_exe = None ; dynamically_linked_foreign_archives = true ; instrument_with = Option.value instrument_with ~default:[] - ; merlin = false + ; merlin = Nothing } } ;; @@ -840,11 +869,11 @@ let step1 clflags = !defined_names (Context_name.Set.of_list (Context.all_names ctx)); match Context.base ctx, acc with - | { merlin = true; _ }, Some _ -> + | { merlin = Selected; _ }, Some _ -> User_error.raise ~loc:(Context.loc ctx) [ Pp.text "you can only have one context for merlin" ] - | { merlin = true; _ }, None -> Some name + | { merlin = Selected; _ }, None -> Some name | _ -> acc) in let contexts = diff --git a/src/dune_rules/workspace.mli b/src/dune_rules/workspace.mli index e6093120b18..a86d7c8153f 100644 --- a/src/dune_rules/workspace.mli +++ b/src/dune_rules/workspace.mli @@ -38,7 +38,18 @@ module Context : sig val equal : t -> t -> bool end + module Merlin : sig + type t = + | Selected + | Rules_only + | Nothing + + val equal : t -> t -> bool + + val to_dyn: t -> Dyn.t + end module Common : sig + type t = { loc : Loc.t ; profile : Profile.t @@ -57,7 +68,7 @@ module Context : sig the runtime system. *) ; dynamically_linked_foreign_archives : bool ; instrument_with : Lib_name.t list - ; merlin : bool + ; merlin : Merlin.t } end diff --git a/test/blackbox-tests/test-cases/merlin/default-based-context.t/run.t b/test/blackbox-tests/test-cases/merlin/default-based-context.t/run.t index d29e5ee4eee..5db4df77c5f 100644 --- a/test/blackbox-tests/test-cases/merlin/default-based-context.t/run.t +++ b/test/blackbox-tests/test-cases/merlin/default-based-context.t/run.t @@ -75,3 +75,44 @@ If Merlin field is present, this context is chosen -short-paths -keep-locs -g))) + +If `generate_merlin_rules` field is present, rules are generated even if merlin +is disabled in that context + + $ cat >dune-workspace < (lang dune 2.9) + > (context (default)) + > (context + > (default + > (name cross) + > (generate_merlin_rules))) + > EOF + + $ dune build + + $ ls -a _build/cross/.merlin-conf + . + .. + lib-foo + + $ ls -a _build/default/.merlin-conf + . + .. + lib-foo + + $ dune ocaml merlin dump-config "$PWD" + Foo: _build/default/foo + ((STDLIB OPAM_PREFIX) + (EXCLUDE_QUERY_DIR) + (B + $TESTCASE_ROOT/_build/default/.foo.objs/byte) + (S + $TESTCASE_ROOT) + (FLG + (-w + @1..3@5..28@30..39@43@46..47@49..57@61..62-40 + -strict-sequence + -strict-formats + -short-paths + -keep-locs + -g)))