File 4391-Add-autoretry-timeout-HttpOption-to-httpc.patch of Package erlang

From a513b4e1738df5b390bfc896c81c4eca8db9291d Mon Sep 17 00:00:00 2001
From: Konrad Pietrzak <konrad@erlang.org>
Date: Fri, 12 Dec 2025 12:39:46 +0100
Subject: [PATCH] Add {autoretry, timeout()} HttpOption to httpc

    This option is used to limit the maximum time httpc is allowed to
    wait before retrying a request due to Retry-After header.
    Responses with a Retry-After value greater then the value of this option
    are not retried
---
 lib/inets/src/http_client/httpc.erl          | 22 +++++++++
 lib/inets/src/http_client/httpc_internal.hrl |  6 ++-
 lib/inets/src/http_client/httpc_manager.erl  |  3 +-
 lib/inets/src/http_client/httpc_response.erl | 49 ++++++++++++++++----
 lib/inets/src/http_lib/http_util.erl         | 32 ++++++++++++-
 lib/inets/test/httpc_SUITE.erl               | 46 ++++++++++++++++--
 6 files changed, 141 insertions(+), 17 deletions(-)

diff --git a/lib/inets/doc/src/httpc.xml b/lib/inets/doc/src/httpc.xml
index 4d4e8670e9..f86698bccb 100644
--- a/lib/inets/doc/src/httpc.xml
+++ b/lib/inets/doc/src/httpc.xml
@@ -260,6 +260,17 @@
 	          <p>Default is <c>true</c>.</p>
 	        </item>
 
+          <tag><c>autoretry</c></tag>
+          <item>
+	          <p>The client automatically retries the request <em>once</em> after receiving
+	          a Retry-After header from the server.</p>
+	          <p>Sometimes servers can suggest a value that is not suitable for application,
+	          so this option allows limiting the wait time <em>(in miliseconds)</em> inbetween requests,
+	          or disabling the retry with a value of <c>0</c>.
+	          If a value of Retry-After header exceeds the set value, no retry will be done.</p>
+	          <p>Default is atom <c>infinity</c></p>
+	        </item>
+
           <tag><c>proxy_auth</c></tag>
           <item>
             <p>A proxy-authorization header using a tuple where the first element is the <c>username</c> and
diff --git a/lib/inets/src/http_client/httpc.erl b/lib/inets/src/http_client/httpc.erl
index 4d4e8670e9..f86698bccb 100644
--- a/lib/inets/src/http_client/httpc.erl
+++ b/lib/inets/src/http_client/httpc.erl
@@ -146,6 +146,7 @@ request(Url, Profile) ->
                   | {connect_timeout, timeout()}
                   | {ssl, [ssl:tls_option()]}
                   | {autoredirect, boolean()}
+                  | {autoretry, timeout()}
                   | {proxy_auth, {string(), string()}}
                   | {version, HttpVersion} | {relaxed, boolean()},
       Options :: [OptionRequest],
