Skip to content

Commit

Permalink
Merge pull request #6944 from rickard-green/rickard/win-reuseaddr-reu…
Browse files Browse the repository at this point in the history
…seport-fix/OTP-18344

Windows reuseaddr/reuseport fix
  • Loading branch information
rickard-green committed Mar 2, 2023
2 parents 01723d5 + 0f2fc92 commit 252c860
Show file tree
Hide file tree
Showing 3 changed files with 145 additions and 63 deletions.
46 changes: 23 additions & 23 deletions erts/emulator/drivers/common/inet_drv.c
Original file line number Diff line number Diff line change
Expand Up @@ -6931,7 +6931,7 @@ static int inet_set_opts(inet_descriptor* desc, char* ptr, int len)
case INET_OPT_EXCLUSIVEADDRUSE:
DDBG(desc,
("INET-DRV-DBG[%d][" SOCKET_FSTR ",%T] "
"inet_set_opts(reuseaddr) -> %s\r\n",
"inet_set_opts(exclusiveaddruse) -> %s\r\n",
__LINE__, desc->s, driver_caller(desc->port), B2S(ival)) );
#ifdef __WIN32__
type = SO_EXCLUSIVEADDRUSE;
Expand Down Expand Up @@ -6979,25 +6979,25 @@ static int inet_set_opts(inet_descriptor* desc, char* ptr, int len)
__LINE__, desc->s, driver_caller(desc->port), B2S(ival)) );
#ifdef __WIN32__
{
int old_ra, new_ra, compat;
int old_ra, new_ra, compat, ra_bits, opt_bit;
/*
* We only set SO_REUSEADDR on Windows if both 'reuseaddr' and
* 'reuseport' has been passed as options, since SO_REUSEADDR
* on Windows behaves like SO_REUSEADDR|SO_REUSEPORT does on BSD.
*/
ra_bits = (1<<INET_OPT_REUSEADDR) | (1<<INET_OPT_REUSEPORT);
opt_bit = (1<<opt);
compat = desc->bsd_compat;
old_ra = ((compat & (INET_OPT_REUSEADDR | INET_OPT_REUSEPORT))
== (INET_OPT_REUSEADDR | INET_OPT_REUSEPORT));
old_ra = (compat & ra_bits) == ra_bits;
if (ival) {
bsd_compat_set = opt;
compat |= opt;
bsd_compat_set = opt_bit;
compat |= opt_bit;
}
else {
bsd_compat_unset = opt;
compat &= ~opt;
bsd_compat_unset = opt_bit;
compat &= ~opt_bit;
}
new_ra = ((compat & (INET_OPT_REUSEADDR | INET_OPT_REUSEPORT))
== (INET_OPT_REUSEADDR | INET_OPT_REUSEPORT));
new_ra = (compat & ra_bits) == ra_bits;
desc->bsd_compat = compat;
if (old_ra == new_ra)
continue;
Expand Down Expand Up @@ -8020,25 +8020,25 @@ static int sctp_set_opts(inet_descriptor* desc, char* ptr, int len)
__LINE__, desc->s, driver_caller(desc->port)) );
#ifdef __WIN32__
{
int old_ra, new_ra, compat;
int old_ra, new_ra, compat, ra_bits, opt_bit;
/*
* We only set SO_REUSEADDR on Windows if both 'reuseaddr' and
* 'reuseport' has been passed as options, since SO_REUSEADDR
* on Windows behaves like SO_REUSEADDR|SO_REUSEPORT does on BSD.
*/
ra_bits = (1<<INET_OPT_REUSEADDR) | (1<<INET_OPT_REUSEPORT);
opt_bit = (1<<opt);
compat = desc->bsd_compat;
old_ra = ((compat & (INET_OPT_REUSEADDR | INET_OPT_REUSEPORT))
== (INET_OPT_REUSEADDR | INET_OPT_REUSEPORT));
old_ra = (compat & ra_bits) == ra_bits;
if (ival) {
bsd_compat_set = opt;
compat |= opt;
bsd_compat_set = opt_bit;
compat |= opt_bit;
}
else {
bsd_compat_unset = opt;
compat &= ~opt;
bsd_compat_unset = opt_bit;
compat &= ~opt_bit;
}
new_ra = ((compat & (INET_OPT_REUSEADDR | INET_OPT_REUSEPORT))
== (INET_OPT_REUSEADDR | INET_OPT_REUSEPORT));
new_ra = (compat & ra_bits) == ra_bits;
desc->bsd_compat = compat;
if (old_ra == new_ra)
continue;
Expand Down Expand Up @@ -8937,7 +8937,7 @@ static ErlDrvSSizeT inet_fill_opts(inet_descriptor* desc,
#endif
case INET_OPT_REUSEADDR: {
#if defined(__WIN32__)
int res = !!(desc->bsd_compat & INET_OPT_REUSEADDR);
int res = !!(desc->bsd_compat & (1<<INET_OPT_REUSEADDR));
*ptr++ = opt;
put_int32(res, ptr);
continue;
Expand All @@ -8962,7 +8962,7 @@ static ErlDrvSSizeT inet_fill_opts(inet_descriptor* desc,
}
case INET_OPT_REUSEPORT: {
#if defined(__WIN32__)
int res = !!(desc->bsd_compat & INET_OPT_REUSEPORT);
int res = !!(desc->bsd_compat & (1<<INET_OPT_REUSEPORT));
*ptr++ = opt;
put_int32(res, ptr);
continue;
Expand Down Expand Up @@ -9637,7 +9637,7 @@ static ErlDrvSSizeT sctp_fill_opts(inet_descriptor* desc,
case INET_OPT_REUSEPORT:
{
#if defined(__WIN32__)
res = !!(desc->bsd_compat & INET_OPT_REUSEPORT);
res = !!(desc->bsd_compat & (1<<INET_OPT_REUSEPORT));
is_int = 0;
tag = am_reuseaddr;
goto form_result;
Expand All @@ -9654,7 +9654,7 @@ static ErlDrvSSizeT sctp_fill_opts(inet_descriptor* desc,
case INET_OPT_REUSEADDR:
{
#if defined(__WIN32__)
res = !!(desc->bsd_compat & INET_OPT_REUSEADDR);
res = !!(desc->bsd_compat & (1<<INET_OPT_REUSEADDR));
is_int = 0;
tag = am_reuseaddr;
goto form_result;
Expand Down
156 changes: 116 additions & 40 deletions lib/kernel/test/inet_sockopt_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -34,6 +34,7 @@
-define(C_GET_SO_REUSEADDR,14).
-define(C_GET_SO_KEEPALIVE,15).
-define(C_GET_SO_LINGER,16).
-define(C_GET_SO_DONTROUTE,17).

-define(C_GET_LINGER_SIZE,21).
-define(C_GET_TCP_INFO_SIZE,22).
Expand All @@ -58,7 +59,7 @@
large_raw/1,large_raw_getbin/1,combined/1,combined_getbin/1,
ipv6_v6only_udp/1, ipv6_v6only_tcp/1, ipv6_v6only_sctp/1,
use_ipv6_v6only_udp/1,
type_errors/1]).
type_errors/1, windows_reuseaddr/1]).

-export([init_per_testcase/2, end_per_testcase/2]).

Expand All @@ -74,7 +75,7 @@ all() ->
large_raw_getbin, combined, combined_getbin,
ipv6_v6only_udp, ipv6_v6only_tcp, ipv6_v6only_sctp,
use_ipv6_v6only_udp,
type_errors].
type_errors, windows_reuseaddr].

groups() ->
[].
Expand Down Expand Up @@ -127,10 +128,12 @@ simple(Config) when is_list(Config) ->
%% Loop through all socket options and check that they work.
loop_all(Config) when is_list(Config) ->
ListenFailures =
lists:foldr(make_check_fun(listen,1),[],all_listen_options()),
lists:foldr(make_check_fun(listen),[],all_listen_options()),
AcceptFailures =
lists:foldr(make_check_fun(accept),[],all_accept_options()),
ConnectFailures =
lists:foldr(make_check_fun(connect,2),[],all_connect_options()),
case ListenFailures++ConnectFailures of
lists:foldr(make_check_fun(connect),[],all_connect_options()),
case ListenFailures++AcceptFailures++ConnectFailures of
[] ->
ok;
Failed ->
Expand Down Expand Up @@ -206,56 +209,56 @@ do_multiple_raw(Config, Binary) ->
SoKeepalive = ask_helper(Port, ?C_GET_SO_KEEPALIVE),
SoKeepaliveTrue = {raw,SolSocket,SoKeepalive,<<1:32/native>>},
SoKeepaliveFalse = {raw,SolSocket,SoKeepalive,<<0:32/native>>},
SoReuseaddr = ask_helper(Port, ?C_GET_SO_REUSEADDR),
SoReuseaddrTrue = {raw,SolSocket,SoReuseaddr,<<1:32/native>>},
SoReuseaddrFalse = {raw,SolSocket,SoReuseaddr,<<0:32/native>>},
SoDontroute = ask_helper(Port, ?C_GET_SO_DONTROUTE),
SoDontrouteTrue = {raw,SolSocket,SoDontroute,<<1:32/native>>},
SoDontrouteFalse = {raw,SolSocket,SoDontroute,<<0:32/native>>},
{S1,S2} =
create_socketpair(
[SoReuseaddrFalse,SoKeepaliveTrue],
[SoKeepaliveFalse,SoReuseaddrTrue]),
{ok,[{reuseaddr,false},{keepalive,true}]} =
inet:getopts(S1, [reuseaddr,keepalive]),
[SoDontrouteFalse,SoKeepaliveTrue],
[SoKeepaliveFalse,SoDontrouteTrue]),
{ok,[{dontroute,false},{keepalive,true}]} =
inet:getopts(S1, [dontroute,keepalive]),
{ok,
[{raw,SolSocket,SoReuseaddr,S1R1},
[{raw,SolSocket,SoDontroute,S1R1},
{raw,SolSocket,SoKeepalive,S1K1}]} =
inet:getopts(
S1,
[{raw,SolSocket,SoReuseaddr,binarify(4, Binary)},
[{raw,SolSocket,SoDontroute,binarify(4, Binary)},
{raw,SolSocket,SoKeepalive,binarify(4, Binary)}]),
true = nintbin2int(S1R1) =:= 0,
true = nintbin2int(S1K1) =/= 0,
{ok,[{keepalive,false},{reuseaddr,true}]} =
inet:getopts(S2, [keepalive,reuseaddr]),
{ok,[{keepalive,false},{dontroute,true}]} =
inet:getopts(S2, [keepalive,dontroute]),
{ok,
[{raw,SolSocket,SoKeepalive,S2K1},
{raw,SolSocket,SoReuseaddr,S2R1}]} =
{raw,SolSocket,SoDontroute,S2R1}]} =
inet:getopts(
S2,
[{raw,SolSocket,SoKeepalive,binarify(4, Binary)},
{raw,SolSocket,SoReuseaddr,binarify(4, Binary)}]),
{raw,SolSocket,SoDontroute,binarify(4, Binary)}]),
true = nintbin2int(S2K1) =:= 0,
true = nintbin2int(S2R1) =/= 0,
%%
ok = inet:setopts(
S1, [SoReuseaddrTrue,SoKeepaliveFalse]),
S1, [SoDontrouteTrue,SoKeepaliveFalse]),
ok = inet:setopts(
S2, [SoKeepaliveTrue,SoReuseaddrFalse]),
S2, [SoKeepaliveTrue,SoDontrouteFalse]),
{ok,
[{raw,SolSocket,SoReuseaddr,S1R2},
[{raw,SolSocket,SoDontroute,S1R2},
{raw,SolSocket,SoKeepalive,S1K2}]} =
inet:getopts(
S1,
[{raw,SolSocket,SoReuseaddr,binarify(4, Binary)},
[{raw,SolSocket,SoDontroute,binarify(4, Binary)},
{raw,SolSocket,SoKeepalive,binarify(4, Binary)}]),
true = nintbin2int(S1R2) =/= 0,
true = nintbin2int(S1K2) =:= 0,
{ok,
[{raw,SolSocket,SoKeepalive,S2K2},
{raw,SolSocket,SoReuseaddr,S2R2}]} =
{raw,SolSocket,SoDontroute,S2R2}]} =
inet:getopts(
S2,
[{raw,SolSocket,SoKeepalive,binarify(4, Binary)},
{raw,SolSocket,SoReuseaddr,binarify(4, Binary)}]),
{raw,SolSocket,SoDontroute,binarify(4, Binary)}]),
true = nintbin2int(S2K2) =/= 0,
true = nintbin2int(S2R2) =:= 0,
%%
Expand Down Expand Up @@ -802,6 +805,57 @@ type_errors(Config) when is_list(Config) ->
gen_tcp:close(Sock2),
ok.

