osmo_smsc/src/osmo_gsup_if.erl

186 lines
6.9 KiB
Erlang

% Osmocom GSUP (Generic Subscriber Update Protocol) interface.
% Simple, blocking / synchronous GSUP client (SMSC -> OsmoHLR).
%
% (C) 2019 by Harald Welte <laforge@gnumonks.org>
%
% All Rights Reserved
%
% This program is free software; you can redistribute it and/or modify
% it under the terms of the GNU Affero General Public License as
% published by the Free Software Foundation; either version 3 of the
% License, or (at your option) any later version.
%
% This program is distributed in the hope that it will be useful,
% but WITHOUT ANY WARRANTY; without even the implied warranty of
% MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
% GNU General Public License for more details.
%
% You should have received a copy of the GNU Affero General Public License
% along with this program. If not, see <http://www.gnu.org/licenses/>.
%
% Additional Permission under GNU AGPL version 3 section 7:
%
% If you modify this Program, or any covered work, by linking or
% combining it with runtime libraries of Erlang/OTP as released by
% Ericsson on http://www.erlang.org (or a modified version of these
% libraries), containing parts covered by the terms of the Erlang Public
% License (http://www.erlang.org/EPLICENSE), the licensors of this
% Program grant you additional permission to convey the resulting work
% without the need to license the runtime libraries of Erlang/OTP under
% the GNU Affero General Public License. Corresponding Source for a
% non-source form of such a combination shall include the source code
% for the parts of the runtime libraries of Erlang/OTP used as well as
% that of the covered work.
-module(osmo_gsup_if).
-behaviour(gen_server).
-include_lib("osmo_gsup/include/gsup_protocol.hrl").
-define(IPAC_PROTO_EXT_GSUP, {osmo, 5}).
-record(smr_data, {imsi, msg_ref, orig_addr, dest_addr, tpdu}).
-record(gsupc_state, {
core,
socket,
ipa_pid
}).
-export([start_link/2]).
-export([init/1, handle_call/3, handle_cast/2, handle_info/2]).
-export([code_change/3, terminate/2]).
%% ------------------------------------------------------------------
%% our exported API
%% ------------------------------------------------------------------
start_link(Core, HLRAddr) ->
gen_server:start_link(?MODULE, [Core, HLRAddr], [{debug, [trace]}]).
%% ------------------------------------------------------------------
%% gen_server Function Definitions
%% ------------------------------------------------------------------
init([Core, {Address, Port, Options}]) ->
ipa_proto:init(),
% register the GSUP codec with the IPA core; ignore result as we mgiht be doing this multiple times
ipa_proto:register_codec(?IPAC_PROTO_EXT_GSUP, fun gsup_protocol:encode/1, fun gsup_protocol:decode/1),
{ok, {Socket, IpaPid}} = ipa_proto:connect(Address, Port, Options),
true = ipa_proto:register_stream(Socket, ?IPAC_PROTO_EXT_GSUP, {process_id, self()}),
ipa_proto:unblock(Socket),
{ok, #gsupc_state{core = Core, socket = Socket, ipa_pid = IpaPid}}.
-define(IPA_GSUP_STREAM_ID, {osmo, 16#05}).
-define(GSUP_MSG_CLS_SM, 16#02).
gen_sm_response(GSUPMsg, MsgType) ->
#{message_class => ?GSUP_MSG_CLS_SM,
message_type => MsgType,
imsi => maps:get(imsi, GSUPMsg),
sm_rp_mr => maps:get(sm_rp_mr, GSUPMsg),
source_name => << "EUSE-OsmoSMSC-00-00-00-00-00-00", 0 >>,
destination_name => maps:get(source_name, GSUPMsg)}.
% IPA/GSUP messages from OsmoHLR
handle_cast({ipa, ?IPA_GSUP_STREAM_ID, GSUPMsg}, State) ->
% Obtain mandatory IEs
#{imsi := IMSI, sm_rp_mr := MR} = GSUPMsg,
% Parse depending on a message type
case GSUPMsg of
% MO RP-DATA / RP-SMMA
#{message_type := mo_forward_sm_req, sm_rp_da := DA, sm_rp_oa := OA, sm_rp_ui := TPDU} ->
io:format("(IMSI:~p, MR:~p) Rx MT-forwardSM Request~n", [IMSI, MR]),
gen_server:cast(State#gsupc_state.core,
{smsc_ev_mo_fwd_sm_req, IMSI, MR, DA, OA, TPDU});
#{message_type := ready_for_sm_req} ->
Response = gen_sm_response(GSUPMsg, ready_for_sm_res),
ipa_proto:send(State#gsupc_state.socket, ?IPA_GSUP_STREAM_ID, Response);
% MT RP-ACK
#{message_type := mt_forward_sm_res} ->
io:format("(IMSI:~p, MR:~p) Rx MT-forwardSM Result~n", [IMSI, MR]),
gen_server:cast(State#gsupc_state.core,
{smsc_ev_mt_fwd_sm_ack, IMSI, MR});
% MT RP-ERROR
#{message_type := mt_forward_sm_err, sm_rp_cause := Cause} ->
io:format("(IMSI:~p, MR:~p) Rx MT-forwardSM Error: cause=~p~n", [IMSI, MR, Cause]),
gen_server:cast(State#gsupc_state.core,
{smsc_ev_mt_fwd_sm_err, IMSI, MR, Cause});
_ ->
error_logger:error_report(["unknown GSUP message",
{module, ?MODULE},
{message, GSUPMsg},
{state, State}])
end,
{noreply, State};
% IPA/GSUP messages from the SMSC
handle_cast({smsc_ev_mt_fwd_sm_req, Data}, State) ->
#smr_data{imsi = IMSI, msg_ref = MR,
orig_addr = OA, dest_addr = DA,
tpdu = TPDU} = Data,
ipa_proto:send(State#gsupc_state.socket, ?IPA_GSUP_STREAM_ID,
#{message_class => ?GSUP_MSG_CLS_SM, message_type => mt_forward_sm_req,
imsi => IMSI, sm_rp_mr => MR,
sm_rp_da => DA, sm_rp_oa => OA,
sm_rp_ui => TPDU,
% FIXME: this must be configurable
source_name => << "EUSE-OsmoSMSC-00-00-00-00-00-00", 0 >>,
destination_name => << "MSC-00-00-00-00-00-00", 0 >> }),
{noreply, State};
handle_cast({smr_ev_fwd_mo_sm_ack, IMSI, MR}, State) ->
ipa_proto:send(State#gsupc_state.socket, ?IPA_GSUP_STREAM_ID,
#{message_class => ?GSUP_MSG_CLS_SM, message_type => mo_forward_sm_res,
imsi => IMSI, sm_rp_mr => MR,
% FIXME: this must be configurable
source_name => << "EUSE-OsmoSMSC-00-00-00-00-00-00", 0 >>,
destination_name => << "MSC-00-00-00-00-00-00", 0 >> }),
{noreply, State};
handle_cast({smr_ev_fwd_mo_sm_err, IMSI, MR, Cause}, State) ->
ipa_proto:send(State#gsupc_state.socket, ?IPA_GSUP_STREAM_ID,
#{message_class => ?GSUP_MSG_CLS_SM, message_type => mo_forward_sm_err,
imsi => IMSI, sm_rp_mr => MR, sm_rp_cause => Cause,
% FIXME: this must be configurable
source_name => << "EUSE-OsmoSMSC-00-00-00-00-00-00", 0 >>,
destination_name => << "MSC-00-00-00-00-00-00", 0 >> }),
{noreply, State};
% All unsupported IPA messages
handle_cast({ipa, StreamID, GSUPMsg}, State) ->
error_logger:error_report(["unknown IPA message",
{module, ?MODULE},
{stream_id, StreamID},
{message, GSUPMsg},
{state, State}]),
{noreply, State};
handle_cast(Info, State) ->
error_logger:error_report(["unknown gen_server:cast()",
{module, ?MODULE},
{info, Info},
{state, State}]),
{noreply, State}.
handle_call(Message, _From, State) ->
error_logger:error_report(["unknown gen_server:call()",
{module, ?MODULE},
{message, Message},
{state, State}]),
{reply, unknown_msg, State}.
handle_info(Info, State) ->
error_logger:error_report(["unknown handle_info",
{module, ?MODULE},
{info, Info},
{state, State}]),
{noreply, State}.
terminate(Reason, _State) ->
io:format("Terminating ~p with reason ~p~n", [?MODULE, Reason]).
code_change(_OldVsn, State, _Extra) ->
{ok, State}.