@@ -10,7 +10,7 @@ module Command = struct
1010end
1111
1212type t =
13- { command : Command .t Lazy .t
13+ { command : Command .t Fiber. Lazy.t
1414 ; suffixes : string list
1515 }
1616
@@ -26,38 +26,56 @@ let make_zip_args ~archive ~target_in_temp =
2626
2727let tar =
2828 let command =
29- lazy
30- ( match
31- (* Test for tar before bsdtar as tar is more likely to be installed
29+ Fiber.Lazy. create ( fun () ->
30+ match
31+ (* Test for tar before bsdtar as tar is more likely to be installed
3232 and both work equally well for tarballs. *)
33- List. find_map [ " tar" ; " bsdtar" ] ~f: which
34- with
35- | Some bin -> { Command. bin; make_args = make_tar_args }
36- | None -> Dune_engine.Utils. program_not_found " tar" ~loc: None )
33+ List. find_map [ " tar" ; " bsdtar" ] ~f: which
34+ with
35+ | Some bin -> Fiber. return { Command. bin; make_args = make_tar_args }
36+ | None ->
37+ Fiber. return
38+ @@ User_error. raise
39+ [ Pp. text " No program found to extract tar file. Tried:"
40+ ; Pp. enumerate [ " tar" ; " bsdtar" ] ~f: Pp. verbatim
41+ ])
3742 in
3843 { command; suffixes = [ " .tar" ; " .tar.gz" ; " .tgz" ; " .tar.bz2" ; " .tbz" ] }
3944;;
4045
46+ let which_bsdtar (bin_name : string ) =
47+ match which bin_name with
48+ | None -> Fiber. return None
49+ | Some bin ->
50+ let + output, _error = Process. run_capture ~display: Quiet Return bin [ " --version" ] in
51+ let re = Re. compile (Re. str " bsdtar" ) in
52+ if Re. execp re output then Some bin else None
53+ ;;
54+
4155let zip =
4256 let command =
43- lazy
44- (match which " unzip" with
45- | Some bin -> { Command. bin; make_args = make_zip_args }
46- | None ->
47- (* Fall back to using tar to extract zip archives, which is possible in some cases. *)
48- (match
49- (* Test for bsdtar before tar, as if bsdtar is installed then it's
50- likely that the tar binary is GNU tar which can't extract zip
51- archives, whereas bsdtar can. If bsdtar is absent, try using the
52- tar command anyway, as on MacOS, Windows, and some BSD systems,
53- the tar command can extract zip archives. *)
54- List. find_map [ " bsdtar" ; " tar" ] ~f: which
55- with
56- | Some bin -> { Command. bin; make_args = make_tar_args }
57- | None ->
58- (* Still reference unzip in the error message, as installing it
59- is the simplest way to fix the problem. *)
60- Dune_engine.Utils. program_not_found " unzip" ~loc: None ))
57+ Fiber.Lazy. create (fun () ->
58+ match which " unzip" with
59+ | Some bin -> Fiber. return { Command. bin; make_args = make_zip_args }
60+ | None ->
61+ let rec find_tar programs =
62+ match programs with
63+ | [] -> Fiber. return None
64+ | x :: xs ->
65+ let * res = which_bsdtar x in
66+ (match res with
67+ | Some _ -> Fiber. return res
68+ | None -> find_tar xs)
69+ in
70+ let * program = find_tar [ " bsdtar" ; " tar" ] in
71+ (match program with
72+ | Some bin -> Fiber. return { Command. bin; make_args = make_tar_args }
73+ | None ->
74+ Fiber. return
75+ @@ User_error. raise
76+ [ Pp. text " No program found to extract zip file. Tried:"
77+ ; Pp. enumerate [ " unzip" ; " bsdtar" ; " tar" ] ~f: Pp. verbatim
78+ ]))
6179 in
6280 { command; suffixes = [ " .zip" ] }
6381;;
@@ -73,7 +91,7 @@ let choose_for_filename_default_to_tar filename =
7391
7492let extract t ~archive ~target =
7593 let * () = Fiber. return () in
76- let command = Lazy. force t.command in
94+ let * command = Fiber. Lazy. force t.command in
7795 let prefix = Path. basename target in
7896 let target_in_temp =
7997 let suffix = Path. basename archive in
0 commit comments