Skip to content

Commit

Permalink
Merge branch 'bmk/kernel/20240911/test_tweaking' into maint
Browse files Browse the repository at this point in the history
  • Loading branch information
bmk committed Nov 27, 2024
2 parents 9650953 + 02dfa1d commit 65d6ac0
Show file tree
Hide file tree
Showing 7 changed files with 123 additions and 21 deletions.
27 changes: 26 additions & 1 deletion lib/kernel/test/gen_sctp_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -203,7 +203,7 @@ init_per_testcase(api_connectx_init = Case, Config) ->
init_per_testcase(t_simple_local_sockaddr_in_connectx_init = Case, Config) ->
check_sctp_connectx(Case, Config);
init_per_testcase(names_multihoming_ipv4 = Case, Config) ->
case lists:keylookup(label, 1, Config) of
case lists:keysearch(label, 1, Config) of
{value, {label, docker}} ->
{skip, "Unstable/broken on docker"};
_ ->
Expand Down Expand Up @@ -2879,16 +2879,22 @@ s_start(Starter, Timeout) ->
s_loop(Socket, Timeout, Parent, State) ->
receive
{?MODULE,AMref,{controlling_process, NewParent}} ->
?P("received (new) controlling process: "
"~n ~p", [NewParent]),
AMref ! {?MODULE,AMref,ok},
s_loop(Socket, Timeout, NewParent, State);
{?MODULE,AMref,close} -> % socket_close()
?P("received close"),
erlang:send_after(Timeout, self(), {?MODULE,AMref,exit}),
s_loop(Socket, Timeout, Parent, State);
{?MODULE,AMref,exit} ->
?P("received exit"),
ok = gen_sctp:close(Socket),
NewState = gb_push(exit, Socket, State),
AMref ! {?MODULE,AMref,{NewState,flush()}};
{?MODULE,AMref,{Req}} ->
?P("received request: "
"~n ~p", [Req]),
Result = s_handle_req(Socket, Req),
NewState = gb_push(req, {Req,Result}, State),
AMref ! {?MODULE, AMref,Result},
Expand All @@ -2899,6 +2905,9 @@ s_loop(Socket, Timeout, Parent, State) ->
{sctp,Socket,Addr,Port,
{[#sctp_sndrcvinfo{stream=Stream,assoc_id=AssocId}=SRI],Data}}
when not is_tuple(Data) ->
?P("received [sctp] snd/rcv info: "
"~n Stream: ~p"
"~n AssocId: ~p", [Stream, AssocId]),
case gb_get({assoc_change,AssocId}, State) of
[{Addr,Port,
#sctp_assoc_change{
Expand All @@ -2914,6 +2923,10 @@ s_loop(Socket, Timeout, Parent, State) ->
s_loop(Socket, Timeout, Parent, NewState);
{sctp,Socket,Addr,Port,
{SRI,#sctp_assoc_change{assoc_id=AssocId,state=St}=SAC}} ->
?P("received [sctp] assoc change: "
"~n AssocId: ~p"
"~n St: ~p"
"~n SRI: ~p", [AssocId, St, SRI]),
case SRI of
[#sctp_sndrcvinfo{assoc_id=AssocId,stream=0}] -> ok;
[] -> ok
Expand All @@ -2932,6 +2945,10 @@ s_loop(Socket, Timeout, Parent, State) ->
{SRI,#sctp_paddr_change{assoc_id=AssocId,
addr={_,P},
state=St}=SPC}} ->
?P("received [sctp] paddr change: "
"~n AssocId: ~p"
"~n P: ~p"
"~n St: ~p", [AssocId, P, St]),
match_unless_solaris(Port, P),
case SRI of
[#sctp_sndrcvinfo{assoc_id=AssocId,stream=0}] -> ok;
Expand All @@ -2949,6 +2966,9 @@ s_loop(Socket, Timeout, Parent, State) ->
s_loop(Socket, Timeout, Parent, NewState);
{sctp,Socket,Addr,Port,
{SRI,#sctp_shutdown_event{assoc_id=AssocId}=SSE}} ->
?P("received [sctp] shutdown event: "
"~n AssocId: ~p"
"~n SRI: ~p", [AssocId, SRI]),
case SRI of
[#sctp_sndrcvinfo{assoc_id=AssocId,stream=0}] -> ok;
[] -> ok
Expand All @@ -2963,6 +2983,11 @@ s_loop(Socket, Timeout, Parent, State) ->
again(Socket),
s_loop(Socket, Timeout, Parent, NewState);
Unexpected ->
?P("received unexpected message: "
"~n ~p"
"~nwhen"
"~n Socket Info: ~p",
[Unexpected, inet:info(Socket)]),
erlang:error({unexpected,Unexpected})
end.

Expand Down
21 changes: 20 additions & 1 deletion lib/kernel/test/gen_tcp_misc_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -8411,6 +8411,8 @@ bidirectional_traffic(Config) when is_list(Config) ->
true ->
{skip, "Inet driver specific test"};
false ->
%% Unstable on our Solaris/SunOS machine(s)
is_not_sunos(),
ok
end
end,
Expand Down Expand Up @@ -9519,7 +9521,24 @@ is_platform(Family, Name, PlatformStr)
_ ->
skip("Require " ++ PlatformStr)
end.


is_not_sunos() ->
is_not_unix(sunos, "SunOS").

is_not_unix(Name, PlatformStr) ->
is_not_platform(unix, Name, PlatformStr).

is_not_platform(Family, Name, PlatformStr)
when is_atom(Family) andalso
is_atom(Name) andalso
is_list(PlatformStr) ->
case os:type() of
{Family, Name} ->
skip("Require *not* " ++ PlatformStr);
_ ->
ok
end.


is_socket_supported() ->
try socket:info() of
Expand Down
12 changes: 12 additions & 0 deletions lib/kernel/test/kernel_test_lib.erl
Original file line number Diff line number Diff line change
Expand Up @@ -49,6 +49,8 @@
-export([
proxy_call/3,

ensure_not_dog_slow/2,

%% Generic 'has support' test function(s)
is_socket_supported/0,
has_support_ipv4/0,
Expand Down Expand Up @@ -2709,6 +2711,16 @@ proxy_call(F, Timeout, Default)



ensure_not_dog_slow(Config, Limit) ->
Key = kernel_factor,
case lists:keysearch(Key, 1, Config) of
{value, {Key, Value}} when (Value > Limit) ->
skip({factor_limit, Value, Limit});
_ ->
ok
end.


%% This is an extremely simple check...
has_support_ipv4() ->
case which_local_addr(inet) of
Expand Down
2 changes: 2 additions & 0 deletions lib/kernel/test/kernel_test_lib.hrl
Original file line number Diff line number Diff line change
Expand Up @@ -56,6 +56,8 @@
-define(WHICH_INET_BACKEND(C), ?LIB:which_inet_backend(C)).
-define(IS_SOCKET_BACKEND(C), ?LIB:is_socket_backend(C)).

-define(ENSURE_NOT_DOG_SLOW(C, L), ?LIB:ensure_not_dog_slow((C), (L))).

-define(HAS_SUPPORT_IPV4(), ?LIB:has_support_ipv4()).
-define(HAS_SUPPORT_IPV6(), ?LIB:has_support_ipv6()).
-define(WHICH_LOCAL_ADDR(D), ?LIB:which_local_addr((D))).
Expand Down
33 changes: 21 additions & 12 deletions lib/kernel/test/net_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -462,8 +462,11 @@ api_b_getservbyname() ->
wrong_port("amqp", tcp, WrongPort, 5672);
{error, Reason} ->
case os:type() of
{unix, openbsd}
when (Reason =:= einval) ->
{unix, Flavor}
when ((Flavor =:= openbsd) orelse
(Flavor =:= solaris) orelse
(Flavor =:= sunos)) andalso
(Reason =:= einval) ->
ok;
_ ->
?P("Unexpected failure: ~p",
Expand All @@ -480,11 +483,12 @@ api_b_getservbyname() ->
wrong_port("amqp", sctp, WrongPort, 5672);
{error, Reason} ->
case os:type() of
{unix, darwin}
when (Reason =:= einval) ->
ok;
{unix, openbsd}
when (Reason =:= einval) ->
{unix, Flavor}
when ((Flavor =:= darwin) orelse
(Flavor =:= openbsd) orelse
(Flavor =:= solaris) orelse
(Flavor =:= sunos)) andalso
(Reason =:= einval) ->
ok;
_ ->
?P("Unexpected failure: ~p",
Expand Down Expand Up @@ -642,8 +646,11 @@ api_b_getservbyport() ->
WrongService, "amqp");
{error, Reason} ->
case os:type() of
{unix, openbsd}
when (Reason =:= einval) ->
{unix, Flavor}
when ((Flavor =:= openbsd) orelse
(Flavor =:= solaris) orelse
(Flavor =:= sunos)) andalso
(Reason =:= einval) ->
ok;
_ ->
?P("Unexpected failure: ~p",
Expand All @@ -661,9 +668,11 @@ api_b_getservbyport() ->
WrongService, "amqp");
{error, Reason} when (Reason =:= einval) ->
case os:type() of
{unix, UNIX}
when (UNIX =:= darwin) orelse
(UNIX =:= openbsd) ->
{unix, Flavor}
when (Flavor =:= darwin) orelse
(Flavor =:= openbsd) orelse
(Flavor =:= solaris) orelse
(Flavor =:= sunos) ->
ok;
_ ->
?P("Unexpected failure: ~p",
Expand Down
10 changes: 8 additions & 2 deletions lib/kernel/test/socket_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -413,6 +413,8 @@ init_per_suite(Config0) ->
?P("init_per_suite -> end when "
"~n Config: ~p", [Config1]),

?ENSURE_NOT_DOG_SLOW(Config1, 15),

%% We need a monitor on this node also
kernel_test_sys_monitor:start(),

Expand Down Expand Up @@ -12787,8 +12789,12 @@ start_node(Name, Timeout) when is_integer(Timeout) andalso (Timeout > 0) ->
?SEV_IPRINT("Started node ~p - now (global) sync", [Name]),
global:sync(), % Again, just in case...
?SEV_IPRINT("ping proxy"),
pong = ?PPING(Node),
{Peer, Node};
case ?PPING(Node) of
{error, Reason} ->
skip({ping_failed, Reason});
pong ->
{Peer, Node}
end;
{error, Reason} ->
?SEV_EPRINT("failed starting node ~p (=> SKIP):"
"~n ~p", [Name, Reason]),
Expand Down
Loading

0 comments on commit 65d6ac0

Please sign in to comment.