windows_reuseaddr(Config) when is_list(Config) ->
%% Check that emulation of reuseaddr and reuseport on Windows
%% works as expected. That is, only set SO_REUSEADDR if both
%% reuseaddr and reuseport are set.
case os:type() of
{win32, _} ->
Port = start_helper(Config),
Def = {ask_helper(Port,?C_GET_SOL_SOCKET),
ask_helper(Port,?C_GET_SO_REUSEADDR)},
stop_helper(Port),
{false, false} = windows_reuseaddr_test(Def,
[{reuseaddr,false},{reuseport,false}],
[{reuseaddr,false},{reuseport,false}]),
{false, false} = windows_reuseaddr_test(Def,
[{reuseaddr,true},{reuseport,false}],
[{reuseaddr,true},{reuseport,false}]),
{false, false} = windows_reuseaddr_test(Def,
[{reuseaddr,false},{reuseport,true}],
[{reuseaddr,false},{reuseport,true}]),
{true, true} = windows_reuseaddr_test(Def,
[{reuseaddr,true},{reuseport,true}],
[{reuseaddr,true},{reuseport,true}]),
ok;
_ ->
{skipped, "Test for Windows only"}
end.

windows_reuseaddr_test({SolSocket, SoReuseaddr}, LOpts, COpts) ->
OptNames = fun (Opts) ->
lists:map(fun ({Name,_}) -> Name end, Opts)
end,
{L,A,C} = create_socketpair_init(LOpts, COpts),
{ok, LOpts} = inet:getopts(L, OptNames(LOpts)),
{ok, COpts} = inet:getopts(L, OptNames(COpts)),
RawOpts = [{raw, SolSocket, SoReuseaddr, 4}],
{ok,[{raw,SolSocket,SoReuseaddr,LRes}]} = inet:getopts(L, RawOpts),
LReuseaddr = case nintbin2int(LRes) of
0 -> false;
_ -> true
end,
{ok,[{raw,SolSocket,SoReuseaddr,CRes}]} = inet:getopts(L, RawOpts),
CReuseaddr = case nintbin2int(CRes) of
0 -> false;
_ -> true
end,
gen_tcp:close(L),
gen_tcp:close(A),
gen_tcp:close(C),
{LReuseaddr, CReuseaddr}.


