make use of local IP address of #sigtran_peer actually work

This commit is contained in:
Harald Welte 2013-09-08 22:22:01 +02:00
parent e126068ec8
commit 48c07f08b1
3 changed files with 23 additions and 18 deletions

View File

@ -58,7 +58,6 @@
user_args,
sctp_remote_ip,
sctp_remote_port,
sctp_local_port,
sctp_sock,
sctp_assoc_id
}).
@ -80,22 +79,25 @@ reconnect_sctp(L = #m3ua_state{sctp_remote_ip = Ip, sctp_remote_port = Port, sct
reconnect_sctp(L)
end.
build_openopt({sctp_local_port, Port}) ->
{port, Port};
build_openopt({sctp_local_ip, undefined}) ->
[];
build_openopt({sctp_local_ip, Ip}) ->
{ip, Ip};
build_openopt(_) ->
[].
build_openopts(PropList) ->
[{active, once}, {reuseaddr, true}] ++
lists:flatten(lists:map(fun build_openopt/1, PropList)).
init(InitOpts) ->
OpenOptsBase = [{active, once}, {reuseaddr, true}],
LocalPort = proplists:get_value(sctp_local_port, InitOpts),
case LocalPort of
undefined ->
OpenOpts = OpenOptsBase;
_ ->
OpenOpts = OpenOptsBase ++ [{port, LocalPort}]
end,
{ok, SctpSock} = gen_sctp:open(OpenOpts),
{ok, SctpSock} = gen_sctp:open(build_openopts(InitOpts)),
LoopDat = #m3ua_state{role = asp, sctp_sock = SctpSock,
user_fun = proplists:get_value(user_fun, InitOpts),
user_args = proplists:get_value(user_args, InitOpts),
sctp_remote_ip = proplists:get_value(sctp_remote_ip, InitOpts),
sctp_remote_port = proplists:get_value(sctp_remote_port, InitOpts),
sctp_local_port = LocalPort},
sctp_remote_port = proplists:get_value(sctp_remote_port, InitOpts)},
LoopDat2 = reconnect_sctp(LoopDat),
{ok, asp_down, LoopDat2}.

View File

@ -86,19 +86,21 @@ reconnect_sctp(L = #sctp_state{sctp_remote_ip = Ip, sctp_remote_port = Port, sct
build_openopt({sctp_local_port, Port}) ->
{port, Port};
build_openopt({sctp_local_ip, undefined}) ->
[];
build_openopt({sctp_local_ip, Ip}) ->
{ip, Ip};
build_openopt(_) ->
[].
build_openopts(PropList) ->
[{active, once}, {reuseaddr, true}] ++
lists:flatten(lists:map(fun build_openopt/1, PropList)).
init(InitOpts) ->
OpenOptsBase = [{active, once}, {reuseaddr, true}],
Module = proplists:get_value(module, InitOpts),
ModuleArgs = proplists:get_value(module_args, InitOpts),
Role = proplists:get_value(sctp_role, InitOpts),
OpenOpts = OpenOptsBase ++ lists:map(fun build_openopt/1, InitOpts),
io:format("sctp_open(~p)~n", [OpenOpts]),
{ok, SctpSock} = gen_sctp:open(OpenOpts),
{ok, SctpSock} = gen_sctp:open(build_openopts(InitOpts)),
case Module:init(ModuleArgs) of
{ok, ExtState} ->
LoopDat = #sctp_state{role = Role, sctp_sock = SctpSock,

View File

@ -57,8 +57,9 @@ init(L = #sigtran_link{type = m3ua, name = Name, linkset_name = LinksetName,
#sigtran_peer{ip = LocalIp, port = LocalPort} = Local,
#sigtran_peer{ip = RemoteIp, port = RemotePort} = Remote,
% start the M3UA link to the SG
Opts = [{user_pid, self()}, {sctp_remote_ip, RemoteIp},
{sctp_remote_port, RemotePort}, {sctp_local_port, LocalPort},
Opts = [{user_pid, self()},
{sctp_remote_ip, RemoteIp}, {sctp_remote_port, RemotePort},
{sctp_local_ip, LocalIp}, {sctp_local_port, LocalPort},
{user_fun, fun m3ua_tx_to_user/2}, {user_args, self()}],
{ok, M3uaPid} = m3ua_core:start_link(Opts),
% FIXME: register this link with SCCP_SCRC