Skip to content

Commit 952156c

Browse files
Move dev-tool lock dirs from source into into build folder
Signed-off-by: Marek Kubica <[email protected]>
1 parent 4421b9d commit 952156c

29 files changed

+136
-75
lines changed

src/dune_pkg/lock_dir.ml

Lines changed: 12 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -1782,9 +1782,18 @@ let loc_in_source_tree loc =
17821782
loc
17831783
|> Loc.map_pos ~f:(fun ({ pos_fname; _ } as pos) ->
17841784
let path = Path.of_string pos_fname in
1785-
let new_path = in_source_tree path in
1786-
let pos_fname = Path.Source.to_string new_path in
1787-
{ pos with pos_fname })
1785+
match Path.of_string pos_fname with
1786+
| External _ | In_source_tree _ -> pos
1787+
| In_build_dir b ->
1788+
(match Path.Build.explode b with
1789+
| ".dev-tools.locks" :: _ ->
1790+
(* we're excluding the hidden dev-tools.locks folders in the build folder
1791+
from rewriting *)
1792+
pos
1793+
| _otherwise ->
1794+
let new_path = in_source_tree path in
1795+
let pos_fname = Path.Source.to_string new_path in
1796+
{ pos with pos_fname }))
17881797
;;
17891798

17901799
let check_if_solved_for_platform { solved_for_platforms; _ } ~platform =

src/dune_rules/format_rules.ml

Lines changed: 2 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -33,8 +33,7 @@ end
3333

3434
module Ocamlformat = struct
3535
let dev_tool_lock_dir_exists () =
36-
let path = Lock_dir.dev_tool_source_lock_dir Ocamlformat in
37-
Source_tree.find_dir path >>| Option.is_some
36+
Lock_dir.dev_tool_source_lock_dir Ocamlformat |> Path.source |> Path.Untracked.exists
3837
;;
3938