all_ok([]) ->
true;
all_ok([H|T]) when H >= 0 ->
Expand All @@ -810,14 +864,23 @@ all_ok(_) ->
false.


make_check_fun(Type,Element) ->
make_check_fun(Type) ->
fun({Name,V1,V2,Mand,Chang},Acc) ->
{LO1,CO1} = setelement(Element,{[],[]}, [{Name,V1}]),
{LO2,CO2} = setelement(Element,{[],[]}, [{Name,V2}]),
{X1,Y1} = create_socketpair(LO1,CO1),
{X2,Y2} = create_socketpair(LO2,CO2),
S1 = element(Element,{X1,Y1}),
S2 = element(Element,{X2,Y2}),
{LO1,CO1} = case Type of
connect -> {[],[{Name,V1}]};
_ -> {[{Name,V1}],[]}
end,
{LO2,CO2} = case Type of
connect -> {[],[{Name,V2}]};
_ -> {[{Name,V2}],[]}
end,
{X1,Y1,Z1} = create_socketpair_init(LO1,CO1),
{X2,Y2,Z2} = create_socketpair_init(LO2,CO2),
{S1,S2} = case Type of
listen -> {X1,X2};
accept -> {Y1,Y2};
connect -> {Z1,Z2}
end,
{ok,[{Name,R1}]} = inet:getopts(S1,[Name]),
{ok,[{Name,R2}]} = inet:getopts(S2,[Name]),
NewAcc =
Expand Down Expand Up @@ -856,8 +919,10 @@ make_check_fun(Type,Element) ->
end,
gen_tcp:close(X1),
gen_tcp:close(Y1),
gen_tcp:close(Z1),
gen_tcp:close(X2),
gen_tcp:close(Y2),
gen_tcp:close(Z2),
NewAcc
end.

