Skip to content

Commit

Permalink
fix(x-compilation): delay evaluation of ppx_runtime_deps until cont…
Browse files Browse the repository at this point in the history
…ext is known

Signed-off-by: Antonio Nuno Monteiro <anmonteiro@gmail.com>
  • Loading branch information
anmonteiro committed Mar 30, 2023
1 parent fc166ec commit fac2335
Show file tree
Hide file tree
Showing 9 changed files with 134 additions and 96 deletions.
7 changes: 6 additions & 1 deletion bin/describe.ml
Original file line number Diff line number Diff line change
Expand Up @@ -429,10 +429,15 @@ module Crawl = struct
in

let+ libs =
let* scope =
let dir = (Super_context.context sctx).build_dir in
let+ expander = Super_context.expander ~dir sctx in
Expander.scope expander
in
(* the executables' libraries, and the project's libraries *)
Lib.Set.union exe_libs project_libs
|> Lib.Set.to_list
|> Lib.descriptive_closure ~with_pps:options.with_pps
|> Lib.descriptive_closure (Scope.libs scope) ~with_pps:options.with_pps
>>= Memo.parallel_map ~f:(library ~options sctx)
>>| List.filter_opt
in
Expand Down
12 changes: 7 additions & 5 deletions src/dune_rules/gen_meta.ml
Original file line number Diff line number Diff line change
Expand Up @@ -64,7 +64,7 @@ let archives ?(preds = []) lib =
; plugin (preds @ [ Pos "native" ]) (make plugins.native)
]

let gen_lib pub_name lib ~path ~version =
let gen_lib pub_name lib ~scope ~path ~version =
let open Memo.O in
let info = Lib.info lib in
let synopsis = Lib_info.synopsis info in
Expand Down Expand Up @@ -94,8 +94,9 @@ let gen_lib pub_name lib ~path ~version =
in
let to_names = Lib_name.Set.of_list_map ~f:name in
let* lib_deps = Resolve.Memo.read_memo (Lib.requires lib) >>| to_names in
let scope_libs = Scope.libs scope in
let* ppx_rt_deps =
Lib.ppx_runtime_deps lib
Lib.ppx_runtime_deps lib scope_libs
|> Memo.bind ~f:Resolve.read_memo
|> Memo.map ~f:to_names
in
Expand All @@ -111,7 +112,8 @@ let gen_lib pub_name lib ~path ~version =
Sigh... *)
let open Resolve.Memo.O in
Lib.closure [ lib ] ~linking:false
>>= Resolve.Memo.List.concat_map ~f:Lib.ppx_runtime_deps
>>= Resolve.Memo.List.concat_map ~f:(fun lib ->
Lib.ppx_runtime_deps lib scope_libs)
>>| to_names |> Resolve.Memo.read_memo
in
List.concat
Expand Down Expand Up @@ -171,7 +173,7 @@ let gen_lib pub_name lib ~path ~version =
])
]

let gen ~(package : Package.t) ~add_directory_entry entries =
let gen ~scope ~(package : Package.t) ~add_directory_entry entries =
let open Memo.O in
let version =
match package.version with
Expand Down Expand Up @@ -210,7 +212,7 @@ let gen ~(package : Package.t) ~add_directory_entry entries =
| _ -> (pub_name, path)
in
let+ entries =
gen_lib pub_name ~path (Lib.Local.to_lib lib) ~version
gen_lib pub_name ~scope ~path (Lib.Local.to_lib lib) ~version
in
(pub_name, entries))
| Deprecated_library_name
Expand Down
3 changes: 2 additions & 1 deletion src/dune_rules/gen_meta.mli
Original file line number Diff line number Diff line change
Expand Up @@ -4,7 +4,8 @@ val requires : ?preds:Meta.predicate list -> Lib_name.Set.t -> Meta.entry

(** Generate the meta for a package containing some libraries *)
val gen :
package:Package.t
scope:Scope.t
-> package:Package.t
-> add_directory_entry:bool
-> Scope.DB.Lib_entry.t list
-> Meta.t Memo.t
16 changes: 10 additions & 6 deletions src/dune_rules/install_rules.ml
Original file line number Diff line number Diff line change
Expand Up @@ -574,6 +574,7 @@ end = struct
in
let lib = Lib.Local.to_lib lib in
let name = Lib.name lib in
let* expander = Super_context.expander sctx ~dir:lib_src_dir in
let* foreign_objects =
(* We are writing the list of .o files to dune-package, but we
actually only install them for virtual libraries. See
Expand All @@ -595,16 +596,14 @@ end = struct
| External _paths -> assert false
| Local (loc, dep_conf) ->
let+ melange_runtime_deps =
let* expander =
Super_context.expander sctx ~dir:lib_src_dir
in
Melange_rules.Runtime_deps.eval ~expander ~loc
~paths:Allow_all dep_conf
in
Path.Set.to_list melange_runtime_deps
in
let+ sub_systems =
Lib.to_dune_lib lib
let scope = Expander.scope expander in
Lib.to_dune_lib lib (Scope.libs scope)
~dir:(Path.build (lib_root lib))
~modules ~foreign_objects ~melange_runtime_deps
>>= Resolve.read_memo
Expand Down Expand Up @@ -768,13 +767,17 @@ end = struct
in
let ctx = Super_context.context sctx in
let meta = Package_paths.meta_file ctx pkg in
let* scope =
let+ expander = Super_context.expander sctx ~dir:ctx.build_dir in
Expander.scope expander
in
let* () =
Super_context.add_rule sctx ~dir:ctx.build_dir
(let open Action_builder.O in
(let* template = template in
let+ meta =
Action_builder.of_memo
(Gen_meta.gen ~package:pkg ~add_directory_entry:true entries)
(Gen_meta.gen ~scope ~package:pkg ~add_directory_entry:true entries)
in
let pp =
Pp.vbox
Expand Down Expand Up @@ -806,7 +809,8 @@ end = struct
| Some entries -> entries
in
Action_builder.of_memo
(Gen_meta.gen ~package:pkg entries ~add_directory_entry:false)
(Gen_meta.gen ~scope ~package:pkg entries
~add_directory_entry:false)
in
let pp =
let open Pp.O in
Expand Down
Loading

0 comments on commit fac2335

Please sign in to comment.