blob: 7d039783080c36ec75fef53d8fbe6f480d444925 [file] [log] [blame]
Harald Welte5c9f3b52013-07-26 22:40:25 +08001% Osmocom adaptor to interface the M2UA core with osmo_sccp
2
3% (C) 2013 by Harald Welte <laforge@gnumonks.org>
4%
5% All Rights Reserved
6%
7% This program is free software; you can redistribute it and/or modify
8% it under the terms of the GNU Affero General Public License as
9% published by the Free Software Foundation; either version 3 of the
10% License, or (at your option) any later version.
11%
12% This program is distributed in the hope that it will be useful,
13% but WITHOUT ANY WARRANTY; without even the implied warranty of
14% MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
15% GNU General Public License for more details.
16%
17% You should have received a copy of the GNU Affero General Public License
18% along with this program. If not, see <http://www.gnu.org/licenses/>.
19%
20% Additional Permission under GNU AGPL version 3 section 7:
21%
22% If you modify this Program, or any covered work, by linking or
23% combining it with runtime libraries of Erlang/OTP as released by
24% Ericsson on http://www.erlang.org (or a modified version of these
25% libraries), containing parts covered by the terms of the Erlang Public
26% License (http://www.erlang.org/EPLICENSE), the licensors of this
27% Program grant you additional permission to convey the resulting work
28% without the need to license the runtime libraries of Erlang/OTP under
29% the GNU Affero General Public License. Corresponding Source for a
30% non-source form of such a combination shall include the source code
31% for the parts of the runtime libraries of Erlang/OTP used as well as
32% that of the covered work.
33
34-module(ss7_link_m2ua).
35-author('Harald Welte <laforge@gnumonks.org>').
36-behavior(gen_server).
37
38-include_lib("osmo_ss7/include/osmo_util.hrl").
39-include_lib("osmo_ss7/include/m2ua.hrl").
40-include_lib("osmo_ss7/include/sccp.hrl").
41-include_lib("osmo_ss7/include/osmo_ss7.hrl").
42
43-export([start_link/1, init/1]).
44
Harald Welte0b928662013-07-27 15:51:56 +080045-export([handle_info/2, terminate/2]).
Harald Welte5c9f3b52013-07-26 22:40:25 +080046
47-record(loop_dat, {
48 m2ua_pid,
49 link
50 }).
51
Harald Welte0d8af6b2013-07-27 15:02:17 +080052start_link(Args = #sigtran_link{name=LinkName}) ->
53 Name = list_to_atom("ss7_link_m2ua_" ++ LinkName),
54 gen_server:start_link({local, Name}, ?MODULE, Args, [{debug, [trace]}]).
Harald Welte5c9f3b52013-07-26 22:40:25 +080055
56init(L = #sigtran_link{type = m2ua, name = Name, linkset_name = LinksetName,
Harald Welte0d8af6b2013-07-27 15:02:17 +080057 sls = Sls, local = Local, remote = Remote, role = Role}) ->
Harald Welte5c9f3b52013-07-26 22:40:25 +080058 #sigtran_peer{ip = LocalIp, port = LocalPort} = Local,
59 #sigtran_peer{ip = RemoteIp, port = RemotePort} = Remote,
60 % start the M2UA link to the SG
Harald Welte0d8af6b2013-07-27 15:02:17 +080061 Opts = [{module, sctp_m2ua}, {module_args, [Role]},
62 {sctp_role, ss7_links:role2sctp_role(Role)},
Harald Welte5c9f3b52013-07-26 22:40:25 +080063 {user_pid, self()}, {sctp_remote_ip, RemoteIp},
64 {sctp_remote_port, RemotePort}, {sctp_local_port, LocalPort},
Harald Welte0b928662013-07-27 15:51:56 +080065 {sctp_local_ip, LocalIp}],
Harald Welte5c9f3b52013-07-26 22:40:25 +080066 {ok, M2uaPid} = sctp_core:start_link(Opts),
67 % FIXME: register this link with SCCP_SCRC
68 ok = ss7_links:register_link(LinksetName, Sls, Name),
69 {ok, #loop_dat{m2ua_pid = M2uaPid, link = L}}.
70
71% % instantiate SCCP routing instance
72% {ok, ScrcPid} = sccp_scrc:start_link([{mtp_tx_action, {callback_fn, fun scrc_tx_to_mtp/2, M3uaPid}}]),
73% loop(#loop_dat{m2ua_pid = M3uaPid, scrc_pid = ScrcPid}).
74
75
76set_link_state(#sigtran_link{linkset_name = LinksetName, sls = Sls}, State) ->
77 ok = ss7_links:set_link_state(LinksetName, Sls, State).
78
79scrc_tx_to_mtp(Prim, Args) ->
80 M2uaPid = Args,
81 gen_fsm:send_event(M2uaPid, Prim).
82
Harald Welte0b928662013-07-27 15:51:56 +080083handle_info(P = #primitive{subsystem = 'MTP', gen_name = 'TRANSFER', spec_name = request}, L) ->
Harald Welte5c9f3b52013-07-26 22:40:25 +080084 scrc_tx_to_mtp(P, L#loop_dat.m2ua_pid),
85 {noreply, L};
Harald Welte0d8af6b2013-07-27 15:02:17 +080086
Harald Welte0b928662013-07-27 15:51:56 +080087handle_info(#primitive{subsystem = 'M', gen_name = 'ASP_UP'}, L) ->
Harald Welte5c9f3b52013-07-26 22:40:25 +080088 set_link_state(L#loop_dat.link, up),
Harald Welte5c9f3b52013-07-26 22:40:25 +080089 {noreply, L};
Harald Welte0b928662013-07-27 15:51:56 +080090handle_info(#primitive{subsystem = 'M', gen_name = 'ASP_ACTIVE'}, L) ->
Harald Welte5c9f3b52013-07-26 22:40:25 +080091 set_link_state(L#loop_dat.link, active),
Harald Welte5c9f3b52013-07-26 22:40:25 +080092 {noreply, L};
Harald Welte0b928662013-07-27 15:51:56 +080093handle_info(#primitive{subsystem = 'M', gen_name = 'ASP_DOWN'}, L) ->
Harald Welte5c9f3b52013-07-26 22:40:25 +080094 set_link_state(L#loop_dat.link, down),
95 {noreply, L};
Harald Welte0b928662013-07-27 15:51:56 +080096handle_info(#primitive{subsystem = 'M', gen_name = 'ASP_INACTIVE'}, L) ->
Harald Welte5c9f3b52013-07-26 22:40:25 +080097 set_link_state(L#loop_dat.link, up),
98 {noreply, L};
Harald Welte0b928662013-07-27 15:51:56 +080099
100handle_info(P, L) ->
101 io:format("~p: Ignoring M2UA cast ~p~n", [?MODULE, P]),
Harald Welte5c9f3b52013-07-26 22:40:25 +0800102 {noreply, L}.
103
104terminate(Reason, _S) ->
105 io:format("terminating ~p with reason ~p", [?MODULE, Reason]),
106 ok.
107
108tx_sccp_udt(ScrcPid) ->
109 CallingP = #sccp_addr{ssn = ?SCCP_SSN_MSC, point_code = osmo_util:pointcode2int(itu, {1,2,2})},
110 CalledP = #sccp_addr{ssn = ?SCCP_SSN_HLR, point_code = osmo_util:pointcode2int(itu, {1,1,1})},
111 Data = <<1,2,3,4>>,
112 Opts = [{protocol_class, 0}, {called_party_addr, CalledP},
113 {calling_party_addr, CallingP}, {user_data, Data}],
114 io:format("~p: Sending N-UNITDATA.req to SCRC~n", [?MODULE]),
115 gen_fsm:send_event(ScrcPid, osmo_util:make_prim('N','UNITDATA',request,Opts)).
116