Skip to content

Commit

Permalink
Merge branch 'rani/sctp-sndrcvinfo/OTP-8795' into dev
Browse files Browse the repository at this point in the history
* rani/sctp-sndrcvinfo/OTP-8795:
  Fix xfer_active close expection for Solaris behaviour
  Keep default #sctp_sndrcvinfo{} fields on gen_sctp:send/4
  Fill in sinfo_assoc_id in struct sctp_sndrcvinfo for getopt()

Conflicts:
	lib/kernel/test/gen_sctp_SUITE.erl
  • Loading branch information
RaimoNiskanen committed Sep 2, 2010
2 parents 9a30a97 + 8a0e142 commit 9ea58df
Show file tree
Hide file tree
Showing 7 changed files with 208 additions and 19 deletions.
4 changes: 4 additions & 0 deletions erts/emulator/drivers/common/inet_drv.c
Expand Up @@ -6193,6 +6193,10 @@ static int sctp_fill_opts(inet_descriptor* desc, char* buf, int buflen,
struct sctp_sndrcvinfo sri;
unsigned int sz = sizeof(sri);

if (buflen < ASSOC_ID_LEN) RETURN_ERROR(spec, -EINVAL);
sri.sinfo_assoc_id = GET_ASSOC_ID(buf);
buf += ASSOC_ID_LEN;
buflen -= ASSOC_ID_LEN;
if (sock_getopt(desc->s, IPPROTO_SCTP, SCTP_DEFAULT_SEND_PARAM,
&sri, &sz) < 0) continue;
/* Fill in the response: */
Expand Down
Binary file modified erts/preloaded/ebin/prim_inet.beam
Binary file not shown.
4 changes: 2 additions & 2 deletions erts/preloaded/src/prim_inet.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
%% Copyright Ericsson AB 2000-2009. All Rights Reserved.
%% Copyright Ericsson AB 2000-2010. All Rights Reserved.
%%
%% The contents of this file are subject to the Erlang Public License,
%% Version 1.1, (the "License"); you may not use this file except in
Expand Down Expand Up @@ -1206,7 +1206,7 @@ type_opt_1(sctp_default_send_param) ->
timetolive = [uint32,0],
tsn = [],
cumtsn = [],
assoc_id = [sctp_assoc_id,0]}}];
assoc_id = [[sctp_assoc_id,0]]}}];
%% for SCTP_OPT_EVENTS
type_opt_1(sctp_events) ->
[{record,#sctp_event_subscribe{
Expand Down
8 changes: 2 additions & 6 deletions lib/kernel/src/gen_sctp.erl
Expand Up @@ -166,18 +166,14 @@ send(S, #sctp_assoc_change{assoc_id=AssocId}, Stream, Data)
when is_port(S), is_integer(Stream) ->
case inet_db:lookup_socket(S) of
{ok,Mod} ->
Mod:sendmsg(S, #sctp_sndrcvinfo{
stream = Stream,
assoc_id = AssocId}, Data);
Mod:send(S, AssocId, Stream, Data);
Error -> Error
end;
send(S, AssocId, Stream, Data)
when is_port(S), is_integer(AssocId), is_integer(Stream) ->
case inet_db:lookup_socket(S) of
{ok,Mod} ->
Mod:sendmsg(S, #sctp_sndrcvinfo{
stream = Stream,
assoc_id = AssocId}, Data);
Mod:send(S, AssocId, Stream, Data);
Error -> Error
end;
send(S, AssocChange, Stream, Data) ->
Expand Down
23 changes: 21 additions & 2 deletions lib/kernel/src/inet6_sctp.erl
@@ -1,7 +1,7 @@
%%
%% %CopyrightBegin%
%%
%% Copyright Ericsson AB 2007-2009. All Rights Reserved.
%% Copyright Ericsson AB 2007-2010. All Rights Reserved.
%%
%% The contents of this file are subject to the Erlang Public License,
%% Version 1.1, (the "License"); you may not use this file except in
Expand Down Expand Up @@ -32,7 +32,7 @@

-define(FAMILY, inet6).
-export([getserv/1,getaddr/1,getaddr/2,translate_ip/1]).
-export([open/1,close/1,listen/2,connect/5,sendmsg/3,recv/2]).
-export([open/1,close/1,listen/2,connect/5,sendmsg/3,send/4,recv/2]).



Expand Down Expand Up @@ -71,5 +71,24 @@ connect(S, Addr, Port, Opts, Timer) ->
sendmsg(S, SRI, Data) ->
prim_inet:sendmsg(S, SRI, Data).

send(S, AssocId, Stream, Data) ->
case prim_inet:getopts(
S,
[{sctp_default_send_param,#sctp_sndrcvinfo{assoc_id=AssocId}}]) of
{ok,
[{sctp_default_send_param,
#sctp_sndrcvinfo{
flags=Flags, context=Context, ppid=PPID, timetolive=TTL}}]} ->
prim_inet:sendmsg(
S,
#sctp_sndrcvinfo{
flags=Flags, context=Context, ppid=PPID, timetolive=TTL,
assoc_id=AssocId, stream=Stream},
Data);
_ ->
prim_inet:sendmsg(
S, #sctp_sndrcvinfo{assoc_id=AssocId, stream=Stream}, Data)
end.

recv(S, Timeout) ->
prim_inet:recvfrom(S, 0, Timeout).
21 changes: 20 additions & 1 deletion lib/kernel/src/inet_sctp.erl
Expand Up @@ -31,7 +31,7 @@

-define(FAMILY, inet).
-export([getserv/1,getaddr/1,getaddr/2,translate_ip/1]).
-export([open/1,close/1,listen/2,connect/5,sendmsg/3,recv/2]).
-export([open/1,close/1,listen/2,connect/5,sendmsg/3,send/4,recv/2]).



Expand Down Expand Up @@ -141,5 +141,24 @@ connect_get_assoc(S, Addr, Port, Active, Timer) ->
sendmsg(S, SRI, Data) ->
prim_inet:sendmsg(S, SRI, Data).

send(S, AssocId, Stream, Data) ->
case prim_inet:getopts(
S,
[{sctp_default_send_param,#sctp_sndrcvinfo{assoc_id=AssocId}}]) of
{ok,
[{sctp_default_send_param,
#sctp_sndrcvinfo{
flags=Flags, context=Context, ppid=PPID, timetolive=TTL}}]} ->
prim_inet:sendmsg(
S,
#sctp_sndrcvinfo{
flags=Flags, context=Context, ppid=PPID, timetolive=TTL,
assoc_id=AssocId, stream=Stream},
Data);
_ ->
prim_inet:sendmsg(
S, #sctp_sndrcvinfo{assoc_id=AssocId, stream=Stream}, Data)
end.

recv(S, Timeout) ->
prim_inet:recvfrom(S, 0, Timeout).
167 changes: 159 additions & 8 deletions lib/kernel/test/gen_sctp_SUITE.erl
Expand Up @@ -27,12 +27,12 @@
-export(
[basic/1,
api_open_close/1,api_listen/1,api_connect_init/1,api_opts/1,
xfer_min/1,xfer_active/1]).
xfer_min/1,xfer_active/1,def_sndrcvinfo/1]).

all(suite) ->
[basic,
api_open_close,api_listen,api_connect_init,api_opts,
xfer_min,xfer_active].
xfer_min,xfer_active,def_sndrcvinfo].

init_per_testcase(_Func, Config) ->
Dog = test_server:timetrap(test_server:seconds(15)),
Expand All @@ -43,6 +43,10 @@ fin_per_testcase(_Func, Config) ->



-define(LOGVAR(Var), begin io:format(??Var" = ~p~n", [Var]) end).



basic(doc) ->
"Hello world";
basic(suite) ->
Expand Down Expand Up @@ -218,12 +222,17 @@ xfer_active(Config) when is_list(Config) ->
end,
?line ok = gen_sctp:close(Sb),
?line receive
{sctp,Sa,Loopback,Pb,
{[],
#sctp_assoc_change{state=comm_lost,
assoc_id=SaAssocId}}} -> ok
after 17 -> ok %% On Solaris this does not arrive
end,
{sctp,Sa,Loopback,Pb,
{[],
#sctp_assoc_change{state=comm_lost,
assoc_id=SaAssocId}}} -> ok
after Timeout ->
?line test_server:fail({unexpected,flush()})
end,
?line receive
{sctp_error,Sa,enotconn} -> ok % Solaris
after 17 -> ok %% Only happens on Solaris
end,
?line ok = gen_sctp:close(Sa),
%%
?line receive
Expand All @@ -232,6 +241,148 @@ xfer_active(Config) when is_list(Config) ->
end,
ok.

