GSUP IE 0x29 got renamed from RAT_TYPE to SUPPORTED_RAT_TYPEs

In git commit b76c7fad94 we introduced
support for the GSUP RAT_TYPE IE (0x29).  At that time, the
corresponding libosmocore change (Change-Id
I93850710ab55a605bf61b95063a69682a2899bb1) was still in review.

Meanwhile, that change has been merged, and the final IE name now
is OSMO_GSUP_SUPPORTED_RAT_TYPES_IE.
This commit is contained in:
Harald Welte 2019-12-01 16:20:50 +01:00
parent b76c7fad94
commit bb32d46b18
3 changed files with 12 additions and 11 deletions

View File

@ -92,7 +92,7 @@
rand => binary(),
auts => binary(),
cn_domain => integer(),
rat_type => 'GSUPRatType'(),
supported_rat_types => ['GSUPRatType'()],
session_id => integer(),
session_state => integer(),
ss_info => binary(),
@ -142,7 +142,7 @@
-define(AUTS, 16#26).
-define(RES, 16#27).
-define(CN_DOMAIN, 16#28).
-define(RAT_TYPE, 16#29).
-define(SUPPORTED_RAT_TYPES, 16#29).
-define(SESSION_ID, 16#30).
-define(SESSION_STATE, 16#31).
-define(SS_INFO, 16#35).
@ -170,7 +170,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, rat_type]},
16#08 => #{message_type => send_auth_info_req, mandatory => [], optional => [cn_domain, auts, rand, supported_rat_types]},
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

@ -108,9 +108,9 @@ decode_ie(<<?CN_DOMAIN, Len, CN_Domain:Len/unit:8, Tail/binary>>, Map) ->
?CHECK_LEN(cn_domain, Len, 1, 1),
decode_ie(Tail, Map#{cn_domain => CN_Domain});
decode_ie(<<?RAT_TYPE, Len, Rat_Type:Len/binary, Tail/binary>>, Map) ->
?CHECK_LEN(rat_type, Len, 1, 8),
decode_ie(Tail, Map#{rat_type => decode_rat_types(binary_to_list(Rat_Type))});
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(<<?SESSION_ID, Len, SesID:Len/unit:8, Tail/binary>>, Map) ->
?CHECK_LEN(session_id, Len, 4, 4),
@ -405,11 +405,11 @@ encode_ie(#{cn_domain := Value} = GSUPMessage, Head) ->
?CHECK_SIZE(cn_domain, Len, Value),
encode_ie(maps:without([cn_domain], GSUPMessage), <<Head/binary, ?CN_DOMAIN, Len, Value:Len/unit:8>>);
encode_ie(#{rat_type := Value} = GSUPMessage, Head) when is_list(Value) ->
encode_ie(#{supported_rat_types := Value} = GSUPMessage, Head) when is_list(Value) ->
Len = length(Value),
?CHECK_LEN(rat_type, Len, 1, 8),
?CHECK_LEN(supported_rat_types, Len, 1, 8),
RatList = encode_rat_types(Value),
encode_ie(maps:without([rat_type], GSUPMessage), <<Head/binary, ?RAT_TYPE, Len, RatList/binary>>);
encode_ie(maps:without([supported_rat_types], GSUPMessage), <<Head/binary, ?SUPPORTED_RAT_TYPES, Len, RatList/binary>>);
encode_ie(#{ss_info := Value} = GSUPMessage, Head) ->
Len = size(Value),

View File

@ -15,6 +15,7 @@
-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).
missing_params_test() ->
@ -43,9 +44,9 @@ sai_req_test() ->
?assertEqual(Bin, gsup_protocol:encode(Map)).
sai_req_eps_test() ->
Bin = <<16#08, ?TEST_IMSI_IE, ?TEST_CLASS_SUBSCR_IE>>,
Bin = <<16#08, ?TEST_IMSI_IE, ?TEST_CLASS_SUBSCR_IE, ?TEST_SUPP_RAT_TYPES_IE>>,
Map = #{imsi => <<"123456789012345">>, message_class => 1, message_type => send_auth_info_req,
rat_type => [rat_eutran_sgs]},
supported_rat_types => [rat_eutran_sgs]},
?assertEqual(Map, gsup_protocol:decode(Bin)),
?assertEqual(Bin, gsup_protocol:encode(Map)).