Skip to content

Commit 422dd9a

Browse files
authored
Add support for hard links (#4360)
Implement a basic support for hard links in Dune, so that building with `--sandbox=hardlink` works. We don't expose the symlink and hardlink actions in the Action DSL, so no version guards are needed. Below are some benchmarks where I build Dune's `runtest` with different sandbox settings. ```bash $ time _build/default/bin/main.exe build @runtest -f real 0m37.884s user 2m11.915s sys 1m27.692s $ time _build/default/bin/main.exe build @runtest -f --sandbox=symlink real 0m39.652s user 2m13.690s sys 1m28.427s $ time _build/default/bin/main.exe build @runtest -f --sandbox=hardlink real 0m31.362s user 2m12.012s sys 1m21.727s $ time _build/default/bin/main.exe build @runtest -f --sandbox=copy real 2m1.192s user 3m18.269s sys 1m47.362s ``` As expected, ` --sandbox=copy` is the slowest. Somewhat surprisingly to me, `--sandbox=hardlink` is noticeably faster than not using sandbox at all, and using `--sandbox=symlink`. Perhaps, in the latter two cases, we need to fall back to copying for some rules that require sandboxing. Signed-off-by: Andrey Mokhov <amokhov@janestreet.com>
1 parent 0693738 commit 422dd9a

16 files changed

+136
-45
lines changed

CHANGES.md

+2
Original file line numberDiff line numberDiff line change
@@ -92,6 +92,8 @@ Unreleased
9292
- If an .ml file is not used by an executable, Dune no longer report
9393
parsing error in this file (#...., @jeremiedimino)
9494

95+
- Add support for sandboxing using hard links (#4360, @snowleopard)
96+
9597
2.8.2 (21/01/2021)
9698
------------------
9799

doc/concepts.rst

+3-3
Original file line numberDiff line numberDiff line change
@@ -814,9 +814,9 @@ directory, filtering it to only contain the files that were declared as
814814
dependencies. Then we run the action in that directory, and then we copy
815815
the targets back to the build directory.
816816

817-
You can configure dune to use sandboxing modes ``symlink`` or ``copy``, which
818-
determines how the individual files are populated (they will be symlinked or
819-
copied into the sandbox directory).
817+
You can configure dune to use sandboxing modes ``symlink``, ``hardlink`` or
818+
``copy``, which determines how the individual files are populated (they will be
819+
symlinked, hardlinked or copied into the sandbox directory).
820820

821821
This approach is very simple and portable, but that comes with
822822
certain limitations:

src/dune_engine/action.ml

+21-10
Original file line numberDiff line numberDiff line change
@@ -136,6 +136,7 @@ let fold_one_step t ~init:acc ~f =
136136
| Cat _
137137
| Copy _
138138
| Symlink _
139+
| Hardlink _
139140
| Copy_and_add_line_directive _
140141
| System _
141142
| Bash _
@@ -185,6 +186,7 @@ let rec is_dynamic = function
185186
| Cat _
186187
| Copy _
187188
| Symlink _
189+
| Hardlink _
188190
| Copy_and_add_line_directive _
189191
| Write_file _
190192
| Rename _
@@ -215,18 +217,26 @@ let prepare_managed_paths ~link ~sandboxed deps =
215217
Progn steps
216218

217219
let link_function ~(mode : Sandbox_mode.some) : path -> target -> t =
220+
let win32_error mode =
221+
let mode = Sandbox_mode.to_string (Some mode) in
222+
Code_error.raise
223+
(sprintf
224+
"Don't have %ss on win32, but [%s] sandboxing mode was selected. To \
225+
use emulation via copy, the [copy] sandboxing mode should be \
226+
selected."
227+
mode mode)
228+
[]
229+
in
218230
match mode with
219-
| Symlink ->
220-
if Sys.win32 then
221-
Code_error.raise
222-
"Don't have symlinks on win32, but [Symlink] sandboxing mode was \
223-
selected. To use emulation via copy, the [Copy] sandboxing mode \
224-
should be selected."
225-
[]
226-
else
227-
fun a b ->
228-
Symlink (a, b)
231+
| Symlink -> (
232+
match Sys.win32 with
233+
| true -> win32_error mode
234+
| false -> fun a b -> Symlink (a, b))
229235
| Copy -> fun a b -> Copy (a, b)
236+
| Hardlink -> (
237+
match Sys.win32 with
238+
| true -> win32_error mode
239+
| false -> fun a b -> Hardlink (a, b))
230240

231241
let maybe_sandbox_path f p =
232242
match Path.as_in_build_dir p with
@@ -266,6 +276,7 @@ let is_useful_to distribute memoize =
266276
| Cat _ -> memoize
267277
| Copy _ -> memoize
268278
| Symlink _ -> false
279+
| Hardlink _ -> false
269280
| Copy_and_add_line_directive _ -> memoize
270281
| Write_file _ -> distribute
271282
| Rename _ -> memoize

src/dune_engine/action_ast.ml

+1
Original file line numberDiff line numberDiff line change
@@ -247,6 +247,7 @@ struct
247247
| Cat x -> List [ atom "cat"; path x ]
248248
| Copy (x, y) -> List [ atom "copy"; path x; target y ]
249249
| Symlink (x, y) -> List [ atom "symlink"; path x; target y ]
250+
| Hardlink (x, y) -> List [ atom "hardlink"; path x; target y ]
250251
| Copy_and_add_line_directive (x, y) ->
251252
List [ atom "copy#"; path x; target y ]
252253
| System x -> List [ atom "system"; string x ]

src/dune_engine/action_dune_lang.ml

+1
Original file line numberDiff line numberDiff line change
@@ -55,6 +55,7 @@ let ensure_at_most_one_dynamic_run ~loc action =
5555
| Cat _
5656
| Copy _
5757
| Symlink _
58+
| Hardlink _
5859
| Copy_and_add_line_directive _
5960
| System _
6061
| Bash _

src/dune_engine/action_exec.ml

+25
Original file line numberDiff line numberDiff line change
@@ -246,6 +246,31 @@ let rec exec t ~ectx ~eenv =
246246
)
247247
| exception _ -> Unix.symlink src dst);
248248
Fiber.return Done
249+
| Hardlink (src, dst) ->
250+
(* CR-someday amokhov: Instead of always falling back to copying, we could
251+
detect if hardlinking works on Windows and if yes, use it. We do this in
252+
the Dune cache implementation, so we can share some code. *)
253+
(match Sys.win32 with
254+
| true -> Io.copy_file ~src ~dst:(Path.build dst) ()
255+
| false -> (
256+
let rec follow_symlinks name =
257+
match Unix.readlink name with
258+
| link_name ->
259+
let name = Filename.concat (Filename.dirname name) link_name in
260+
follow_symlinks name
261+
| exception Unix.Unix_error (Unix.EINVAL, _, _) -> name
262+
in
263+
let src = follow_symlinks (Path.to_string src) in
264+
let dst = Path.Build.to_string dst in
265+
try Unix.link src dst with
266+
| Unix.Unix_error (Unix.EEXIST, _, _) ->
267+
(* CR-someday amokhov: Investigate why we need to occasionally clear the
268+
destination (we also do this in the symlink case above). Perhaps, the
269+
list of dependencies may have duplicates? If yes, it may be better to
270+
filter out the duplicates first. *)
271+
Unix.unlink dst;
272+
Unix.link src dst));
273+
Fiber.return Done
249274
| Copy_and_add_line_directive (src, dst) ->
250275
Io.with_file_in src ~f:(fun ic ->
251276
Path.build dst

src/dune_engine/action_intf.ml

+1
Original file line numberDiff line numberDiff line change
@@ -36,6 +36,7 @@ module type Ast = sig
3636
| Cat of path
3737
| Copy of path * target
3838
| Symlink of path * target
39+
| Hardlink of path * target
3940
| Copy_and_add_line_directive of path * target
4041
| System of string
4142
| Bash of string

src/dune_engine/action_mapper.ml

+1
Original file line numberDiff line numberDiff line change
@@ -33,6 +33,7 @@ module Make (Src : Action_intf.Ast) (Dst : Action_intf.Ast) = struct
3333
| Cat x -> Cat (f_path ~dir x)
3434
| Copy (x, y) -> Copy (f_path ~dir x, f_target ~dir y)
3535
| Symlink (x, y) -> Symlink (f_path ~dir x, f_target ~dir y)
36+
| Hardlink (x, y) -> Hardlink (f_path ~dir x, f_target ~dir y)
3637
| Copy_and_add_line_directive (x, y) ->
3738
Copy_and_add_line_directive (f_path ~dir x, f_target ~dir y)
3839
| System x -> System (f_string ~dir x)

src/dune_engine/build_system.ml

+19-14
Original file line numberDiff line numberDiff line change
@@ -1326,23 +1326,28 @@ end = struct
13261326
let select_sandbox_mode (config : Sandbox_config.t) ~loc
13271327
~sandboxing_preference =
13281328
let evaluate_sandboxing_preference preference =
1329+
let use_copy_on_windows mode =
1330+
match Sandbox_mode.Set.mem config Sandbox_mode.copy with
1331+
| true ->
1332+
Some
1333+
(if Sys.win32 then
1334+
Sandbox_mode.copy
1335+
else
1336+
mode)
1337+
| false ->
1338+
User_error.raise ~loc
1339+
[ Pp.textf
1340+
"This rule requires sandboxing with %ss, but that won't work \
1341+
on Windows."
1342+
(Sandbox_mode.to_string mode)
1343+
]
1344+
in
13291345
match Sandbox_mode.Set.mem config preference with
13301346
| false -> None
13311347
| true -> (
13321348
match preference with
1333-
| Some Symlink ->
1334-
if Sandbox_mode.Set.mem config Sandbox_mode.copy then
1335-
Some
1336-
(if Sys.win32 then
1337-
Sandbox_mode.copy
1338-
else
1339-
Sandbox_mode.symlink)
1340-
else
1341-
User_error.raise ~loc
1342-
[ Pp.text
1343-
"This rule requires sandboxing with symlinks, but that won't \
1344-
work on Windows."
1345-
]
1349+
| Some Symlink -> use_copy_on_windows Sandbox_mode.symlink
1350+
| Some Hardlink -> use_copy_on_windows Sandbox_mode.hardlink
13461351
| _ -> Some preference)
13471352
in
13481353
match
@@ -1376,7 +1381,7 @@ end = struct
13761381

13771382
(* The current version of the rule digest scheme. We should increment it when
13781383
making any changes to the scheme, to avoid collisions. *)
1379-
let rule_digest_version = 2
1384+
let rule_digest_version = 3
13801385

13811386
let compute_rule_digest (rule : Rule.t) ~deps ~action ~sandbox_mode =
13821387
let env = Rule.effective_env rule in

src/dune_engine/dep.ml

+2-7
Original file line numberDiff line numberDiff line change
@@ -42,18 +42,13 @@ module T = struct
4242

4343
let encode t =
4444
let open Dune_lang.Encoder in
45-
let sandbox_mode (mode : Sandbox_mode.t) =
46-
match mode with
47-
| None -> "none"
48-
| Some Copy -> "copy"
49-
| Some Symlink -> "symlink"
50-
in
5145
let sandbox_config (config : Sandbox_config.t) =
5246
list
5347
(fun x -> x)
5448
(List.filter_map Sandbox_mode.all ~f:(fun mode ->
5549
if not (Sandbox_config.mem config mode) then
56-
Some (pair string string ("disallow", sandbox_mode mode))
50+
Some
51+
(pair string string ("disallow", Sandbox_mode.to_string mode))
5752
else
5853
None))
5954
in

src/dune_engine/sandbox_mode.ml

+24-6
Original file line numberDiff line numberDiff line change
@@ -3,13 +3,17 @@ open! Stdune
33
type some =
44
| Symlink
55
| Copy
6+
| Hardlink
67

78
let compare_some a b =
89
match (a, b) with
910
| Symlink, Symlink -> Eq
1011
| Symlink, _ -> Lt
1112
| _, Symlink -> Gt
1213
| Copy, Copy -> Eq
14+
| Copy, _ -> Lt
15+
| _, Copy -> Gt
16+
| Hardlink, Hardlink -> Eq
1317

1418
type t = some option
1519

@@ -29,6 +33,7 @@ module Dict = struct
2933
{ none : 'a
3034
; symlink : 'a
3135
; copy : 'a
36+
; hardlink : 'a
3237
}
3338

3439
let compare compare x y =
@@ -39,16 +44,22 @@ module Dict = struct
3944
| Gt -> Gt
4045
in
4146
compare_k x.none y.none (fun () ->
42-
compare_k x.symlink y.symlink (fun () -> compare x.copy y.copy))
47+
compare_k x.symlink y.symlink (fun () ->
48+
compare_k x.copy y.copy (fun () -> compare x.hardlink y.hardlink)))
4349

4450
let of_func (f : key -> _) =
45-
{ none = f None; symlink = f (Some Symlink); copy = f (Some Copy) }
51+
{ none = f None
52+
; symlink = f (Some Symlink)
53+
; copy = f (Some Copy)
54+
; hardlink = f (Some Hardlink)
55+
}
4656

47-
let get { none; symlink; copy } (key : key) =
57+
let get { none; symlink; copy; hardlink } (key : key) =
4858
match key with
4959
| None -> none
5060
| Some Copy -> copy
5161
| Some Symlink -> symlink
62+
| Some Hardlink -> hardlink
5263
end
5364

5465
module Set = struct
@@ -73,27 +84,34 @@ module Set = struct
7384
{ none = x.none && y.none
7485
; copy = x.copy && y.copy
7586
; symlink = x.symlink && y.symlink
87+
; hardlink = x.hardlink && y.hardlink
7688
}
7789
end
7890

7991
(* these should be listed in the default order of preference *)
80-
let all = [ None; Some Symlink; Some Copy ]
92+
let all = [ None; Some Symlink; Some Copy; Some Hardlink ]
8193

8294
let none = None
8395

8496
let symlink = Some Symlink
8597

8698
let copy = Some Copy
8799

88-
let error = Error "invalid sandboxing mode, must be 'none', 'symlink' or 'copy'"
100+
let hardlink = Some Hardlink
101+
102+
let error =
103+
Error
104+
"invalid sandboxing mode, must be 'none', 'symlink', 'copy' or 'hardlink'"
89105

90106
let of_string = function
91107
| "none" -> Ok None
92-
| "symlink" -> Ok (Some Symlink : t)
108+
| "symlink" -> Ok (Some Symlink)
93109
| "copy" -> Ok (Some Copy)
110+
| "hardlink" -> Ok (Some Hardlink)
94111
| _ -> error
95112

96113
let to_string = function
97114
| None -> "none"
98115
| Some Symlink -> "symlink"
99116
| Some Copy -> "copy"
117+
| Some Hardlink -> "hardlink"

src/dune_engine/sandbox_mode.mli

+4
Original file line numberDiff line numberDiff line change
@@ -10,6 +10,7 @@ open! Stdune
1010
type some =
1111
| Symlink
1212
| Copy
13+
| Hardlink
1314

1415
type t = some option
1516

@@ -24,6 +25,7 @@ module Dict : sig
2425
{ none : 'a
2526
; symlink : 'a
2627
; copy : 'a
28+
; hardlink : 'a
2729
}
2830

2931
val compare : ('a -> 'a -> Ordering.t) -> 'a t -> 'a t -> Ordering.t
@@ -57,6 +59,8 @@ val symlink : t
5759

5860
val copy : t
5961

62+
val hardlink : t
63+
6064
val of_string : string -> (t, string) Result.t
6165

6266
val to_string : t -> string

src/dune_rules/action_to_sh.ml

+1
Original file line numberDiff line numberDiff line change
@@ -57,6 +57,7 @@ let simplify act =
5757
| Copy (x, y) -> Run ("cp", [ x; y ]) :: acc
5858
| Symlink (x, y) ->
5959
Run ("ln", [ "-s"; x; y ]) :: Run ("rm", [ "-f"; y ]) :: acc
60+
| Hardlink (x, y) -> Run ("ln", [ x; y ]) :: Run ("rm", [ "-f"; y ]) :: acc
6061
| Copy_and_add_line_directive (x, y) ->
6162
Redirect_out
6263
( echo (Utils.line_directive ~filename:x ~line_number:1) @ [ cat x ]

src/dune_rules/action_unexpanded.ml

+4
Original file line numberDiff line numberDiff line change
@@ -453,6 +453,10 @@ let rec expand (t : Action_dune_lang.t) : Action.t Action_expander.t =
453453
let+ x = E.dep x
454454
and+ y = E.target y in
455455
O.Symlink (x, y)
456+
| Hardlink (x, y) ->
457+
let+ x = E.dep x
458+
and+ y = E.target y in
459+
O.Hardlink (x, y)
456460
| Copy_and_add_line_directive (x, y) ->
457461
let+ x = E.dep x
458462
and+ y = E.target y in

test/blackbox-tests/test-cases/dune-cache/trim.t/run.t

+5-4
Original file line numberDiff line numberDiff line change
@@ -64,15 +64,16 @@ end up in a situation where the same hash means something different
6464
before and after the change, which is bad. To reduce the risk, we
6565
inject a version number into rule digests.
6666

67-
If you see the bellow test breaking, then you probably accidentally
67+
If you see the below test breaking, then you probably accidentally
6868
changed the way the digest is computed and you should increase this
6969
version number. This number is stored in the [rule_digest_version]
7070
variable in [build_system.ml].
7171

72-
$ cat $PWD/.xdg-cache/dune/db/meta/v4/70/70e20e84ad3f1df3a3b6e2fabcc6465b
73-
((8:metadata)(5:files(16:default/target_b32:8a53bfae3829b48866079fa7f2d97781)))
72+
$ (cd "$PWD/.xdg-cache/dune/db/meta/v4"; grep -rws . -e 'metadata' | sort)
73+
./a5/a5577fffaa751cd2aa8b2345ac11119a:((8:metadata)(5:files(16:default/target_a32:5637dd9730e430c7477f52d46de3909c)))
74+
./c5/c5af296726141def07847e5510a680c6:((8:metadata)(5:files(16:default/target_b32:8a53bfae3829b48866079fa7f2d97781)))
7475

75-
$ dune_cmd stat size $PWD/.xdg-cache/dune/db/meta/v4/70/70e20e84ad3f1df3a3b6e2fabcc6465b
76+
$ dune_cmd stat size "$PWD/.xdg-cache/dune/db/meta/v4/a5/a5577fffaa751cd2aa8b2345ac11119a"
7677
79
7778

7879
Trimming the cache at this point should not remove anything, as all

0 commit comments

Comments
 (0)