blob: 815eaf65e081b1fe5afd21ba60bb0e2fb66c903d [file] [log] [blame]
Harald Welte31912172024-06-04 22:38:32 +02001% (C) 2019 by Harald Welte <laforge@gnumonks.org>
2%
3% All Rights Reserved
4%
5% This program is free software; you can redistribute it and/or modify
6% it under the terms of the GNU Affero General Public License as
7% published by the Free Software Foundation; either version 3 of the
8% License, or (at your option) any later version.
9%
10% This program is distributed in the hope that it will be useful,
11% but WITHOUT ANY WARRANTY; without even the implied warranty of
12% MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
13% GNU General Public License for more details.
14%
15% You should have received a copy of the GNU Affero General Public License
Harald Weltec78954f2024-06-05 15:40:43 +020016% along with this program. If not, see <https://www.gnu.org/licenses/>.
Harald Welte31912172024-06-04 22:38:32 +020017%
18% Additional Permission under GNU AGPL version 3 section 7:
19%
20% If you modify this Program, or any covered work, by linking or
21% combining it with runtime libraries of Erlang/OTP as released by
Harald Weltec78954f2024-06-05 15:40:43 +020022% Ericsson on https://www.erlang.org (or a modified version of these
Harald Welte31912172024-06-04 22:38:32 +020023% libraries), containing parts covered by the terms of the Erlang Public
Harald Weltec78954f2024-06-05 15:40:43 +020024% License (https://www.erlang.org/EPLICENSE), the licensors of this
Harald Welte31912172024-06-04 22:38:32 +020025% Program grant you additional permission to convey the resulting work
26% without the need to license the runtime libraries of Erlang/OTP under
27% the GNU Affero General Public License. Corresponding Source for a
28% non-source form of such a combination shall include the source code
29% for the parts of the runtime libraries of Erlang/OTP used as well as
30% that of the covered work.
Harald Welte61276c42019-08-10 22:14:50 +020031
Harald Welte31912172024-06-04 22:38:32 +020032-module(server_cb).
Harald Welte61276c42019-08-10 22:14:50 +020033
34-include_lib("diameter/include/diameter.hrl").
35-include_lib("diameter/include/diameter_gen_base_rfc6733.hrl").
36-include_lib("diameter_3gpp_ts29_272.hrl").
Harald Welte44da7d72019-08-14 13:28:08 +020037-include_lib("osmo_gsup/include/gsup_protocol.hrl").
Harald Welte61276c42019-08-10 22:14:50 +020038
Alexander Couzens6ba22c22023-09-01 15:42:18 +020039-define(DIA_VENDOR_3GPP, 10415).
Harald Welte61276c42019-08-10 22:14:50 +020040
41%% diameter callbacks
42-export([peer_up/3, peer_down/3, pick_peer/4, prepare_request/3, prepare_retransmit/3,
43 handle_answer/4, handle_error/4, handle_request/3]).
44
45-define(UNEXPECTED, erlang:error({unexpected, ?MODULE, ?LINE})).
46
47peer_up(_SvcName, {PeerRef, Caps}, State) ->
48 lager:info("Peer up ~p - ~p~n", [PeerRef, lager:pr(Caps, ?MODULE)]),
49 State.
50
51peer_down(_SvcName, {PeerRef, Caps}, State) ->
52 lager:info("Peer down ~p - ~p~n", [PeerRef, lager:pr(Caps, ?MODULE)]),
53 State.
54
55pick_peer(_, _, _SvcName, _State) ->
56 ?UNEXPECTED.
57
58prepare_request(_, _SvcName, _Peer) ->
59 ?UNEXPECTED.
60
61prepare_retransmit(_Packet, _SvcName, _Peer) ->
62 ?UNEXPECTED.
63
64handle_answer(_Packet, _Request, _SvcName, _Peer) ->
65 ?UNEXPECTED.
66
67handle_error(_Reason, _Request, _SvcName, _Peer) ->
68 lager:error("Request error: ~p~n", [_Reason]),
69 ?UNEXPECTED.
70
Harald Welte44da7d72019-08-14 13:28:08 +020071% generate Diameter E-UTRAN / UTRAN / GERAN Vectors from GSUP tuple input
72-spec gsup_tuple2dia_eutran('GSUPAuthTuple'(), binary(), integer()) -> #'E-UTRAN-Vector'{}.
73gsup_tuple2dia_eutran(#{autn:=Autn, ck:=Ck, ik:=Ik, rand:=Rand, res:=Res}, Vplmn, Idx) ->
74 #'E-UTRAN-Vector'{'Item-Number'=Idx, 'RAND'=Rand, 'XRES'=Res , 'AUTN'=Autn,
75 'KASME'=compute_kasme(Ck, Ik, Vplmn, Autn)}.
76
77-spec gsup_tuple2dia_utran('GSUPAuthTuple'()) -> #'UTRAN-Vector'{}.
78gsup_tuple2dia_utran(#{autn:=Autn, ck:=Ck, ik:=Ik, rand:=Rand, res:=Res}) ->
79 #'UTRAN-Vector'{'RAND'=Rand, 'XRES'=Res, 'AUTN'=Autn, 'Confidentiality-Key'=Ck, 'Integrity-Key'=Ik}.
80
81-spec gsup_tuple2dia_geran('GSUPAuthTuple'()) -> #'GERAN-Vector'{}.
82gsup_tuple2dia_geran(#{rand:=Rand, sres:=Sres, kc:=Kc}) ->
83 #'GERAN-Vector'{'RAND'=Rand, 'SRES'=Sres, 'Kc'=Kc}.
84
85-spec gsup_tuples2dia_eutran(['GSUPAuthTuple'()], binary()) -> [#'E-UTRAN-Vector'{}].
86gsup_tuples2dia_eutran(List, Vplmn) -> gsup_tuples2dia_eutran(List, Vplmn, [], 1).
87gsup_tuples2dia_eutran([], _Vplmn, Out, _Idx) -> Out;
88gsup_tuples2dia_eutran([Head|Tail], Vplmn, Out, Ctr) ->
89 Dia = gsup_tuple2dia_eutran(Head, Vplmn, Ctr),
90 gsup_tuples2dia_eutran(Tail, Vplmn, [Dia|Out], Ctr+1).
91
92-type int_or_false() :: false | integer().
93-spec gsup_tuples2dia(['GSUPAuthTuple'()], binary(), int_or_false(), int_or_false(), int_or_false()) -> #'Authentication-Info'{}.
94gsup_tuples2dia(Tuples, Vplmn, NumEutran, NumUtran, NumGeran) ->
95 case NumEutran of
96 false -> EutranVecs = [];
97 0 -> EutranVecs = [];
98 _ -> EutranVecs = gsup_tuples2dia_eutran(lists:sublist(Tuples,NumEutran), Vplmn)
99 end,
100 case NumUtran of
101 false -> UtranVecs = [];
102 0 -> UtranVecs = [];
103 _ -> UtranVecs = lists:map(fun gsup_tuple2dia_utran/1, lists:sublist(Tuples,NumUtran))
104 end,
105 case NumGeran of
106 false -> GeranVecs = [];
107 0 -> GeranVecs = [];
108 _ -> GeranVecs = lists:map(fun gsup_tuple2dia_geran/1, lists:sublist(Tuples,NumGeran))
109 end,
110 #'Authentication-Info'{'E-UTRAN-Vector'=EutranVecs, 'UTRAN-Vector'=UtranVecs,
111 'GERAN-Vector'=GeranVecs}.
112
113
114-spec compute_kasme(<<_:16>>, <<_:16>>, <<_:3>>, <<_:16>>) -> <<_:32>>.
115compute_kasme(Ck, Ik, VplmnId, Autn) ->
116 Autn6 = binary_part(Autn, 0, 6),
117 K = <<Ck:16/binary, Ik:16/binary>>,
118 S = <<16, VplmnId:3/binary, 0, 3, Autn6:6/binary, 0, 6>>,
Daniel Willmann592cc8b2022-04-22 16:08:48 +0200119 Release = erlang:system_info(otp_release),
120 if
121 Release >= "24" ->
122 crypto:macN(hmac, sha256, K, S, 32);
123 true ->
124 crypto:hmac(sha256, K, S, 32)
125 end.
Harald Welte44da7d72019-08-14 13:28:08 +0200126
127-spec req_num_of_vec([tuple()]) -> int_or_false().
128req_num_of_vec([#'Requested-EUTRAN-Authentication-Info'{'Number-Of-Requested-Vectors'=[]}]) -> false;
129req_num_of_vec([#'Requested-EUTRAN-Authentication-Info'{'Number-Of-Requested-Vectors'=[Num]}]) -> Num;
130req_num_of_vec([#'Requested-UTRAN-GERAN-Authentication-Info'{'Number-Of-Requested-Vectors'=[]}]) -> false;
131req_num_of_vec([#'Requested-UTRAN-GERAN-Authentication-Info'{'Number-Of-Requested-Vectors'=[Num]}]) -> Num;
132req_num_of_vec(_) -> false.
133
Matt Johnson9e0bd802020-08-21 17:31:57 -0700134
135-type binary_or_false() :: false | binary().
136-spec req_resynchronization_info([tuple()]) -> binary_or_false().
137req_resynchronization_info([#'Requested-EUTRAN-Authentication-Info'{'Re-Synchronization-Info'=[]}]) ->
138 false;
139req_resynchronization_info([#'Requested-EUTRAN-Authentication-Info'{'Re-Synchronization-Info'=[Info]}]) ->
140 list_to_binary(Info);
141
142req_resynchronization_info([#'Requested-UTRAN-GERAN-Authentication-Info'{'Re-Synchronization-Info'=[]}]) ->
143 false;
144req_resynchronization_info([#'Requested-UTRAN-GERAN-Authentication-Info'{'Re-Synchronization-Info'=[Info]}]) ->
145 list_to_binary(Info);
146
147req_resynchronization_info(_) ->
148 false.
149
Harald Welte299ba932019-08-15 18:31:12 +0200150-define(PDP_TYPE_DEFAULT, <<0,0,0,16#21>>). % IPv4
151-define(PDP_QOS_DEFAULT, <<0,0,0,0,0,0,0,0,0,0,0,0,0,0>>). % fixme
152
Harald Welte44da7d72019-08-14 13:28:08 +0200153-spec gsup_pdp2dia('GSUPPdpInfo'()) -> #'PDP-Context'{}.
154gsup_pdp2dia(GsupPdpInfo) ->
Harald Welte299ba932019-08-15 18:31:12 +0200155 #'PDP-Context'{'PDP-Type' = maps:get(pdp_type, GsupPdpInfo, ?PDP_TYPE_DEFAULT),
Harald Welte44da7d72019-08-14 13:28:08 +0200156 'Context-Identifier' = maps:get(pdp_context_id, GsupPdpInfo),
Alexander Couzens7c912ff2023-04-26 17:58:00 +0000157 'Service-Selection' = decode_apn:decode_apn(maps:get(access_point_name, GsupPdpInfo)),
Harald Welte299ba932019-08-15 18:31:12 +0200158 'QoS-Subscribed' = maps:get(quality_of_service, GsupPdpInfo, ?PDP_QOS_DEFAULT)
Harald Welte44da7d72019-08-14 13:28:08 +0200159 }.
160
Harald Welte299ba932019-08-15 18:31:12 +0200161-define(PDN_TYPE_DEFAULT, 0). % IPv4
162-define(EPS_QOS_DEFAULT,
163 #'EPS-Subscribed-QoS-Profile'{'QoS-Class-Identifier'=9,
164 'Allocation-Retention-Priority'=
165 #'Allocation-Retention-Priority'{'Priority-Level'=8,
166 'Pre-emption-Capability'=1,
167 'Pre-emption-Vulnerability'=1}
168 }).
169
170-spec gsup_pdp2dia_apn('GSUPPdpInfo'()) -> #'APN-Configuration'{}.
171gsup_pdp2dia_apn(GsupPdpInfo) ->
172 #'APN-Configuration'{'Context-Identifier' = maps:get(pdp_context_id, GsupPdpInfo),
173 'PDN-Type' = maps:get(pdp_type, GsupPdpInfo, ?PDN_TYPE_DEFAULT),
174 % The EPS-Subscribed-QoS-Profile AVP and the AMBR AVP shall be present in the
175 % APN-Configuration AVP when the APN-Configuration AVP is sent in the
176 % APN-Configuration-Profile AVP and when the APN-Configuration-Profile AVP is
177 % sent within a ULA (as part of the Subscription-Data AVP).
178 'EPS-Subscribed-QoS-Profile' = ?EPS_QOS_DEFAULT,
179 'AMBR' = #'AMBR'{'Max-Requested-Bandwidth-UL' = 100000000,
180 'Max-Requested-Bandwidth-DL' = 100000000},
181 % The default APN Configuration shall not contain the Wildcard APN (see 3GPP TS
182 % 23.003 [3], clause 9.2); the default APN shall always contain an explicit APN
Alexander Couzens7c912ff2023-04-26 17:58:00 +0000183 'Service-Selection' = decode_apn:decode_apn(maps:get(access_point_name, GsupPdpInfo))
Harald Welte299ba932019-08-15 18:31:12 +0200184 }.
185
Harald Welte44da7d72019-08-14 13:28:08 +0200186% transient (only in Experimental-Result-Code)
187-define(DIAMETER_AUTHENTICATION_DATA_UNAVAILABLE, 4181).
188-define(DIAMETER_ERROR_CAMEL_SUBSCRIPTION_PRESENT, 4182).
189% permanent (only in Experimental-Result-Code)
190-define(DIAMETER_ERROR_USER_UNKNOWN, 5001).
Pau Espin Pedrolb524e242023-08-30 16:33:55 +0200191-define(DIAMETER_AUTHORIZATION_REJECTED, 5003).
Harald Welte44da7d72019-08-14 13:28:08 +0200192-define(DIAMETER_ERROR_ROAMING_NOT_ALLOWED, 5004).
Pau Espin Pedrolb524e242023-08-30 16:33:55 +0200193-define(DIAMETER_MISSING_AVP, 5005).
194-define(DIAMETER_UNABLE_TO_COMPLY, 5012).
Harald Welte44da7d72019-08-14 13:28:08 +0200195-define(DIAMETER_ERROR_UNKNOWN_EPS_SUBSCRIPTION, 5420).
196-define(DIAMETER_ERROR_RAT_NOT_ALLOWED, 5421).
197-define(DIAMETER_ERROR_EQUIPMENT_UNKNOWN, 5422).
198-define(DIAMETER_ERROR_UNKOWN_SERVING_NODE, 5423).
199
200% 10.5.5.14
201-define(GMM_CAUSE_IMSI_UNKNOWN, 16#02).
Pau Espin Pedrol5e11d282023-08-30 16:27:42 +0200202-define(GMM_CAUSE_ILLEGAL_MS, 16#03).
Harald Welte44da7d72019-08-14 13:28:08 +0200203-define(GMM_CAUSE_GPRS_NOTALLOWED, 16#07).
Pau Espin Pedrol5e11d282023-08-30 16:27:42 +0200204-define(GMM_CAUSE_PLMN_NOTALLOWED, 16#0b).
205-define(GMM_CAUSE_LA_NOTALLOWED, 16#0c).
206-define(GMM_CAUSE_ROAMING_NOTALLOWED, 16#0d).
207-define(GMM_CAUSE_NO_SUIT_CELL_IN_LA, 16#0f).
Harald Welte44da7d72019-08-14 13:28:08 +0200208-define(GMM_CAUSE_NET_FAIL, 16#11).
Pau Espin Pedrol5e11d282023-08-30 16:27:42 +0200209-define(GMM_CAUSE_CONGESTION, 16#16).
210-define(GMM_CAUSE_GSM_AUTH_UNACCEPT, 16#17).
211-define(GMM_CAUSE_INV_MAND_INFO, 16#60).
212-define(GMM_CAUSE_PROTO_ERR_UNSPEC, 16#6f).
Harald Welte44da7d72019-08-14 13:28:08 +0200213
Alexander Couzens6ba22c22023-09-01 15:42:18 +0200214-define(EXP_RES(Exp), #'Experimental-Result'{'Vendor-Id'=?DIA_VENDOR_3GPP, 'Experimental-Result-Code'=Exp}).
Harald Welte44da7d72019-08-14 13:28:08 +0200215
Pau Espin Pedrolb524e242023-08-30 16:33:55 +0200216%% see 29.272 Annex A/B
Harald Welte44da7d72019-08-14 13:28:08 +0200217-type empty_or_intl() :: [] | [integer()].
218-spec gsup_cause2dia(integer()) -> {empty_or_intl(), empty_or_intl()}.
219gsup_cause2dia(?GMM_CAUSE_IMSI_UNKNOWN) -> {[], [?EXP_RES(?DIAMETER_ERROR_USER_UNKNOWN)]};
Pau Espin Pedrolb524e242023-08-30 16:33:55 +0200220gsup_cause2dia(?GMM_CAUSE_ILLEGAL_MS) -> {[], [?EXP_RES(?DIAMETER_ERROR_USER_UNKNOWN)]};
221gsup_cause2dia(?GMM_CAUSE_PLMN_NOTALLOWED) -> {[], [?EXP_RES(?DIAMETER_ERROR_ROAMING_NOT_ALLOWED)]};
222gsup_cause2dia(?GMM_CAUSE_GPRS_NOTALLOWED) -> {[], [?EXP_RES(?DIAMETER_ERROR_UNKNOWN_EPS_SUBSCRIPTION)]};
223
224gsup_cause2dia(?GMM_CAUSE_LA_NOTALLOWED) -> {[?DIAMETER_AUTHORIZATION_REJECTED], []};
225gsup_cause2dia(?GMM_CAUSE_ROAMING_NOTALLOWED) -> {[], [?EXP_RES(?DIAMETER_ERROR_ROAMING_NOT_ALLOWED)]};
226gsup_cause2dia(?GMM_CAUSE_NO_SUIT_CELL_IN_LA) -> {[], [?EXP_RES(?DIAMETER_ERROR_UNKNOWN_EPS_SUBSCRIPTION)]};
227gsup_cause2dia(?GMM_CAUSE_NET_FAIL) -> {[?DIAMETER_UNABLE_TO_COMPLY], []};
228gsup_cause2dia(?GMM_CAUSE_CONGESTION) -> {[?DIAMETER_UNABLE_TO_COMPLY], []};
229gsup_cause2dia(?GMM_CAUSE_INV_MAND_INFO) -> {[?DIAMETER_MISSING_AVP], []};
230gsup_cause2dia(?GMM_CAUSE_PROTO_ERR_UNSPEC) -> {[?DIAMETER_UNABLE_TO_COMPLY], []};
Alexander Couzensb8aef302023-09-01 15:44:58 +0200231gsup_cause2dia(_) -> {[?DIAMETER_UNABLE_TO_COMPLY], []}.
Harald Welte44da7d72019-08-14 13:28:08 +0200232
233% get the value for a tiven key in Map1. If not found, try same key in Map2. If not found, return Default
234-spec twomap_get(atom(), map(), map(), any()) -> any().
235twomap_get(Key, Map1, Map2, Default) ->
236 maps:get(Key, Map1, maps:get(Key, Map2, Default)).
237
238handle_request(#diameter_packet{msg = Req, errors = []}, _SvcName, {_, Caps}) when is_record(Req, 'AIR') ->
239 lager:info("AIR: ~p~n", [Req]),
240 % extract relevant fields from DIAMETER AIR
241 #diameter_caps{origin_host = {OH,_}, origin_realm = {OR,_}} = Caps,
242 #'AIR'{'Session-Id' = SessionId,
243 'User-Name' = UserName,
244 'Visited-PLMN-Id' = VplmnId,
245 'Requested-EUTRAN-Authentication-Info' = ReqEU,
246 'Requested-UTRAN-GERAN-Authentication-Info' = ReqUG} = Req,
247 VplmnIdBin = list_to_binary(VplmnId),
248 NumEutran = req_num_of_vec(ReqEU),
249 NumUgran = req_num_of_vec(ReqUG),
250 lager:info("Num EUTRAN=~p, UTRAN=~p~n", [NumEutran, NumUgran]),
251 % construct GSUP request to HLR and transceive it
Harald Welte388d3872019-12-01 17:03:15 +0100252 GsupTx1 = #{message_type => send_auth_info_req, imsi => list_to_binary(UserName),
253 supported_rat_types => [rat_eutran_sgs], current_rat_type => rat_eutran_sgs},
Matt Johnson9e0bd802020-08-21 17:31:57 -0700254 ResyncInfo = req_resynchronization_info(ReqEU),
255 case ResyncInfo of
256 false ->
257 GsupTx2 = #{};
258 ValidResyncInfo ->
259 lager:info("ResyncInfo is valid ~p", [ResyncInfo]),
260 GsupTx2 = #{rand => binary:part(ValidResyncInfo, 0, 16),
261 auts => binary:part(ValidResyncInfo, 16, 14)}
Harald Welte332fe7f2019-08-20 22:36:50 +0200262 end,
263 GsupTx = maps:merge(GsupTx1, GsupTx2),
Harald Welte44da7d72019-08-14 13:28:08 +0200264 GsupRx = gen_server:call(gsup_client, {transceive_gsup, GsupTx, send_auth_info_res, send_auth_info_err}),
265 lager:info("GsupRx: ~p~n", [GsupRx]),
266 % construct DIAMETER AIA response
267 case GsupRx of
268 #{message_type:=send_auth_info_res, auth_tuples:=GsupAuthTuples} ->
269 AuthInfo = gsup_tuples2dia(GsupAuthTuples, VplmnIdBin, NumEutran, NumUgran, NumUgran),
270 Resp = #'AIA'{'Session-Id'=SessionId, 'Origin-Host'=OH, 'Origin-Realm'=OR,
271 'Result-Code'=2001, 'Auth-Session-State'=1,
272 'Authentication-Info'=AuthInfo};
Pau Espin Pedrolb524e242023-08-30 16:33:55 +0200273 #{message_type := send_auth_info_err, cause:=Cause} ->
274 {Res, ExpRes} = gsup_cause2dia(Cause),
Harald Welte44da7d72019-08-14 13:28:08 +0200275 Resp = #'AIA'{'Session-Id'=SessionId, 'Origin-Host'=OH, 'Origin-Realm'=OR,
Pau Espin Pedrolb524e242023-08-30 16:33:55 +0200276 'Result-Code'=Res,
277 'Experimental-Result'=ExpRes,
Harald Welte44da7d72019-08-14 13:28:08 +0200278 'Auth-Session-State'=1};
279 timeout ->
280 Resp = #'AIA'{'Session-Id'=SessionId, 'Origin-Host'=OH, 'Origin-Realm'=OR,
281 'Result-Code'=4181, 'Auth-Session-State'=1}
282 end,
283 lager:info("Resp: ~p~n", [Resp]),
284 {reply, Resp};
285
286handle_request(#diameter_packet{msg = Req, errors = []}, _SvcName, {_, Caps}) when is_record(Req, 'ULR') ->
Harald Welte6f529082019-08-21 14:54:27 +0200287 % extract relevant fields from DIAMETER ULR
Harald Welte44da7d72019-08-14 13:28:08 +0200288 #diameter_caps{origin_host = {OH,_}, origin_realm = {OR,_}} = Caps,
289 #'ULR'{'Session-Id' = SessionId,
290 'RAT-Type' = RatType,
291 'ULR-Flags' = UlrFlags,
292 'User-Name' = UserName} = Req,
293
294 % construct GSUP UpdateLocation request to HLR and transceive it; expect InsertSubscrDataReq
Harald Welte299ba932019-08-15 18:31:12 +0200295 GsupTxUlReq = #{message_type => location_upd_req, imsi => list_to_binary(UserName),
296 cn_domain => 1},
Harald Welte44da7d72019-08-14 13:28:08 +0200297 GsupRxIsdReq = gen_server:call(gsup_client,
298 {transceive_gsup, GsupTxUlReq, insert_sub_data_req, location_upd_err}),
299 lager:info("GsupRxIsdReq: ~p~n", [GsupRxIsdReq]),
300 case GsupRxIsdReq of
301 #{message_type:=location_upd_err, cause:=Cause} ->
302 {Res, ExpRes} = gsup_cause2dia(Cause),
303 Resp = #'ULA'{'Session-Id'= SessionId, 'Auth-Session-State'=1,
304 'Origin-Host'=OH, 'Origin-Realm'=OR,
305 'Result-Code'=Res, 'Experimental-Result'=ExpRes};
306 #{message_type:=insert_sub_data_req} ->
307 % construct GSUP InsertSubscrData response to HLR and transceive it; expect
308 % UpdateLocationRes
Harald Welte299ba932019-08-15 18:31:12 +0200309 GsupTxIsdRes = #{message_type => insert_sub_data_res,
310 imsi => list_to_binary(UserName)},
Harald Welte44da7d72019-08-14 13:28:08 +0200311 GsupRxUlRes = gen_server:call(gsup_client,
312 {transceive_gsup, GsupTxIsdRes, location_upd_res, location_upd_err}),
313 lager:info("GsupRxUlRes: ~p~n", [GsupRxUlRes]),
314
315 case GsupRxUlRes of
316 #{message_type:=location_upd_res} ->
317 Msisdn = twomap_get(msisdn, GsupRxIsdReq, GsupRxUlRes, []),
Harald Welte299ba932019-08-15 18:31:12 +0200318 Compl = twomap_get(pdp_info_complete, GsupRxIsdReq, GsupRxUlRes, 0),
319
320 % build the GPRS Subscription Data
Harald Welte44da7d72019-08-14 13:28:08 +0200321 PdpInfoList = twomap_get(pdp_info_list, GsupRxIsdReq, GsupRxUlRes, []),
Harald Welte299ba932019-08-15 18:31:12 +0200322 PdpContexts = lists:map(fun gsup_pdp2dia/1, PdpInfoList),
323 GSubD = #'GPRS-Subscription-Data'{'Complete-Data-List-Included-Indicator'=Compl,
Harald Welte44da7d72019-08-14 13:28:08 +0200324 'PDP-Context'=PdpContexts},
Harald Welte299ba932019-08-15 18:31:12 +0200325
326 % build the APN-Configuration-Profile
327 ApnCfgList = lists:map(fun gsup_pdp2dia_apn/1, PdpInfoList),
328 FirstApn = lists:nth(1, ApnCfgList),
329 DefaultCtxId = FirstApn#'APN-Configuration'.'Context-Identifier',
330 ApnCfgProf = #'APN-Configuration-Profile'{'Context-Identifier' = DefaultCtxId,
331 'All-APN-Configurations-Included-Indicator'=Compl,
332 'APN-Configuration' = ApnCfgList},
333
334 % put together the Subscription-Data and finally the ULA response
335 SubscrData = #'Subscription-Data'{'MSISDN' = Msisdn,
336
337 'Network-Access-Mode' = 0, % PACKET_AND_CIRCUIT
338 'GPRS-Subscription-Data' = GSubD,
339 % Subscriber-Status must be present in ULA
340 'Subscriber-Status' = 0,
341 % AMBR must be present if this is an ULA; let's permit 100MBps UL + DL
342 'AMBR' = #'AMBR'{'Max-Requested-Bandwidth-UL' = 100000000,
343 'Max-Requested-Bandwidth-DL' = 100000000},
344 'APN-Configuration-Profile' = ApnCfgProf},
345 Resp = #'ULA'{'Session-Id' = SessionId, 'Auth-Session-State' = 1,
346 'Origin-Host' = OH, 'Origin-Realm' = OR,
347 'Result-Code' = 2001,
348 'Subscription-Data' = SubscrData, 'ULA-Flags' = 0};
Harald Welte44da7d72019-08-14 13:28:08 +0200349 #{message_type:=location_upd_err, cause:=Cause} ->
350 {Res, ExpRes} = gsup_cause2dia(Cause),
351 Resp = #'ULA'{'Session-Id'= SessionId, 'Auth-Session-State'=1,
352 'Origin-Host'=OH, 'Origin-Realm'=OR,
353 'Result-Code'=Res, 'Experimental-Result'=ExpRes};
354 _ ->
355 Resp = #'ULA'{'Session-Id'= SessionId, 'Auth-Session-State'=1,
356 'Origin-Host'=OH, 'Origin-Realm'=OR,
357 'Result-Code'=fixme}
358 end
359 end,
Harald Welte299ba932019-08-15 18:31:12 +0200360 lager:info("ULR Resp: ~p~n", [Resp]),
Harald Welte44da7d72019-08-14 13:28:08 +0200361 {reply, Resp};
362
363handle_request(Packet, _SvcName, {_,_}) ->
364 lager:error("Unsuppoerted message: ~p~n", [Packet]),
Harald Welte61276c42019-08-10 22:14:50 +0200365 discard.