Expand All @@ -867,10 +932,10 @@ all_listen_options() ->
OsVersion = os:version(),
[{tos,0,1,false,true},
{priority,0,1,false,true},
{reuseaddr,false,true,mandatory_reuseaddr(OsType,OsVersion),true},
{reuseport,false,true,mandatory_reuseport(OsType,OsVersion),true},
{reuseport_lb,false,true,mandatory_reuseport_lb(OsType,OsVersion),true},
{exclusiveaddruse,false,true,mandatory_exclusiveaddruse(OsType,OsVersion),true},
{reuseaddr,false,true,mandatory_reuseaddr(OsType,OsVersion),false},
{reuseport,false,true,mandatory_reuseport(OsType,OsVersion),false},
{reuseport_lb,false,true,mandatory_reuseport_lb(OsType,OsVersion),false},
{exclusiveaddruse,false,true,mandatory_exclusiveaddruse(OsType,OsVersion),false},
{keepalive,false,true,true,true},
{linger, {false,10}, {true,10},true,true},
{sndbuf,2048,4096,false,true},
Expand All @@ -892,15 +957,22 @@ all_listen_options() ->
{delay_send,false,true,true,true},
{packet_size,0,4,true,true}
].

all_accept_options() ->
A0 = lists:keydelete(exclusiveaddruse, 1, all_listen_options()),
A1 = lists:keydelete(reuseaddr, 1, A0),
A2 = lists:keydelete(reuseport, 1, A1),
lists:keydelete(reuseport_lb, 1, A2).

