11open Stdune
22
3- type t = string
3+ module T = struct
4+ type t = Blake3_mini.Digest .t
45
5- external md5_fd : Unix .file_descr -> string = " dune_md5_fd"
6+ let to_string = Blake3_mini.Digest. to_hex
7+ let to_dyn s = Dyn. variant " digest" [ String (to_string s) ]
8+ let compare x y = Ordering. of_int (Blake3_mini.Digest. compare x y)
9+ end
610
7- module D = Stdlib. Digest
8- module Set = String. Set
9- module Map = String. Map
11+ include T
12+ module C = Comparable. Make (T )
13+ module Set = C. Set
14+ module Map = C. Map
1015module Metrics = Dune_metrics
1116
1217let file file =
@@ -21,24 +26,24 @@ let file file =
2126 raise (Sys_error (sprintf " %s: Permission denied" file))
2227 | exception exn -> reraise exn
2328 in
24- Exn. protectx fd ~f: md5_fd ~finally: Unix. close
29+ Exn. protectx fd ~f: Blake3_mini. fd ~finally: Unix. close
2530;;
2631
32+ let equal = Blake3_mini.Digest. equal
2733let hash = Poly. hash
28- let equal = String. equal
2934let file p = file (Path. to_string p)
30- let compare x y = Ordering. of_int (D. compare x y)
31- let to_string = D. to_hex
32- let to_dyn s = Dyn. variant " digest" [ String (to_string s) ]
33-
34- let from_hex s =
35- match D. from_hex s with
36- | s -> Some s
37- | exception Invalid_argument _ -> None
35+ let from_hex s = Blake3_mini.Digest. of_hex s
36+ let hasher = lazy (Blake3_mini. create () )
37+
38+ let string s =
39+ let hasher = Lazy. force hasher in
40+ Blake3_mini. feed_string hasher s ~pos: 0 ~len: (String. length s);
41+ let res = Blake3_mini. digest hasher in
42+ Blake3_mini. reset hasher;
43+ res
3844;;
3945
40- let string = D. string
41- let to_string_raw s = s
46+ let to_string_raw s = Blake3_mini.Digest. to_binary s
4247
4348(* We use [No_sharing] to avoid generating different digests for inputs that
4449 differ only in how they share internal values. Without [No_sharing], if a
@@ -54,7 +59,7 @@ let generic a =
5459let path_with_executable_bit =
5560 (* We follow the digest scheme used by Jenga. *)
5661 let string_and_bool ~digest_hex ~bool =
57- string (digest_hex ^ if bool then " \001 " else " \000 " )
62+ string (Blake3_mini.Digest. to_hex digest_hex ^ if bool then " \001 " else " \000 " )
5863 in
5964 fun ~executable ~content_digest ->
6065 string_and_bool ~digest_hex: content_digest ~bool: executable
@@ -94,7 +99,12 @@ let path_with_stats ~allow_dirs path (stats : Stats_for_digest.t) =
9499 | S_LNK ->
95100 Dune_filesystem_stubs.Unix_error.Detailed. catch
96101 (fun path ->
97- let contents = Unix. readlink (Path. to_string path) in
102+ let contents =
103+ Path. to_string path
104+ |> Unix. readlink
105+ |> Blake3_mini.Digest. of_hex
106+ |> Option. value_exn
107+ in
98108 path_with_executable_bit ~executable: stats.executable ~content_digest: contents)
99109 path
100110 |> Result. map_error ~f: (fun x -> Path_digest_error. Unix_error x)
0 commit comments