gsup: Convert PDP-Type IE to PDP-Address IE

The previous PDP-Type IE should have been a PDP-Address from the
start, since having only PDP-Type with no address is only a specific
case (dynamic addressing).
This becomes clear by looking at other similar protocols like:
* MAP: APN-Configuration IE has servedPartyIP-IP{v4,v6}-Address IEs
* Diameter S6b, 3GPP TS 29.272 7.3.35 APN-Configuration contains
  Served-Party-IP-Address AVPs
* Diameter SWx, 3GPP TS 29.273 APN-Configuration.
* GTPv1C Ts 29.060 7.7.29 PDP Context containing PDP Address.

Since PDP-Type on its own really makes no sense, being it a special case
of PDP-Address, let's keep the IE by renaming it (keeping old name too
for API backward compat) and extend it to support lengths > 2 bytes.

Old implementation of libosmogsm gsup actually ignored lengths > 2
bytes, so we are safe acting against older implementations here, both
on the sending and receiving side on the wire.

The big drawback of this commit is that it breaks ABI compatibility due
to adding "struct osmo_sockaddr pdp_address[2];" to struct
osmo_gsup_pdp_info, which in turn affects shift of fields in struct
osmo_gsup_message. Unfortunately, there's not much that can be done to
improve the situation when adding the missing field, due to existing API
having the same struct for all messages. Ideally we'd have 1 union with
structs per message type inside, this way the ABI break would be far
less pronounced.

Related: OS#6091
Depends: libosmocore.git Change-Id 70be3560659c58f24b8db529c4fc85da4bb0ec04
Depends: osmo-gsm-manuals.git Change-Id Ifb4e44b23d19ea049f03a3602c39f2471ff1bff4
Change-Id: I05562d7b0c0941ee619cbf07d90af47652c3897c
This commit is contained in:
Pau Espin 2024-01-22 14:15:43 +01:00
parent d023f75c55
commit 058a99393e
3 changed files with 48 additions and 17 deletions

View File

