blob: 15ba8374f701548fbc7ee6ab4580dbaa9682c43b [file] [log] [blame]
Harald Weltec6e466e2011-10-10 14:03:50 +02001% Osmocom adaptor to interface the M3UA core with osmo_sccp
2
3% (C) 2011 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/>.
Harald Weltef8bf0322012-04-16 13:10:47 +020019%
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.
Harald Weltec6e466e2011-10-10 14:03:50 +020033
34-module(ss7_link_m3ua).
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/m3ua.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
45-export([handle_cast/2]).
46
47-record(loop_dat, {
48 m3ua_pid,
49 link
50 }).
51
52start_link(Args) ->
53 gen_server:start_link(?MODULE, Args, [{debug, [trace]}]).
54
55init(L = #sigtran_link{type = m3ua, name = Name, linkset_name = LinksetName,
56 sls = Sls, local = Local, remote = Remote}) ->
57 #sigtran_peer{ip = LocalIp, port = LocalPort} = Local,
58 #sigtran_peer{ip = RemoteIp, port = RemotePort} = Remote,
59 % start the M3UA link to the SG
Harald Welte48c07f02013-09-08 22:22:01 +020060 Opts = [{user_pid, self()},
61 {sctp_remote_ip, RemoteIp}, {sctp_remote_port, RemotePort},
62 {sctp_local_ip, LocalIp}, {sctp_local_port, LocalPort},
Harald Weltec6e466e2011-10-10 14:03:50 +020063 {user_fun, fun m3ua_tx_to_user/2}, {user_args, self()}],
64 {ok, M3uaPid} = m3ua_core:start_link(Opts),
65 % FIXME: register this link with SCCP_SCRC
66 ok = ss7_links:register_link(LinksetName, Sls, Name),
67 {ok, #loop_dat{m3ua_pid = M3uaPid, link = L}}.
68
69% % instantiate SCCP routing instance
70% {ok, ScrcPid} = sccp_scrc:start_link([{mtp_tx_action, {callback_fn, fun scrc_tx_to_mtp/2, M3uaPid}}]),
71% loop(#loop_dat{m3ua_pid = M3uaPid, scrc_pid = ScrcPid}).
72
73
74set_link_state(#sigtran_link{linkset_name = LinksetName, sls = Sls}, State) ->
75 ok = ss7_links:set_link_state(LinksetName, Sls, State).
76
77scrc_tx_to_mtp(Prim, Args) ->
78 M3uaPid = Args,
79 gen_fsm:send_event(M3uaPid, Prim).
80
81% Callback that we pass to the m3ua_core, which it will call when it wants to
82% send a primitive up the stack to SCCP
Harald Welte7dadde82011-10-19 13:40:39 +020083m3ua_tx_to_user(P=#primitive{subsystem = 'MTP'}, Args) ->
84 % send it directly to the 'service' that has bound
85 ss7_links:mtp3_rx(P);
86m3ua_tx_to_user(P=#primitive{subsystem = 'M'}, Args) ->
87 % send management primitives into the m3ua_link process
Harald Weltec6e466e2011-10-10 14:03:50 +020088 UserPid = Args,
Harald Welte7dadde82011-10-19 13:40:39 +020089 gen_server:cast(UserPid, P).
Harald Weltec6e466e2011-10-10 14:03:50 +020090
91handle_cast(P = #primitive{subsystem = 'MTP', gen_name = 'TRANSFER', spec_name = request}, L) ->
92 scrc_tx_to_mtp(P, L#loop_dat.m3ua_pid),
93 {noreply, L};
94% This is what we receive from m3ua_tx_to_user/2
95handle_cast(#primitive{subsystem = 'M', gen_name = 'SCTP_ESTABLISH', spec_name = confirm}, L) ->
96 io:format("~p: SCTP_ESTABLISH.ind -> ASP_UP.req~n", [?MODULE]),
97 gen_fsm:send_event(L#loop_dat.m3ua_pid, osmo_util:make_prim('M','ASP_UP',request)),
98 {noreply, L};
99handle_cast(#primitive{subsystem = 'M', gen_name = 'ASP_UP', spec_name = confirm}, L) ->
100 io:format("~p: ASP_UP.ind -> ASP_ACTIVE.req~n", [?MODULE]),
101 set_link_state(L#loop_dat.link, up),
102 gen_fsm:send_event(L#loop_dat.m3ua_pid, osmo_util:make_prim('M','ASP_ACTIVE',request)),
103 {noreply, L};
104handle_cast(#primitive{subsystem = 'M', gen_name = 'ASP_ACTIVE', spec_name = confirm}, L) ->
105 io:format("~p: ASP_ACTIVE.ind - M3UA now active and ready~n", [?MODULE]),
106 set_link_state(L#loop_dat.link, active),
107 %tx_sccp_udt(L#loop_dat.scrc_pid),
108 {noreply, L};
109handle_cast(#primitive{subsystem = 'M', gen_name = 'ASP_DOWN'}, L) ->
110 io:format("~p: ASP_DOWN.ind~n", [?MODULE]),
111 set_link_state(L#loop_dat.link, down),
112 {noreply, L};
113handle_cast(#primitive{subsystem = 'M', gen_name = 'ASP_INACTIVE'}, L) ->
Harald Weltef0e315d2011-10-11 18:48:42 +0200114 io:format("~p: ASP_INACTIVE.ind~n", [?MODULE]),
115 set_link_state(L#loop_dat.link, up),
Harald Weltec6e466e2011-10-10 14:03:50 +0200116 {noreply, L};
117handle_cast(P, L) ->
118 io:format("~p: Ignoring M3UA prim ~p~n", [?MODULE, P]),
119 {noreply, L}.
120
121terminate(Reason, _S) ->
122 io:format("terminating ~p with reason ~p", [?MODULE, Reason]),
123 ok.
124
125tx_sccp_udt(ScrcPid) ->
126 CallingP = #sccp_addr{ssn = ?SCCP_SSN_MSC, point_code = osmo_util:pointcode2int(itu, {1,2,2})},
127 CalledP = #sccp_addr{ssn = ?SCCP_SSN_HLR, point_code = osmo_util:pointcode2int(itu, {1,1,1})},
128 Data = <<1,2,3,4>>,
129 Opts = [{protocol_class, 0}, {called_party_addr, CalledP},
130 {calling_party_addr, CallingP}, {user_data, Data}],
131 io:format("~p: Sending N-UNITDATA.req to SCRC~n", [?MODULE]),
132 gen_fsm:send_event(ScrcPid, osmo_util:make_prim('N','UNITDATA',request,Opts)).
133