def_sndrcvinfo(doc) ->
"Test that #sctp_sndrcvinfo{} parameters set on a socket "
"are used by gen_sctp:send/4";
def_sndrcvinfo(suite) ->
[];
def_sndrcvinfo(Config) when is_list(Config) ->
?line Loopback = {127,0,0,1},
?line Data = <<"What goes up, must come down.">>,
%%
?line S1 =
ok(gen_sctp:open(
0, [{sctp_default_send_param,#sctp_sndrcvinfo{ppid=17}}])),
?LOGVAR(S1),
?line P1 =
ok(inet:port(S1)),
?LOGVAR(P1),
?line #sctp_sndrcvinfo{ppid=17, context=0, timetolive=0, assoc_id=0} =
getopt(S1, sctp_default_send_param),
?line ok =
gen_sctp:listen(S1, true),
%%
?line S2 =
ok(gen_sctp:open()),
?LOGVAR(S2),
?line P2 =
ok(inet:port(S2)),
?LOGVAR(P2),
?line #sctp_sndrcvinfo{ppid=0, context=0, timetolive=0, assoc_id=0} =
getopt(S2, sctp_default_send_param),
%%
?line #sctp_assoc_change{
state=comm_up,
error=0,
assoc_id=S2AssocId} = S2AssocChange =
ok(gen_sctp:connect(S2, Loopback, P1, [])),
?LOGVAR(S2AssocChange),
?line case ok(gen_sctp:recv(S1)) of
{Loopback, P2,[],
#sctp_assoc_change{
state=comm_up,
error=0,
assoc_id=S1AssocId}} ->
?LOGVAR(S1AssocId)
end,
?line #sctp_sndrcvinfo{
ppid=17, context=0, timetolive=0, assoc_id=S1AssocId} =
getopt(
S1, sctp_default_send_param, #sctp_sndrcvinfo{assoc_id=S1AssocId}),
?line #sctp_sndrcvinfo{
ppid=0, context=0, timetolive=0, assoc_id=S2AssocId} =
getopt(
S2, sctp_default_send_param, #sctp_sndrcvinfo{assoc_id=S2AssocId}),
%%
?line ok =
gen_sctp:send(S1, S1AssocId, 1, <<"1: ",Data/binary>>),
?line case ok(gen_sctp:recv(S2)) of
{Loopback,P1,
[#sctp_sndrcvinfo{
stream=1, ppid=17, context=0, assoc_id=S2AssocId}],
<<"1: ",Data/binary>>} -> ok
end,
%%
?line ok =
setopt(
S1, sctp_default_send_param, #sctp_sndrcvinfo{ppid=18}),
?line ok =
setopt(
S1, sctp_default_send_param,
#sctp_sndrcvinfo{ppid=19, assoc_id=S1AssocId}),
?line #sctp_sndrcvinfo{
ppid=18, context=0, timetolive=0, assoc_id=0} =
getopt(S1, sctp_default_send_param),
?line #sctp_sndrcvinfo{
ppid=19, context=0, timetolive=0, assoc_id=S1AssocId} =
getopt(
S1, sctp_default_send_param, #sctp_sndrcvinfo{assoc_id=S1AssocId}),
%%
?line ok =
gen_sctp:send(S1, S1AssocId, 0, <<"2: ",Data/binary>>),
?line case ok(gen_sctp:recv(S2)) of
{Loopback,P1,
[#sctp_sndrcvinfo{
stream=0, ppid=19, context=0, assoc_id=S2AssocId}],
<<"2: ",Data/binary>>} -> ok
end,
?line ok =
gen_sctp:send(S2, S2AssocChange, 1, <<"3: ",Data/binary>>),
?line case ok(gen_sctp:recv(S1)) of
{Loopback,P2,
[#sctp_sndrcvinfo{
stream=1, ppid=0, context=0, assoc_id=S1AssocId}],
<<"3: ",Data/binary>>} -> ok;
{Loopback,P2,[],
#sctp_paddr_change{
addr={Loopback,_}, state=addr_available,
error=0, assoc_id=S1AssocId}} ->
?line case ok(gen_sctp:recv(S1)) of
{Loopback,P2,
[#sctp_sndrcvinfo{
stream=1, ppid=0, context=0,
assoc_id=S1AssocId}],
<<"3: ",Data/binary>>} -> ok
end
end,
?line ok =
gen_sctp:send(
S2,
#sctp_sndrcvinfo{stream=0, ppid=20, assoc_id=S2AssocId},
<<"4: ",Data/binary>>),
?line case ok(gen_sctp:recv(S1)) of
{Loopback,P2,
[#sctp_sndrcvinfo{
stream=0, ppid=20, context=0, assoc_id=S1AssocId}],
<<"4: ",Data/binary>>} -> ok
end,
%%
?line ok =
gen_sctp:close(S1),
?line ok =
gen_sctp:close(S2),
?line receive
Msg ->
test_server:fail({received,Msg})
after 17 -> ok
end,
ok.

getopt(S, Opt) ->
{ok,[{Opt,Val}]} = inet:getopts(S, [Opt]),
Val.

getopt(S, Opt, Param) ->
{ok,[{Opt,Val}]} = inet:getopts(S, [{Opt,Param}]),
Val.

setopt(S, Opt, Val) ->
inet:setopts(S, [{Opt,Val}]).

ok({ok,X}) ->
io:format("OK: ~p~n", [X]),
X.

flush() ->
receive
Msg ->
Expand Down

0 comments on commit 9ea58df

Please sign in to comment.