Skip to content

Commit

Permalink
refactor: remove some unnecessary memoization fomr dune evaluation (#…
Browse files Browse the repository at this point in the history
…9915)

Re-running the OCaml syntax every time we re-read the stanzas is fine
since they don't track deps anyway.

Signed-off-by: Rudi Grinberg <[email protected]>
  • Loading branch information
rgrinberg authored Feb 3, 2024
1 parent ce21136 commit f246e94
Showing 1 changed file with 1 addition and 25 deletions.
26 changes: 1 addition & 25 deletions src/dune_rules/dune_file.ml
Original file line number Diff line number Diff line change
Expand Up @@ -237,29 +237,18 @@ module Script = struct
; project : Dune_project.t
}

let script_equal t { dir; file; project } =
Path.Source.equal t.dir dir
&& Path.Source.equal t.file file
&& Dune_project.equal t.project project
;;

open Memo.O

type t =
{ script : script
; from_parent : Dune_lang.Ast.t list
}

let equal t { script; from_parent } =
script_equal t.script script
&& List.equal Dune_lang.Ast.equal t.from_parent from_parent
;;

(* CR-rgrinberg: context handling code should be aware of this special
directory *)
let generated_dune_files_dir = Path.Build.relative Path.Build.root ".dune"

let eval_one (context, { script = { dir; file; project }; from_parent }) =
let eval_one ~context { script = { dir; file; project }; from_parent } =
let generated_dune_file =
Path.Build.append_source
(Path.Build.relative generated_dune_files_dir (Context_name.to_string context))
Expand Down Expand Up @@ -301,19 +290,6 @@ module Script = struct
|> List.rev_append from_parent
|> parse ~dir ~file:(Some file) ~project
;;

let eval_one =
let module Input = struct
type nonrec t = Context_name.t * t

let equal = Tuple.T2.equal Context_name.equal equal
let hash = Tuple.T2.hash Context_name.hash Poly.hash
let to_dyn = Dyn.opaque
end
in
let memo = Memo.create "Script.eval_one" ~input:(module Input) eval_one in
fun ~context t -> Memo.exec memo (context, t)
;;
end

let filter_out_stanzas_from_hidden_packages ~visible_pkgs =
Expand Down

0 comments on commit f246e94

Please sign in to comment.