osmo_dia2gsup/src/osmo_cx2gsup_cb.erl

218 lines
9.1 KiB
Erlang

-module(osmo_cx2gsup_cb).
-include_lib("diameter/include/diameter.hrl").
-include_lib("diameter/include/diameter_gen_base_rfc6733.hrl").
-include_lib("diameter_3gpp_ts29_229_cx.hrl").
-include_lib("osmo_gsup/include/gsup_protocol.hrl").
-define(DIA_VENDOR_3GPP, 10415).
%% diameter callbacks
-export([peer_up/3, peer_down/3, pick_peer/4, prepare_request/3, prepare_retransmit/3,
handle_answer/4, handle_error/4, handle_request/3]).
-define(UNEXPECTED, erlang:error({unexpected, ?MODULE, ?LINE})).
peer_up(_SvcName, {PeerRef, Caps}, State) ->
lager:info("Peer up ~p - ~p~n", [PeerRef, lager:pr(Caps, ?MODULE)]),
State.
peer_down(_SvcName, {PeerRef, Caps}, State) ->
lager:info("Peer down ~p - ~p~n", [PeerRef, lager:pr(Caps, ?MODULE)]),
State.
pick_peer(_, _, _SvcName, _State) ->
?UNEXPECTED.
prepare_request(_, _SvcName, _Peer) ->
?UNEXPECTED.
prepare_retransmit(_Packet, _SvcName, _Peer) ->
?UNEXPECTED.
handle_answer(_Packet, _Request, _SvcName, _Peer) ->
?UNEXPECTED.
handle_error(_Reason, _Request, _SvcName, _Peer) ->
lager:error("Request error: ~p~n", [_Reason]),
?UNEXPECTED.
% transient (only in Experimental-Result-Code)
-define(DIAMETER_AUTHENTICATION_DATA_UNAVAILABLE, 4181).
-define(DIAMETER_ERROR_CAMEL_SUBSCRIPTION_PRESENT, 4182).
% permanent (only in Experimental-Result-Code)
-define(DIAMETER_ERROR_USER_UNKNOWN, 5001).
-define(DIAMETER_AUTHORIZATION_REJECTED, 5003).
-define(DIAMETER_ERROR_ROAMING_NOT_ALLOWED, 5004).
-define(DIAMETER_MISSING_AVP, 5005).
-define(DIAMETER_UNABLE_TO_COMPLY, 5012).
-define(DIAMETER_ERROR_UNKNOWN_EPS_SUBSCRIPTION, 5420).
-define(DIAMETER_ERROR_RAT_NOT_ALLOWED, 5421).
-define(DIAMETER_ERROR_EQUIPMENT_UNKNOWN, 5422).
-define(DIAMETER_ERROR_UNKOWN_SERVING_NODE, 5423).
% 10.5.5.14
-define(GMM_CAUSE_IMSI_UNKNOWN, 16#02).
-define(GMM_CAUSE_ILLEGAL_MS, 16#03).
-define(GMM_CAUSE_GPRS_NOTALLOWED, 16#07).
-define(GMM_CAUSE_PLMN_NOTALLOWED, 16#0b).
-define(GMM_CAUSE_LA_NOTALLOWED, 16#0c).
-define(GMM_CAUSE_ROAMING_NOTALLOWED, 16#0d).
-define(GMM_CAUSE_NO_SUIT_CELL_IN_LA, 16#0f).
-define(GMM_CAUSE_NET_FAIL, 16#11).
-define(GMM_CAUSE_CONGESTION, 16#16).
-define(GMM_CAUSE_GSM_AUTH_UNACCEPT, 16#17).
-define(GMM_CAUSE_INV_MAND_INFO, 16#60).
-define(GMM_CAUSE_PROTO_ERR_UNSPEC, 16#6f).
-define(EXP_RES(Exp), #'Experimental-Result'{'Vendor-Id'=?DIA_VENDOR_3GPP, 'Experimental-Result-Code'=Exp}).
%% see 29.272 Annex A/B
-type empty_or_intl() :: [] | [integer()].
-spec gsup_cause2dia(integer()) -> {empty_or_intl(), empty_or_intl()}.
gsup_cause2dia(?GMM_CAUSE_IMSI_UNKNOWN) -> {[], [?EXP_RES(?DIAMETER_ERROR_USER_UNKNOWN)]};
gsup_cause2dia(?GMM_CAUSE_ILLEGAL_MS) -> {[], [?EXP_RES(?DIAMETER_ERROR_USER_UNKNOWN)]};
gsup_cause2dia(?GMM_CAUSE_PLMN_NOTALLOWED) -> {[], [?EXP_RES(?DIAMETER_ERROR_ROAMING_NOT_ALLOWED)]};
gsup_cause2dia(?GMM_CAUSE_GPRS_NOTALLOWED) -> {[], [?EXP_RES(?DIAMETER_ERROR_UNKNOWN_EPS_SUBSCRIPTION)]};
gsup_cause2dia(?GMM_CAUSE_LA_NOTALLOWED) -> {[?DIAMETER_AUTHORIZATION_REJECTED], []};
gsup_cause2dia(?GMM_CAUSE_ROAMING_NOTALLOWED) -> {[], [?EXP_RES(?DIAMETER_ERROR_ROAMING_NOT_ALLOWED)]};
gsup_cause2dia(?GMM_CAUSE_NO_SUIT_CELL_IN_LA) -> {[], [?EXP_RES(?DIAMETER_ERROR_UNKNOWN_EPS_SUBSCRIPTION)]};
gsup_cause2dia(?GMM_CAUSE_NET_FAIL) -> {[?DIAMETER_UNABLE_TO_COMPLY], []};
gsup_cause2dia(?GMM_CAUSE_CONGESTION) -> {[?DIAMETER_UNABLE_TO_COMPLY], []};
gsup_cause2dia(?GMM_CAUSE_INV_MAND_INFO) -> {[?DIAMETER_MISSING_AVP], []};
gsup_cause2dia(?GMM_CAUSE_PROTO_ERR_UNSPEC) -> {[?DIAMETER_UNABLE_TO_COMPLY], []};
gsup_cause2dia(_) -> {[?DIAMETER_UNABLE_TO_COMPLY], []}.
% get the value for a tiven key in Map1. If not found, try same key in Map2. If not found, return Default
-spec twomap_get(atom(), map(), map(), any()) -> any().
twomap_get(Key, Map1, Map2, Default) ->
maps:get(Key, Map1, maps:get(Key, Map2, Default)).
dia_sip2gsup(#'SIP-Auth-Data-Item'{'SIP-Authenticate' = [Authenticate], 'SIP-Authorization' = [Authorization],
'Confidentiality-Key' = [CKey], 'Integrity-Key' = [IKey]}) ->
#{rand => list_to_binary(lists:sublist(Authenticate, 1, 16)),
autn=> list_to_binary(lists:sublist(Authenticate, 17, 16)),
res=> list_to_binary(Authorization),
ik=> list_to_binary(IKey),
ck=> list_to_binary(CKey)}.
-spec gsup_tuple2dia_sip('GSUPAuthTuple'(), integer()) -> #'E-UTRAN-Vector'{}.
gsup_tuple2dia_sip(#{autn:=Autn, ck:=Ck, ik:=Ik, rand:=Rand, res:=Res}, Idx) ->
#'SIP-Auth-Data-Item'{
'SIP-Item-Number' = Idx,
'Confidentiality-Key' = Ck,
'Integrity-Key' = Ik,
'SIP-Authenticate' = lists:merge(Rand, Autn),
'SIP-Authorization' = Res
}.
-spec gsup_tuples2dia_sip(['GSUPAuthTuple'()]) -> [#'E-UTRAN-Vector'{}].
gsup_tuples2dia_sip(List) -> gsup_tuples2dia_sip(List, [], 1).
gsup_tuples2dia_sip([], Out, _Idx) -> Out;
gsup_tuples2dia_sip([Head|Tail], Out, Ctr) ->
Dia = gsup_tuple2dia_sip(Head, Ctr),
gsup_tuples2dia_sip(Tail, [Dia|Out], Ctr+1).
-type int_or_false() :: false | integer().
-spec gsup_tuples2dia(['GSUPAuthTuple'()], int_or_false()) -> #'Authentication-Info'{}.
gsup_tuples2dia(Tuples, NumEutran) ->
case NumEutran of
false -> EutranVecs = [];
0 -> EutranVecs = [];
_ -> EutranVecs = gsup_tuples2dia_sip(lists:sublist(Tuples, NumEutran))
end,
[EutranVecs].
-type binary_or_false() :: false | binary().
-spec req_resynchronization_info([tuple()]) -> binary_or_false().
req_resynchronization_info(#'SIP-Auth-Data-Item'{'SIP-Authorization'=[]}) ->
false;
req_resynchronization_info(#'SIP-Auth-Data-Item'{'SIP-Authorization'=[Auth]}) ->
list_to_binary(Auth);
req_resynchronization_info(_) ->
false.
% Cx
handle_request(#diameter_packet{msg = Req, errors = []}, _SvcName, {_, Caps}) when is_record(Req, 'UAR') ->
% extract relevant fields from DIAMETER ULR
#diameter_caps{origin_host = {OH,_}, origin_realm = {OR,_}} = Caps,
#'UAR'{'Session-Id' = SessionId,
'UAR-Flags' = UarFlags,
'User-Name' = UserName} = Req,
ServerName = "sip:scscf.core.osmocom.org:6060",
Resp = #'UAA'{'Session-Id'= SessionId, 'Auth-Session-State'=1,
'Origin-Host'=OH, 'Origin-Realm'=OR,
'Experimental-Result'=2001,
'Server-Name'=ServerName},
lager:info("UAA Resp: ~p~n", [Resp]),
{reply, Resp};
% Server Assignement Request
handle_request(#diameter_packet{msg = Req, errors = []}, _SvcName, {_, Caps}) when is_record(Req, 'SAR') ->
% extract relevant fields from DIAMETER ULR
#diameter_caps{origin_host = {OH,_}, origin_realm = {OR,_}} = Caps,
#'SAR'{'Session-Id' = SessionId,
'User-Name' = UserName,
'Server-Name' = ServerName,
'Server-Assignment-Type' = Type} = Req,
% TODO: Type == 0
ServerName = "sip:scscf.core.osmocom.org:6060",
Resp = #'SAA'{'Session-Id'= SessionId, 'Auth-Session-State'=1,
'Origin-Host'=OH, 'Origin-Realm'=OR,
'Experimental-Result'=2001,
'User-Name' = UserName,
'Server-Name'=ServerName},
lager:info("SAA Resp: ~p~n", [Resp]),
{reply, Resp};
% Multimedia Authentication Request
handle_request(#diameter_packet{msg = Req, errors = []}, _SvcName, {_, Caps}) when is_record(Req, 'MAR') ->
#diameter_caps{origin_host = {OH,_}, origin_realm = {OR,_}} = Caps,
#'MAR'{'Session-Id' = SessionId,
'User-Name' = UserName,
'Server-Name' = ServerName,
'Public-Identity' = PublicIdentity,
'SIP-Auth-Data-Item' = AuthData,
'SIP-Number-Auth-Items' = NumAuthData} = Req,
% TODO: parse User-Name and Public-Identity, get the MNC/MCC from it
GsupTx1 = #{message_type => send_auth_info_req, imsi => list_to_binary(UserName),
supported_rat_types => [rat_eutran_sgs], current_rat_type => rat_eutran_sgs},
ResyncInfo = req_resynchronization_info(Req),
case ResyncInfo of
false ->
GsupTx2 = #{};
ValidResyncInfo ->
GsupTx2 = #{rand => binary:part(ValidResyncInfo, 0, 16),
auts => binary:part(ValidResyncInfo, 16, 14)}
end,
GsupTx = maps:merge(GsupTx1, GsupTx2),
GsupRx = gen_server:call(gsup_client, {transceive_gsup, GsupTx, send_auth_info_res, send_auth_info_err}),
lager:info("GsupRx: ~p~n", [GsupRx]),
case GsupRx of
#{message_type:=send_auth_info_res, auth_tuples:=GsupAuthTuples} ->
AuthInfo = gsup_tuples2dia(GsupAuthTuples, NumAuthData),
Resp = #'MAA'{'Session-Id'=SessionId, 'Origin-Host'=OH, 'Origin-Realm'=OR,
'Experimental-Result'=2001, 'Auth-Session-State'=1,
'SIP-Auth-Data-Item'=AuthInfo};
#{message_type := send_auth_info_err, cause:=Cause} ->
{Res, ExpRes} = gsup_cause2dia(Cause),
Resp = #'MAA'{'Session-Id'=SessionId, 'Origin-Host'=OH, 'Origin-Realm'=OR,
'Result-Code'=Res, 'Experimental-Result'=ExpRes,
'Auth-Session-State'=1};
timeout ->
Resp = #'MAA'{'Session-Id'=SessionId, 'Origin-Host'=OH, 'Origin-Realm'=OR,
'Result-Code'=4181, 'Auth-Session-State'=1}
end,
lager:info("Resp: ~p~n", [Resp]),
{reply, Resp};
handle_request(Packet, _SvcName, {_,_}) ->
lager:error("Unsuppoerted message: ~p~n", [Packet]),
discard.