blob: 967bf99addebdaf3c4d27b793e0a07236a9fab61 [file] [log] [blame]
Harald Welte51f47c02019-08-14 13:30:49 +02001% simple, blocking/synchronous GSUP client
2
3% (C) 2019 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(gsup_client).
35
36-behaviour(gen_server).
37
38-include_lib("osmo_gsup/include/gsup_protocol.hrl").
Alexander Couzensee090f42021-12-30 20:28:54 +010039-include_lib("osmo_ss7/include/ipa.hrl").
Harald Welte51f47c02019-08-14 13:30:49 +020040
41-define(IPAC_PROTO_EXT_GSUP, {osmo, 5}).
Alexander Couzensbe945302023-09-01 15:23:07 +020042-define(GSUP_TIMEOUT_MS, 5000).
Harald Welte51f47c02019-08-14 13:30:49 +020043
44-record(gsupc_state, {
Alexander Couzensbe945302023-09-01 15:23:07 +020045 address,
46 port,
47 ccmoptions,
48 socket,
Harald Welte51f47c02019-08-14 13:30:49 +020049 ipa_pid
50 }).
51
52-export([start_link/3]).
53
54-export([init/1, handle_call/3, handle_cast/2, handle_info/2]).
55-export([code_change/3, terminate/2]).
56
57%% ------------------------------------------------------------------
58%% our exported API
59%% ------------------------------------------------------------------
60
Alexander Couzensbe945302023-09-01 15:23:07 +020061start_link(ServerAddr, ServerPort, GsupName) ->
62 gen_server:start_link(?MODULE, [ServerAddr, ServerPort, GsupName], [{debug, [trace]}]).
Harald Welte51f47c02019-08-14 13:30:49 +020063
64%% ------------------------------------------------------------------
65%% gen_server Function Definitions
66%% ------------------------------------------------------------------
67
Alexander Couzensbe945302023-09-01 15:23:07 +020068init([Address, Port, GsupName]) ->
Harald Welte51f47c02019-08-14 13:30:49 +020069 ipa_proto:init(),
Pau Espin Pedrol89ac8712023-08-24 17:12:00 +020070 % register the GSUP codec with the IPA core; ignore result as we might be doing this multiple times
Harald Welte51f47c02019-08-14 13:30:49 +020071 ipa_proto:register_codec(?IPAC_PROTO_EXT_GSUP, fun gsup_protocol:encode/1, fun gsup_protocol:decode/1),
Harald Weltee795af32019-08-20 20:05:36 +020072 lager:info("Connecting to GSUP HLR on IP ~s port ~p~n", [Address, Port]),
Alexander Couzensbe945302023-09-01 15:23:07 +020073 CcmOptions = #ipa_ccm_options{
74 serial_number=GsupName,
75 unit_id="0/0/0",
76 mac_address="00:00:00:00:00:00",
77 location="00:00:00:00:00:00",
78 unit_type="00:00:00:00:00:00",
79 equipment_version="00:00:00:00:00:00",
80 sw_version="00:00:00:00:00:00",
81 unit_name=GsupName
82 },
83 State = #gsupc_state{address = Address, port = Port, ccmoptions = CcmOptions, socket = [], ipa_pid = []},
84 case connect(State) of
85 {ok, State2} -> {ok, State2};
86 {error, _, State2} -> {ok, State2, ?GSUP_TIMEOUT_MS}
87 end.
88
89connect(State) ->
90 #gsupc_state{address = Address, port = Port, ccmoptions = Options} = State,
91 case ipa_proto:connect(Address, Port, []) of
Harald Weltee795af32019-08-20 20:05:36 +020092 {ok, {Socket, IpaPid}} ->
Alexander Couzensbe945302023-09-01 15:23:07 +020093 ipa_proto:set_ccm_options(Socket, Options),
Harald Weltee795af32019-08-20 20:05:36 +020094 lager:info("connected!~n", []),
95 true = ipa_proto:register_stream(Socket, ?IPAC_PROTO_EXT_GSUP, {process_id, self()}),
96 ipa_proto:unblock(Socket),
Alexander Couzensbe945302023-09-01 15:23:07 +020097 {ok, State#gsupc_state{socket=Socket, ipa_pid=IpaPid}};
98 {error, Error} ->
99 lager:info("Failed to GSUP HLR on IP ~s port ~p ~p~n", [Address, Port, Error]),
100 {error, Error, State}
Harald Weltee795af32019-08-20 20:05:36 +0200101 end.
Harald Welte51f47c02019-08-14 13:30:49 +0200102
Harald Welte51f47c02019-08-14 13:30:49 +0200103% send a given GSUP message and synchronously wait for message type ExpRes or ExpErr
104handle_call({transceive_gsup, GsupMsgTx, ExpRes, ExpErr}, _From, State) ->
105 Socket = State#gsupc_state.socket,
106 {ok, Imsi} = maps:find(imsi, GsupMsgTx),
107 ipa_proto:send(Socket, ?IPAC_PROTO_EXT_GSUP, GsupMsgTx),
108 % selective receive for only those GSUP responses we expect
109 receive
110 {ipa, Socket, ?IPAC_PROTO_EXT_GSUP, GsupMsgRx = #{message_type := ExpRes, imsi := Imsi}} ->
111 {reply, GsupMsgRx, State};
Harald Welte51f47c02019-08-14 13:30:49 +0200112 {ipa, Socket, ?IPAC_PROTO_EXT_GSUP, GsupMsgRx = #{message_type := ExpErr, imsi := Imsi}} ->
113 {reply, GsupMsgRx, State}
Alexander Couzensbe945302023-09-01 15:23:07 +0200114 after ?GSUP_TIMEOUT_MS ->
Harald Welte51f47c02019-08-14 13:30:49 +0200115 {reply, timeout, State}
116 end.
117
118handle_cast(Info, S) ->
119 error_logger:error_report(["unknown handle_cast", {module, ?MODULE}, {info, Info}, {state, S}]),
120 {noreply, S}.
121
Harald Weltee795af32019-08-20 20:05:36 +0200122handle_info({ipa_closed, _}, S) ->
Alexander Couzensbe945302023-09-01 15:23:07 +0200123 lager:error("GSUP connection has been closed, Reconnecting in 5sec."),
124 {noreply, S, ?GSUP_TIMEOUT_MS};
125handle_info(timeout, S) ->
126 case connect(S) of
127 {ok, State} -> {noreply, State};
128 {error, _, State} -> {noreply, State, ?GSUP_TIMEOUT_MS}
129 end;
130
Harald Welte51f47c02019-08-14 13:30:49 +0200131handle_info(Info, S) ->
132 error_logger:error_report(["unknown handle_info", {module, ?MODULE}, {info, Info}, {state, S}]),
133 {noreply, S}.
134
135terminate(Reason, _S) ->
136 lager:info("terminating ~p with reason ~p~n", [?MODULE, Reason]).
137
138code_change(_OldVsn, State, _Extra) ->
139 {ok, State}.