Make Auth Compl procedure more similar to specs

Properly document our LU Request message matching the 2nd DER in usual
3GPP architecture, which should contain the Auth RES from the MS and be
forwarded up to the AAA-Server.
In our architecture, the auth is handled earlier, in strongswan (part of
ePDG node), hence why our LU Request contains no Auth RES info, and it's
only signalled by strongswan to osmo-epdg to signal the auth completed
successfuly.
Make the handling of LU Req and events triggered by it asynchronous and
clean up a bit some related code paths and states.

Change-Id: I480c110deeb04abf1ff19147a70e10be9cbafae8
This commit is contained in:
Pau Espin 2024-01-25 21:59:09 +01:00
parent cd03bdf9ce
commit eed8608da0
5 changed files with 90 additions and 21 deletions

View File

@ -57,8 +57,9 @@ handle_request(#diameter_packet{msg = Req, errors = []}, _SvcName, {_, Caps}) wh
#'AAR'{'Session-Id' = SessionId,
'Auth-Application-Id' = AuthAppId,
'Auth-Request-Type' = AuthReqType,
'User-Name' = UserName} = Req,
Result = aaa_diameter_swx:server_assignment_request(UserName, 1, "internet"),
'User-Name' = [UserName],
'Service-Selection' = [Apn]} = Req,
Result = aaa_diameter_swx:server_assignment_request(UserName, 1, Apn),
case Result of
{ok, _} ->
ResultCode = 2001;

View File

@ -14,12 +14,10 @@
-export([init/1, handle_call/3, handle_cast/2, handle_info/2]).
-export([code_change/3, terminate/2]).
-export[(auth_request/1)].
-export([auth_request/1, auth_compl_request/2]).
-define(SERVER, ?MODULE).
% The ets table contains only IMSIs
start_link() ->
gen_server:start_link({local, ?MODULE}, ?MODULE, [], []).
@ -31,6 +29,9 @@ init([]) ->
auth_request(Imsi) ->
gen_server:cast(?SERVER, {epdg_auth_req, Imsi}).
auth_compl_request(Imsi, Apn) ->
gen_server:cast(?SERVER, {epdg_auth_compl_req, Imsi, Apn}).
handle_cast({epdg_auth_req, Imsi}, State) ->
% request the diameter code for a tuple
CKey = [],
@ -38,11 +39,21 @@ handle_cast({epdg_auth_req, Imsi}, State) ->
Result = aaa_diameter_swx:multimedia_auth_request(Imsi, 1, "EAP-AKA", 1, CKey, IntegrityKey),
case Result of
{ok, _MAA} -> epdg_diameter_swm:auth_response(Imsi, Result);
{error, Err} -> epdg_diameter_swm:auth_response(Imsi, Result);
{error, _Err} -> epdg_diameter_swm:auth_response(Imsi, Result);
_ -> epdg_diameter_swm:auth_response(Imsi, {error, unknown})
end,
{noreply, State};
handle_cast({epdg_auth_compl_req, Imsi, Apn}, State) ->
% request the diameter code for a tuple
Result = aaa_diameter_swx:server_assignment_request(Imsi, 1, Apn),
case Result of
{ok, _SAA} -> epdg_diameter_swm:auth_compl_response(Imsi, Result);
{error, _Err} -> epdg_diameter_swm:auth_compl_response(Imsi, Result);
_ -> epdg_diameter_swm:auth_compl_response(Imsi, {error, unknown})
end,
{noreply, State};
handle_cast(Info, S) ->
error_logger:error_report(["unknown handle_cast", {module, ?MODULE}, {info, Info}, {state, S}]),
{noreply, S}.

View File