@ -72,9 +72,15 @@
res => binary()
}.
-type 'GSUPPdpAddress'() :: #{
pdp_type_org => integer(),
pdp_type_nr => integer(),
address => binary()
}.
-type 'GSUPPdpInfo'() :: #{
pdp_context_id => integer(),
pdp_type => integer(),
pdp_address => 'GSUPPdpAddress'(),
access_point_name => binary(),
quality_of_service => binary(),
pdp_charging => integer()
@ -135,7 +141,7 @@
-define(HLR_NUMBER, 16#09).
-define(MESSAGE_CLASS, 16#0a).
-define(PDP_CONTEXT_ID, 16#10).
-define(PDP_TYPE, 16#11).
-define(PDP_ADDRESS, 16#11).
-define(ACCESS_POINT_NAME, 16#12).
-define(QUALITY_OF_SERVICE, 16#13).
-define(PDP_CHARGING, 16#14).
@ -225,12 +231,12 @@
16#4e => #{message_type => e_routing_err, mandatory => [message_class, source_name, destination_name], optional => [session_id, session_state]},
16#50 => #{message_type => epdg_tunnel_request, mandatory => [message_class], optional => []},
16#51 => #{message_type => epdg_tunnel_error, mandatory => [message_class, cause], optional => []},
16#52 => #{message_type => epdg_tunnel_result, mandatory => [message_class], optional => []}
16#52 => #{message_type => epdg_tunnel_result, mandatory => [message_class, pdp_info_complete, pdp_info_list], optional => []}
}).
-define(AUTH_TUPLE_MANDATORY, []).
-define(AUTH_TUPLE_OPTIONAL, [rand, sres, kc, ik, ck, autn, res]).
-define(PDP_INFO_MANDATORY, []).
-define(PDP_INFO_OPTIONAL, [pdp_context_id, pdp_type, access_point_name, quality_of_service, pdp_charging]).
-define(PDP_INFO_OPTIONAL, [pdp_context_id, pdp_address, access_point_name, quality_of_service, pdp_charging]).
-endif.

View File

@ -251,9 +251,19 @@ decode_pdp_info(<<?PDP_CONTEXT_ID, Len, PDPContextId:Len/unit:8, Tail/binary>>,
?CHECK_LEN(pdp_context_id, Len, 1, 1),
decode_pdp_info(Tail, Map#{pdp_context_id => PDPContextId});
decode_pdp_info(<<?PDP_TYPE, Len, PDPType:Len/unit:8, Tail/binary>>, Map) ->
?CHECK_LEN(pdp_type, Len, 2, 2),
decode_pdp_info(Tail, Map#{pdp_type => PDPType});
decode_pdp_info(<<?PDP_ADDRESS, Len, PDPAddress:Len/binary, Tail/binary>>, Map) ->
?CHECK_LEN(pdp_address, Len, 2, 22),
<<PDPTypeOrg:8, PDPTypeNr:8, Addr/binary>> = PDPAddress,
case Len - 2 of
20 -> <<IPv4:4/binary, IPv6:16/binary>> = Addr,
AddrMap = #{ipv4 => IPv4, ipv6 => IPv6};
16 -> <<IPv6:16/binary>> = Addr,
AddrMap = #{ipv6 => IPv6};
4 -> <<IPv4:4/binary>> = Addr,
AddrMap = #{ipv4 => IPv4};
0 -> AddrMap = #{}
end,
decode_pdp_info(Tail, Map#{pdp_address => #{pdp_type_org => PDPTypeOrg, pdp_type_nr => PDPTypeNr, address => AddrMap}});
decode_pdp_info(<<?ACCESS_POINT_NAME, Len, APN:Len/binary, Tail/binary>>, Map) ->
?CHECK_LEN(access_point_name, Len, 1, 100),
@ -594,10 +604,20 @@ encode_pdp_info(#{pdp_context_id := Value} = Map, Head) ->
?CHECK_SIZE(pdp_context_id, Len, Value),
encode_pdp_info(maps:without([pdp_context_id], Map), <<Head/binary, ?PDP_CONTEXT_ID, Len, Value:Len/unit:8>>);
encode_pdp_info(#{pdp_type := Value} = Map, Head) ->
Len = 2,
?CHECK_SIZE(pdp_type, Len, Value),
encode_pdp_info(maps:without([pdp_type], Map), <<Head/binary, ?PDP_TYPE, Len, Value:Len/unit:8>>);
encode_pdp_info(#{pdp_address := Value} = Map, Head) ->
#{pdp_type_org := PDPTypeOrg, pdp_type_nr := PDPTypeNr, address := AddrMap} = Value,
case AddrMap of
#{ipv4 := IPv4, ipv6 := IPv6} ->
Addr = <<IPv4/binary, IPv6/binary>>;
#{ipv4 := IPv4} ->
Addr = <<IPv4/binary>>;
#{ipv6 := IPv6} ->
Addr = <<IPv6/binary>>;
#{} ->
Addr = <<>>
end,
Len = 2 + size(Addr),
encode_pdp_info(maps:without([pdp_address], Map), <<Head/binary, ?PDP_ADDRESS, Len, PDPTypeOrg, PDPTypeNr, Addr/binary>>);
encode_pdp_info(#{access_point_name := Value} = Map, Head) ->
Len = size(Value),

View File

@ -2,7 +2,7 @@
% License, v. 2.0. If a copy of the MPL was not distributed with this
% 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 Fairwaves (edited)
-module (gsup_encode_decode_test).
@ -67,7 +67,7 @@ sai_err_test() ->
?assertEqual(Bin, gsup_protocol:encode(Map)).
sai_res_test() ->
Bin = <<16#0a, ?TEST_IMSI_IE,
Bin = <<16#0a, ?TEST_IMSI_IE,
16#03, 16#22, %% Auth tuple
16#20, 16#10,
16#01, 16#02, 16#03, 16#04, 16#05, 16#06, 16#07, 16#08,
@ -100,7 +100,7 @@ sai_res_test() ->
?assertEqual(Bin, gsup_protocol:encode(Map)).
sai_res_umts_test() ->
Bin = <<16#0a, ?TEST_IMSI_IE,
Bin = <<16#0a, ?TEST_IMSI_IE,
16#03, 16#62, %% Auth tuple
16#20, 16#10, %% rand
16#01, 16#02, 16#03, 16#04, 16#05, 16#06, 16#07, 16#08,
@ -166,7 +166,7 @@ sai_res_umts_test() ->
?assertEqual(Bin, gsup_protocol:encode(Map)).
sai_res_auts_test() ->
Bin = <<16#0a, ?TEST_IMSI_IE,
Bin = <<16#0a, ?TEST_IMSI_IE,
16#26, 16#0e, %% AUTS (UMTS)
16#01, 16#02, 16#03, 16#04, 16#05, 16#06, 16#07, 16#08,
16#09, 16#0a, 16#0b, 16#0c, 16#0d, 16#0e,
@ -220,10 +220,15 @@ lu_res_test() ->
[#{access_point_name =>
<<4,116,101,115,116,3,97,112,110>>,
pdp_charging => 65315,pdp_context_id => 1,
pdp_type => 61729,
pdp_address => #{address => #{},
pdp_type_org => 241,
pdp_type_nr => 33},
quality_of_service => <<2>>},
#{access_point_name => <<3,102,111,111,3,97,112,110>>,
pdp_context_id => 2,pdp_type => 61729}]},
pdp_context_id => 2,
pdp_address => #{address => #{},
pdp_type_org => 241,
pdp_type_nr => 33}}]},
?assertEqual(Map, gsup_protocol:decode(Bin)),
?assertEqual(Bin, gsup_protocol:encode(Map)).