Initial S6b support

So far only the Rx of AAR msg and Tx of AAA is supported.
This allows already going forward during the session creation, where PGW
sends AAR to the AAA server and expects AAA message.

Related: OS#6229
Change-Id: Ia2b138317cb291a95882853f5403949c5e6a5a1b
This commit is contained in:
Pau Espin 2023-10-23 14:34:00 +02:00
parent 6b2e105570
commit bffb425812
4 changed files with 291 additions and 3 deletions

View File

@ -5,15 +5,22 @@
[% GSUP Server connection parameters
{gsup_local_ip, "0.0.0.0"},
{gsup_local_port, 4222},
% Diameter Connection parameters
% Diameter SWx Connection parameters
{diameter_remote_ip, "127.0.0.1"},
{diameter_remote_port, 3868},
{diameter_proto, sctp},
% Diameter Server parameters
{vendor_id, 0},
{origin_host, "epdg.localdomain"},
{origin_realm, "localdomain"},
{context_id, "epdg@localdomain"},
% Diameter s6b Connection parameters
{dia_s6b_local_ip, "127.0.0.10"},
{dia_s6b_local_port, 3868},
{dia_s6b_proto, sctp},
{dia_s6b_vendor_id, 0},
{dia_s6b_origin_host, "aaa.localdomain"},
{dia_s6b_origin_realm, "localdomain"},
{dia_s6b_context_id, "aaa@localdomain"},
% GTPv2C Connection parameters
{gtpc_local_ip, "127.0.0.2"},
{gtpc_local_port, 2123},

203
src/aaa_diameter_s6b.erl Normal file
View File

@ -0,0 +1,203 @@
% S6b: AAA side
%
% 3GPP TS 29.273 section 9
%
% (C) 2023 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(aaa_diameter_s6b).
-author('Pau Espin Pedrol <pespin@sysmocom.de>').
-behaviour(gen_server).
-include_lib("diameter_3gpp_ts29_273_s6b.hrl").
-include_lib("diameter/include/diameter_gen_base_rfc6733.hrl").
%% API Function Exports
-export([start_link/0]).
-export([start/0, stop/0, terminate/2]).
%% gen_server Function Exports
-export([init/1, handle_call/3, handle_cast/2, handle_info/2]).
-export([code_change/3]).
-export([multimedia_auth_request/6]).
-export([server_assignment_request/3]).
-export([test/0, test/1]).
%% Diameter Application Definitions
-define(SERVER, ?MODULE).
-define(SVC_NAME, ?MODULE).
-define(APP_ALIAS, ?MODULE).
-define(CALLBACK_MOD, aaa_diameter_s6b_cb).
-define(DIAMETER_DICT_S6b, diameter_3gpp_ts29_273_s6b).
-define(ENV_APP_NAME, osmo_epdg).
-define(ENV_DEFAULT_SESSION_ID, "aaa@localdomain").
-define(ENV_DEFAULT_ORIG_REALM, "localdomain").
-define(ENV_DEFAULT_ORIG_HOST, "aaa.localdomain").
-define(ENV_DEFAULT_VENDOR_ID, 0).
-define(ENV_DEFAULT_DIAMETER_PROTO, sctp).
-define(ENV_DEFAULT_DIAMETER_REMOTE_IP, "127.0.0.10").
-define(ENV_DEFAULT_DIAMETER_REMOTE_PORT, 3868).
-define(VENDOR_ID_3GPP, 10415).
-define(VENDOR_ID_3GPP2, 5535).
-define(VENDOR_ID_ETSI, 13019).
-define(DIAMETER_APP_ID_S6b, ?DIAMETER_DICT_S6b:id()).
%% The service configuration. As in the server example, a client
%% supporting multiple Diameter applications may or may not want to
%% configure a common callback module on all applications.
-define(SERVICE,
[{'Origin-Host', application:get_env(?ENV_APP_NAME, dia_s6b_origin_host, ?ENV_DEFAULT_ORIG_HOST)},
{'Origin-Realm', application:get_env(?ENV_APP_NAME, dia_s6b_origin_realm, ?ENV_DEFAULT_ORIG_REALM)},
{'Vendor-Id', application:get_env(?ENV_APP_NAME, dia_s6b_vendor_id, ?ENV_DEFAULT_VENDOR_ID)},
{'Vendor-Specific-Application-Id',
[#'diameter_base_Vendor-Specific-Application-Id'{
'Vendor-Id' = ?VENDOR_ID_3GPP,
'Auth-Application-Id' = [?DIAMETER_APP_ID_S6b]}]},
{'Product-Name', "osmo-epdg-AAA"},
% TODO: check which we should annouce here as Supported-Vendor-Id
{'Supported-Vendor-Id', [?VENDOR_ID_3GPP, ?VENDOR_ID_ETSI, ?VENDOR_ID_3GPP2]},
{ application,
[{alias, ?APP_ALIAS},
{dictionary, ?DIAMETER_DICT_S6b},
{module, ?CALLBACK_MOD},
{answer_errors, callback}]}]).
-record(state, {
handlers,
peers = #{}
}).
%% @doc starts gen_server implementation process
-spec start() -> ok | {error, term()}.
start() ->
application:ensure_all_started(?MODULE),
start_link().
%% @doc stops gen_server implementation process
-spec stop() -> ok.
stop() ->
gen_server:cast(?SERVER, stop).
start_link() ->
gen_server:start_link({local, ?SERVER}, ?MODULE, [], []).
peer_down(API, SvcName, {PeerRef, _} = Peer) ->
% fixme: why do we still have ets here?
(catch ets:delete(?MODULE, {API, PeerRef})),
gen_server:cast(?SERVER, {peer_down, SvcName, Peer}),
ok.
init(State) ->
Proto = application:get_env(?ENV_APP_NAME, dia_s6b_proto, ?ENV_DEFAULT_DIAMETER_PROTO),
Ip = application:get_env(?ENV_APP_NAME, dia_s6b_local_ip, ?ENV_DEFAULT_DIAMETER_REMOTE_IP),
Port = application:get_env(?ENV_APP_NAME, dia_s6b_local_port, ?ENV_DEFAULT_DIAMETER_REMOTE_PORT),
ok = diameter:start_service(?MODULE, ?SERVICE),
% lager:info("DiaServices is ~p~n", [DiaServ]),
{ok, _} = listen({address, Proto, Ip, Port}),
{ok, State}.
test() ->
test("001011234567890").
test(IMSI) ->
multimedia_auth_request(IMSI, 3, "EAP-AKA", 1, [], []).
multimedia_auth_request(IMSI, NumAuthItems, AuthScheme, RAT, CKey, IntegrityKey) ->
gen_server:call(?SERVER,
{mar, {IMSI, NumAuthItems, AuthScheme, RAT, CKey, IntegrityKey}}).
% APN is optional and should be []
server_assignment_request(IMSI, Type, APN) ->
gen_server:call(?SERVER,
{sar, {IMSI, Type, APN}}).
result_code_success(2001) -> ok;
result_code_success(2002) -> ok;
result_code_success(_) -> invalid_result_code.
handle_call({aar, {IMSI, Type, APN}}, _From, State) ->
SessionId = diameter:session_id(application:get_env(?ENV_APP_NAME, origin_host, ?ENV_DEFAULT_ORIG_HOST)).
%% @callback gen_server
handle_cast(stop, State) ->
{stop, normal, State};
handle_cast(_Req, State) ->
{noreply, State}.
%% @callback gen_server
handle_info(_Info, State) ->
{noreply, State}.
%% @callback gen_server
code_change(_OldVsn, State, _Extra) ->
{ok, State}.
%% @callback gen_server
terminate(normal, _State) ->
diameter:stop_service(?SVC_NAME),
ok;
terminate(shutdown, _State) ->
ok;
terminate({shutdown, _Reason}, _State) ->
ok;
terminate(_Reason, _State) ->
ok.
%% ------------------------------------------------------------------
%% Internal Function Definitions
%% ------------------------------------------------------------------
%% connect/2
listen(Name, {address, Protocol, IPAddr, Port}) ->
lager:notice("~s Listening on IP ~s port ~p~n", [Name, IPAddr, Port]),
{ok, IP} = inet_parse:address(IPAddr),
TransportOpts =
[{transport_module, tmod(Protocol)},
{transport_config,
[{reuseaddr, true},
{ip, IP},
{port, Port}
%%{raddr, IP},
%%{rport, Port}
]}],
diameter:add_transport(Name, {listen, [{reconnect_timer, 1000} | TransportOpts]}).
listen(Address) ->
listen(?SVC_NAME, Address).
%% Convert connection type
tmod(tcp) ->
diameter_tcp;
tmod(sctp) ->
diameter_sctp.

