Add support for CURRENT_RAT_TYPE IE

In libosmcore.git Change-Id I93850710ab55a605bf61b95063a69682a2899bb1,
a new OSMO_GSUP_CURRENT_RAT_TYPE_IE was introduced.  Let's add support
for it here, too.
This commit is contained in:
Harald Welte 2019-12-01 16:28:48 +01:00
parent bb32d46b18
commit b470dfa204
3 changed files with 18 additions and 4 deletions

View File

@ -3,6 +3,7 @@
% file, You can obtain one at https://mozilla.org/MPL/2.0/.
% (C) 2019 Andrey Velikiy <agreat22@gmail.com>
% (C) 2019 Fairwaves (edited)
% (C) 2019 Harald Welte <laforge@gnumonks.org>
-ifndef(GSUP_PROTOCOL).
-define(GSUP_PROTOCOL, true).
@ -93,6 +94,7 @@
auts => binary(),
cn_domain => integer(),
supported_rat_types => ['GSUPRatType'()],
current_rat_type => 'GSUPRatType'(),
session_id => integer(),
session_state => integer(),
ss_info => binary(),
@ -143,6 +145,7 @@
-define(RES, 16#27).
-define(CN_DOMAIN, 16#28).
-define(SUPPORTED_RAT_TYPES, 16#29).
-define(CURRENT_RAT_TYPE, 16#2a).
-define(SESSION_ID, 16#30).
-define(SESSION_STATE, 16#31).
-define(SS_INFO, 16#35).
@ -170,7 +173,7 @@
16#04 => #{message_type => location_upd_req, mandatory => [], optional => [cn_domain]},
16#05 => #{message_type => location_upd_err, mandatory => [cause]},
16#06 => #{message_type => location_upd_res, mandatory => [], optional => [msisdn, hlr_number, pdp_info_complete, pdp_info_list, pdp_charging]},
16#08 => #{message_type => send_auth_info_req, mandatory => [], optional => [cn_domain, auts, rand, supported_rat_types]},
16#08 => #{message_type => send_auth_info_req, mandatory => [], optional => [cn_domain, auts, rand, supported_rat_types, current_rat_type]},
16#09 => #{message_type => send_auth_info_err, mandatory => [cause]},
16#0a => #{message_type => send_auth_info_res, mandatory => [], optional => [auth_tuples, auts, rand]},
16#0b => #{message_type => auth_failure_report, mandatory => [], optional => [cn_domain]},

View File

@ -112,6 +112,10 @@ decode_ie(<<?SUPPORTED_RAT_TYPES, Len, Rat_Type:Len/binary, Tail/binary>>, Map)
?CHECK_LEN(supported_rat_types, Len, 1, 8),
decode_ie(Tail, Map#{supported_rat_types => decode_rat_types(binary_to_list(Rat_Type))});
decode_ie(<<?CURRENT_RAT_TYPE, Len, Rat_Type:Len/unit:8, Tail/binary>>, Map) ->
?CHECK_LEN(current_rat_type, Len, 1, 1),
decode_ie(Tail, Map#{current_rat_type => decode_rat_type(Rat_Type)});
decode_ie(<<?SESSION_ID, Len, SesID:Len/unit:8, Tail/binary>>, Map) ->
?CHECK_LEN(session_id, Len, 4, 4),
decode_ie(Tail, Map#{session_id => SesID});
@ -411,6 +415,12 @@ encode_ie(#{supported_rat_types := Value} = GSUPMessage, Head) when is_list(Valu
RatList = encode_rat_types(Value),
encode_ie(maps:without([supported_rat_types], GSUPMessage), <<Head/binary, ?SUPPORTED_RAT_TYPES, Len, RatList/binary>>);
encode_ie(#{current_rat_type := Value} = GSUPMessage, Head) ->
Len = 1,
?CHECK_LEN(current_rat_type, Len, 1, 1),
Rat = encode_rat_type(Value),
encode_ie(maps:without([current_rat_type], GSUPMessage), <<Head/binary, ?CURRENT_RAT_TYPE, Len, Rat:Len/unit:8>>);
encode_ie(#{ss_info := Value} = GSUPMessage, Head) ->
Len = size(Value),
encode_ie(maps:without([ss_info], GSUPMessage), <<Head/binary, ?SS_INFO, Len, Value/binary>>);

View File

@ -15,7 +15,8 @@
-define(TEST_AN_APDU_IE, 16#62, 16#05, 16#01, 16#42, 16#42, 16#42, 16#42).
-define(TEST_SOURCE_NAME_IE, 16#60, 16#05, "MSC-A").
-define(TEST_DESTINATION_NAME_IE, 16#61, 16#05, "MSC-B").
-define(TEST_SUPP_RAT_TYPES_IE, 16#29, 16#01, 16#03).
-define(TEST_SUPP_RAT_TYPES_IE, 16#29, 16#02, 16#01, 16#03).
-define(TEST_CURR_RAT_TYPE_LTE_IE, 16#2a, 16#01, 16#03).
missing_params_test() ->
@ -44,9 +45,9 @@ sai_req_test() ->
?assertEqual(Bin, gsup_protocol:encode(Map)).
sai_req_eps_test() ->
Bin = <<16#08, ?TEST_IMSI_IE, ?TEST_CLASS_SUBSCR_IE, ?TEST_SUPP_RAT_TYPES_IE>>,
Bin = <<16#08, ?TEST_IMSI_IE, ?TEST_CLASS_SUBSCR_IE, ?TEST_SUPP_RAT_TYPES_IE, ?TEST_CURR_RAT_TYPE_LTE_IE>>,
Map = #{imsi => <<"123456789012345">>, message_class => 1, message_type => send_auth_info_req,
supported_rat_types => [rat_eutran_sgs]},
supported_rat_types => [rat_geran_a, rat_eutran_sgs], current_rat_type => rat_eutran_sgs},
?assertEqual(Map, gsup_protocol:decode(Bin)),
?assertEqual(Bin, gsup_protocol:encode(Map)).