blob: 0bd15986983ab9b1d386705b4564825a606998a7 [file] [log] [blame]
Harald Weltec6e466e2011-10-10 14:03:50 +02001% Osmocom adaptor to interface the IPA 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/>.
19
20-module(ss7_link_ipa_client).
21-author('Harald Welte <laforge@gnumonks.org>').
22-behavior(gen_server).
23
24-include_lib("osmo_ss7/include/osmo_util.hrl").
25%-include_lib("osmo_ss7/include/ipa.hrl").
26-include_lib("osmo_ss7/include/sccp.hrl").
27-include_lib("osmo_ss7/include/osmo_ss7.hrl").
28
29-export([start_link/1, init/1]).
30
31-export([handle_cast/2]).
32
33-record(loop_dat, {
34 ipa_pid,
35 link
36 }).
37
38start_link(Args) ->
39 gen_server:start_link(?MODULE, Args, []).
40
41init(L = #sigtran_link{type = ipa_client, name = Name, linkset_name = LinksetName,
42 sls = Sls, local = Local, remote = Remote}) ->
43 #sigtran_peer{ip = LocalIp, port = LocalPort} = Local,
44 #sigtran_peer{ip = RemoteIp, port = RemotePort} = Remote,
45 % start the IPA link to the SG
46 Opts = [{user_pid, self()}, {sctp_remote_ip, RemoteIp},
47 {sctp_remote_port, RemotePort}, {sctp_local_port, LocalPort},
48 {user_fun, fun ipa_tx_to_user/2}, {user_args, self()}],
49 {ok, IpaPid} = ipa_core:start_link(Opts),
50 % FIXME: register this link with SCCP_SCRC
51 ok = ss7_link:register_link(LinksetName, Sls, Name),
52 {ok, #loop_dat{ipa_pid = IpaPid, link = L}}.
53
54% % instantiate SCCP routing instance
55% {ok, ScrcPid} = sccp_scrc:start_link([{mtp_tx_action, {callback_fn, fun scrc_tx_to_mtp/2, M3uaPid}}]),
56% loop(#loop_dat{ipa_pid = M3uaPid, scrc_pid = ScrcPid}).
57
58
59set_link_state(#sigtran_link{linkset_name = LinksetName, sls = Sls}, State) ->
60 ok = ss7_links:set_link_state(LinksetName, Sls, State).
61
62scrc_tx_to_mtp(Prim, Args) ->
63 M3uaPid = Args,
64 gen_fsm:send_event(M3uaPid, Prim).
65
66% Callback that we pass to the ipa_core, which it will call when it wants to
67% send a primitive up the stack to SCCP
68ipa_tx_to_user(Prim, Args) ->
69 UserPid = Args,
70 gen_server:cast(UserPid, Prim).
71
72% This is what we receive from ipa_tx_to_user/2
73handle_cast(#primitive{subsystem = 'M', gen_name = 'SCTP_ESTABLISH', spec_name = confirm}, L) ->
74 io:format("~p: SCTP_ESTABLISH.ind -> ASP_UP.req~n", [?MODULE]),
75 gen_fsm:send_event(L#loop_dat.ipa_pid, osmo_util:make_prim('M','ASP_UP',request)),
76 {noreply, L};
77handle_cast(#primitive{subsystem = 'M', gen_name = 'ASP_UP', spec_name = confirm}, L) ->
78 io:format("~p: ASP_UP.ind -> ASP_ACTIVE.req~n", [?MODULE]),
Harald Weltedbe1c882011-11-04 21:49:23 +010079 set_link_state(L#loop_dat.link, up),
Harald Weltec6e466e2011-10-10 14:03:50 +020080 gen_fsm:send_event(L#loop_dat.ipa_pid, osmo_util:make_prim('M','ASP_ACTIVE',request)),
81 {noreply, L};
82handle_cast(#primitive{subsystem = 'M', gen_name = 'ASP_ACTIVE', spec_name = confirm}, L) ->
83 io:format("~p: ASP_ACTIVE.ind - M3UA now active and ready~n", [?MODULE]),
Harald Weltedbe1c882011-11-04 21:49:23 +010084 set_link_state(L#loop_dat.link, active),
Harald Weltec6e466e2011-10-10 14:03:50 +020085 %tx_sccp_udt(L#loop_dat.scrc_pid),
86 {noreply, L};
87handle_cast(#primitive{subsystem = 'M', gen_name = 'ASP_DOWN'}, L) ->
88 io:format("~p: ASP_DOWN.ind~n", [?MODULE]),
89 set_link_state(L, down),
90 {noreply, L};
91handle_cast(#primitive{subsystem = 'M', gen_name = 'ASP_INACTIVE'}, L) ->
92 io:format("~p: ASP_DOWN.ind~n", [?MODULE]),
93 set_link_state(L, inactive),
94 {noreply, L};
95handle_cast(P, L) ->
96 io:format("~p: Ignoring M3UA prim ~p~n", [?MODULE, P]),
97 {noreply, L}.
98
99
100tx_sccp_udt(ScrcPid) ->
101 CallingP = #sccp_addr{ssn = ?SCCP_SSN_MSC, point_code = osmo_util:pointcode2int(itu, {1,2,2})},
102 CalledP = #sccp_addr{ssn = ?SCCP_SSN_HLR, point_code = osmo_util:pointcode2int(itu, {1,1,1})},
103 Data = <<1,2,3,4>>,
104 Opts = [{protocol_class, 0}, {called_party_addr, CalledP},
105 {calling_party_addr, CallingP}, {user_data, Data}],
106 io:format("~p: Sending N-UNITDATA.req to SCRC~n", [?MODULE]),
107 gen_fsm:send_event(ScrcPid, osmo_util:make_prim('N','UNITDATA',request,Opts)).
108