@@ -4,49 +4,83 @@ open Memo.O
44let bin_dir_basename = " .bin"
55let 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+
723type 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
1733let 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+
2240let 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
4179let 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
5286let 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;;
0 commit comments