Skip to content

Commit

Permalink
Fallback to curl --fail on exit code 43
Browse files Browse the repository at this point in the history
Mitigates a known issue in curl 8.8.0 especially affecting Windows
hosts. cf curl/curl#13845
  • Loading branch information
dra27 authored and rjbou committed Aug 21, 2024
1 parent 23a1b2b commit 43ed48d
Show file tree
Hide file tree
Showing 2 changed files with 74 additions and 36 deletions.
1 change: 1 addition & 0 deletions master_changes.md
Original file line number Diff line number Diff line change
Expand Up @@ -71,6 +71,7 @@ users)
## Lint

## Repository
* Mitigate curl/curl#13845 by falling back from --write-out to --fail if exit code 43 is returned by curl [#6168 @dra27 - fix #6120]

## Lock

Expand Down
109 changes: 73 additions & 36 deletions src/repository/opamDownload.ml
Original file line number Diff line number Diff line change
Expand Up @@ -20,19 +20,28 @@ let fail (s,l) = raise (Download_fail (s,l))
let user_agent =
CString (Printf.sprintf "opam/%s" (OpamVersion.(to_string current)))

let curl_args = [
CString "--write-out", None;
CString "%%{http_code}\\n", None; (* 6.5 13-Mar-2000 *)
CString "--retry", None; CIdent "retry", None; (* 7.12.3 20-Dec-2004 *)
CString "--retry-delay", None; CString "2", None; (* 7.12.3 20-Dec-2004 *)
CString "--compressed",
Some (FIdent (OpamFilter.ident_of_string "compress")); (* 7.10 1-Oct-2002 *)
CString "--user-agent", None; user_agent, None; (* 4.5.1 12-Jun-1998 *)
CString "-L", None; (* 4.9 7-Oct-1998 *)
CString "-o", None; CIdent "out", None; (* 2.3 21-Aug-1997 *)
CString "--", None; (* End list of options; 5.0 1-Dec-1998 *)
CIdent "url", None;
]
let curl_args =
let main_args = [
CString "--retry", None; CIdent "retry", None; (* 7.12.3 20-Dec-2004 *)
CString "--retry-delay", None; CString "2", None; (* 7.12.3 20-Dec-2004 *)
CString "--compressed",
Some (FIdent (OpamFilter.ident_of_string "compress")); (* 7.10 1-Oct-2002 *)
CString "--user-agent", None; user_agent, None; (* 4.5.1 12-Jun-1998 *)
CString "-L", None; (* 4.9 7-Oct-1998 *)
CString "-o", None; CIdent "out", None; (* 2.3 21-Aug-1997 *)
CString "--", None; (* End list of options; 5.0 1-Dec-1998 *)
CIdent "url", None;
] in
fun ~with_mitigation ->
if with_mitigation then
(* --fail is as old as curl; though the assumption that it leads to exit
code 22 when there's an error is probably 5.3 21-Dec-1998 (prior to
that it led to exit code 21) *)
(CString "--fail", None) :: main_args
else
(CString "--write-out", None) ::
(CString "%%{http_code}\\n", None) :: (* 6.5 13-Mar-2000 *)
main_args

let wget_args = [
CString "-t", None; CIdent "retry", None;
Expand All @@ -56,14 +65,16 @@ let ftp_args = [
CIdent "url", None;
]

let download_args ~url ~out ~retry ?checksum ~compress () =
let download_args ~url ~out ~retry ?(with_curl_mitigation=false)
?checksum ~compress () =
let cmd, _ = Lazy.force OpamRepositoryConfig.(!r.download_tool) in
let cmd =
match cmd with
| [(CIdent "wget"), _] -> cmd @ wget_args
| [(CIdent "fetch"), _] -> cmd @ fetch_args
| [(CIdent "ftp"), _] -> cmd @ ftp_args
| [_] -> cmd @ curl_args (* Assume curl if the command is a single arg *)
(* Assume curl if the command is a single arg *)
| [_] -> cmd @ curl_args ~with_mitigation:with_curl_mitigation
| _ -> cmd
in
OpamFilter.single_command (fun v ->
Expand All @@ -89,7 +100,28 @@ let download_args ~url ~out ~retry ?checksum ~compress () =
| _ -> None)
cmd

let tool_return url ret =
let download_command_t ~with_curl_mitigation ~compress ?checksum ~url ~dst c =
let cmd, args =
match
download_args
~url
~out:dst
~retry:OpamRepositoryConfig.(!r.retries)
~with_curl_mitigation
?checksum
~compress
()
with
| cmd::args -> cmd, args
| [] ->
OpamConsole.error_and_exit `Configuration_error
"Empty custom download command"
in
let stdout = OpamSystem.temp_file ~auto_clean:false "dl" in
OpamProcess.Job.finally (fun () -> OpamSystem.remove_file stdout) @@ fun () ->
OpamSystem.make_command ~allow_stdin:false ~stdout cmd args @@> c

let tool_return redownload_command url ret =
match Lazy.force OpamRepositoryConfig.(!r.download_tool) with
| _, `Default ->
if OpamProcess.is_failure ret then
Expand All @@ -99,8 +131,28 @@ let tool_return url ret =
else Done ()
| _, `Curl ->
if OpamProcess.is_failure ret then
fail (Some "Curl failed", Printf.sprintf "Curl failed: %s"
(OpamProcess.result_summary ret))
if ret.r_code = 43 then begin
(* Code 43 is CURLE_BAD_FUNCTION_ARGUMENT (7.1 7-Aug-2000). This should
never be encountered using the curl binary, so we assume that it's
a manifestation of curl/curl#13845 (see also #6120). *)
log "Attempting to mitigate curl/curl#13845";
redownload_command ~with_curl_mitigation:true @@ function ret ->
if OpamProcess.is_failure ret then
if ret.r_code = 22 then
(* If this broken version of curl persists for some time, it is
relatively straightforward to parse the http response code from
the message, as it hasn't changed. *)
fail (Some "curl failed owing to a server-side issue",
Printf.sprintf "curl failed with server-side error: %s"
(OpamProcess.result_summary ret))
else
fail (Some "curl failed",
Printf.sprintf "curl failed: %s"
(OpamProcess.result_summary ret))
else Done ()
end else
fail (Some "curl failed", Printf.sprintf "curl failed: %s"
(OpamProcess.result_summary ret))
else
match ret.OpamProcess.r_stdout with
| [] ->
Expand All @@ -117,24 +169,9 @@ let tool_return url ret =
else Done ()

let download_command ~compress ?checksum ~url ~dst () =
let cmd, args =
match
download_args
~url
~out:dst
~retry:OpamRepositoryConfig.(!r.retries)
?checksum
~compress
()
with
| cmd::args -> cmd, args
| [] ->
OpamConsole.error_and_exit `Configuration_error
"Empty custom download command"
in
let stdout = OpamSystem.temp_file ~auto_clean:false "dl" in
OpamProcess.Job.finally (fun () -> OpamSystem.remove_file stdout) @@ fun () ->
OpamSystem.make_command ~allow_stdin:false ~stdout cmd args @@> tool_return url
let download_command = download_command_t ~compress ?checksum ~url ~dst in
download_command ~with_curl_mitigation:false
@@ tool_return download_command url

let really_download
?(quiet=false) ~overwrite ?(compress=false) ?checksum ?(validate=true)
Expand Down

0 comments on commit 43ed48d

Please sign in to comment.