Skip to content

Commit

Permalink
Merge branch 'whaileee/OTP-25.3.2/inets/httpc/set_option-override-fix…
Browse files Browse the repository at this point in the history
…/OTP-19379' into maint

* whaileee/OTP-25.3.2/inets/httpc/set_option-override-fix/OTP-19379:
  backport httpc:set_options fix to OTP-25.3.2
  get_option error handling
  catch badoption throw
  get_option call fix
  blank line removed
  removed unused legacy option handling
  ipfamily-unix_socket combo validation fix
  invalid validation of ipfamily-unix_socket combo
  • Loading branch information
Whaileee committed Dec 2, 2024
2 parents 0e4e1f5 + 4ad1570 commit ff3d6dd
Show file tree
Hide file tree
Showing 3 changed files with 46 additions and 39 deletions.
54 changes: 29 additions & 25 deletions lib/inets/src/http_client/httpc.erl
Original file line number Diff line number Diff line change
Expand Up @@ -698,12 +698,20 @@ Sets options to be used for subsequent requests.
DomainDesc :: string(),
HostName :: uri_string:uri_string().
set_options(Options, Profile) when is_atom(Profile) orelse is_pid(Profile) ->
case validate_options(Options) of
{ok, Opts} ->
httpc_manager:set_options(Opts, profile_name(Profile));
{error, Reason} ->
{error, Reason}
end.
IsInetsRunning = [Application || {inets, _, _} = Application <- application:which_applications()] =/= [],
case IsInetsRunning of
true ->
{ok, IpFamily} = get_option(ipfamily, Profile),
{ok, UnixSock} = get_option(unix_socket, Profile),
case validate_options(Options, IpFamily, UnixSock) of
{ok, Opts} ->
httpc_manager:set_options(Opts, profile_name(Profile));
Error ->
Error
end;
_ ->
{error, inets_not_started}
end.
-doc false.
-spec set_option(atom(), term()) -> ok | {error, term()}.
Expand Down Expand Up @@ -1601,30 +1609,26 @@ request_options_sanity_check(Opts) ->
end,
ok.
validate_ipfamily_unix_socket(Options0) ->
IpFamily = proplists:get_value(ipfamily, Options0, inet),
UnixSocket = proplists:get_value(unix_socket, Options0, undefined),
Options1 = proplists:delete(ipfamily, Options0),
Options2 = proplists:delete(ipfamily, Options1),
validate_ipfamily_unix_socket(IpFamily, UnixSocket, Options2,
[{ipfamily, IpFamily}, {unix_socket, UnixSocket}]).
%%
validate_ipfamily_unix_socket(local, undefined, _Options, _Acc) ->
bad_option(unix_socket, undefined);
validate_ipfamily_unix_socket(IpFamily, UnixSocket, _Options, _Acc)
validate_ipfamily_unix_socket(Options0, CurrIpFamily, CurrUnixSock) ->
IpFamily = proplists:get_value(ipfamily, Options0, CurrIpFamily),
UnixSocket = proplists:get_value(unix_socket, Options0, CurrUnixSock),
validate_ipfamily_unix_socket(IpFamily, UnixSocket).
validate_ipfamily_unix_socket(local, undefined) ->
throw({error, {bad_ipfamily_unix_socket_combination, local, undefined}});
validate_ipfamily_unix_socket(IpFamily, UnixSocket)
when IpFamily =/= local, UnixSocket =/= undefined ->
bad_option(ipfamily, IpFamily);
validate_ipfamily_unix_socket(IpFamily, UnixSocket, Options, Acc) ->
throw({error, {bad_ipfamily_unix_socket_combination, IpFamily, UnixSocket}});
validate_ipfamily_unix_socket(IpFamily, UnixSocket) ->
validate_ipfamily(IpFamily),
validate_unix_socket(UnixSocket),
{Options, Acc}.
validate_unix_socket(UnixSocket).
validate_options(Options0) ->
validate_options(Options0, CurrIpFamily, CurrUnixSock) ->
try
{Options, Acc} = validate_ipfamily_unix_socket(Options0),
validate_options(Options, Acc)
validate_ipfamily_unix_socket(Options0, CurrIpFamily, CurrUnixSock),
validate_options(Options0, [])
catch
error:Reason ->
throw:Reason ->
{error, Reason}
end.
%%
Expand Down
14 changes: 1 addition & 13 deletions lib/inets/src/http_client/httpc_manager.erl
Original file line number Diff line number Diff line change
Expand Up @@ -1029,19 +1029,7 @@ get_cookies(Opts, #options{cookies = Default}) ->
proplists:get_value(cookies, Opts, Default).

get_ipfamily(Opts, #options{ipfamily = IpFamily}) ->
case lists:keysearch(ipfamily, 1, Opts) of
false ->
case proplists:get_value(ipv6, Opts) of
enabled ->
inet6fb4;
disabled ->
inet;
_ ->
IpFamily
end;
{value, {_, Value}} ->
Value
end.
proplists:get_value(ipfamily, Opts, IpFamily).

get_ip(Opts, #options{ip = Default}) ->
proplists:get_value(ip, Opts, Default).
Expand Down
17 changes: 16 additions & 1 deletion lib/inets/test/httpc_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -154,7 +154,8 @@ real_requests_esi() ->
[slow_connection].

simulated_unix_socket() ->
[unix_domain_socket].
[unix_domain_socket,
invalid_ipfamily_unix_socket].

only_simulated() ->
[
Expand Down Expand Up @@ -2006,6 +2007,20 @@ unix_domain_socket(Config) when is_list(Config) ->
{ok, {{_,200,_}, [_ | _], _}}
= httpc:request(get, {URL, []}, [], [], Profile).

invalid_ipfamily_unix_socket() ->
[{doc, "Test that httpc profile can't end up having invalid combination of ipfamily and unix_socket options"}].
invalid_ipfamily_unix_socket(Config) when is_list(Config) ->
Profile = proplists:get_value(profile, Config, httpc:default_profile()),

ct:log("Using profile ~w", [Profile]),
{ok,[{unix_socket,?UNIX_SOCKET}, {ipfamily, local}]} =
httpc:get_options([unix_socket, ipfamily], Profile),
?assertMatch({error, _}, httpc:set_option(unix_socket, undefined, Profile)),
?assertMatch({error, _}, httpc:set_option(ipfamily, inet, Profile)),
?assertMatch({error, _}, httpc:set_option(ipfamily, inetv6, Profile)),
ok = httpc:set_options([{unix_socket, undefined}, {ipfamily, inet}], Profile),
?assertMatch({error, _}, httpc:set_option(unix_socket, ?UNIX_SOCKET, Profile)).

%%-------------------------------------------------------------------------
delete_no_body() ->
[{doc, "Test that a DELETE request without Body does not send a Content-Type header - Solves ERL-536"}].
Expand Down

0 comments on commit ff3d6dd

Please sign in to comment.