@@ -607,26 +607,6 @@ let compute_target_digests_or_raise_error exec_params ~loc targets =
607607 (pp_path (Path. build target) :: error))
608608 ])
609609
610- let sandbox_dir = Path.Build. relative Path.Build. root " .sandbox"
611-
612- let init_sandbox =
613- let init =
614- lazy
615- (let dir = Path. build sandbox_dir in
616- Path. mkdir_p (Path. relative dir " .hg" );
617- (* We create an empty [.git] file to prevent git from escaping the
618- sandbox. It will choke on this empty .git and report an error about
619- its format being invalid. *)
620- Io. write_file (Path. relative dir " .git" ) " " ;
621- (* We create a [.hg/requires] file to prevent hg from escaping the
622- sandbox. It will complain that "Escaping the Dune sandbox" is an
623- unkown feature. *)
624- Io. write_file
625- (Path. relative dir " .hg/requires" )
626- " Escaping the Dune sandbox" )
627- in
628- fun () -> Lazy. force init
629-
630610let rec with_locks t mutexes ~f =
631611 match mutexes with
632612 | [] -> f ()
@@ -1371,18 +1351,6 @@ end = struct
13711351
13721352 let start_rule t _rule = t.rule_total < - t.rule_total + 1
13731353
1374- (* Same as [rename] except that if the source doesn't exist we delete the
1375- destination *)
1376- let rename_optional_file ~src ~dst =
1377- let src = Path.Build. to_string src in
1378- let dst = Path.Build. to_string dst in
1379- match Unix. rename src dst with
1380- | () -> ()
1381- | exception Unix. Unix_error ((ENOENT | ENOTDIR ), _ , _ ) -> (
1382- match Unix. unlink dst with
1383- | exception Unix. Unix_error (ENOENT, _ , _ ) -> ()
1384- | () -> () )
1385-
13861354 (* The current version of the rule digest scheme. We should increment it when
13871355 making any changes to the scheme, to avoid collisions. *)
13881356 let rule_digest_version = 7
@@ -1463,45 +1431,18 @@ end = struct
14631431 action
14641432 in
14651433 pending_targets := Path.Build.Set. union targets ! pending_targets;
1434+ let chdirs = Action. chdirs action in
14661435 let sandbox =
14671436 Option. map sandbox_mode ~f: (fun mode ->
1468- let sandbox_suffix = rule_digest |> Digest. to_string in
1469- (Path.Build. relative sandbox_dir sandbox_suffix, mode))
1437+ Sandbox. create ~mode ~deps ~rule_dir: dir ~chdirs ~rule_digest
1438+ ~expand_aliases:
1439+ (Execution_parameters. expand_aliases_in_sandbox
1440+ execution_parameters))
14701441 in
1471- let chdirs = Action. chdirs action in
1472- let sandboxed, action =
1442+ let action =
14731443 match sandbox with
1474- | None -> (None , action)
1475- | Some (sandbox_dir , sandbox_mode ) ->
1476- init_sandbox () ;
1477- Path. rm_rf (Path. build sandbox_dir);
1478- let sandboxed path : Path.Build.t =
1479- Path.Build. append_local sandbox_dir (Path.Build. local path)
1480- in
1481- Path.Set. iter
1482- (Path.Set. union (Dep.Facts. dirs deps) chdirs)
1483- ~f: (fun path ->
1484- match Path. as_in_build_dir path with
1485- | None ->
1486- (* This [path] is not in the build directory, so we do not need to
1487- create it. If it comes from [deps], it must exist already. If
1488- it comes from [chdirs], we'll ensure that it exists in the call
1489- to [Fs.mkdir_p_or_assert_existence] below. *)
1490- ()
1491- | Some path ->
1492- (* There is no point in using the memoized version [Fs.mkdir_p]
1493- since these directories are not shared between actions. *)
1494- Path. mkdir_p (Path. build (sandboxed path)));
1495- Path. mkdir_p (Path. build (sandboxed dir));
1496- let deps =
1497- if Execution_parameters. expand_aliases_in_sandbox execution_parameters
1498- then
1499- Dep.Facts. paths deps
1500- else
1501- Dep.Facts. paths_without_expanding_aliases deps
1502- in
1503- ( Some sandboxed
1504- , Action. sandbox action ~sandboxed ~mode: sandbox_mode ~deps )
1444+ | None -> action
1445+ | Some sandbox -> Action. sandbox action sandbox
15051446 in
15061447 let * () =
15071448 Fiber. parallel_iter_set
@@ -1511,26 +1452,26 @@ end = struct
15111452 in
15121453 let build_deps deps = Memo.Build. run (build_deps deps) in
15131454 let root =
1514- ( match context with
1455+ match context with
15151456 | None -> Path.Build. root
1516- | Some context -> context.build_dir)
1517- |> Option. value sandboxed ~default: Fun. id
1518- |> Path. build
1457+ | Some context -> context.build_dir
1458+ in
1459+ let root =
1460+ Path. build
1461+ (match sandbox with
1462+ | None -> root
1463+ | Some sandbox -> Sandbox. map_path sandbox root)
15191464 in
15201465 let + exec_result =
15211466 with_locks t locks ~f: (fun () ->
1522- let copy_files_from_sandbox sandboxed =
1523- Path.Build.Set. iter targets ~f: (fun target ->
1524- rename_optional_file ~src: (sandboxed target) ~dst: target)
1525- in
15261467 let + exec_result =
15271468 Action_exec. exec ~root ~context ~env ~targets ~rule_loc: loc
15281469 ~build_deps ~execution_parameters action
15291470 in
1530- Option. iter sandboxed ~f: copy_files_from_sandbox ;
1471+ Option. iter sandbox ~f: ( Sandbox. move_targets_to_build_dir ~targets ) ;
15311472 exec_result)
15321473 in
1533- Option. iter sandbox ~f: ( fun ( p , _mode ) -> Path. rm_rf ( Path. build p)) ;
1474+ Option. iter sandbox ~f: Sandbox. destroy ;
15341475 (* All went well, these targets are no longer pending *)
15351476 pending_targets := Path.Build.Set. diff ! pending_targets targets;
15361477 exec_result
0 commit comments