@ -19,8 +19,8 @@
-export([init/1, handle_call/3, handle_cast/2, handle_info/2]).
-export([code_change/3, terminate/2]).
-export[(auth_request/1)].
-export[(auth_response/2)].
-export([auth_request/1, auth_compl_request/2]).
-export([auth_response/2, auth_compl_response/2]).
-define(SERVER, ?MODULE).
@ -42,12 +42,33 @@ auth_request(Imsi) ->
_ -> Result
end.
% Rx "GSUP CEAI LU Req" is our way of saying Rx "Swm Diameter-EAP REQ (DER) with EAP AVP containing successuful auth":
auth_compl_request(Imsi, Apn) ->
Result = gen_server:call(?SERVER, {epdg_auth_compl_req, Imsi, Apn}),
case Result of
{ok, _Mar} ->
epdg_ue_fsm:received_swm_auth_compl_response(self(), Result),
ok;
_ -> Result
end.
handle_call({epdg_auth_req, Imsi}, {Pid, _Tag} = _From, State0) ->
% we yet don't implement the Diameter SWm interface on the wire, we process the call internally:
{_Sess, State1} = find_or_new_swm_session(Imsi, Pid, State0),
ok = aaa_diameter_swm:auth_request(Imsi),
{reply, ok, State1}.
{reply, ok, State1};
handle_call({epdg_auth_compl_req, Imsi, Apn}, _From, State) ->
% we yet don't implement the Diameter SWm interface on the wire, we process the call internally:
Sess = find_swm_session_by_imsi(Imsi, State),
case Sess of
#swm_session{imsi = Imsi} ->
Reply = aaa_diameter_swm:auth_compl_request(Imsi, Apn);
undefined ->
Reply = {error,unknown_imsi}
end,
{reply, Reply, State}.
handle_cast({epdg_auth_resp, Imsi, Result}, State) ->
Sess = find_swm_session_by_imsi(Imsi, State),
@ -59,6 +80,16 @@ handle_cast({epdg_auth_resp, Imsi, Result}, State) ->
end,
{noreply, State};
handle_cast({epdg_auth_compl_resp, Imsi, Result}, State) ->
Sess = find_swm_session_by_imsi(Imsi, State),
case Sess of
#swm_session{imsi = Imsi} ->
epdg_ue_fsm:received_swm_auth_compl_response(Sess#swm_session.pid, Result);
undefined ->
error_logger:error_report(["unknown swm_session", {module, ?MODULE}, {imsi, Imsi}, {state, State}])
end,
{noreply, State};
handle_cast(Info, S) ->
error_logger:error_report(["unknown handle_cast", {module, ?MODULE}, {info, Info}, {state, S}]),
{noreply, S}.
@ -80,6 +111,11 @@ terminate(Reason, _S) ->
auth_response(Imsi, Result) ->
ok = gen_server:cast(?SERVER, {epdg_auth_resp, Imsi, Result}).
%Rx Swm Diameter-EAP Answer (DEA) containing APN-Configuration, triggered by
%earlier Tx DER EAP AVP containing successuful auth":
auth_compl_response(Imsi, Result) ->
ok = gen_server:cast(?SERVER, {epdg_auth_compl_resp, Imsi, Result}).
%% ------------------------------------------------------------------
%% Internal Function Definitions
%% ------------------------------------------------------------------

View File

@ -40,12 +40,13 @@
-export([start_link/1]).
-export([init/1,callback_mode/0,terminate/3]).
-export([auth_request/1, lu_request/1, tunnel_request/1, purge_ms_request/1]).
-export([received_swm_auth_response/2]).
-export([received_swm_auth_response/2, received_swm_auth_compl_response/2]).
-export([received_gtpc_create_session_response/2, received_gtpc_delete_session_response/2]).
-export([state_new/3, state_wait_auth_resp/3, state_authenticated/3, state_wait_delete_session_resp/3]).
-export([state_new/3, state_wait_auth_resp/3, state_authenticating/3, state_authenticated/3, state_wait_delete_session_resp/3]).
-record(ue_fsm_data, {
imsi
imsi,
apn = "internet" :: string()
}).
start_link(Imsi) ->
@ -98,6 +99,15 @@ received_swm_auth_response(Pid, Result) ->
{error, Err}
end.
received_swm_auth_compl_response(Pid, Result) ->
lager:info("ue_fsm received_swm_auth_compl_response ~p~n", [Result]),
try
gen_statem:call(Pid, {received_swm_auth_compl_response, Result})
catch
exit:Err ->
{error, Err}
end.
received_gtpc_create_session_response(Pid, Msg) ->
lager:info("ue_fsm received_gtpc_create_session_response ~p~n", [Msg]),
try
@ -152,23 +162,34 @@ state_wait_auth_resp({call, From}, {received_swm_auth_response, Auth}, Data) ->
gsup_server:auth_response(Data#ue_fsm_data.imsi, Auth),
case Auth of
{ok, _} ->
{next_state, state_authenticated, Data, [{reply,From,ok}]};
{next_state, state_authenticating, Data, [{reply,From,ok}]};
{error, Err} ->
{next_state, state_new, Data, [{reply,From,{error,Err}}]};
_ ->
{next_state, state_new, Data, [{reply,From,{error,unknown}}]}
end.
state_authenticated({call, From}, lu_request, Data) ->
lager:info("ue_fsm state_authenticated event=lu_request, ~p~n", [Data]),
Result = aaa_diameter_swx:server_assignment_request(Data#ue_fsm_data.imsi, 1, "internet"),
gsup_server:lu_response(Data#ue_fsm_data.imsi, Result),
state_authenticating({call, From}, lu_request, Data) ->
lager:info("ue_fsm state_authenticating event=lu_request, ~p~n", [Data]),
% Rx "GSUP CEAI LU Req" is our way of saying Rx "Swm Diameter-EAP REQ (DER) with EAP AVP containing successuful auth":
case epdg_diameter_swm:auth_compl_request(Data#ue_fsm_data.imsi, Data#ue_fsm_data.apn) of
ok -> {keep_state, Data, [{reply,From,ok}]};
{error, Err} -> {stop_and_reply, Err, Data, [{reply,From,{error,Err}}]}
end;
% Rx Swm Diameter-EAP Answer (DEA) containing APN-Configuration, triggered by
% earlier Tx DER EAP AVP containing successuful auth", when we received GSUP LU Req:
state_authenticating({call, From}, {received_swm_auth_compl_response, Result}, Data) ->
lager:info("ue_fsm state_authenticating event=lu_request, ~p, ~p~n", [Result, Data]),
% Rx "GSUP CEAI LU Req" is our way of saying Rx "Swm Diameter-EAP REQ (DER) with EAP AVP containing successuful auth":
case Result of
{ok, _} ->
{keep_state, Data, [{reply,From,ok}]};
Ret = ok;
{error, Err} ->
{stop, Err, Data, [{reply,From,{error,Err}}]}
end;
Ret = {error, Err}
end,
gsup_server:lu_response(Data#ue_fsm_data.imsi, Ret),
{next_state, state_authenticated, Data, [{reply,From,Ret}]}.
state_authenticated({call, From}, tunnel_request, Data) ->
lager:info("ue_fsm state_authenticated event=tunnel_request, ~p~n", [Data]),

View File

@ -138,7 +138,7 @@ handle_cast({lu_response, {Imsi, Result}}, State) ->
lager:info("lu_response for ~p: ~p~n", [Imsi, Result]),
Socket = State#gsups_state.socket,
case Result of
{ok, _Sar} -> Resp = #{message_type => location_upd_res,
ok -> Resp = #{message_type => location_upd_res,
imsi => Imsi,
message_class => 5
};