4039
(* Config files for ocamlformat. When these are changed, running
@@ -129,7 +128,7 @@ let gen_rules_output
129128
let loc = Format_config.loc config in
130129
let dir = Path.Build.parent_exn output_dir in
131130
let alias_formatted = Alias.fmt ~dir:output_dir in
132-
let* ocamlformat_is_locked = Ocamlformat.dev_tool_lock_dir_exists () in
131+
let ocamlformat_is_locked = Ocamlformat.dev_tool_lock_dir_exists () in
133132
let setup_formatting file =
134133
(let input_basename = Path.Source.basename file in
135134
let input = Path.Build.relative dir input_basename in

src/dune_rules/lock_dir.ml

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -148,7 +148,9 @@ let dev_tool_to_path_segment dev_tool =
148148
;;
149149

150150
let dev_tool_source_lock_dir dev_tool =
151-
let dev_tools_path = Path.Source.(relative root "dev-tools.locks") in
151+
let dev_tools_path =
152+
Path.Source.L.relative Path.Source.root [ "_build"; ".dev-tools.locks" ]
153+
in
152154
let dev_tool_segment = dev_tool_to_path_segment dev_tool in
153155
Path.Source.append_local dev_tools_path dev_tool_segment
154156
;;

src/dune_rules/lock_rules.ml

Lines changed: 54 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -25,12 +25,60 @@ let copy_lock_dir ~target ~lock_dir ~deps ~files =
2525
|> action_builder_with_dir_targets ~directory_targets:[ target ]
2626
;;
2727

28-
let setup_copy_rules ~dir:target ~lock_dir =
29-
let+ deps, files = Source_deps.files (Path.source lock_dir) in
28+
let files dir =
29+
let rec recurse dir =
30+
match Path.Untracked.readdir_unsorted_with_kinds dir with
31+
| Ok entries ->
32+
entries
33+
|> List.fold_left
34+
~init:(Path.Set.empty, Path.Set.empty)
35+
~f:(fun (files, empty_directories) (entry, kind) ->
36+
let path = Path.relative dir entry in
37+
match (kind : Unix.file_kind) with
38+
| S_REG ->
39+
let files = Path.Set.add files path in
40+
files, empty_directories
41+
| S_DIR ->
42+
let files', empty_directories' = recurse path in
43+
(match Path.Set.is_empty files', Path.Set.is_empty empty_directories' with
44+
| true, true ->
45+
let empty_directories = Path.Set.add empty_directories path in
46+
files, empty_directories
47+
| _, _ ->
48+
let files = Path.Set.union files files' in
49+
let empty_directories =
50+
Path.Set.union empty_directories empty_directories'
51+
in
52+
files, empty_directories)
53+
| otherwise ->
54+
Code_error.raise
55+
"unsupported kind of file in folder"
56+
[ "path", Path.to_dyn path; "kind", File_kind.to_dyn otherwise ])
57+
| Error (ENOENT, _, _) -> Path.Set.empty, Path.Set.empty
58+
| Error unix_error ->
59+
User_error.raise
60+
[ Pp.textf
61+
"Failed to read lock dir files of %s:"
62+
(Path.to_string_maybe_quoted dir)
63+
; Pp.text (Unix_error.Detailed.to_string_hum unix_error)
64+
]
65+
in
66+
let files, empty_directories = recurse dir in
67+
Dep.Set.of_source_files ~files ~empty_directories, files
68+
;;
69+
70+
let setup_copy_rules ~dir:target ~assume_src_exists ~lock_dir =
71+
let+ () = Memo.return () in
72+
let deps, files = files (Path.source lock_dir) in
3073
let directory_targets, rules =
3174
match Path.Set.is_empty files with
3275
| true -> Path.Build.Map.empty, Rules.empty
3376
| false ->
77+
let deps =
78+
match assume_src_exists with
79+
| false -> deps
80+
| true -> Dep.Set.empty
81+
in
3482
let directory_targets = Path.Build.Map.singleton target Loc.none in
3583
let { Action_builder.With_targets.build; targets } =
3684
copy_lock_dir ~target ~lock_dir ~deps ~files
@@ -44,15 +92,17 @@ let setup_copy_rules ~dir:target ~lock_dir =
4492
let setup_lock_rules (workspace : Workspace.t) ~dir ~lock_dir =
4593
let dir = Path.Build.append_local dir lock_dir in
4694
let lock_dir = Path.Source.append_local workspace.dir lock_dir in
47-
setup_copy_rules ~dir ~lock_dir
95+
setup_copy_rules ~dir ~assume_src_exists:false ~lock_dir
4896
;;
4997

5098
let setup_dev_tool_lock_rules ~dir dev_tool =
5199
let package_name = Dune_pkg.Dev_tool.package_name dev_tool in
52100
let dev_tool_name = Dune_lang.Package_name.to_string package_name in
53101
let dir = Path.Build.relative dir dev_tool_name in
54102
let lock_dir = Lock_dir.dev_tool_source_lock_dir dev_tool in
55-
setup_copy_rules ~dir ~lock_dir
103+
(* dev tool lock files are created in _build outside of the build system
104+
so we have to tell the build system not to try to create them *)
105+
setup_copy_rules ~dir ~assume_src_exists:true ~lock_dir
56106
;;
57107

58108
let lock_dirs_of_workspace (workspace : Workspace.t) =

src/dune_rules/pkg_rules.ml

Lines changed: 12 additions & 18 deletions
Original file line numberDiff line numberDiff line change
@@ -1494,10 +1494,10 @@ end = struct
14941494
in
14951495
resolve db dep_loc dep_pkg_digest package_universe)
14961496
and+ files_dir =
1497-
let* lock_dir =
1497+
let+ lock_dir =
14981498
Package_universe.lock_dir_path package_universe >>| Option.value_exn
14991499
in
1500-
let+ files_dir =
1500+
let files_dir =
15011501
let module Pkg = Dune_pkg.Lock_dir.Pkg in
15021502
(* TODO(steve): simplify this once portable lockdirs become the
15031503
default. This logic currently handles both the cases where
@@ -1509,17 +1509,15 @@ end = struct
15091509
let path_with_version =
15101510
Pkg.source_files_dir info.name (Some info.version) ~lock_dir
15111511
in
1512-
let* path_with_version_exists =
1513-
Fs_memo.dir_exists (Path.Outside_build_dir.In_source_dir path_with_version)
1512+
let path_with_version_exists =
1513+
Path.Untracked.exists (Path.source path_with_version)
15141514
in
15151515
match path_with_version_exists with
1516-
| true ->
1517-
Memo.return @@ Some (Pkg.files_dir info.name (Some info.version) ~lock_dir)
1516+
| true -> Some (Pkg.files_dir info.name (Some info.version) ~lock_dir)
15181517
| false ->
15191518
let path_without_version = Pkg.source_files_dir info.name None ~lock_dir in
1520-
let+ path_without_version_exists =
1521-
Fs_memo.dir_exists
1522-
(Path.Outside_build_dir.In_source_dir path_without_version)
1519+
let path_without_version_exists =
1520+
Path.Untracked.exists (Path.source path_without_version)
15231521
in
15241522
(match path_without_version_exists with
15251523
| true -> Some (Pkg.files_dir info.name None ~lock_dir)
@@ -1533,18 +1531,14 @@ end = struct
15331531
"Package files directory is external source directory, this is unsupported"
15341532
[ "dir", Path.External.to_dyn e ]
15351533
| In_source_tree s ->
1536-
(match Path.Source.explode s with
1537-
| [ "dev-tools.locks"; dev_tool; files_dir ] ->
1534+
Code_error.raise "Unexpected files_dir path" [ "dir", Path.Source.to_dyn s ]
1535+
| In_build_dir b ->
1536+
(match Path.Build.explode b with
1537+
| [ ".dev-tools.locks"; dev_tool; files_dir ] ->
15381538
Path.Build.L.relative
15391539
Private_context.t.build_dir
15401540
[ "default"; ".dev-tool-locks"; dev_tool; files_dir ]
1541-
| otherwise ->
1542-
Code_error.raise
1543-
"Unexpected files_dir path"
1544-
[ "components", (Dyn.list Dyn.string) otherwise ])
1545-
| In_build_dir b ->
1546-
(* it's already a build path, no need to do anything *)
1547-
b)
1541+
| _otherwise -> b))
15481542
in
15491543
let id = Pkg.Id.gen () in
15501544
let write_paths =

test/blackbox-tests/test-cases/pkg/ocamlformat/gh10991.t

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -19,7 +19,7 @@ Initial file:
1919
let () = print_endline "Hello, world"
2020

2121
$ DUNE_CONFIG__LOCK_DEV_TOOL=enabled dune fmt
22-
Solution for dev-tools.locks/ocamlformat:
22+
Solution for _build/.dev-tools.locks/ocamlformat:
2323
- ocamlformat.0.0.1
2424
File "foo.ml", line 1, characters 0-0:
2525
Error: Files _build/default/foo.ml and _build/default/.formatted/foo.ml

test/blackbox-tests/test-cases/pkg/ocamlformat/gh11037.t

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -40,7 +40,7 @@ attempt to build the package "foo".
4040
$ cat foo.ml
4141
let () = print_endline "Hello, world"
4242
$ DUNE_CONFIG__LOCK_DEV_TOOL=enabled dune fmt
43-
Solution for dev-tools.locks/ocamlformat:
43+
Solution for _build/.dev-tools.locks/ocamlformat:
4444
- ocamlformat.0.0.1
4545
File "foo.ml", line 1, characters 0-0:
4646
Error: Files _build/default/foo.ml and _build/default/.formatted/foo.ml

test/blackbox-tests/test-cases/pkg/ocamlformat/helpers.sh

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,7 @@
11
. ../helpers.sh
22

3+
dev_tool_lock_dir="_build/.dev-tools.locks/ocamlformat"
4+
35
make_fake_ocamlformat() {
46
version=$1
57
if [ "$#" -eq "1" ]
@@ -97,7 +99,7 @@ EOF
9799
(lang dune 3.20)
98100
99101
(lock_dir
100-
(path "dev-tools.locks/ocamlformat")
102+
(path "${dev_tool_lock_dir}")
101103
(repositories mock))
102104
103105
(lock_dir

test/blackbox-tests/test-cases/pkg/ocamlformat/ocamlformat-avoid-conflict-with-project.t

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -29,7 +29,7 @@ Add a fake executable in the PATH
2929

3030
Build the OCamlFormat binary dev-tool
3131
$ DUNE_CONFIG__LOCK_DEV_TOOL=enabled dune fmt --preview
32-
Solution for dev-tools.locks/ocamlformat:
32+
Solution for _build/.dev-tools.locks/ocamlformat:
3333
- ocamlformat.0.26.2
3434
File "dune", line 1, characters 0-0:
3535
Error: Files _build/default/dune and _build/default/.formatted/dune differ.

test/blackbox-tests/test-cases/pkg/ocamlformat/ocamlformat-avoid-taking-from-project-deps.t

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -45,7 +45,7 @@ Format using the dev-tools feature, it does not invoke the OCamlFormat binary fr
4545
the project dependencies (0.26.2) but instead builds and runs the OCamlFormat binary as a
4646
dev-tool (0.26.3).
4747
$ DUNE_CONFIG__LOCK_DEV_TOOL=enabled dune fmt
48-
Solution for dev-tools.locks/ocamlformat:
48+
Solution for _build/.dev-tools.locks/ocamlformat:
4949
- ocamlformat.0.26.3
5050
File "foo.ml", line 1, characters 0-0:
5151
Error: Files _build/default/foo.ml and _build/default/.formatted/foo.ml
@@ -59,7 +59,7 @@ Retry, without dev-tools feature and without cleaning. This time it uses the OCa
5959
binary from the project dependencies rather than the dev-tool. This exercises the
6060
behavior when OCamlFormat is installed simultaneously as both a dev-tool and as a
6161
regular package dependency.
62-
$ rm -rf dev-tools.locks/ocamlformat
62+
$ rm -r "${dev_tool_lock_dir}"
6363
$ dune fmt --preview
6464
File "foo.ml", line 1, characters 0-0:
6565
Error: Files _build/default/foo.ml and _build/default/.formatted/foo.ml

0 commit comments

Comments
 (0)