Skip to content

Commit 0c8f161

Browse files
committed
Use Path functions instead of Unix
This lets us to reduce path conversions in the code Signed-off-by: Rudi Grinberg <[email protected]>
1 parent ff67bfd commit 0c8f161

File tree

1 file changed

+15
-17
lines changed

1 file changed

+15
-17
lines changed

src/cache/local.ml

Lines changed: 15 additions & 17 deletions
Original file line numberDiff line numberDiff line change
@@ -176,21 +176,20 @@ let deduplicate cache (file : File.t) =
176176
match cache.duplication_mode with
177177
| Copy -> ()
178178
| Hardlink -> (
179-
let path = Path.Build.to_string file.path in
180-
let path_in_cache = file_path cache file.digest |> Path.to_string in
181-
let tmpname = Path.Build.to_string (Path.Build.of_string ".dedup") in
182-
cache.info [ Pp.textf "deduplicate %s from %s" path path_in_cache ];
183-
let rm p =
184-
try Unix.unlink p with
185-
| _ -> ()
186-
in
179+
let path = Path.build file.path in
180+
let path_in_cache = file_path cache file.digest in
181+
let tmpname = Path.build (Path.Build.of_string ".dedup") in
182+
cache.info
183+
[ Pp.textf "deduplicate %s from %s" (Path.to_string path)
184+
(Path.to_string path_in_cache)
185+
];
187186
try
188-
rm tmpname;
189-
Unix.link path_in_cache tmpname;
190-
Unix.rename tmpname path
187+
Path.unlink_no_err tmpname;
188+
Path.link path_in_cache tmpname;
189+
Path.rename tmpname path
191190
with
192191
| Unix.Unix_error (e, syscall, _) ->
193-
rm tmpname;
192+
Path.unlink_no_err tmpname;
194193
cache.warn
195194
[ Pp.textf "error handling dune-cache command: %s: %s" syscall
196195
(Unix.error_message e)
@@ -205,11 +204,11 @@ let promote_sync cache paths key metadata ~repository ~duplication =
205204
let open Result.O in
206205
let* repo =
207206
match repository with
207+
| None -> Result.Ok None
208208
| Some idx -> (
209209
match List.nth cache.repositories idx with
210210
| None -> Result.Error (Printf.sprintf "repository out of range: %i" idx)
211211
| repo -> Result.Ok repo)
212-
| None -> Result.Ok None
213212
in
214213
let metadata =
215214
apply
@@ -223,7 +222,7 @@ let promote_sync cache paths key metadata ~repository ~duplication =
223222
let promote (path, expected_digest) =
224223
let* abs_path = make_path cache (Path.Build.local path) in
225224
cache.info [ Pp.textf "promote %s" (Path.to_string abs_path) ];
226-
let stat = Unix.lstat (Path.to_string abs_path) in
225+
let stat = Path.lstat abs_path in
227226
let* stat =
228227
if stat.st_kind = S_REG then
229228
Result.Ok stat
@@ -271,12 +270,11 @@ let promote_sync cache paths key metadata ~repository ~duplication =
271270
Result.Ok (Already_promoted { path; digest = effective_digest })
272271
| false ->
273272
Path.mkdir_p (Path.parent_exn in_the_cache);
274-
let dest = Path.to_string in_the_cache in
275273
(* Move the temporary file to the cache. *)
276-
Unix.rename (Path.to_string tmp) dest;
274+
Path.rename tmp in_the_cache;
277275
(* Remove write permissions, making the cache entry immutable. We assume
278276
that users do not modify the files in the cache. *)
279-
Unix.chmod dest (stat.st_perm land 0o555);
277+
Path.chmod in_the_cache ~mode:(stat.st_perm land 0o555);
280278
Result.Ok (Promoted { path; digest = effective_digest })
281279
in
282280
let+ promoted = Result.List.map ~f:promote paths in

0 commit comments

Comments
 (0)