Skip to content

Commit 6d4ab70

Browse files
committed
fix: allow reolving binaries to original paths
Previously, we'd always binaries from the install context (_build/install/$context/bin). This would unnecessarily load the install rules. Now, we add an argument that allows us to resolve to the original paths. Reducing the amount of rules that need to be loaded. We use this argument in a few cases where we don't need to build the path in _build/install <!-- ps-id: cb6fc8f6-5f50-439b-b542-6b933c656af0 --> Signed-off-by: Rudi Grinberg <[email protected]>
1 parent 01364a7 commit 6d4ab70

File tree

10 files changed

+112
-39
lines changed

10 files changed

+112
-39
lines changed

otherlibs/stdune/src/map.ml

Lines changed: 6 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -44,6 +44,12 @@ module Make (Key : Key) : S with type key = Key.t = struct
4444
let merge a b ~f = merge a b ~f
4545
let union a b ~f = union a b ~f
4646

47+
let union_all maps ~f =
48+
match maps with
49+
| [] -> empty
50+
| init :: maps -> List.fold_left maps ~init ~f:(fun acc map -> union acc map ~f)
51+
;;
52+
4753
let union_exn a b =
4854
union a b ~f:(fun key _ _ ->
4955
Code_error.raise

otherlibs/stdune/src/map_intf.ml

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -20,6 +20,7 @@ module type S = sig
2020
val add_multi : 'a list t -> key -> 'a -> 'a list t
2121
val merge : 'a t -> 'b t -> f:(key -> 'a option -> 'b option -> 'c option) -> 'c t
2222
val union : 'a t -> 'a t -> f:(key -> 'a -> 'a -> 'a option) -> 'a t
23+
val union_all : 'a t list -> f:(key -> 'a -> 'a -> 'a option) -> 'a t
2324

2425
(** Like [union] but raises a code error if a key appears in both maps. *)
2526
val union_exn : 'a t -> 'a t -> 'a t

src/dune_rules/artifacts.ml

Lines changed: 54 additions & 21 deletions
Original file line numberDiff line numberDiff line change
@@ -4,49 +4,83 @@ open Memo.O
44
let bin_dir_basename = ".bin"
55
let local_bin p = Path.Build.relative p bin_dir_basename
66

7+
type origin =
8+
{ binding : File_binding.Unexpanded.t
9+
; dir : Path.Build.t
10+
; dst : Path.Local.t
11+
}
12+
13+
type where =
14+
| Install_dir
15+
| Original_path
16+
17+
type path =
18+
| Resolved of Path.Build.t
19+
| Origin of origin
20+
21+
type local_bins = path Filename.Map.t
22+
723
type t =
824
{ context : Context.t
925
; (* Mapping from executable names to their actual path in the workspace.
1026
The keys are the executable names without the .exe, even on Windows.
1127
Enumerating binaries from install stanzas may involve expanding globs,
1228
but the artifacts database is depended on by the logic which expands
1329
globs. The computation of this field is deferred to break the cycle. *)
14-
local_bins : Path.Build.t Filename.Map.t Memo.Lazy.t
30+
local_bins : local_bins Memo.Lazy.t
1531
}
1632

1733
let force { local_bins; _ } =
18-
let+ (_ : Path.Build.t Filename.Map.t) = Memo.Lazy.force local_bins in
34+
let+ (_ : local_bins) = Memo.Lazy.force local_bins in
1935
()
2036
;;
2137

38+
let expand = Fdecl.create Dyn.opaque
39+
2240
let analyze_binary t name =
2341
match Filename.is_relative name with
24-
| false -> Memo.return (Some (Path.of_filename_relative_to_initial_cwd name))
42+
| false -> Memo.return (`Resolved (Path.of_filename_relative_to_initial_cwd name))
2543
| true ->
2644
let* local_bins = Memo.Lazy.force t.local_bins in
2745
(match Filename.Map.find local_bins name with
28-
| Some path -> Memo.return (Some (Path.build path))
29-
| None -> Context.which t.context name)
46+
| Some (Resolved p) -> Memo.return (`Resolved (Path.build p))
47+
| Some (Origin o) -> Memo.return (`Origin o)
48+
| None ->
49+
Context.which t.context name
50+
>>| (function
51+
| None -> `None
52+
| Some path -> `Resolved path))
3053
;;
3154

32-
let binary t ?hint ~loc name =
55+
let binary t ?hint ?(where = Install_dir) ~loc name =
3356
analyze_binary t name
34-
>>| function
35-
| Some path -> Ok path
36-
| None ->
57+
>>= function
58+
| `Resolved path -> Memo.return @@ Ok path
59+
| `None ->
3760
let context = Context.name t.context in
38-
Error (Action.Prog.Not_found.create ~program:name ?hint ~context ~loc ())
61+
Memo.return
62+
@@ Error (Action.Prog.Not_found.create ~program:name ?hint ~context ~loc ())
63+
| `Origin { dir; binding; dst } ->
64+
(match where with
65+
| Install_dir ->
66+
let install_dir = Install.Context.bin_dir ~context:(Context.name t.context) in
67+
Memo.return @@ Ok (Path.build @@ Path.Build.append_local install_dir dst)
68+
| Original_path ->
69+
let+ expanded =
70+
File_binding.Unexpanded.expand
71+
binding
72+
~dir
73+
~f:(Fdecl.get expand ~context:t.context ~dir)
74+
in
75+
let src = File_binding.Expanded.src expanded in
76+
Ok (Path.build src))
3977
;;
4078

4179
let binary_available t name =
4280
analyze_binary t name
43-
>>= function
44-
| None -> Memo.return false
45-
| Some path ->
46-
(match path with
47-
| External e -> Fs_memo.file_exists @@ External e
48-
| In_source_tree e -> Fs_memo.file_exists @@ In_source_dir e
49-
| In_build_dir _ -> Memo.return true)
81+
>>| function
82+
| `None -> false
83+
| `Resolved _ | `Origin _ -> true
5084
;;
5185

5286
let add_binaries t ~dir l =
@@ -55,7 +89,7 @@ let add_binaries t ~dir l =
5589
let+ local_bins = Memo.Lazy.force t.local_bins in
5690
List.fold_left l ~init:local_bins ~f:(fun acc fb ->
5791
let path = File_binding.Expanded.dst_path fb ~dir:(local_bin dir) in
58-
Filename.Map.set acc (Path.Build.basename path) path))
92+
Filename.Map.set acc (Path.Build.basename path) (Resolved path)))
5993
in
6094
{ t with local_bins }
6195
;;
@@ -70,10 +104,9 @@ let create =
70104
let local_bins =
71105
Memo.lazy_ (fun () ->
72106
let+ local_bins = Memo.Lazy.force local_bins in
73-
Path.Build.Set.fold local_bins ~init:Filename.Map.empty ~f:(fun path acc ->
74-
let name = Path.Build.basename path in
107+
Filename.Map.foldi local_bins ~init:Filename.Map.empty ~f:(fun name origin acc ->
75108
let key = drop_suffix name in
76-
Filename.Map.set acc key path))
109+
Filename.Map.set acc key (Origin origin)))
77110
in
78111
{ context; local_bins }
79112
;;

src/dune_rules/artifacts.mli

Lines changed: 21 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -2,6 +2,16 @@ open Import
22

33
type t
44

5+
type origin =
6+
{ binding : File_binding.Unexpanded.t
7+
; dir : Path.Build.t
8+
; dst : Path.Local.t
9+
}
10+
11+
type where =
12+
| Install_dir
13+
| Original_path
14+
515
(** Force the computation of the internal list of binaries. This is exposed as
616
some error checking is only performed during this computation and some
717
errors will go unreported unless this computation takes place. *)
@@ -15,8 +25,17 @@ val local_bin : Path.Build.t -> Path.Build.t
1525

1626
(** A named artifact that is looked up in the PATH if not found in the tree If
1727
the name is an absolute path, it is used as it. *)
18-
val binary : t -> ?hint:string -> loc:Loc.t option -> string -> Action.Prog.t Memo.t
28+
val binary
29+
: t
30+
-> ?hint:string
31+
-> ?where:where
32+
-> loc:Loc.t option
33+
-> Filename.t
34+
-> Action.Prog.t Memo.t
1935

2036
val binary_available : t -> string -> bool Memo.t
2137
val add_binaries : t -> dir:Path.Build.t -> File_binding.Expanded.t list -> t
22-
val create : Context.t -> local_bins:Path.Build.Set.t Memo.Lazy.t -> t
38+
val create : Context.t -> local_bins:origin Filename.Map.t Memo.Lazy.t -> t
39+
40+
val expand
41+
: (context:Context.t -> dir:Path.Build.t -> String_with_vars.t -> string Memo.t) Fdecl.t

src/dune_rules/artifacts_db.ml

Lines changed: 11 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -35,8 +35,8 @@ let available_exes ~dir (exes : Dune_file.Executables.t) =
3535
;;
3636

3737
let get_installed_binaries ~(context : Context.t) stanzas =
38+
let merge _ _ x = Some x in
3839
let open Memo.O in
39-
let install_dir = Install.Context.bin_dir ~context:(Context.name context) in
4040
let expand ~dir sw = Expander.With_reduced_var_set.expand ~context ~dir sw in
4141
let expand_str ~dir sw = Expander.With_reduced_var_set.expand_str ~context ~dir sw in
4242
let expand_str_partial ~dir sw =
@@ -56,12 +56,14 @@ let get_installed_binaries ~(context : Context.t) stanzas =
5656
~expand:(expand_str ~dir)
5757
~expand_partial:(expand_str_partial ~dir)
5858
in
59-
let p = Path.Local.of_string (Install.Entry.Dst.to_string p) in
60-
if Path.Local.is_root (Path.Local.parent_exn p)
61-
then Some (Path.Build.append_local install_dir p)
59+
let dst = Path.Local.of_string (Install.Entry.Dst.to_string p) in
60+
if Path.Local.is_root (Path.Local.parent_exn dst)
61+
then (
62+
let origin = { Artifacts.binding = fb; dir; dst } in
63+
Some (Path.Local.basename dst, origin))
6264
else None)
6365
>>| List.filter_opt
64-
>>| Path.Build.Set.of_list
66+
>>| Filename.Map.of_list_reduce ~f:(fun _ y -> y)
6567
in
6668
Memo.List.map d.stanzas ~f:(fun stanza ->
6769
match Stanza.repr stanza with
@@ -79,12 +81,10 @@ let get_installed_binaries ~(context : Context.t) stanzas =
7981
| false -> Memo.return true
8082
| true -> available_exes ~dir exes)
8183
in
82-
if available
83-
then binaries_from_install files
84-
else Memo.return Path.Build.Set.empty
85-
| _ -> Memo.return Path.Build.Set.empty)
86-
>>| Path.Build.Set.union_all)
87-
>>| Path.Build.Set.union_all
84+
if available then binaries_from_install files else Memo.return Filename.Map.empty
85+
| _ -> Memo.return Filename.Map.empty)
86+
>>| Filename.Map.union_all ~f:merge)
87+
>>| Filename.Map.union_all ~f:merge
8888
;;
8989

9090
let all =

src/dune_rules/coq/coq_rules.ml

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -95,6 +95,7 @@ let coqc ~loc ~dir ~sctx =
9595
Super_context.resolve_program_memo
9696
sctx
9797
"coqc"
98+
~where:Original_path
9899
~dir
99100
~loc:(Some loc)
100101
~hint:"opam install coq"

src/dune_rules/expander.ml

Lines changed: 5 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -931,3 +931,8 @@ let expand_lock ~base expander (Locks.Lock sw) =
931931
let expand_locks ~base expander locks =
932932
Memo.List.map locks ~f:(expand_lock ~base expander) |> Action_builder.of_memo
933933
;;
934+
935+
let () =
936+
Fdecl.set Artifacts.expand (fun ~context ~dir sw ->
937+
With_reduced_var_set.expand_str ~context ~dir sw)
938+
;;

src/dune_rules/melange/melange_binary.ml

Lines changed: 7 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,7 +1,13 @@
11
open Import
22

33
let melc sctx ~loc ~dir =
4-
Super_context.resolve_program_memo sctx ~loc ~dir ~hint:"opam install melange" "melc"
4+
Super_context.resolve_program_memo
5+
sctx
6+
~loc
7+
~dir
8+
~where:Original_path
9+
~hint:"opam install melange"
10+
"melc"
511
;;
612

713
let where =

src/dune_rules/super_context.ml

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -275,13 +275,13 @@ let add_alias_action t alias ~dir ~loc action =
275275

276276
let env_node = Env_tree.get_node
277277

278-
let resolve_program_memo t ~dir ?hint ~loc bin =
278+
let resolve_program_memo t ~dir ?where ?hint ~loc bin =
279279
let* artifacts = Env_tree.artifacts_host t ~dir in
280-
Artifacts.binary ?hint ~loc artifacts bin
280+
Artifacts.binary ?hint ?where ~loc artifacts bin
281281
;;
282282

283-
let resolve_program t ~dir ?hint ~loc bin =
284-
Action_builder.of_memo @@ resolve_program_memo t ~dir ?hint ~loc bin
283+
let resolve_program t ~dir ?where ?hint ~loc bin =
284+
Action_builder.of_memo @@ resolve_program_memo t ~dir ?where ?hint ~loc bin
285285
;;
286286

287287
let add_packages_env context ~base stanzas packages =

src/dune_rules/super_context.mli

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -69,6 +69,7 @@ val add_alias_action
6969
val resolve_program
7070
: t
7171
-> dir:Path.Build.t
72+
-> ?where:Artifacts.where
7273
-> ?hint:string
7374
-> loc:Loc.t option
7475
-> string
@@ -78,6 +79,7 @@ val resolve_program
7879
val resolve_program_memo
7980
: t
8081
-> dir:Path.Build.t
82+
-> ?where:Artifacts.where
8183
-> ?hint:string
8284
-> loc:Loc.t option
8385
-> string

0 commit comments

Comments
 (0)