Create PDP Context in tunnel after rx S6b CreateSessionResp

This refactoring is a preparation to call the gtp_u_kmod APIs.

Change-Id: I911985743af6b3fa90fd78631a562b85ecacce15
This commit is contained in:
Pau Espin 2024-02-08 15:01:27 +01:00 committed by pespin
parent 4802aaca86
commit 50f17900a1
5 changed files with 134 additions and 38 deletions

View File

@ -38,7 +38,27 @@
-include_lib("gtp_utils.hrl").
-include_lib("conv.hrl").
-export([cause_gtp2gsup/1, gtp2_paa_to_epdg_eua/1, epdg_eua_to_gsup_pdp_address/1]).
-export([ip_to_bin/1, bin_to_ip/1]).
-export([cause_gtp2gsup/1]).
-export([gtp2_paa_to_epdg_eua/1, epdg_eua_to_gsup_pdp_address/1]).
% ergw_aaa/src/ergw_aaa_3gpp_dict.erl
% under GPLv2+
ip_to_bin(IP) when is_binary(IP) ->
IP;
ip_to_bin({A, B, C, D}) ->
<<A, B, C, D>>;
ip_to_bin({A, B, C, D, E, F, G, H}) ->
<<A:16, B:16, C:16, D:16, E:16, F:16, G:16, H:16>>.
bin_to_ip(<<A:8, B:8, C:8, D:8>> = IP) when is_binary(IP) ->
{A, B, C, D};
bin_to_ip(<<A:16, B:16, C:16, D:16, E:16, F:16, G:16, H:16>> = IP) when is_binary(IP) ->
{A, B, C, D, E, F, G, H};
bin_to_ip({_, _, _, _} = IP) ->
IP;
bin_to_ip({_, _, _, _, _, _, _, _} = IP) ->
IP.
-spec cause_gtp2gsup(integer()) -> integer().

View File

