Skip to content

Commit

Permalink
Merge branch 'maint'
Browse files Browse the repository at this point in the history
  • Loading branch information
bmk committed Nov 13, 2023
2 parents f7a9891 + ca16eb2 commit a9a30c1
Show file tree
Hide file tree
Showing 6 changed files with 480 additions and 28 deletions.
45 changes: 44 additions & 1 deletion erts/emulator/nifs/win32/win_socket_asyncio.c
Original file line number Diff line number Diff line change
Expand Up @@ -2051,7 +2051,50 @@ ERL_NIF_TERM esaio_connect_dgram(ErlNifEnv* env,
ESockAddress* addrP,
SOCKLEN_T addrLen)
{
return enif_make_badarg(env);
int save_errno;
ErlNifPid self;

ESOCK_ASSERT( enif_self(env, &self) != NULL );

if (! IS_OPEN(descP->writeState))
return esock_make_error_closed(env);

if (descP->connectorP != NULL) {
/* Connect in progress */

return esock_make_error(env, esock_atom_already);
}

/* No connect in progress */

if (addrP == NULL) {
/* Connect without an address is not allowed
*/
return esock_raise_invalid(env, esock_atom_state);
}

/* Initial connect call, with address */

if (sock_connect(descP->sock, (struct sockaddr*) addrP, addrLen) == 0) {
/* Success! */
SSDBG( descP, ("WIN-ESAIO",
"essio_connect_dgram {%d} -> connected\r\n",
descP->sock) );

descP->writeState |= ESOCK_STATE_CONNECTED;

return esock_atom_ok;
}

/* Connect returned error */
save_errno = sock_errno();

SSDBG( descP,
("WIN-ESAIO", "esaio_connect_dgram {%d} -> error: %d\r\n",
descP->sock, save_errno) );

return esock_make_error_errno(env, save_errno);

}


Expand Down
9 changes: 8 additions & 1 deletion lib/kernel/src/gen_udp.erl
Original file line number Diff line number Diff line change
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
%% Copyright Ericsson AB 1997-2022. All Rights Reserved.
%% Copyright Ericsson AB 1997-2023. All Rights Reserved.
%%
%% Licensed under the Apache License, Version 2.0 (the "License");
%% you may not use this file except in compliance with the License.
Expand Down Expand Up @@ -29,6 +29,8 @@
-define(module_socket(Handler, Handle),
{'$inet', (Handler), (Handle)}).

%% -define(DBG(T), erlang:display({{self(), ?MODULE, ?LINE, ?FUNCTION_NAME}, T})).

-type option() ::
{active, true | false | once | -32768..32767} |
{add_membership, membership()} |
Expand Down Expand Up @@ -377,15 +379,20 @@ connect(?module_socket(GenUdpMod, _) = S, Address, Port)
GenUdpMod:?FUNCTION_NAME(S, Address, Port);

connect(S, Address, Port) when is_port(S) ->
%% ?DBG([{address, Address}, {port, Port}]),
case inet_db:lookup_socket(S) of
{ok, Mod} ->
%% ?DBG([{mod, Mod}]),
case Mod:getaddr(Address) of
{ok, IP} ->
%% ?DBG([{ip, IP}]),
Mod:connect(S, IP, Port);
Error ->
%% ?DBG(['getaddr', {error, Error}]),
Error
end;
Error ->
%% ?DBG(['lookup', {error, Error}]),
Error
end.

Expand Down
9 changes: 8 additions & 1 deletion lib/kernel/src/gen_udp_socket.erl
Original file line number Diff line number Diff line change
Expand Up @@ -124,17 +124,22 @@ close_server(Server) ->
%% -- connect ----------------------------------------------------------------

