add support for the RAT Type IE of GSUP

This commit is contained in:
Harald Welte 2019-08-22 13:48:00 +02:00
parent c92ebfa444
commit b76c7fad94
3 changed files with 44 additions and 1 deletions

View File

@ -56,6 +56,8 @@
| e_abort
| e_routing_err.
-type 'GSUPRatType'() :: rat_unknown | rat_geran_a | rat_utran_iu | rat_eutran_sgs.
-type 'GSUPAuthTuple'() :: #{
rand := binary(),
sres := binary(),
@ -90,6 +92,7 @@
rand => binary(),
auts => binary(),
cn_domain => integer(),
rat_type => 'GSUPRatType'(),
session_id => integer(),
session_state => integer(),
ss_info => binary(),
@ -139,6 +142,7 @@
-define(AUTS, 16#26).
-define(RES, 16#27).
-define(CN_DOMAIN, 16#28).
-define(RAT_TYPE, 16#29).
-define(SESSION_ID, 16#30).
-define(SESSION_STATE, 16#31).
-define(SS_INFO, 16#35).
@ -166,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]},
16#08 => #{message_type => send_auth_info_req, mandatory => [], optional => [cn_domain, auts, rand, 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

@ -108,6 +108,10 @@ 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(<<?SESSION_ID, Len, SesID:Len/unit:8, Tail/binary>>, Map) ->
?CHECK_LEN(session_id, Len, 4, 4),
decode_ie(Tail, Map#{session_id => SesID});
@ -257,6 +261,17 @@ decode_pdp_info(<<?PDP_CHARGING, Len, PDPCharging:Len/unit:8, Tail/binary>>, Map
decode_pdp_info(<<>>, Map) -> Map.
decode_rat_type(0) -> rat_unknown;
decode_rat_type(1) -> rat_geran_a;
decode_rat_type(2) -> rat_utran_iu;
decode_rat_type(3) -> rat_eutran_sgs.
decode_rat_types([], Acc) -> lists:reverse(Acc);
decode_rat_types([Head|Tail], Acc) ->
T = decode_rat_type(Head),
decode_rat_types(Tail, [T|Acc]).
decode_rat_types(List) -> decode_rat_types(List, []).
-spec encode('GSUPMessage'()) -> binary() | no_return().
encode(GSUPMessage = #{message_type := MsgTypeAtom}) when is_atom(MsgTypeAtom) ->
F = fun
@ -390,6 +405,12 @@ 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) ->
Len = length(Value),
?CHECK_LEN(rat_type, Len, 1, 8),
RatList = encode_rat_types(Value),
encode_ie(maps:without([rat_type], GSUPMessage), <<Head/binary, ?RAT_TYPE, Len, RatList/binary>>);
encode_ie(#{ss_info := Value} = GSUPMessage, Head) ->
Len = size(Value),
encode_ie(maps:without([ss_info], GSUPMessage), <<Head/binary, ?SS_INFO, Len, Value/binary>>);
@ -575,3 +596,14 @@ encode_pdp_info(#{pdp_charging := Value} = Map, Head) ->
encode_pdp_info(maps:without([pdp_charging], Map), <<Head/binary, ?PDP_CHARGING, Len, Value:Len/unit:8>>);
encode_pdp_info(#{}, Head) -> Head.
encode_rat_type(rat_unknown) -> 0;
encode_rat_type(rat_geran_a) -> 1;
encode_rat_type(rat_utran_iu) -> 2;
encode_rat_type(rat_eutran_sgs) -> 3.
encode_rat_types([], Acc) -> list_to_binary(lists:reverse(Acc));
encode_rat_types([Head|Tail], Acc) ->
T = encode_rat_type(Head),
encode_rat_types(Tail, [T|Acc]).
encode_rat_types(List) -> encode_rat_types(List, []).

View File

@ -42,6 +42,13 @@ sai_req_test() ->
?assertEqual(Map, gsup_protocol:decode(Bin)),
?assertEqual(Bin, gsup_protocol:encode(Map)).
sai_req_eps_test() ->
Bin = <<16#08, ?TEST_IMSI_IE, ?TEST_CLASS_SUBSCR_IE>>,
Map = #{imsi => <<"123456789012345">>, message_class => 1, message_type => send_auth_info_req,
rat_type => [rat_eutran_sgs]},
?assertEqual(Map, gsup_protocol:decode(Bin)),
?assertEqual(Bin, gsup_protocol:encode(Map)).
sai_err_test() ->
Bin = <<16#09, ?TEST_IMSI_IE, 16#02, 16#01, 16#07>>,
Map = #{imsi => <<"123456789012345">>, message_type => send_auth_info_err, cause=>7},