@@ -208,6 +209,7 @@ request(Method, Request, HttpOptions, Op
                   | {connect_timeout, timeout()}
                   | {ssl, [ssl:tls_option()]}
                   | {autoredirect, boolean()}
+                  | {autoretry, timeout()}
                   | {proxy_auth, {string(), string()}}
                   | {version, HttpVersion} | {relaxed, boolean()},
       Options :: [OptionRequest],
@@ -1409,6 +1421,15 @@ http_options_default() ->
 		  end,
     AutoRedirectPost =  boolfun(),
 
+    AutoRetryPost = fun(Value) when is_integer(Value)
+                                    andalso Value >= 0 ->
+                            {ok, Value};
+                       (Value) when Value =:= infinity ->
+                            {ok, Value};
+                       (_) ->
+                            error
+                    end,
+
     SslPost = fun(Value) when is_list(Value) ->
                       {ok, {ssl, Value}};
                  ({ssl, SslOptions}) when is_list(SslOptions) ->
@@ -1445,6 +1466,7 @@ http_options_default() ->
      {version,         {value, "HTTP/1.1"},            #http_options.version,         VersionPost}, 
      {timeout,         {value, ?HTTP_REQUEST_TIMEOUT}, #http_options.timeout,         TimeoutPost},
      {autoredirect,    {value, true},                  #http_options.autoredirect,    AutoRedirectPost},
+     {autoretry,       {value, infinity},              #http_options.autoretry,       AutoRetryPost},
      %% can crash if no os bundle is present. therefore the options are only evaluated on demand
      {ssl,             {value_lazy, SslOptsLazyFn},    #http_options.ssl,             SslPost},
      {proxy_auth,      {value, undefined},             #http_options.proxy_auth,      ProxyAuthPost},
diff --git a/lib/inets/src/http_client/httpc_internal.hrl b/lib/inets/src/http_client/httpc_internal.hrl
index 8027ddc580..85f9e28a4a 100644
--- a/lib/inets/src/http_client/httpc_internal.hrl
+++ b/lib/inets/src/http_client/httpc_internal.hrl
@@ -54,6 +54,9 @@
 	  %% true if auto redirect on 30x response
 	  autoredirect = true :: boolean(),
 
+          %% limits the maximum wait time before a retry
+          autoretry = infinity :: timeout(),
+
 	  %% ssl socket options
 	  ssl = [],
 
@@ -120,7 +123,8 @@
 	  socket_opts,   % undefined | [socket_option()]
 	  unix_socket,   % undefined | string()
 	  ipv6_host_with_brackets, % boolean()
-	  request_options :: undefined | proplists:proplist()
+	  request_options :: undefined | proplists:proplist(),
+          retried = false :: boolean() % indicates whether the request was already retried
 	}
        ).
 -type request() :: #request{}.
diff --git a/lib/inets/src/http_client/httpc_manager.erl b/lib/inets/src/http_client/httpc_manager.erl
index eb035c70a4..cd2b028b3c 100644
--- a/lib/inets/src/http_client/httpc_manager.erl
+++ b/lib/inets/src/http_client/httpc_manager.erl
@@ -511,7 +511,8 @@ handle_call(Req, From, #state{profile_name = ProfileName} = State) ->
 %%--------------------------------------------------------------------
 handle_cast({retry_or_redirect_request, {Time, Request}}, 
 	    #state{profile_name = ProfileName} = State) ->
-    {ok, _} = timer:apply_after(Time, ?MODULE, retry_request, [Request, ProfileName]),
+    NewRequest = Request#request{retried = true},
+    {ok, _} = timer:apply_after(Time, ?MODULE, retry_request, [NewRequest, ProfileName]),
     {noreply, State};
 
 handle_cast({retry_or_redirect_request, Request}, State) ->
diff --git a/lib/inets/src/http_client/httpc_response.erl b/lib/inets/src/http_client/httpc_response.erl
index 38049d8e0b..d54fe6ddcf 100644
--- a/lib/inets/src/http_client/httpc_response.erl
+++ b/lib/inets/src/http_client/httpc_response.erl
@@ -357,6 +357,26 @@ parse_headers(<<Octet, Rest/binary>>, Header, Headers,
 		  Result, Relaxed).
 
 
+get_ms_from_retry_after(undefined = _RetryAfterValue) ->
+    undefined;
+%% Parse as seconds
+get_ms_from_retry_after([C | _] = RetryAfterValue) when C >= $0
+                                                  andalso C =< $9 ->
+    list_to_integer(RetryAfterValue) * 1000; %% return milliseconds
+get_ms_from_retry_after(RetryAfterValue) ->
+    case httpd_util:convert_request_date(RetryAfterValue) of
+        {{Year, Month, Day}, {H,M,S}} ->
+                RetryAfterSeconds = calendar:datetime_to_gregorian_seconds({{Year, Month, Day}, {H, M, S}}),
+                TimeNow = calendar:datetime_to_gregorian_seconds(calendar:universal_time()),
+                calc_time_difference(RetryAfterSeconds, TimeNow); %% return milliseconds
+        _ -> undefined
+    end.
+
+calc_time_difference(T1, T2) when T1 >= T2 ->
+    (T1 - T2) * 1000;
+calc_time_difference(_, _) ->
+    undefined.
+
 %% RFC2616, Section 10.1.1
 %% Note:
 %% - Only act on the 100 status if the request included the
@@ -370,16 +390,25 @@ status_continue({_,_, Data}, _) ->
     %% response.
     {ignore, Data}.
 
-status_service_unavailable(Response = {_, Headers, _}, Request) ->
-    case Headers#http_response_h.'retry-after' of 
-	undefined ->
-	    status_server_error_50x(Response, Request);
-	Time when (length(Time) < 3) -> % Wait only 99 s or less 
-	    NewTime = list_to_integer(Time) * 1000, % time in ms
-	    {_, Data} =  format_response(Response),
-	    {retry, {NewTime, Request}, Data};
-	_ ->
-	    status_server_error_50x(Response, Request)
+status_service_unavailable(Response = {_, _, _},
+                           Request = #request{retried = true}) ->
+    status_server_error_50x(Response, Request);
+status_service_unavailable(Response = {_, Headers, _},
+                           Request = #request{settings =
+                                                  #http_options{autoretry = MaxSecondsBeforeRetry}}) ->
+    RetryAfter = get_ms_from_retry_after(Headers#http_response_h.'retry-after'),
+    case RetryAfter of
+        Undefined when
+              Undefined =:= undefined orelse
+              MaxSecondsBeforeRetry =:= 0 ->
+            status_server_error_50x(Response, Request);
+        Time when MaxSecondsBeforeRetry =:= infinity
+                  orelse (is_integer(MaxSecondsBeforeRetry)
+                          andalso Time =< MaxSecondsBeforeRetry) ->
+            {_, Data} = format_response(Response),
+            {retry, {Time, Request}, Data};
+        _ ->
+            status_server_error_50x(Response, Request)
     end.
 
 status_server_error_50x(Response, Request) ->
diff --git a/lib/inets/src/http_lib/http_util.erl b/lib/inets/src/http_lib/http_util.erl
index b6b6474eb0..73859cda34 100644
--- a/lib/inets/src/http_lib/http_util.erl
+++ b/lib/inets/src/http_lib/http_util.erl
@@ -26,6 +26,7 @@
 -export([
 	 to_upper/1, to_lower/1, 
 	 convert_netscapecookie_date/1,
+         convert_day/1,
 	 hexlist_to_integer/1, integer_to_hexlist/1, 
 	 convert_month/1, 
 	 is_hostname/1,
@@ -174,7 +175,36 @@ convert_month("Aug") -> 8;
 convert_month("Sep") -> 9;
 convert_month("Oct") -> 10;
 convert_month("Nov") -> 11;
-convert_month("Dec") -> 12.
+convert_month("Dec") -> 12;
+convert_month(1) -> "Jan";
+convert_month(2) -> "Feb";
+convert_month(3) -> "Mar";
+convert_month(4) -> "Apr";
+convert_month(5) -> "May";
+convert_month(6) -> "Jun";
+convert_month(7) -> "Jul";
+convert_month(8) -> "Aug";
+convert_month(9) -> "Sep";
+convert_month(10) -> "Oct";
+convert_month(11) -> "Nov";
+convert_month(12) -> "Dec".
+
+convert_day(1) -> "Mon";
+convert_day(2) -> "Tue";
+convert_day(3) -> "Wed";
+convert_day(4) -> "Thu";
+convert_day(5) -> "Fri";
+convert_day(6) -> "Sat";
+convert_day(7) -> "Sun";
+convert_day("Mon") -> 1;
+convert_day("Tue") -> 2;
+convert_day("Wed") -> 3;
+convert_day("Thu") -> 4;
+convert_day("Fri") -> 5;
+convert_day("Sat") -> 6;
+convert_day("Sun") -> 7.
+
+
 
 is_hostname(Dest) ->
     inet_parse:domain(Dest).
diff --git a/lib/inets/test/httpc_SUITE.erl b/lib/inets/test/httpc_SUITE.erl
index 5d3df21659..f8dbf434ad 100644
--- a/lib/inets/test/httpc_SUITE.erl
+++ b/lib/inets/test/httpc_SUITE.erl
@@ -2972,8 +2990,28 @@ handle_uri(_,"/503.html",_,_,_,DefaultResponse) ->
 	[{503, available}]   ->
 	    DefaultResponse;
 	[{503, long_unavailable}]  ->
+            %% Available after 120 seconds, in http-date format
+            {MS0, S0, NS0} = erlang:timestamp(),
+            ModifiedTimestamp = {MS0, S0 + 120, NS0},
+            {{Year, Month, Day}, {H, M, S}} = calendar:now_to_datetime(ModifiedTimestamp),
+            HttpYear = integer_to_list(Year),
+            DoW = calendar:day_of_the_week(Year, Month, Day),
+            HttpDay = lists:flatten(string:pad(integer_to_list(Day), 2, leading, $0)),
+            DayName = http_util:convert_day(DoW),
+            MonthName = http_util:convert_month(Month),
+            HttpHour = lists:flatten(string:pad(integer_to_list(H), 2, leading, $0)),
+            HttpMin = lists:flatten(string:pad(integer_to_list(M), 2, leading, $0)),
+            HttpSec = lists:flatten(string:pad(integer_to_list(S), 2, leading, $0)),
+            HttpDate = lists:flatten(io_lib:format("~ts, ~ts ~ts ~ts ~ts:~ts:~ts GMT",
+                                     [DayName, HttpDay, MonthName, HttpYear, HttpHour, HttpMin, HttpSec])),
+            ets:insert(unavailable, {503, available}),
 	    "HTTP/1.1 503 Service Unavailable\r\n" ++
-		"Retry-After:120\r\n" ++
+		"Retry-After:" ++ HttpDate ++ "\r\n" ++
+		"Content-Length:47\r\n\r\n" ++
+		"<HTML><BODY>Internal Server Error</BODY></HTML>";
+        [{503, always_unavailable}] ->
+            "HTTP/1.1 503 Service Unavailable\r\n" ++
+		"Retry-After:5\r\n" ++
 		"Content-Length:47\r\n\r\n" ++
 		"<HTML><BODY>Internal Server Error</BODY></HTML>"
     end;
-- 
2.51.0

openSUSE Build Service is sponsored by