connect(?MODULE_socket(_Server, Socket), Address, Port) ->
%% ?DBG([{address, Address}, {port, Port}]),
{Mod, _} = inet:udp_module([], Address),
Domain = domain(Mod),
%% ?DBG([{mod, Mod}, {domain, Domain}]),
try
begin
Dest =
case Mod:getaddr(Address) of
{ok, IP} when (Domain =:= local) ->
%% ?DBG([{ip, IP}]),
dest2sockaddr(IP);
{ok, IP} ->
%% ?DBG([{ip, IP}]),
dest2sockaddr({IP, Port});
{error, _Reason} = ERROR ->
%% ?DBG(['getaddr', {error, ERROR}]),
throw(ERROR)
end,
case os:type() of
Expand All @@ -149,6 +154,7 @@ connect(?MODULE_socket(_Server, Socket), Address, Port) ->
socket:connect(Socket, Dest)
end;
_ ->
%% ?DBG(['try connect']),
socket:connect(Socket, Dest)
end
end
Expand Down Expand Up @@ -331,8 +337,9 @@ which_default_bind_address2(Domain) ->
%% Pick first *non-loopback* interface that is 'up'
UpNonLoopbackAddrs =
[Addr ||
#{flags := Flags} = Addr <-
#{flags := Flags, addr := #{addr := _A}} = Addr <-
Addrs,
%% (element(1, A) =/= 169) andalso
(not lists:member(loopback, Flags)) andalso
lists:member(up, Flags)],
%% ?DBG([{up_non_loopback_addrs, UpNonLoopbackAddrs}]),
Expand Down
55 changes: 47 additions & 8 deletions lib/kernel/src/inet.erl
Original file line number Diff line number Diff line change
Expand Up @@ -642,8 +642,10 @@ gethostbyname(Name,Family,Timeout) ->
_ = stop_timer(Timer),
Res.

