diff --git a/src/dune_rules/expander.ml b/src/dune_rules/expander.ml index 91b6ada9b8f4..10b9472ab0af 100644 --- a/src/dune_rules/expander.ml +++ b/src/dune_rules/expander.ml @@ -909,24 +909,6 @@ let expand_and_eval_set t set ~standard = Ordered_set_lang.eval set ~standard ~eq:String.equal ~parse:(fun ~loc:_ s -> s) ;; -module Unordered (Key : Ordered_set_lang.Key) = struct - module Unordered = Ordered_set_lang.Unordered (Key) - - let expand_and_eval t set ~ctx ~parse ~key ~standard = - let dir = Path.build (dir t) in - let+ set = expand_ordered_set_lang set ~dir ~f:(expand_pform t) in - let ctx = ref ctx in - let parse ~loc x = - let x, ctx' = parse ~loc ~ctx:!ctx x in - ctx := ctx'; - x - in - let r = Unordered.eval_loc set ~parse ~key ~standard in - let ctx = !ctx in - r, ctx - ;; -end - let eval_blang t blang = Blang_expand.eval ~f:(No_deps.expand_pform t) ~dir:(Path.build t.dir) blang ;; diff --git a/src/dune_rules/expander.mli b/src/dune_rules/expander.mli index 4d2d3434ed28..befe45951269 100644 --- a/src/dune_rules/expander.mli +++ b/src/dune_rules/expander.mli @@ -107,6 +107,12 @@ module With_reduced_var_set : sig val eval_blang : context:Context.t -> dir:Path.Build.t -> Blang.t -> bool Memo.t end +val expand_ordered_set_lang + : Ordered_set_lang.Unexpanded.t + -> dir:Path.t + -> f:Value.t list Action_builder.t String_with_vars.expander + -> Ordered_set_lang.t Action_builder.t + (** Expand forms of the form (:standard \ foo bar). Expansion is only possible inside [Action_builder.t] because such forms may contain the form (:include ..) which needs files to be built. *) @@ -116,17 +122,6 @@ val expand_and_eval_set -> standard:string list Action_builder.t -> string list Action_builder.t -module Unordered (Key : Ordered_set_lang.Key) : sig - val expand_and_eval - : t - -> Ordered_set_lang.Unexpanded.t - -> ctx:'ctx - -> parse:(loc:Loc.t -> ctx:'ctx -> string -> 'a * 'ctx) - -> key:('a -> Key.t) - -> standard:(Loc.t * 'a) Key.Map.t - -> ((Loc.t * 'a) Key.Map.t * 'ctx) Action_builder.t -end - val eval_blang : t -> Blang.t -> bool Memo.t val map_exe : t -> Path.t -> Path.t val artifacts : t -> Artifacts.t diff --git a/src/dune_rules/modules_field_evaluator.ml b/src/dune_rules/modules_field_evaluator.ml index 5707074434dc..b78a4d2e8e86 100644 --- a/src/dune_rules/modules_field_evaluator.ml +++ b/src/dune_rules/modules_field_evaluator.ml @@ -30,14 +30,25 @@ let eval0 = module Map = Module_trie end in - let module Unordered = Expander.Unordered (Key) in + let module Unordered = Ordered_set_lang.Unordered (Key) in (* Fake modules are modules that do not exist but it doesn't matter because they are only removed from a set (for jbuild file compatibility) *) - let parse ~all_modules ~loc ~ctx:fake_modules s = + let expand_and_eval t set ~parse ~key ~standard = + let open Action_builder.O in + let dir = Path.build (Expander.dir t) in + let+ set = Expander.expand_ordered_set_lang set ~dir ~f:(Expander.expand_pform t) in + let fake_modules = ref Module_name.Map.empty in + let parse ~loc x = parse ~loc ~fake_modules x in + let r = Unordered.eval_loc set ~parse ~key ~standard in + r, !fake_modules + in + let parse ~all_modules ~loc ~fake_modules s = let name = Module_name.of_string_allow_invalid (loc, s) in match Module_trie.find all_modules [ name ] with - | Some m -> Ok m, fake_modules - | None -> Error name, Module_name.Map.set fake_modules name loc + | Some m -> Ok m + | None -> + fake_modules := Module_name.Map.set !fake_modules name loc; + Error name in fun ~expander ~loc ~all_modules ~standard osl -> let open Memo.O in @@ -45,13 +56,7 @@ let eval0 = let standard = Module_trie.map standard ~f:(fun m -> loc, Ok m) in let+ (modules, fake_modules), _ = Action_builder.evaluate_and_collect_facts - (Unordered.expand_and_eval - expander - ~ctx:Module_name.Map.empty - ~parse - ~standard - ~key - osl) + (expand_and_eval expander ~parse ~standard ~key osl) in let modules = Module_trie.filter_map modules ~f:(fun (loc, m) ->