Skip to content

Commit

Permalink
fixup: reident + remove (seemingly) unnecessary ~with_curl_mitigation
Browse files Browse the repository at this point in the history
  • Loading branch information
kit-ty-kate committed Aug 20, 2024
1 parent d60ee28 commit 5afed56
Showing 1 changed file with 15 additions and 23 deletions.
38 changes: 15 additions & 23 deletions src/repository/opamDownload.ml
Original file line number Diff line number Diff line change
Expand Up @@ -21,6 +21,12 @@ let user_agent =
CString (Printf.sprintf "opam/%s" (OpamVersion.(to_string current)))

let curl_args = [
(* --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); (* Mitigation for curl/curl#13845 *)
(* (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",
Expand All @@ -32,17 +38,6 @@ let curl_args = [
CIdent "url", None;
]

let curl_args ~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) :: curl_args
else
(CString "--write-out", None) ::
(CString "%%{http_code}\\n", None) :: (* 6.5 13-Mar-2000 *)
curl_args

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

let download_args ~url ~out ~retry ?(with_curl_mitigation=false)
?checksum ~compress () =
let download_args ~url ~out ~retry ?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
(* Assume curl if the command is a single arg *)
| [_] -> cmd @ curl_args ~with_mitigation:with_curl_mitigation
| [_] -> cmd @ curl_args (* Assume curl if the command is a single arg *)
| _ -> cmd
in
OpamFilter.single_command (fun v ->
Expand All @@ -100,14 +93,13 @@ let download_args ~url ~out ~retry ?(with_curl_mitigation=false)
| _ -> None)
cmd

let download_command ~with_curl_mitigation ~compress ?checksum ~url ~dst c =
let download_command ~compress ?checksum ~url ~dst c =
let cmd, args =
match
download_args
~url
~out:dst
~retry:OpamRepositoryConfig.(!r.retries)
~with_curl_mitigation
?checksum
~compress
()
Expand Down Expand Up @@ -136,19 +128,19 @@ let tool_return redownload_command url ret =
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 ->
redownload_command @@ 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))
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))
Printf.sprintf "cURL failed: %s"
(OpamProcess.result_summary ret))
else Done ()
end else
fail (Some "Curl failed", Printf.sprintf "Curl failed: %s"
Expand All @@ -170,7 +162,7 @@ let tool_return redownload_command url ret =

let download_command ~compress ?checksum ~url ~dst () =
let download_command = download_command ~compress ?checksum ~url ~dst in
download_command ~with_curl_mitigation:false @@ tool_return download_command url
download_command (tool_return download_command url)

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

0 comments on commit 5afed56

Please sign in to comment.