Skip to content

Commit ac78d7b

Browse files
Turn the dev-tool path to a Path.External.t
Signed-off-by: Marek Kubica <[email protected]>
1 parent 5b6d2a6 commit ac78d7b

File tree

17 files changed

+122
-51
lines changed

17 files changed

+122
-51
lines changed

bin/lock_dev_tool.ml

Lines changed: 8 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -80,7 +80,9 @@ let solve ~dev_tool ~local_packages =
8080
| `Disabled -> workspace
8181
in
8282
(* as we want to write to the source, we're using the source lock dir here *)
83-
let lock_dir = Dune_rules.Lock_dir.dev_tool_untracked_lock_dir dev_tool in
83+
let lock_dir =
84+
Dune_rules.Lock_dir.dev_tool_external_lock_dir dev_tool |> Path.external_
85+
in
8486
Memo.of_reproducible_fiber
8587
@@ Pkg.Lock.solve
8688
workspace
@@ -174,11 +176,14 @@ let extra_dependencies dev_tool =
174176

175177
let lockdir_status dev_tool =
176178
let open Memo.O in
177-
let dev_tool_lock_dir = Dune_rules.Lock_dir.dev_tool_untracked_lock_dir dev_tool in
178-
let lock_dir_exists = Path.exists dev_tool_lock_dir in
179+
let dev_tool_lock_dir = Dune_rules.Lock_dir.dev_tool_external_lock_dir dev_tool in
180+
let* lock_dir_exists =
181+
Dune_engine.Fs_memo.dir_exists (Path.Outside_build_dir.External dev_tool_lock_dir)
182+
in
179183
match lock_dir_exists with
180184
| false -> Memo.return `No_lockdir
181185
| true ->
186+
let dev_tool_lock_dir = Path.external_ dev_tool_lock_dir in
182187
(match Lock_dir.read_disk dev_tool_lock_dir with
183188
| Error _ -> Memo.return `No_lockdir
184189
| Ok { packages; _ } ->

bin/ocaml/utop.ml

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -58,8 +58,8 @@ let term =
5858
[ Pp.textf "no library is defined in %s" (String.maybe_quoted dir) ]
5959
| true ->
6060
let* () = Build_system.build_file utop_exe in
61-
let utop_dev_tool_lock_dir_exists =
62-
Lazy.force Utop.utop_dev_tool_lock_dir_exists
61+
let* utop_dev_tool_lock_dir_exists =
62+
Memo.Lazy.force Utop.utop_dev_tool_lock_dir_exists
6363
in
6464
let* () =
6565
if utop_dev_tool_lock_dir_exists

bin/pkg/lock.ml

Lines changed: 16 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -197,6 +197,13 @@ let solve_multiple_platforms
197197
|> Platforms_by_message.all_solver_errors_raising_if_any_manifest_errors )
198198
;;
199199

200+
let user_lock_dir_path path =
201+
match (path : Path.t) with
202+
| In_source_tree _ -> path
203+
| In_build_dir _ -> path
204+
| External e -> Dune_pkg.Pkg_workspace.dev_tool_path_to_source_dir e |> Path.source
205+
;;
206+
200207
let summary_message
201208
~portable_lock_dir
202209
~lock_dir_path
@@ -259,7 +266,9 @@ let summary_message
259266
in
260267
(Pp.tag
261268
User_message.Style.Success
262-
(Pp.textf "Solution for %s" (Path.to_string_maybe_quoted lock_dir_path))
269+
(Pp.textf
270+
"Solution for %s"
271+
(Path.to_string_maybe_quoted (user_lock_dir_path lock_dir_path)))
263272
:: Pp.nop
264273
:: Pp.text "Dependencies common to all supported platforms:"
265274
:: pp_package_set common_packages
@@ -268,7 +277,9 @@ let summary_message
268277
else
269278
(Pp.tag
270279
User_message.Style.Success
271-
(Pp.textf "Solution for %s:" (Path.to_string_maybe_quoted lock_dir_path))
280+
(Pp.textf
281+
"Solution for %s:"
282+
(Path.to_string_maybe_quoted (user_lock_dir_path lock_dir_path)))
272283
:: (match Lock_dir.Packages.to_pkg_list lock_dir.packages with
273284
| [] -> Pp.tag User_message.Style.Warning @@ Pp.text "(no dependencies to lock)"
274285
| packages -> pp_packages packages)
@@ -491,7 +502,9 @@ let solve
491502
([ Pp.text "Unable to solve dependencies for the following lock directories:" ]
492503
@ List.concat_map errors ~f:(fun (path, errors) ->
493504
let messages = List.map errors ~f:fst in
494-
[ Pp.textf "Lock directory %s:" (Path.to_string_maybe_quoted path)
505+
[ Pp.textf
506+
"Lock directory %s:"
507+
(Path.to_string_maybe_quoted (user_lock_dir_path path))
495508
; Pp.vbox (Pp.concat ~sep:Pp.cut messages)
496509
]))
497510
| Ok write_disks_with_summaries ->

src/dune_pkg/lock_dir.ml

Lines changed: 8 additions & 12 deletions
Original file line numberDiff line numberDiff line change
@@ -538,10 +538,7 @@ let in_source_tree path =
538538
; "source_components", Dyn.(list string) source_components
539539
; "build_components", Dyn.(list string) build_components
540540
]))
541-
| External e ->
542-
Code_error.raise
543-
"External path returned when loading a lock dir"
544-
[ "path", Path.External.to_dyn e ]
541+
| External e -> Workspace.dev_tool_path_to_source_dir e
545542
;;
546543

547544
module Pkg = struct
@@ -887,14 +884,9 @@ module Pkg = struct
887884
^ extension)
888885
;;
889886

887+
(* TODO remove *)
890888
let files_dir package_name maybe_package_version ~lock_dir =
891-
match files_dir_generic package_name maybe_package_version ~lock_dir with
892-
| In_source_tree _ as path -> path
893-
| In_build_dir _ as path -> path
894-
| External e ->
895-
Code_error.raise
896-
"file_dir is an external path, this is unsupported"
897-
[ "path", Path.External.to_dyn e ]
889+
files_dir_generic package_name maybe_package_version ~lock_dir
898890
;;
899891

900892
let source_files_dir package_name maybe_package_version ~lock_dir =
@@ -1402,7 +1394,11 @@ module Write_disk = struct
14021394
let safely_remove_lock_dir_if_exists_thunk path =
14031395
match check_existing_lock_dir path with
14041396
| Ok `Non_existant -> Fun.const ()
1405-
| Ok `Is_existing_lock_dir -> fun () -> Path.rm_rf path
1397+
| Ok `Is_existing_lock_dir ->
1398+
fun () ->
1399+
(* dev-tool lock dirs are external paths despite living in _build, they're
1400+
safe to remove *)
1401+
Path.rm_rf ~allow_external:true path
14061402
| Error e -> raise_user_error_on_check_existance path e
14071403
;;
14081404

src/dune_pkg/workspace.ml

Lines changed: 34 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -70,3 +70,37 @@ module Repository = struct
7070

7171
let opam_url { name = _; url } = url
7272
end
73+
74+
let dev_tool_path_to_source_dir path =
75+
let of_ =
76+
Path.Build.relative Path.Build.root ".dev-tools.locks"
77+
|> Path.build
78+
|> Path.to_absolute_filename
79+
|> Path.External.of_string
80+
in
81+
let in_dev_tool_dir = Path.External.is_descendant ~of_ path in
82+
match in_dev_tool_dir with
83+
| false ->
84+
Code_error.raise
85+
"External lock dir path is unsupported"
86+
[ "dir", Path.External.to_dyn path ]
87+
| true ->
88+
let prefix = Path.External.to_string of_ in
89+
let as_string = Path.External.to_string path in
90+
let relative =
91+
String.sub
92+
as_string
93+
~pos:(String.length prefix)
94+
~len:(String.length as_string - String.length prefix)
95+
in
96+
let exploded = String.split ~on:'/' relative in
97+
(match exploded with
98+
| "" :: dev_tool_name :: components ->
99+
Path.Source.L.relative
100+
Path.Source.root
101+
([ "_build"; ".dev-tools.locks"; dev_tool_name ] @ components)
102+
| components ->
103+
Code_error.raise
104+
"Unexpected external path"
105+
[ "dir", Path.External.to_dyn path; "components", Dyn.(list string) components ])
106+
;;

src/dune_pkg/workspace.mli

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -25,3 +25,5 @@ module Repository : sig
2525

2626
val name : t -> Name.t
2727
end
28+
29+
val dev_tool_path_to_source_dir : Path.External.t -> Path.Source.t

src/dune_rules/fetch_rules.ml

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -189,11 +189,11 @@ let find_checksum, find_url =
189189
Dune_pkg.Dev_tool.all
190190
~init:(Checksum.Map.empty, Digest.Map.empty)
191191
~f:(fun acc dev_tool ->
192-
let dir = Lock_dir.dev_tool_untracked_lock_dir dev_tool in
192+
let dir = Lock_dir.dev_tool_external_lock_dir dev_tool in
193193
let exists =
194194
(* Note we use [Path.Untracked] here rather than [Fs_memo] because a tool's
195195
lockdir may be generated part way through a build. *)
196-
Path.Untracked.exists dir
196+
Path.Untracked.exists (Path.external_ dir)
197197
in
198198
match exists with
199199
| false -> Memo.return acc

src/dune_rules/format_rules.ml

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -33,7 +33,9 @@ end
3333

3434
module Ocamlformat = struct
3535
let dev_tool_lock_dir_exists () =
36-
Lock_dir.dev_tool_untracked_lock_dir Ocamlformat |> Path.Untracked.exists
36+
Lock_dir.dev_tool_external_lock_dir Ocamlformat
37+
|> Path.external_
38+
|> Path.Untracked.exists
3739
;;
3840

3941
(* Config files for ocamlformat. When these are changed, running

src/dune_rules/lock_dir.ml

Lines changed: 8 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -148,10 +148,13 @@ let dev_tool_to_path_segment dev_tool =
148148
;;
149149

150150
(* This function returns the lock dir that is created outside the build system. *)
151-
let dev_tool_untracked_lock_dir dev_tool =
152-
let dev_tools_path = Path.Build.relative Path.Build.root ".dev-tools.locks" in
151+
let dev_tool_external_lock_dir dev_tool =
152+
let external_root =
153+
Path.Build.root |> Path.build |> Path.to_absolute_filename |> Path.External.of_string
154+
in
155+
let dev_tools_path = Path.External.relative external_root ".dev-tools.locks" in
153156
let dev_tool_segment = dev_tool_to_path_segment dev_tool in
154-
Path.Build.append_local dev_tools_path dev_tool_segment |> Path.build
157+
Path.External.append_local dev_tools_path dev_tool_segment
155158
;;
156159

157160
(* This function returns the lock dir location where the build system can create
@@ -230,12 +233,12 @@ let get ctx = get_with_path ctx >>| Result.map ~f:snd
230233
let get_exn ctx = get ctx >>| User_error.ok_exn
231234

232235
let of_dev_tool dev_tool =
233-
let path = dev_tool_untracked_lock_dir dev_tool in
236+
let path = dev_tool |> dev_tool_external_lock_dir |> Path.external_ in
234237
Load.load_exn path
235238
;;
236239

237240
let of_dev_tool_if_lock_dir_exists dev_tool =
238-
let path = dev_tool_untracked_lock_dir dev_tool in
241+
let path = dev_tool |> dev_tool_external_lock_dir |> Path.external_ in
239242
let exists =
240243
(* Note we use [Path.Untracked] here rather than [Fs_memo] because a tool's
241244
lockdir may be generated part way through a build. *)

src/dune_rules/lock_dir.mli

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -21,7 +21,7 @@ val default_path : Path.t
2121
val default_source_path : Path.Source.t
2222

2323
(** The location in the source tree where a dev tool lock dir is expected *)
24-
val dev_tool_untracked_lock_dir : Dune_pkg.Dev_tool.t -> Path.t
24+
val dev_tool_external_lock_dir : Dune_pkg.Dev_tool.t -> Path.External.t
2525

2626
(** Returns the path to the lock_dir that will be used to lock the
2727
given dev tool *)

0 commit comments

Comments
 (0)