Skip to content

Commit

Permalink
Move Expander.Unordered to Modules_field_evaluator
Browse files Browse the repository at this point in the history
Signed-off-by: Nicolás Ojeda Bär <n.oje.bar@gmail.com>
  • Loading branch information
nojb committed Jan 9, 2024
1 parent 4d71aa2 commit 1debb81
Show file tree
Hide file tree
Showing 3 changed files with 22 additions and 40 deletions.
18 changes: 0 additions & 18 deletions src/dune_rules/expander.ml
Original file line number Diff line number Diff line change
Expand Up @@ -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
;;
Expand Down
17 changes: 6 additions & 11 deletions src/dune_rules/expander.mli
Original file line number Diff line number Diff line change
Expand Up @@ -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. *)
Expand All @@ -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
Expand Down
27 changes: 16 additions & 11 deletions src/dune_rules/modules_field_evaluator.ml
Original file line number Diff line number Diff line change
Expand Up @@ -30,28 +30,33 @@ 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
let parse = parse ~all_modules in
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) ->
Expand Down

0 comments on commit 1debb81

Please sign in to comment.