blob: b3de0a6f1bfef7c0646327beaf7e1f159df1c959 [file] [log] [blame]
Harald Welte61276c42019-08-10 22:14:50 +02001-module(server_cb).
2
3
4-include_lib("diameter/include/diameter.hrl").
5-include_lib("diameter/include/diameter_gen_base_rfc6733.hrl").
6-include_lib("diameter_3gpp_ts29_272.hrl").
Harald Welte44da7d72019-08-14 13:28:08 +02007-include_lib("osmo_gsup/include/gsup_protocol.hrl").
Harald Welte61276c42019-08-10 22:14:50 +02008
9
10%% diameter callbacks
11-export([peer_up/3, peer_down/3, pick_peer/4, prepare_request/3, prepare_retransmit/3,
12 handle_answer/4, handle_error/4, handle_request/3]).
13
14-define(UNEXPECTED, erlang:error({unexpected, ?MODULE, ?LINE})).
15
16peer_up(_SvcName, {PeerRef, Caps}, State) ->
17 lager:info("Peer up ~p - ~p~n", [PeerRef, lager:pr(Caps, ?MODULE)]),
18 State.
19
20peer_down(_SvcName, {PeerRef, Caps}, State) ->
21 lager:info("Peer down ~p - ~p~n", [PeerRef, lager:pr(Caps, ?MODULE)]),
22 State.
23
24pick_peer(_, _, _SvcName, _State) ->
25 ?UNEXPECTED.
26
27prepare_request(_, _SvcName, _Peer) ->
28 ?UNEXPECTED.
29
30prepare_retransmit(_Packet, _SvcName, _Peer) ->
31 ?UNEXPECTED.
32
33handle_answer(_Packet, _Request, _SvcName, _Peer) ->
34 ?UNEXPECTED.
35
36handle_error(_Reason, _Request, _SvcName, _Peer) ->
37 lager:error("Request error: ~p~n", [_Reason]),
38 ?UNEXPECTED.
39
Harald Welte44da7d72019-08-14 13:28:08 +020040% generate Diameter E-UTRAN / UTRAN / GERAN Vectors from GSUP tuple input
41-spec gsup_tuple2dia_eutran('GSUPAuthTuple'(), binary(), integer()) -> #'E-UTRAN-Vector'{}.
42gsup_tuple2dia_eutran(#{autn:=Autn, ck:=Ck, ik:=Ik, rand:=Rand, res:=Res}, Vplmn, Idx) ->
43 #'E-UTRAN-Vector'{'Item-Number'=Idx, 'RAND'=Rand, 'XRES'=Res , 'AUTN'=Autn,
44 'KASME'=compute_kasme(Ck, Ik, Vplmn, Autn)}.
45
46-spec gsup_tuple2dia_utran('GSUPAuthTuple'()) -> #'UTRAN-Vector'{}.
47gsup_tuple2dia_utran(#{autn:=Autn, ck:=Ck, ik:=Ik, rand:=Rand, res:=Res}) ->
48 #'UTRAN-Vector'{'RAND'=Rand, 'XRES'=Res, 'AUTN'=Autn, 'Confidentiality-Key'=Ck, 'Integrity-Key'=Ik}.
49
50-spec gsup_tuple2dia_geran('GSUPAuthTuple'()) -> #'GERAN-Vector'{}.
51gsup_tuple2dia_geran(#{rand:=Rand, sres:=Sres, kc:=Kc}) ->
52 #'GERAN-Vector'{'RAND'=Rand, 'SRES'=Sres, 'Kc'=Kc}.
53
54-spec gsup_tuples2dia_eutran(['GSUPAuthTuple'()], binary()) -> [#'E-UTRAN-Vector'{}].
55gsup_tuples2dia_eutran(List, Vplmn) -> gsup_tuples2dia_eutran(List, Vplmn, [], 1).
56gsup_tuples2dia_eutran([], _Vplmn, Out, _Idx) -> Out;
57gsup_tuples2dia_eutran([Head|Tail], Vplmn, Out, Ctr) ->
58 Dia = gsup_tuple2dia_eutran(Head, Vplmn, Ctr),
59 gsup_tuples2dia_eutran(Tail, Vplmn, [Dia|Out], Ctr+1).
60
61-type int_or_false() :: false | integer().
62-spec gsup_tuples2dia(['GSUPAuthTuple'()], binary(), int_or_false(), int_or_false(), int_or_false()) -> #'Authentication-Info'{}.
63gsup_tuples2dia(Tuples, Vplmn, NumEutran, NumUtran, NumGeran) ->
64 case NumEutran of
65 false -> EutranVecs = [];
66 0 -> EutranVecs = [];
67 _ -> EutranVecs = gsup_tuples2dia_eutran(lists:sublist(Tuples,NumEutran), Vplmn)
68 end,
69 case NumUtran of
70 false -> UtranVecs = [];
71 0 -> UtranVecs = [];
72 _ -> UtranVecs = lists:map(fun gsup_tuple2dia_utran/1, lists:sublist(Tuples,NumUtran))
73 end,
74 case NumGeran of
75 false -> GeranVecs = [];
76 0 -> GeranVecs = [];
77 _ -> GeranVecs = lists:map(fun gsup_tuple2dia_geran/1, lists:sublist(Tuples,NumGeran))
78 end,
79 #'Authentication-Info'{'E-UTRAN-Vector'=EutranVecs, 'UTRAN-Vector'=UtranVecs,
80 'GERAN-Vector'=GeranVecs}.
81
82
83-spec compute_kasme(<<_:16>>, <<_:16>>, <<_:3>>, <<_:16>>) -> <<_:32>>.
84compute_kasme(Ck, Ik, VplmnId, Autn) ->
85 Autn6 = binary_part(Autn, 0, 6),
86 K = <<Ck:16/binary, Ik:16/binary>>,
87 S = <<16, VplmnId:3/binary, 0, 3, Autn6:6/binary, 0, 6>>,
88 crypto:hmac(sha256, K, S, 32).
89
90-spec req_num_of_vec([tuple()]) -> int_or_false().
91req_num_of_vec([#'Requested-EUTRAN-Authentication-Info'{'Number-Of-Requested-Vectors'=[]}]) -> false;
92req_num_of_vec([#'Requested-EUTRAN-Authentication-Info'{'Number-Of-Requested-Vectors'=[Num]}]) -> Num;
93req_num_of_vec([#'Requested-UTRAN-GERAN-Authentication-Info'{'Number-Of-Requested-Vectors'=[]}]) -> false;
94req_num_of_vec([#'Requested-UTRAN-GERAN-Authentication-Info'{'Number-Of-Requested-Vectors'=[Num]}]) -> Num;
95req_num_of_vec(_) -> false.
96
Harald Welte299ba932019-08-15 18:31:12 +020097-define(PDP_TYPE_DEFAULT, <<0,0,0,16#21>>). % IPv4
98-define(PDP_QOS_DEFAULT, <<0,0,0,0,0,0,0,0,0,0,0,0,0,0>>). % fixme
99
Harald Welte44da7d72019-08-14 13:28:08 +0200100-spec gsup_pdp2dia('GSUPPdpInfo'()) -> #'PDP-Context'{}.
101gsup_pdp2dia(GsupPdpInfo) ->
Harald Welte299ba932019-08-15 18:31:12 +0200102 #'PDP-Context'{'PDP-Type' = maps:get(pdp_type, GsupPdpInfo, ?PDP_TYPE_DEFAULT),
Harald Welte44da7d72019-08-14 13:28:08 +0200103 'Context-Identifier' = maps:get(pdp_context_id, GsupPdpInfo),
Harald Welte299ba932019-08-15 18:31:12 +0200104 'Service-Selection' = maps:get(access_point_name, GsupPdpInfo),
105 'QoS-Subscribed' = maps:get(quality_of_service, GsupPdpInfo, ?PDP_QOS_DEFAULT)
Harald Welte44da7d72019-08-14 13:28:08 +0200106 }.
107
Harald Welte299ba932019-08-15 18:31:12 +0200108-define(PDN_TYPE_DEFAULT, 0). % IPv4
109-define(EPS_QOS_DEFAULT,
110 #'EPS-Subscribed-QoS-Profile'{'QoS-Class-Identifier'=9,
111 'Allocation-Retention-Priority'=
112 #'Allocation-Retention-Priority'{'Priority-Level'=8,
113 'Pre-emption-Capability'=1,
114 'Pre-emption-Vulnerability'=1}
115 }).
116
117-spec gsup_pdp2dia_apn('GSUPPdpInfo'()) -> #'APN-Configuration'{}.
118gsup_pdp2dia_apn(GsupPdpInfo) ->
119 #'APN-Configuration'{'Context-Identifier' = maps:get(pdp_context_id, GsupPdpInfo),
120 'PDN-Type' = maps:get(pdp_type, GsupPdpInfo, ?PDN_TYPE_DEFAULT),
121 % The EPS-Subscribed-QoS-Profile AVP and the AMBR AVP shall be present in the
122 % APN-Configuration AVP when the APN-Configuration AVP is sent in the
123 % APN-Configuration-Profile AVP and when the APN-Configuration-Profile AVP is
124 % sent within a ULA (as part of the Subscription-Data AVP).
125 'EPS-Subscribed-QoS-Profile' = ?EPS_QOS_DEFAULT,
126 'AMBR' = #'AMBR'{'Max-Requested-Bandwidth-UL' = 100000000,
127 'Max-Requested-Bandwidth-DL' = 100000000},
128 % The default APN Configuration shall not contain the Wildcard APN (see 3GPP TS
129 % 23.003 [3], clause 9.2); the default APN shall always contain an explicit APN
130 'Service-Selection' = "internet"%maps:get(access_point_name, GsupPdpInfo)
131 }.
132
Harald Welte44da7d72019-08-14 13:28:08 +0200133% transient (only in Experimental-Result-Code)
134-define(DIAMETER_AUTHENTICATION_DATA_UNAVAILABLE, 4181).
135-define(DIAMETER_ERROR_CAMEL_SUBSCRIPTION_PRESENT, 4182).
136% permanent (only in Experimental-Result-Code)
137-define(DIAMETER_ERROR_USER_UNKNOWN, 5001).
138-define(DIAMETER_ERROR_ROAMING_NOT_ALLOWED, 5004).
139-define(DIAMETER_ERROR_UNKNOWN_EPS_SUBSCRIPTION, 5420).
140-define(DIAMETER_ERROR_RAT_NOT_ALLOWED, 5421).
141-define(DIAMETER_ERROR_EQUIPMENT_UNKNOWN, 5422).
142-define(DIAMETER_ERROR_UNKOWN_SERVING_NODE, 5423).
143
144% 10.5.5.14
145-define(GMM_CAUSE_IMSI_UNKNOWN, 16#02).
146-define(GMM_CAUSE_PLMN_NOTALLOWED, 16#0b).
147-define(GMM_CAUSE_GPRS_NOTALLOWED, 16#07).
148-define(GMM_CAUSE_INV_MAND_INFO, 16#60).
149-define(GMM_CAUSE_NET_FAIL, 16#11).
150% TODO: more values
151
152-define(EXP_RES(Foo), #'Experimental-Result'{'Vendor-Id'=fixme, 'Experimental-Result-Code'=Foo}).
153
154-type empty_or_intl() :: [] | [integer()].
155-spec gsup_cause2dia(integer()) -> {empty_or_intl(), empty_or_intl()}.
156gsup_cause2dia(?GMM_CAUSE_IMSI_UNKNOWN) -> {[], [?EXP_RES(?DIAMETER_ERROR_USER_UNKNOWN)]};
157gsup_cause2dia(?GMM_CAUSE_PLMN_NOTALLOWED) -> {[], [?DIAMETER_ERROR_ROAMING_NOT_ALLOWED]};
158gsup_cause2dia(?GMM_CAUSE_GPRS_NOTALLOWED) -> {[], [?DIAMETER_ERROR_RAT_NOT_ALLOWED]};
159%gsup_cause2dia(?GMM_CAUSE_INV_MAND_INFO) ->
160%gsup_cause2dia(?GMM_CAUSE_NET_FAIL) ->
161% TODO: more values
162gsup_cause2dia(_) -> {fixme, []}.
163
164% get the value for a tiven key in Map1. If not found, try same key in Map2. If not found, return Default
165-spec twomap_get(atom(), map(), map(), any()) -> any().
166twomap_get(Key, Map1, Map2, Default) ->
167 maps:get(Key, Map1, maps:get(Key, Map2, Default)).
168
169handle_request(#diameter_packet{msg = Req, errors = []}, _SvcName, {_, Caps}) when is_record(Req, 'AIR') ->
170 lager:info("AIR: ~p~n", [Req]),
171 % extract relevant fields from DIAMETER AIR
172 #diameter_caps{origin_host = {OH,_}, origin_realm = {OR,_}} = Caps,
173 #'AIR'{'Session-Id' = SessionId,
174 'User-Name' = UserName,
175 'Visited-PLMN-Id' = VplmnId,
176 'Requested-EUTRAN-Authentication-Info' = ReqEU,
177 'Requested-UTRAN-GERAN-Authentication-Info' = ReqUG} = Req,
178 VplmnIdBin = list_to_binary(VplmnId),
179 NumEutran = req_num_of_vec(ReqEU),
180 NumUgran = req_num_of_vec(ReqUG),
181 lager:info("Num EUTRAN=~p, UTRAN=~p~n", [NumEutran, NumUgran]),
182 % construct GSUP request to HLR and transceive it
Harald Welte332fe7f2019-08-20 22:36:50 +0200183 GsupTx1 = #{message_type => send_auth_info_req, imsi => list_to_binary(UserName)},
184 case ReqEU of
185 #'Requested-EUTRAN-Authentication-Info'{'Re-Synchronization-Info' = ReSyncInfo}
186 when is_binary(ReSyncInfo) ->
187 GsupTx2 = #{rand => string:substr(ReSyncInfo, 1, 16),
188 auts => string:substr(ReSyncInfo, 17)};
189 _ ->
190 GsupTx2 = #{}
191 end,
192 GsupTx = maps:merge(GsupTx1, GsupTx2),
Harald Welte44da7d72019-08-14 13:28:08 +0200193 GsupRx = gen_server:call(gsup_client, {transceive_gsup, GsupTx, send_auth_info_res, send_auth_info_err}),
194 lager:info("GsupRx: ~p~n", [GsupRx]),
195 % construct DIAMETER AIA response
196 case GsupRx of
197 #{message_type:=send_auth_info_res, auth_tuples:=GsupAuthTuples} ->
198 AuthInfo = gsup_tuples2dia(GsupAuthTuples, VplmnIdBin, NumEutran, NumUgran, NumUgran),
199 Resp = #'AIA'{'Session-Id'=SessionId, 'Origin-Host'=OH, 'Origin-Realm'=OR,
200 'Result-Code'=2001, 'Auth-Session-State'=1,
201 'Authentication-Info'=AuthInfo};
202 #{message_type := send_auth_info_err} ->
203 Resp = #'AIA'{'Session-Id'=SessionId, 'Origin-Host'=OH, 'Origin-Realm'=OR,
204 'Result-Code'=?DIAMETER_ERROR_USER_UNKNOWN,
205 'Auth-Session-State'=1};
206 timeout ->
207 Resp = #'AIA'{'Session-Id'=SessionId, 'Origin-Host'=OH, 'Origin-Realm'=OR,
208 'Result-Code'=4181, 'Auth-Session-State'=1}
209 end,
210 lager:info("Resp: ~p~n", [Resp]),
211 {reply, Resp};
212
213handle_request(#diameter_packet{msg = Req, errors = []}, _SvcName, {_, Caps}) when is_record(Req, 'ULR') ->
214 % extract relevant fields from DIAMETER AIR
215 #diameter_caps{origin_host = {OH,_}, origin_realm = {OR,_}} = Caps,
216 #'ULR'{'Session-Id' = SessionId,
217 'RAT-Type' = RatType,
218 'ULR-Flags' = UlrFlags,
219 'User-Name' = UserName} = Req,
220
221 % construct GSUP UpdateLocation request to HLR and transceive it; expect InsertSubscrDataReq
Harald Welte299ba932019-08-15 18:31:12 +0200222 GsupTxUlReq = #{message_type => location_upd_req, imsi => list_to_binary(UserName),
223 cn_domain => 1},
Harald Welte44da7d72019-08-14 13:28:08 +0200224 GsupRxIsdReq = gen_server:call(gsup_client,
225 {transceive_gsup, GsupTxUlReq, insert_sub_data_req, location_upd_err}),
226 lager:info("GsupRxIsdReq: ~p~n", [GsupRxIsdReq]),
227 case GsupRxIsdReq of
228 #{message_type:=location_upd_err, cause:=Cause} ->
229 {Res, ExpRes} = gsup_cause2dia(Cause),
230 Resp = #'ULA'{'Session-Id'= SessionId, 'Auth-Session-State'=1,
231 'Origin-Host'=OH, 'Origin-Realm'=OR,
232 'Result-Code'=Res, 'Experimental-Result'=ExpRes};
233 #{message_type:=insert_sub_data_req} ->
234 % construct GSUP InsertSubscrData response to HLR and transceive it; expect
235 % UpdateLocationRes
Harald Welte299ba932019-08-15 18:31:12 +0200236 GsupTxIsdRes = #{message_type => insert_sub_data_res,
237 imsi => list_to_binary(UserName)},
Harald Welte44da7d72019-08-14 13:28:08 +0200238 GsupRxUlRes = gen_server:call(gsup_client,
239 {transceive_gsup, GsupTxIsdRes, location_upd_res, location_upd_err}),
240 lager:info("GsupRxUlRes: ~p~n", [GsupRxUlRes]),
241
242 case GsupRxUlRes of
243 #{message_type:=location_upd_res} ->
244 Msisdn = twomap_get(msisdn, GsupRxIsdReq, GsupRxUlRes, []),
Harald Welte299ba932019-08-15 18:31:12 +0200245 Compl = twomap_get(pdp_info_complete, GsupRxIsdReq, GsupRxUlRes, 0),
246
247 % build the GPRS Subscription Data
Harald Welte44da7d72019-08-14 13:28:08 +0200248 PdpInfoList = twomap_get(pdp_info_list, GsupRxIsdReq, GsupRxUlRes, []),
Harald Welte299ba932019-08-15 18:31:12 +0200249 PdpContexts = lists:map(fun gsup_pdp2dia/1, PdpInfoList),
250 GSubD = #'GPRS-Subscription-Data'{'Complete-Data-List-Included-Indicator'=Compl,
Harald Welte44da7d72019-08-14 13:28:08 +0200251 'PDP-Context'=PdpContexts},
Harald Welte299ba932019-08-15 18:31:12 +0200252
253 % build the APN-Configuration-Profile
254 ApnCfgList = lists:map(fun gsup_pdp2dia_apn/1, PdpInfoList),
255 FirstApn = lists:nth(1, ApnCfgList),
256 DefaultCtxId = FirstApn#'APN-Configuration'.'Context-Identifier',
257 ApnCfgProf = #'APN-Configuration-Profile'{'Context-Identifier' = DefaultCtxId,
258 'All-APN-Configurations-Included-Indicator'=Compl,
259 'APN-Configuration' = ApnCfgList},
260
261 % put together the Subscription-Data and finally the ULA response
262 SubscrData = #'Subscription-Data'{'MSISDN' = Msisdn,
263
264 'Network-Access-Mode' = 0, % PACKET_AND_CIRCUIT
265 'GPRS-Subscription-Data' = GSubD,
266 % Subscriber-Status must be present in ULA
267 'Subscriber-Status' = 0,
268 % AMBR must be present if this is an ULA; let's permit 100MBps UL + DL
269 'AMBR' = #'AMBR'{'Max-Requested-Bandwidth-UL' = 100000000,
270 'Max-Requested-Bandwidth-DL' = 100000000},
271 'APN-Configuration-Profile' = ApnCfgProf},
272 Resp = #'ULA'{'Session-Id' = SessionId, 'Auth-Session-State' = 1,
273 'Origin-Host' = OH, 'Origin-Realm' = OR,
274 'Result-Code' = 2001,
275 'Subscription-Data' = SubscrData, 'ULA-Flags' = 0};
Harald Welte44da7d72019-08-14 13:28:08 +0200276 #{message_type:=location_upd_err, cause:=Cause} ->
277 {Res, ExpRes} = gsup_cause2dia(Cause),
278 Resp = #'ULA'{'Session-Id'= SessionId, 'Auth-Session-State'=1,
279 'Origin-Host'=OH, 'Origin-Realm'=OR,
280 'Result-Code'=Res, 'Experimental-Result'=ExpRes};
281 _ ->
282 Resp = #'ULA'{'Session-Id'= SessionId, 'Auth-Session-State'=1,
283 'Origin-Host'=OH, 'Origin-Realm'=OR,
284 'Result-Code'=fixme}
285 end
286 end,
Harald Welte299ba932019-08-15 18:31:12 +0200287 lager:info("ULR Resp: ~p~n", [Resp]),
Harald Welte44da7d72019-08-14 13:28:08 +0200288 {reply, Resp};
289
290handle_request(Packet, _SvcName, {_,_}) ->
291 lager:error("Unsuppoerted message: ~p~n", [Packet]),
Harald Welte61276c42019-08-10 22:14:50 +0200292 discard.