gethostbyname_tm(Name,Family,Timer) ->
gethostbyname_tm(Name, Family, Timer) ->
%% ?DBG([{name, Name}, {family, Family}, {timer, Timer}]),
Opts0 = inet_db:res_option(lookup),
%% ?DBG([{opts0, Opts0}]),
Opts =
case (lists:member(native, Opts0) orelse
lists:member(string, Opts0) orelse
Expand All @@ -653,6 +655,7 @@ gethostbyname_tm(Name,Family,Timer) ->
false ->
[string|Opts0]
end,
%% ?DBG([{opts, Opts}]),
gethostbyname_tm(Name, Family, Timer, Opts).


Expand Down Expand Up @@ -819,15 +822,22 @@ getaddr(Address, Family) ->
{'ok', ip_address()} | {'error', posix()}.

getaddr(Address, Family, Timeout) ->
%% ?DBG([{address, Address}, {family, Family}, {timeout, Timeout}]),
Timer = start_timer(Timeout),
Res = getaddr_tm(Address, Family, Timer),
_ = stop_timer(Timer),
Res = getaddr_tm(Address, Family, Timer),
%% ?DBG([{res, Res}]),
_ = stop_timer(Timer),
Res.

getaddr_tm(Address, Family, Timer) ->
%% ?DBG([{address, Address}, {family, Family}, {timer, Timer}]),
case getaddrs_tm(Address, Family, Timer) of
{ok, [IP|_]} -> {ok, IP};
Error -> Error
{ok, [IP|_]} ->
%% ?DBG([{ip, IP}]),
{ok, IP};
Error ->
%% ?DBG([{error, Error}]),
Error
end.

-spec getaddrs(Host, Family) ->
Expand Down Expand Up @@ -1553,48 +1563,68 @@ getaddrs_tm({A,B,C,D,E,F,G,H} = IP, Fam, _) ->
getaddrs_tm(Address, Family, Timer) when is_atom(Address) ->
getaddrs_tm(atom_to_list(Address), Family, Timer);
getaddrs_tm(Address, Family, Timer) ->
%% ?DBG([{address, Address}, {family, Family}, {timer, Timer}]),
case inet_parse:visible_string(Address) of
false ->
{error,einval};
true ->
%% Address is a host name or a valid IP address,
%% either way check it with the resolver.
case gethostbyname_tm(Address, Family, Timer) of
{ok,Ent} -> {ok,Ent#hostent.h_addr_list};
Error -> Error
{ok, Ent} ->
%% ?DBG([{ent, Ent}]),
{ok, Ent#hostent.h_addr_list};
Error ->
%% ?DBG([{error, Error}]),
Error
end
end.

%%
%% gethostbyname with option search
%%
gethostbyname_tm(Name, Type, Timer, [string|_]=Opts) ->
%% ?DBG([string, {name, Name}, {type, Type}, {timer, Timer}]),
Result = gethostbyname_string(Name, Type),
gethostbyname_tm(Name, Type, Timer, Opts, Result);
gethostbyname_tm(Name, Type, Timer, [dns|_]=Opts) ->
%% ?DBG([dns, {name, Name}, {type, Type}, {timer, Timer}]),
Result = inet_res:gethostbyname_tm(Name, Type, Timer),
%% ?DBG([{result, Result}]),
gethostbyname_tm(Name, Type, Timer, Opts, Result);
gethostbyname_tm(Name, Type, Timer, [file|_]=Opts) ->
%% ?DBG([file, {name, Name}, {type, Type}, {timer, Timer}]),
Result = inet_hosts:gethostbyname(Name, Type),
%% ?DBG([{result, Result}]),
gethostbyname_tm(Name, Type, Timer, Opts, Result);
gethostbyname_tm(Name, Type, Timer, [yp|_]=Opts) ->
%% ?DBG([yp, {name, Name}, {type, Type}, {timer, Timer}]),
gethostbyname_tm_native(Name, Type, Timer, Opts);
gethostbyname_tm(Name, Type, Timer, [nis|_]=Opts) ->
%% ?DBG([nis, {name, Name}, {type, Type}, {timer, Timer}]),
gethostbyname_tm_native(Name, Type, Timer, Opts);
gethostbyname_tm(Name, Type, Timer, [nisplus|_]=Opts) ->
%% ?DBG([niplus, {name, Name}, {type, Type}, {timer, Timer}]),
gethostbyname_tm_native(Name, Type, Timer, Opts);
gethostbyname_tm(Name, Type, Timer, [wins|_]=Opts) ->
%% ?DBG([wins, {name, Name}, {type, Type}, {timer, Timer}]),
gethostbyname_tm_native(Name, Type, Timer, Opts);
gethostbyname_tm(Name, Type, Timer, [native|_]=Opts) ->
%% ?DBG([native, {name, Name}, {type, Type}, {timer, Timer}]),
gethostbyname_tm_native(Name, Type, Timer, Opts);
gethostbyname_tm(Name, Type, Timer, [_|Opts]) ->
%% ?DBG([{name, Name}, {type, Type}, {timer, Timer}]),
gethostbyname_tm(Name, Type, Timer, Opts);
%% Make sure we always can look up our own hostname.
gethostbyname_tm(Name, Type, Timer, []) ->
%% ?DBG([{name, Name}, {type, Type}, {timer, Timer}]),
Result = gethostbyname_self(Name, Type),
%% ?DBG([{result, Result}]),
gethostbyname_tm(Name, Type, Timer, [], Result).

gethostbyname_tm(Name, Type, Timer, Opts, Result) ->
%% ?DBG([string, {name, Name}, {type, Type}, {timer, Timer},
%% {opts, Opts}, {result, Result}]),
case Result of
{ok,_} ->
Result;
Expand All @@ -1607,19 +1637,24 @@ gethostbyname_tm(Name, Type, Timer, Opts, Result) ->
end.

gethostbyname_tm_native(Name, Type, Timer, Opts) ->
%% ?DBG([{name, Name}, {type, Type}, {timer, Timer}, {opts, Opts}]),
%% Fixme: add (global) timeout to gethost_native
Result = inet_gethost_native:gethostbyname(Name, Type),
%% ?DBG([{result, Result}]),
gethostbyname_tm(Name, Type, Timer, Opts, Result).



gethostbyname_self(Name, Type) when is_atom(Name) ->
%% ?DBG([{name, Name}, {type, Type}]),
gethostbyname_self(atom_to_list(Name), Type);
gethostbyname_self(Name, Type)
when is_list(Name), Type =:= inet;
is_list(Name), Type =:= inet6 ->
N = inet_db:tolower(Name),
%% ?DBG([{name, Name}, {type, Type}]),
N = inet_db:tolower(Name),
Self = inet_db:gethostname(),
%% ?DBG([{n, N}, {self, Self}]),
%%
%% This is the final fallback that pretends /etc/hosts has got
%% a line for the hostname on the loopback address.
Expand All @@ -1629,14 +1664,17 @@ gethostbyname_self(Name, Type)
%%
case inet_db:tolower(Self) of
N ->
%% ?DBG([{n, N}]),
{ok,
make_hostent(
Self, [translate_ip(loopback, Type)], [], Type)};
_ ->
case inet_db:res_option(domain) of
"" ->
%% ?DBG(['res option empty domain']),
{error,nxdomain};
Domain ->
%% ?DBG([{domain, Domain}]),
FQDN = lists:append([Self,".",Domain]),
case inet_db:tolower(FQDN) of
N ->
Expand All @@ -1645,6 +1683,7 @@ gethostbyname_self(Name, Type)
FQDN,
[translate_ip(loopback, Type)], [], Type)};
_ ->
%% ?DBG(['invalid domain', {fqdn, FQDN}]),
{error,nxdomain}
end
end
Expand Down
Loading

0 comments on commit a9a30c1

Please sign in to comment.