View File

@ -0,0 +1,73 @@
%%
%% The diameter application callback module configured by client.erl.
%%
-module(aaa_diameter_s6b_cb).
-include_lib("diameter/include/diameter.hrl").
-include_lib("diameter_3gpp_ts29_273_s6b.hrl").
%% diameter callbacks
-export([peer_up/3, peer_down/3, pick_peer/4, prepare_request/3, prepare_retransmit/3,
handle_answer/4, handle_error/4, handle_request/3]).
-define(UNEXPECTED, erlang:error({unexpected, ?MODULE, ?LINE})).
%% peer_up/3
peer_up(_SvcName, Peer, State) ->
lager:info("Peer up: ~p~n", [Peer]),
State.
%% peer_down/3
peer_down(_SvcName, Peer, State) ->
lager:info("Peer down: ~p~n", [Peer]),
State.
%% pick_peer/4
pick_peer([_Peer | _], _, _SvcName, _State) ->
?UNEXPECTED.
%% prepare_request/3
prepare_request(_, _SvcName, _Peer) ->
?UNEXPECTED.
%% prepare_retransmit/3
prepare_retransmit(_Packet, _SvcName, _Peer) ->
?UNEXPECTED.
%% handle_answer/4
%% Since client.erl has detached the call when using the list
%% encoding and not otherwise, output to the terminal in the
%% the former case, return in the latter.
handle_answer(_Packet, _Request, _SvcName, _Peer) ->
?UNEXPECTED.
%% handle_error/4
handle_error(Reason, Request, _SvcName, _Peer) when is_list(Request) ->
lager:error("Request error: ~p~n", [Reason]),
?UNEXPECTED.
handle_request(#diameter_packet{msg = Req, errors = []}, _SvcName, {_, Caps}) when is_record(Req, 'AAR') ->
lager:info("S6b Rx from ~p: ~p~n", [Caps, Req]),
% extract relevant fields from DIAMETER AAR
#diameter_caps{origin_host = {OH,_}, origin_realm = {OR,_}} = Caps,
#'AAR'{'Session-Id' = SessionId,
'Auth-Application-Id' = AuthAppId,
'Auth-Request-Type' = AuthReqType,
'User-Name' = _UserName} = Req,
Resp = #'AAA'{'Session-Id'=SessionId,
'Auth-Application-Id' = AuthAppId,
'Auth-Request-Type' = AuthReqType,
'Result-Code'=2001,
'Origin-Host'=OH,
'Origin-Realm'=OR},
lager:info("S6b Tx to ~p: ~p~n", [Caps, Resp]),
{reply, Resp};
% TODO: extract relevant fields from DIAMETER AAA
%% handle_request/3
handle_request(Packet, _SvcName, Peer) ->
lager:error("S6b Rx unexpected msg from ~p: ~p~n", [Peer, Packet]),
%PESPIN: TODO: handle S6b AAR here, see osmo_dia2gsup "handle_request" as example.
erlang:error({unexpected, ?MODULE, ?LINE}).

View File

@ -28,6 +28,11 @@ init([]) ->
5000,
worker,
[epdg_diameter_swx_cb]},
DiaS6bServer = {aaa_diameter_s6b, {aaa_diameter_s6b,start_link,[]},
permanent,
5000,
worker,
[aaa_diameter_s6b_cb]},
GtpcServer = {epdg_gtpc_s2b, {epdg_gtpc_s2b,start_link, [GtpcLocalIp, GtpcLocalPort, GtpcRemoteIp, GtpcRemotePort, []]},
permanent,
5000,
@ -43,4 +48,4 @@ init([]) ->
5000,
worker,
[auth_handler]},
{ok, { {one_for_all, 5, 10}, [DiaServer, GtpcServer, GsupServer, AuthHandler]} }.
{ok, { {one_for_all, 5, 10}, [DiaServer, DiaS6bServer, GtpcServer, GsupServer, AuthHandler]} }.