@ -258,6 +258,11 @@ gtp_session_add_bearer(Sess, Bearer) ->
lager:debug("Add bearer ~p to session ~p~n", [Bearer, Sess]),
Sess#gtp_session{bearers = sets:add_element(Bearer, Sess#gtp_session.bearers)}.
gtp_session_update_bearer(Sess, OldBearer, NewBearer) ->
SetRemoved = sets:del_element(OldBearer, Sess#gtp_session.bearers),
SetUpdated = sets:add_element(NewBearer, SetRemoved),
Sess#gtp_session{bearers = SetUpdated}.
gtp_session_del_bearer(Sess, Bearer) ->
lager:debug("Remove bearer ~p from session ~p~n", [Bearer, Sess]),
Sess1 = Sess#gtp_session{bearers = sets:del_element(Bearer, Sess#gtp_session.bearers)},
@ -269,25 +274,6 @@ gtp_session_del_bearer(Sess, Bearer) ->
gtp_session_default_bearer(Sess) ->
gtp_session_find_bearer_by_ebi(Sess, Sess#gtp_session.default_bearer_id).
update_gtp_session_from_create_session_response_ie(none, Sess) ->
Sess;
update_gtp_session_from_create_session_response_ie({_,
#v2_fully_qualified_tunnel_endpoint_identifier{
interface_type = _Interface,
key = TEI, ipv4 = _IP4, ipv6 = _IP6},
Next}, Sess) ->
update_gtp_session_from_create_session_response_ie(maps:next(Next), Sess#gtp_session{remote_control_tei = TEI});
update_gtp_session_from_create_session_response_ie({_, _, Next},
Sess) ->
update_gtp_session_from_create_session_response_ie(maps:next(Next), Sess).
update_gtp_session_from_create_session_response_ies(#gtp{ie = IEs}, Sess) ->
update_gtp_session_from_create_session_response_ie(maps:next(maps:iterator(IEs)), Sess).
update_gtp_session_from_create_session_response(Resp = #gtp{version = v2, type = create_session_response}, Sess) ->
update_gtp_session_from_create_session_response_ies(#gtp{ie = Resp#gtp.ie}, Sess).
% returns Sess if found, undefined it not
find_gtp_session_by_local_teic(LocalControlTei, State) ->
{LocalControlTei, Res} = sets:fold(
@ -313,13 +299,31 @@ rx_gtp(Resp = #gtp{version = v2, type = create_session_response}, State0) ->
lager:error("Rx unknown TEI ~p: ~p~n", [Resp#gtp.tei, Resp]),
{noreply, State0};
Sess0 ->
Sess1 = update_gtp_session_from_create_session_response(Resp, Sess0),
lager:info("s2b: Updated Session after create_session_response: ~p~n", [Sess1]),
State1 = update_gtp_session(Sess0, Sess1, State0),
% Do GTP specific msg parsing here, pass only relevant fields:
#{{v2_pdn_address_allocation,0} := Paa} = Resp#gtp.ie,
#{{v2_fully_qualified_tunnel_endpoint_identifier,1} :=
#v2_fully_qualified_tunnel_endpoint_identifier{
interface_type = 30, %% "S2b ePDG GTP-C"
key = RemoteTEIC, ipv4 = _IPc4, ipv6 = _IPc6},
{v2_pdn_address_allocation,0} := Paa,
{v2_bearer_context,0} := #v2_bearer_context{instance = 0, group = BearerIE}} = Resp#gtp.ie,
% Parse BearerContext:
#{{v2_eps_bearer_id,0} := #v2_eps_bearer_id{instance = 0, eps_bearer_id = Ebi},
{v2_fully_qualified_tunnel_endpoint_identifier,4} :=
#v2_fully_qualified_tunnel_endpoint_identifier{
interface_type = 31, %% "S2b-U ePDG GTP-U"
key = RemoteTEID, ipv4 = IPu4, ipv6 = IPu6}
} = BearerIE,
Bearer = gtp_session_find_bearer_by_ebi(Sess0, Ebi),
Sess1 = gtp_session_update_bearer(Sess0, Bearer, Bearer#gtp_bearer{remote_data_tei = RemoteTEID}),
Sess2 = Sess1#gtp_session{remote_control_tei = RemoteTEIC},
lager:info("s2b: Updated Session after create_session_response: ~p~n", [Sess2]),
State1 = update_gtp_session(Sess0, Sess2, State0),
ResInfo = #{
eua => conv:gtp2_paa_to_epdg_eua(Paa)
eua => conv:gtp2_paa_to_epdg_eua(Paa),
local_teid => Bearer#gtp_bearer.local_data_tei,
remote_teid => RemoteTEID,
remote_ipv4 => IPu4,
remote_ipv6 => IPu6
},
epdg_ue_fsm:received_gtpc_create_session_response(Sess0#gtp_session.pid, {ok, ResInfo}),
{noreply, State1}
@ -406,7 +410,7 @@ gen_create_session_request(#gtp_session{imsi = Imsi,
instance = Bearer#gtp_bearer.ebi,
interface_type = 31, %% "S2b-U ePDG GTP-U"
key = Bearer#gtp_bearer.local_data_tei,
ipv4 = gtp_utils:ip_to_bin(LocalAddr)
ipv4 = conv:ip_to_bin(LocalAddr)
}
],
IEs = [#v2_recovery{restart_counter = RCnt},
@ -416,7 +420,7 @@ gen_create_session_request(#gtp_session{imsi = Imsi,
instance = 0,
interface_type = 30, %% "S2b ePDG GTP-C"
key = LocalCtlTEI,
ipv4 = gtp_utils:ip_to_bin(LocalAddr)
ipv4 = conv:ip_to_bin(LocalAddr)
},
#v2_access_point_name{instance = 0, apn = [Apn]},
#v2_selection_mode{mode = 0},
@ -438,7 +442,7 @@ gen_delete_session_request(#gtp_session{remote_control_tei = RemoteCtlTEI} = Ses
instance = 0,
interface_type = 30, %% "S2b ePDG GTP-C"
key = Bearer#gtp_bearer.local_data_tei,
ipv4 = gtp_utils:ip_to_bin(LocalAddr)
ipv4 = conv:ip_to_bin(LocalAddr)
}
],
#gtp{version = v2, type = delete_session_request, tei = RemoteCtlTEI, seq_no = SeqNo, ie = IEs}.
@ -461,7 +465,7 @@ gen_create_bearer_response(Req = #gtp{version = v2, type = create_bearer_request
instance = 0,
interface_type = 31, %% "S2b-U ePDG GTP-U"
key = Bearer#gtp_bearer.local_data_tei,
ipv4 = gtp_utils:ip_to_bin(LocalAddr)
ipv4 = conv:ip_to_bin(LocalAddr)
}
],
IEs = [#v2_cause{v2_cause = GtpCause},

View File

@ -244,6 +244,16 @@ state_authenticated({call, From}, tunnel_request, Data) ->
state_authenticated({call, From}, {received_gtpc_create_session_response, Result}, Data) ->
lager:info("ue_fsm state_authenticated event=received_gtpc_create_session_response, ~p~n", [Data]),
case Result of
{ok, ResInfo} ->
#{eua := EUA,
local_teid := LocalTEID,
remote_teid := RemoteTEID,
remote_ipv4 := RemoteIPv4 % TODO: remote_ipv6
} = ResInfo,
gtp_u_tun:create_pdp_context(RemoteIPv4, EUA, LocalTEID, RemoteTEID);
_ -> ok
end,
gsup_server:tunnel_response(Data#ue_fsm_data.imsi, Result),
{keep_state, Data, [{reply,From,ok}]};

70
src/gtp_u_tun.erl Normal file
View File

@ -0,0 +1,70 @@
% GTP-U tun related functionalities
%
% (C) 2024 by sysmocom - s.f.m.c. GmbH <info@sysmocom.de>
% Author: Pau Espin Pedrol <pespin@sysmocom.de>
%
% All Rights Reserved
%
% This program is free software; you can redistribute it and/or modify
% it under the terms of the GNU Affero General Public License as
% published by the Free Software Foundation; either version 3 of the
% License, or (at your option) any later version.
%
% This program is distributed in the hope that it will be useful,
% but WITHOUT ANY WARRANTY; without even the implied warranty of
% MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
% GNU General Public License for more details.
%
% You should have received a copy of the GNU Affero General Public License
% along with this program. If not, see <http://www.gnu.org/licenses/>.
%
% Additional Permission under GNU AGPL version 3 section 7:
%
% If you modify this Program, or any covered work, by linking or
% combining it with runtime libraries of Erlang/OTP as released by
% Ericsson on http://www.erlang.org (or a modified version of these
% libraries), containing parts covered by the terms of the Erlang Public
% License (http://www.erlang.org/EPLICENSE), the licensors of this
% Program grant you additional permission to convey the resulting work
% without the need to license the runtime libraries of Erlang/OTP under
% the GNU Affero General Public License. Corresponding Source for a
% non-source form of such a combination shall include the source code
% for the parts of the runtime libraries of Erlang/OTP used as well as
% that of the covered work.
-module(gtp_u_tun).
-author('Pau Espin Pedrol <pespin@sysmocom.de>').
-include("conv.hrl").
-export([create_pdp_context/4]).
%%%%%%%%%%%%%%%%%%%%%%
%%% Internal API
%%%%%%%%%%%%%%%%%%%%%%
% Obtain ServerRef of the gtp_u_kmod_port process spawned during startup based on
% gtp_u_kmod config:
get_env_gtp_u_kmod_server_ref() ->
GtpuKmodSockets = application:get_env(gtp_u_kmod, sockets, []),
[GtpuKmodSocket | _] = GtpuKmodSockets,
{GtpuKmodName, _GtpuKmodSockOpts} = GtpuKmodSocket,
GtpuKmodServRef = gtp_u_kmod_port:port_reg_name(GtpuKmodName),
GtpuKmodServRef.
%%%%%%%%%%%%%%%%%%%%%%
%%% Internal API
%%%%%%%%%%%%%%%%%%%%%%
% Create a PDP Context on the GTP tundev
create_pdp_context(PeerAddr, EUA, LocalTEID, RemoteTEID) ->
%SGSNaddr = {127,0,0,1}, % TODO: This should be set to the GTP-U IP address provided by the PGW
%EUA = {127,0,0,1}, % TODO: This should be set to the EUA IP address provided by the PGW
%LocalTEID = 1234, % TODO: this should be set to our locally generated TEID.
%RemoteTEID = 56768, % TODO: this should be set to TEID obtained from CreateSessionResponse
PeerIP = conv:bin_to_ip(PeerAddr), % TODO: IPv6
UEIP = conv:bin_to_ip(EUA#epdg_eua.ipv4), % TODO: IPv6.
ok.
% TODO: This will be enabled once we depend on the gtp_u_kmod module:
%ServRef = get_env_gtp_u_kmod_server_ref(),
%gen_server:call(ServRef, {PeerIP, UEIP, LocalTEID, RemoteTEID}).

View File

@ -35,16 +35,8 @@
-module(gtp_utils).
-author('Alexander Couzens <lynxis@fe80.eu>').
-export([ip_to_bin/1, plmn_to_bin/3, enum_v2_cause/1]).
-export([plmn_to_bin/3, enum_v2_cause/1]).
% ergw_aaa/src/ergw_aaa_3gpp_dict.erl
% under GPLv2+
ip_to_bin(IP) when is_binary(IP) ->
IP;
ip_to_bin({A, B, C, D}) ->
<<A, B, C, D>>;
ip_to_bin({A, B, C, D, E, F, G, H}) ->
<<A:16, B:16, C:16, D:16, E:16, F:16, G:16, H:16>>.
% ergw/apps/ergw/test/*.erl
% under GPLv2+