all_connect_options() ->
OsType = os:type(),
OsVersion = os:version(),
[{tos,0,1,false,true},
{priority,0,1,false,true},
{reuseaddr,false,true,mandatory_reuseaddr(OsType,OsVersion),true},
{reuseport,false,true,mandatory_reuseport(OsType,OsVersion),true},
{reuseport_lb,false,true,mandatory_reuseport_lb(OsType,OsVersion),true},
{exclusiveaddruse,false,true,mandatory_exclusiveaddruse(OsType,OsVersion),true},
{reuseaddr,false,true,mandatory_reuseaddr(OsType,OsVersion),false},
{reuseport,false,true,mandatory_reuseport(OsType,OsVersion),false},
{reuseport_lb,false,true,mandatory_reuseport_lb(OsType,OsVersion),false},
{exclusiveaddruse,false,true,mandatory_exclusiveaddruse(OsType,OsVersion),false},
{keepalive,false,true,true,true},
{linger, {false,10}, {true,10},true,true},
{sndbuf,2048,4096,false,true},
Expand Down Expand Up @@ -964,11 +1036,15 @@ mandatory_exclusiveaddruse({win32, _}, {X,Y,_Z}) when X > 5 orelse X == 5 andals
mandatory_exclusiveaddruse(_OsType, _OsVersion) ->
false.

create_socketpair(ListenOptions,ConnectOptions) ->
create_socketpair_init(ListenOptions,ConnectOptions) ->
{ok,LS}=gen_tcp:listen(0,ListenOptions),
{ok,Port}=inet:port(LS),
{ok,CS}=gen_tcp:connect(localhost,Port,ConnectOptions),
{ok,AS}=gen_tcp:accept(LS),
{LS,AS,CS}.

create_socketpair(ListenOptions,ConnectOptions) ->
{LS,AS,CS} = create_socketpair_init(ListenOptions,ConnectOptions),
gen_tcp:close(LS),
{AS,CS}.

Expand Down
Loading

0 comments on commit 252c860

Please sign in to comment.