File 4592-ssl-Refactor-alert-handling.patch of Package erlang

From 75baaf75c362f40da5cd128e828ad12180dbda4b Mon Sep 17 00:00:00 2001
From: Dan Gudmundsson <dgud@erlang.org>
Date: Fri, 24 Sep 2021 09:38:04 +0200
Subject: [PATCH 02/10] ssl: Refactor alert handling

Throw alerts in common handling, so usage can be specialized in
specific modules later, we will need that in dtls.

Throw of alerts have been done before but are now thrown further,
this can be improved even more.
---
 lib/ssl/src/dtls_connection.erl     | 128 ++++++++++----------
 lib/ssl/src/dtls_gen_connection.erl |   6 +-
 lib/ssl/src/dtls_handshake.erl      |  34 +++---
 lib/ssl/src/ssl_alert.hrl           |  11 +-
 lib/ssl/src/ssl_gen_statem.erl      |   6 +-
 lib/ssl/src/tls_connection.erl      | 173 +++++++++++++++-------------
 lib/ssl/src/tls_dtls_connection.erl | 147 ++++++++++-------------
 lib/ssl/src/tls_handshake.erl       |  83 ++++++-------
 8 files changed, 281 insertions(+), 307 deletions(-)

diff --git a/lib/ssl/src/dtls_connection.erl b/lib/ssl/src/dtls_connection.erl
index 32ccb18176..ae24dc31cc 100644
--- a/lib/ssl/src/dtls_connection.erl
+++ b/lib/ssl/src/dtls_connection.erl
@@ -268,7 +268,7 @@ hello(internal, #client_hello{cookie = <<>>,
              handshake_env = HsEnv,
              connection_env = CEnv,
              protocol_specific = #{current_cookie_secret := Secret}} = State0) ->
-    case tls_dtls_connection:handle_sni_extension(State0, Hello) of
+    try tls_dtls_connection:handle_sni_extension(State0, Hello) of
         #state{} = State1 ->
             {ok, {IP, Port}} = dtls_socket:peername(Transport, Socket),
             Cookie = dtls_handshake:cookie(Secret, IP, Port, Hello),
@@ -285,8 +285,8 @@ hello(internal, #client_hello{cookie = <<>>,
                                            State#state{handshake_env = HsEnv#handshake_env{
                                                                          tls_handshake_history =
                                                                              ssl_handshake:init_handshake_history()}},
-                       Actions);
-        #alert{} = Alert ->
+                                           Actions)
+    catch throw:#alert{} = Alert ->
             ssl_gen_statem:handle_own_alert(Alert,?FUNCTION_NAME, State0)
     end;
 hello(internal, #hello_verify_request{cookie = Cookie}, 
@@ -321,17 +321,17 @@ hello(internal, #client_hello{extensions = Extensions} = Hello,
       #state{ssl_options = #{handshake := hello},
              handshake_env = HsEnv,
              start_or_recv_from = From} = State0) ->
-    case tls_dtls_connection:handle_sni_extension(State0, Hello) of
+    try tls_dtls_connection:handle_sni_extension(State0, Hello) of
         #state{} = State ->
             {next_state, user_hello, State#state{start_or_recv_from = undefined,
                                                  handshake_env = HsEnv#handshake_env{hello = Hello}},
-             [{reply, From, {ok, Extensions}}]};
-        #alert{} = Alert ->
+             [{reply, From, {ok, Extensions}}]}
+    catch throw:#alert{} = Alert ->
             ssl_gen_statem:handle_own_alert(Alert, ?FUNCTION_NAME, State0)
     end;
 hello(internal, #server_hello{extensions = Extensions} = Hello, 
       #state{ssl_options = #{
-                 handshake := hello},
+                             handshake := hello},
              handshake_env = HsEnv,
              start_or_recv_from = From} = State) ->
     {next_state, user_hello, State#state{start_or_recv_from = undefined,
@@ -361,20 +361,21 @@ hello(internal, #server_hello{} = Hello,
       #state{
          static_env = #static_env{role = client},
          handshake_env = #handshake_env{
-             renegotiation = {Renegotiation, _},
-             ocsp_stapling_state = OcspState0} = HsEnv,
+                            renegotiation = {Renegotiation, _},
+                            ocsp_stapling_state = OcspState0} = HsEnv,
          connection_states = ConnectionStates0,
          session = #session{session_id = OldId},
          ssl_options = SslOptions} = State) ->
-    case dtls_handshake:hello(Hello, SslOptions, ConnectionStates0, Renegotiation, OldId) of
-        #alert{} = Alert ->
-            ssl_gen_statem:handle_own_alert(Alert, ?FUNCTION_NAME, State);
-        {Version, NewId, ConnectionStates, ProtoExt, Protocol, OcspState} ->
-            tls_dtls_connection:handle_session(Hello, 
-                                          Version, NewId, ConnectionStates, ProtoExt, Protocol,
-                                          State#state{handshake_env = 
-                                                          HsEnv#handshake_env{
-                                                            ocsp_stapling_state = maps:merge(OcspState0,OcspState)}})
+    try
+        {Version, NewId, ConnectionStates, ProtoExt, Protocol, OcspState} =
+            dtls_handshake:hello(Hello, SslOptions, ConnectionStates0, Renegotiation, OldId),
+        tls_dtls_connection:handle_session(Hello,
+                                           Version, NewId, ConnectionStates, ProtoExt, Protocol,
+                                           State#state{handshake_env =
+                                                           HsEnv#handshake_env{
+                                                             ocsp_stapling_state = maps:merge(OcspState0,OcspState)}})
+    catch throw:#alert{} = Alert ->
+            ssl_gen_statem:handle_own_alert(Alert, ?FUNCTION_NAME, State)
     end;
 hello(internal, {handshake, {#client_hello{cookie = <<>>} = Handshake, _}}, State) ->
     %% Initial hello should not be in handshake history
@@ -547,7 +548,11 @@ connection({call, From}, {application_data, Data}, State) ->
             ssl_gen_statem:hibernate_after(?FUNCTION_NAME, State, [{reply, From, Error}])
     end;
 connection(Type, Event, State) ->
-    tls_dtls_connection:?FUNCTION_NAME(Type, Event, State).
+    try
+        tls_dtls_connection:?FUNCTION_NAME(Type, Event, State)
+    catch throw:#alert{}=Alert ->
+            ssl_gen_statem:handle_own_alert(Alert, ?FUNCTION_NAME, State)
+    end.
 
 %%TODO does this make sense for DTLS ?
 %%--------------------------------------------------------------------
@@ -557,7 +562,12 @@ connection(Type, Event, State) ->
 downgrade(enter, _, State) ->
     {keep_state, State};
 downgrade(Type, Event, State) ->
-     tls_dtls_connection:?FUNCTION_NAME(Type, Event, State).
+    try
+        tls_dtls_connection:?FUNCTION_NAME(Type, Event, State)
+    catch throw:#alert{}=Alert ->
+            ssl_gen_statem:handle_own_alert(Alert, ?FUNCTION_NAME, State)
+    end.
+
 
 %%--------------------------------------------------------------------
 %% gen_statem callbacks
@@ -624,7 +634,7 @@ initial_state(Role, Host, Port, Socket,
 
 
 handle_client_hello(#client_hello{client_version = ClientVersion} = Hello, State0) ->
-    case tls_dtls_connection:handle_sni_extension(State0, Hello) of
+    try
         #state{connection_states = ConnectionStates0,
                static_env = #static_env{trackers = Trackers},
                handshake_env = #handshake_env{kex_algorithm = KeyExAlg,
@@ -632,31 +642,28 @@ handle_client_hello(#client_hello{client_version = ClientVersion} = Hello, State
                                               negotiated_protocol = CurrentProtocol} = HsEnv,
                connection_env = CEnv,
                session = #session{own_certificates = OwnCerts} = Session0,
-               ssl_options = SslOpts} = State1 ->
-            SessionTracker = proplists:get_value(session_id_tracker, Trackers),
-            case dtls_handshake:hello(Hello, SslOpts, {SessionTracker, Session0,
-                                                       ConnectionStates0, OwnCerts, KeyExAlg}, Renegotiation) of
-                #alert{} = Alert ->
-                    ssl_gen_statem:handle_own_alert(Alert, hello, State1);
-                {Version, {Type, Session},
-                 ConnectionStates, Protocol0, ServerHelloExt, HashSign} ->
-                    Protocol = case Protocol0 of
-                                   undefined -> CurrentProtocol;
-                                   _ -> Protocol0
-                               end,
-
-                    State = prepare_flight(State0#state{connection_states = ConnectionStates,
-                                                        connection_env = CEnv#connection_env{negotiated_version = Version},
-                                                        handshake_env = HsEnv#handshake_env{
-                                                                          hashsign_algorithm = HashSign,
-                                                                          client_hello_version = ClientVersion,
-                                                                          negotiated_protocol = Protocol},
-                                                        session = Session}),
-                    {next_state, hello, State, [{next_event, internal, {common_client_hello, Type, ServerHelloExt}}]}
-            end;
-        #alert{} = Alert ->
-             ssl_gen_statem:handle_own_alert(Alert, hello, State0)
-        end.
+               ssl_options = SslOpts} =
+            tls_dtls_connection:handle_sni_extension(State0, Hello),
+        SessionTracker = proplists:get_value(session_id_tracker, Trackers),
+        {Version, {Type, Session}, ConnectionStates, Protocol0, ServerHelloExt, HashSign} =
+            dtls_handshake:hello(Hello, SslOpts, {SessionTracker, Session0,
+                                                  ConnectionStates0, OwnCerts, KeyExAlg}, Renegotiation),
+        Protocol = case Protocol0 of
+                       undefined -> CurrentProtocol;
+                       _ -> Protocol0
+                   end,
+
+        State = prepare_flight(State0#state{connection_states = ConnectionStates,
+                                            connection_env = CEnv#connection_env{negotiated_version = Version},
+                                            handshake_env = HsEnv#handshake_env{
+                                                              hashsign_algorithm = HashSign,
+                                                              client_hello_version = ClientVersion,
+                                                              negotiated_protocol = Protocol},
+                                            session = Session}),
+        {next_state, hello, State, [{next_event, internal, {common_client_hello, Type, ServerHelloExt}}]}
+    catch #alert{} = Alert ->
+            ssl_gen_statem:handle_own_alert(Alert, hello, State0)
+    end.
 
 
 handle_state_timeout(flight_retransmission_timeout, StateName,
@@ -672,33 +679,26 @@ handle_state_timeout(flight_retransmission_timeout, StateName,
 
 
 gen_handshake(StateName, Type, Event, State) ->
-    try tls_dtls_connection:StateName(Type, Event, State) of
-	Result ->
-	    Result
-    catch 
-	_:_ ->
-	    ssl_gen_statem:handle_own_alert(?ALERT_REC(?FATAL, ?HANDSHAKE_FAILURE,
-						       malformed_handshake_data),
-					    StateName, State)  
+    try tls_dtls_connection:StateName(Type, Event, State)
+    catch
+        throw:#alert{}=Alert ->
+            ssl_gen_statem:handle_own_alert(Alert, StateName,State);
+        error:_ ->
+            Alert = ?ALERT_REC(?FATAL, ?HANDSHAKE_FAILURE, malformed_handshake_data),
+            ssl_gen_statem:handle_own_alert(Alert, StateName,State)
     end.
 
 gen_info(Event, connection = StateName, State) ->
-    try dtls_gen_connection:handle_info(Event, StateName, State) of
-	Result ->
-	    Result
-    catch 
-	_:_ ->
+    try dtls_gen_connection:handle_info(Event, StateName, State)
+    catch error:_ ->
 	    ssl_gen_statem:handle_own_alert(?ALERT_REC(?FATAL, ?INTERNAL_ERROR,
 						       malformed_data), 
 					    StateName, State)  
     end;
 
 gen_info(Event, StateName, State) ->
-    try dtls_gen_connection:handle_info(Event, StateName, State) of
-	Result ->
-	    Result
-    catch 
-        _:_ ->
+    try dtls_gen_connection:handle_info(Event, StateName, State)
+    catch error:_ ->
 	    ssl_gen_statem:handle_own_alert(?ALERT_REC(?FATAL, ?HANDSHAKE_FAILURE,
 						       malformed_handshake_data), 
 					    StateName, State)  
diff --git a/lib/ssl/src/dtls_gen_connection.erl b/lib/ssl/src/dtls_gen_connection.erl
index 4b402f6841..68f6ff0ec8 100644
--- a/lib/ssl/src/dtls_gen_connection.erl
+++ b/lib/ssl/src/dtls_gen_connection.erl
@@ -486,14 +486,12 @@ getopts(Transport, Socket, Tag) ->
 
 %% raw data from socket, unpack records
 handle_info({Protocol, _, _, _, Data}, StateName,
-            #state{static_env = #static_env{role = Role,
-                                            data_tag = Protocol}} = State0) ->
+            #state{static_env = #static_env{data_tag = Protocol}} = State0) ->
     case next_dtls_record(Data, StateName, State0) of
 	{Record, State} ->
 	    next_event(StateName, Record, State);
 	#alert{} = Alert ->
-	    ssl_gen_statem:handle_normal_shutdown(Alert#alert{role = Role}, StateName, State0),
-            {stop, {shutdown, own_alert}, State0}
+            handle_own_alert(Alert, StateName, State0)
     end;
 
 handle_info({PassiveTag, Socket}, StateName,
diff --git a/lib/ssl/src/dtls_handshake.erl b/lib/ssl/src/dtls_handshake.erl
index 9999933d90..d1ce428ae2 100644
--- a/lib/ssl/src/dtls_handshake.erl
+++ b/lib/ssl/src/dtls_handshake.erl
@@ -108,7 +108,7 @@ hello(#server_hello{server_version = Version, random = Random,
 					   Compression, HelloExt, SslOpt, 
                                            ConnectionStates0, Renegotiation, IsNew);
 	false ->
-	    ?ALERT_REC(?FATAL, ?PROTOCOL_VERSION)
+	    throw(?ALERT_REC(?FATAL, ?PROTOCOL_VERSION))
     end.
 hello(#client_hello{client_version = ClientVersion} = Hello,
       #{versions := Versions} = SslOpts,
@@ -195,13 +195,13 @@ handle_client_hello(Version,
 					       SslOpts, OwnCert),
 	    case CipherSuite of
 		no_suite ->
-		    ?ALERT_REC(?FATAL, ?INSUFFICIENT_SECURITY);
+		    throw(?ALERT_REC(?FATAL, ?INSUFFICIENT_SECURITY));
 		_ ->
 		    #{key_exchange := KeyExAlg} = ssl_cipher_format:suite_bin_to_map(CipherSuite),
 		    case ssl_handshake:select_hashsign({ClientHashSigns, undefined}, OwnCert, KeyExAlg,
 						       SupportedHashSigns, TLSVersion) of
 			#alert{} = Alert ->
-			    Alert;
+			    throw(Alert);
 			HashSign ->
 			    handle_client_hello_extensions(Version, Type, Random, CipherSuites, HelloExt,
 							   SslOpts, Session1, ConnectionStates0,
@@ -209,33 +209,27 @@ handle_client_hello(Version,
 		    end
 	    end;
 	false ->
-	    ?ALERT_REC(?FATAL, ?PROTOCOL_VERSION)
+	    throw(?ALERT_REC(?FATAL, ?PROTOCOL_VERSION))
     end.
 
 handle_client_hello_extensions(Version, Type, Random, CipherSuites,
 			HelloExt, SslOpts, Session0, ConnectionStates0, Renegotiation, HashSign) ->
-    try ssl_handshake:handle_client_hello_extensions(dtls_record, Random, CipherSuites,
-						     HelloExt, dtls_v1:corresponding_tls_version(Version),
-						     SslOpts, Session0, 
+    {Session, ConnectionStates, Protocol, ServerHelloExt} =
+        ssl_handshake:handle_client_hello_extensions(dtls_record, Random, CipherSuites,
+                                                     HelloExt, dtls_v1:corresponding_tls_version(Version),
+                                                     SslOpts, Session0, 
                                                      ConnectionStates0, Renegotiation,
-                                                     Session0#session.is_resumable) of
-	{Session, ConnectionStates, Protocol, ServerHelloExt} ->
-	    {Version, {Type, Session}, ConnectionStates, Protocol, ServerHelloExt, HashSign}
-    catch throw:Alert ->
-	    Alert
-    end.
+                                                     Session0#session.is_resumable),
+    {Version, {Type, Session}, ConnectionStates, Protocol, ServerHelloExt, HashSign}.
 
 handle_server_hello_extensions(Version, SessionId, Random, CipherSuite,
 			       Compression, HelloExt, SslOpt, ConnectionStates0, Renegotiation, IsNew) ->
-    try ssl_handshake:handle_server_hello_extensions(dtls_record, Random, CipherSuite,
+    {ConnectionStates, ProtoExt, Protocol, OcspState} =
+        ssl_handshake:handle_server_hello_extensions(dtls_record, Random, CipherSuite,
                                                      Compression, HelloExt,
                                                      dtls_v1:corresponding_tls_version(Version),
-                                                     SslOpt, ConnectionStates0, Renegotiation, IsNew) of
-	{ConnectionStates, ProtoExt, Protocol, OcspState} ->
-	    {Version, SessionId, ConnectionStates, ProtoExt, Protocol, OcspState}
-    catch throw:Alert ->
-	    Alert
-    end.
+                                                     SslOpt, ConnectionStates0, Renegotiation, IsNew),
+    {Version, SessionId, ConnectionStates, ProtoExt, Protocol, OcspState}.
 
 %%--------------------------------------------------------------------
 
diff --git a/lib/ssl/src/ssl_alert.hrl b/lib/ssl/src/ssl_alert.hrl
index eb3e3ec837..420b014aae 100644
--- a/lib/ssl/src/ssl_alert.hrl
+++ b/lib/ssl/src/ssl_alert.hrl
@@ -26,6 +26,7 @@
 
 -ifndef(ssl_alert).
 -define(ssl_alert, true).
+%%-define(ssl_debug, true).
 -include_lib("kernel/include/logger.hrl").
 
 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
@@ -114,8 +115,14 @@
 -define(CERTIFICATE_REQUIRED, 116).
 -define(NO_APPLICATION_PROTOCOL, 120).
 
--define(ALERT_REC(Level,Desc), #alert{level=Level,description=Desc,where= ?LOCATION}).
--define(ALERT_REC(Level,Desc,Reason), #alert{level=Level,description=Desc,where=?LOCATION,reason=Reason}).
+-ifdef(ssl_debug).
+-define(ST_LOCATION, fun(Map) -> Map#{st => process_info(self(), current_stacktrace)} end (?LOCATION)).
+-else.
+-define(ST_LOCATION, ?LOCATION).
+-endif.
+
+-define(ALERT_REC(Level,Desc), #alert{level=Level,description=Desc,where= ?ST_LOCATION}).
+-define(ALERT_REC(Level,Desc,Reason), #alert{level=Level,description=Desc,where=?ST_LOCATION,reason=Reason}).
 
 -define(MAX_ALERTS, 10).
 
diff --git a/lib/ssl/src/ssl_gen_statem.erl b/lib/ssl/src/ssl_gen_statem.erl
index d8573f06dc..1370036013 100644
--- a/lib/ssl/src/ssl_gen_statem.erl
+++ b/lib/ssl/src/ssl_gen_statem.erl
@@ -686,7 +686,11 @@ downgrade(info, {CloseTag, Socket},
 downgrade(info, Info, State) ->
     tls_gen_connection:handle_info(Info, ?FUNCTION_NAME, State);
 downgrade(Type, Event, State) ->
-     tls_dtls_connection:?FUNCTION_NAME(Type, Event, State).
+    try
+        tls_dtls_connection:?FUNCTION_NAME(Type, Event, State)
+    catch throw:#alert{} = Alert ->
+            handle_own_alert(Alert, ?FUNCTION_NAME, State)
+    end.
 
 %%====================================================================
 %%  Event/Msg handling
diff --git a/lib/ssl/src/tls_connection.erl b/lib/ssl/src/tls_connection.erl
index f4786e3c6a..162390b74b 100644
--- a/lib/ssl/src/tls_connection.erl
+++ b/lib/ssl/src/tls_connection.erl
@@ -215,7 +215,7 @@ hello(internal, #client_hello{extensions = Extensions} = Hello,
      [{reply, From, {ok, Extensions}}]};
 hello(internal, #server_hello{extensions = Extensions} = Hello,
       #state{ssl_options = #{
-                 handshake := hello},
+                             handshake := hello},
              handshake_env = HsEnv,
              start_or_recv_from = From} = State) ->   
     {next_state, user_hello,
@@ -229,52 +229,56 @@ hello(internal, #client_hello{client_version = ClientVersion} = Hello, #state{ss
             %% Continue in TLS 1.3 'start' state
             {next_state, start, State0, [{change_callback_module, tls_connection_1_3}, {next_event, internal, Hello}]};
         tls_1_0_to_1_2_fsm ->
-            case handle_client_hello(Hello, State0) of
+            try handle_client_hello(Hello, State0) of
                 {ServerHelloExt, Type, State} ->
-                    {next_state, hello, State, [{next_event, internal, {common_client_hello, Type, ServerHelloExt}}]};
-                Alert ->
-                    ssl_gen_statem:handle_own_alert(Alert, hello,
-                                                        State0#state{connection_env = CEnv#connection_env{negotiated_version
-                                                                                                          = ClientVersion}})
+                    {next_state, hello, State, [{next_event, internal, {common_client_hello, Type, ServerHelloExt}}]}
+            catch throw:#alert{} = Alert ->
+                    State = State0#state{connection_env = CEnv#connection_env{negotiated_version = ClientVersion}},
+                    ssl_gen_statem:handle_own_alert(Alert, hello, State)
             end
     end;
 hello(internal, #server_hello{} = Hello,
       #state{connection_states = ConnectionStates0,
-             connection_env = #connection_env{negotiated_version = ReqVersion} = CEnv,
+             connection_env = CEnv,
 	     static_env = #static_env{role = client},
              handshake_env = #handshake_env{
                                 ocsp_stapling_state = OcspState0,
                                 renegotiation = {Renegotiation, _}} = HsEnv,
              session = #session{session_id = OldId},
-	     ssl_options = SslOptions} = State) ->   
-    case tls_handshake:hello(Hello, SslOptions, ConnectionStates0, Renegotiation, OldId) of
-        #alert{} = Alert -> 
-            ssl_gen_statem:handle_own_alert(Alert, hello,
-                                            State#state{connection_env =
-                                                            CEnv#connection_env{negotiated_version = ReqVersion}
-                                                       });
-        %% Legacy TLS 1.2 and older
-        {Version, NewId, ConnectionStates, ProtoExt, Protocol, OcspState} ->
-            tls_dtls_connection:handle_session(Hello, 
-                                          Version, NewId, ConnectionStates, ProtoExt, Protocol,
-                                          State#state{
-                                            handshake_env = HsEnv#handshake_env{
-                                                              ocsp_stapling_state = maps:merge(OcspState0,OcspState)}});
-        %% TLS 1.3
-        {next_state, wait_sh, SelectedVersion, OcspState} ->
-            %% Continue in TLS 1.3 'wait_sh' state
-            {next_state, wait_sh,
-             State#state{handshake_env = HsEnv#handshake_env{ocsp_stapling_state =  maps:merge(OcspState0,OcspState)}, 
-                         connection_env = CEnv#connection_env{negotiated_version = SelectedVersion}},
-             [{change_callback_module, tls_connection_1_3}, {next_event, internal, Hello}]}
+	     ssl_options = SslOptions} = State) ->
+    try
+        case tls_handshake:hello(Hello, SslOptions, ConnectionStates0, Renegotiation, OldId) of
+            %% Legacy TLS 1.2 and older
+            {Version, NewId, ConnectionStates, ProtoExt, Protocol, OcspState} ->
+                tls_dtls_connection:handle_session(Hello,
+                                                   Version, NewId, ConnectionStates, ProtoExt, Protocol,
+                                                   State#state{
+                                                     handshake_env = HsEnv#handshake_env{
+                                                                       ocsp_stapling_state = maps:merge(OcspState0,OcspState)}});
+            %% TLS 1.3
+            {next_state, wait_sh, SelectedVersion, OcspState} ->
+                %% Continue in TLS 1.3 'wait_sh' state
+                {next_state, wait_sh,
+                 State#state{handshake_env = HsEnv#handshake_env{ocsp_stapling_state =  maps:merge(OcspState0,OcspState)}, 
+                             connection_env = CEnv#connection_env{negotiated_version = SelectedVersion}},
+                 [{change_callback_module, tls_connection_1_3}, {next_event, internal, Hello}]}
+        end
+    catch throw:#alert{} = Alert ->
+            ssl_gen_statem:handle_own_alert(Alert, hello, State)
     end;
 hello(info, Event, State) ->
     tls_gen_connection:handle_info(Event, ?FUNCTION_NAME, State);
 hello(Type, Event, State) ->
-    tls_dtls_connection:gen_handshake(?FUNCTION_NAME, Type, Event, State).
+    try tls_dtls_connection:gen_handshake(?FUNCTION_NAME, Type, Event, State)
+    catch throw:#alert{} = Alert ->
+            ssl_gen_statem:handle_own_alert(Alert, ?FUNCTION_NAME, State)
+    end.
 
 user_hello(Type, Event, State) ->
-    tls_dtls_connection:gen_handshake(?FUNCTION_NAME, Type, Event, State).
+    try tls_dtls_connection:gen_handshake(?FUNCTION_NAME, Type, Event, State)
+    catch throw:#alert{} = Alert ->
+            ssl_gen_statem:handle_own_alert(Alert, ?FUNCTION_NAME, State)
+    end.
 
 %%--------------------------------------------------------------------
 -spec abbreviated(gen_statem:event_type(), term(), #state{}) ->
@@ -283,7 +287,10 @@ user_hello(Type, Event, State) ->
 abbreviated(info, Event, State) ->
     gen_info(Event, ?FUNCTION_NAME, State);
 abbreviated(Type, Event, State) ->
-    tls_dtls_connection:gen_handshake(?FUNCTION_NAME, Type, Event, State).
+    try tls_dtls_connection:gen_handshake(?FUNCTION_NAME, Type, Event, State)
+    catch throw:#alert{} = Alert ->
+            ssl_gen_statem:handle_own_alert(Alert, ?FUNCTION_NAME, State)
+    end.
 
 %%--------------------------------------------------------------------
 -spec wait_ocsp_stapling(gen_statem:event_type(), term(), #state{}) ->
@@ -292,7 +299,10 @@ abbreviated(Type, Event, State) ->
 wait_ocsp_stapling(info, Event, State) ->
     gen_info(Event, ?FUNCTION_NAME, State);
 wait_ocsp_stapling(Type, Event, State) ->
-    tls_dtls_connection:gen_handshake(?FUNCTION_NAME, Type, Event, State).
+    try tls_dtls_connection:gen_handshake(?FUNCTION_NAME, Type, Event, State)
+    catch throw:#alert{} = Alert ->
+            ssl_gen_statem:handle_own_alert(Alert, ?FUNCTION_NAME, State)
+    end.
 
 %%--------------------------------------------------------------------
 -spec certify(gen_statem:event_type(), term(), #state{}) ->
@@ -301,7 +311,10 @@ wait_ocsp_stapling(Type, Event, State) ->
 certify(info, Event, State) ->
     gen_info(Event, ?FUNCTION_NAME, State);
 certify(Type, Event, State) ->
-    tls_dtls_connection:gen_handshake(?FUNCTION_NAME, Type, Event, State).
+    try tls_dtls_connection:gen_handshake(?FUNCTION_NAME, Type, Event, State)
+    catch throw:#alert{} = Alert ->
+            ssl_gen_statem:handle_own_alert(Alert, ?FUNCTION_NAME, State)
+    end.
 
 
 %%--------------------------------------------------------------------
@@ -310,7 +323,10 @@ certify(Type, Event, State) ->
 cipher(info, Event, State) ->
     gen_info(Event, ?FUNCTION_NAME, State);
 cipher(Type, Event, State) ->
-     tls_dtls_connection:gen_handshake(?FUNCTION_NAME, Type, Event, State).
+    try tls_dtls_connection:gen_handshake(?FUNCTION_NAME, Type, Event, State)
+    catch throw:#alert{} = Alert ->
+            ssl_gen_statem:handle_own_alert(Alert, ?FUNCTION_NAME, State)
+    end.
 
 %%--------------------------------------------------------------------
 -spec connection(gen_statem:event_type(),  
@@ -395,7 +411,10 @@ connection(internal, #client_hello{},
     State = tls_gen_connection:reinit_handshake_data(State0),
     tls_gen_connection:next_event(?FUNCTION_NAME, no_record, State);
 connection(Type, Event, State) ->
-    tls_dtls_connection:?FUNCTION_NAME(Type, Event, State).
+    try tls_dtls_connection:?FUNCTION_NAME(Type, Event, State)
+    catch throw:#alert{} = Alert ->
+            ssl_gen_statem:handle_own_alert(Alert, ?FUNCTION_NAME, State)
+    end.
 
 %%--------------------------------------------------------------------
 -spec downgrade(gen_statem:event_type(), term(), #state{}) ->
@@ -474,50 +493,44 @@ initial_state(Role, Sender, Host, Port, Socket, {SSLOptions, SocketOptions, Trac
       }.
 
 handle_client_hello(#client_hello{client_version = ClientVersion} = Hello, State0) ->
-    case tls_dtls_connection:handle_sni_extension(State0, Hello) of
-        #state{connection_states = ConnectionStates0,
-                    static_env = #static_env{trackers = Trackers},
-                    handshake_env = #handshake_env{
-                                       kex_algorithm = KeyExAlg,
-                                       renegotiation = {Renegotiation, _},
-                                       negotiated_protocol = CurrentProtocol,
-                                       sni_guided_cert_selection = SNICertSelection} = HsEnv,
-                    connection_env = CEnv,
-                    session = #session{own_certificates = OwnCerts} = Session0,
-               ssl_options = SslOpts} = State ->
-            SessionTracker = proplists:get_value(session_id_tracker, Trackers),
-            case tls_handshake:hello(Hello,
-                                     SslOpts,
-                                     {SessionTracker, Session0,
-                                      ConnectionStates0, OwnCerts, KeyExAlg},
-                                     Renegotiation) of
-                #alert{} = Alert ->
-                    Alert;
-                {Version, {Type, Session},
-                 ConnectionStates, Protocol0, ServerHelloExt0, HashSign} ->
-                    Protocol = case Protocol0 of
-                                   undefined -> CurrentProtocol;
-                                   _ -> Protocol0
-                               end,
-                    ServerHelloExt =
-                        case SNICertSelection of
-                            true ->
-                                ServerHelloExt0#{sni => #sni{hostname = ""}};
-                            false ->
-                                ServerHelloExt0
-                        end,
-                    {ServerHelloExt, Type, State#state{connection_states  = ConnectionStates,
-                                                       connection_env = CEnv#connection_env{negotiated_version = Version},
-                                                       handshake_env = HsEnv#handshake_env{
-                                                                         hashsign_algorithm = HashSign,
-                                                                         client_hello_version = ClientVersion,
-                                                                         negotiated_protocol = Protocol},
-                                                       session = Session
-                                                      }}
-            end;
-        #alert{} = Alert ->
-            Alert
-    end.
+    State = tls_dtls_connection:handle_sni_extension(State0, Hello),
+    #state{connection_states = ConnectionStates0,
+           static_env = #static_env{trackers = Trackers},
+           handshake_env = #handshake_env{
+                              kex_algorithm = KeyExAlg,
+                              renegotiation = {Renegotiation, _},
+                              negotiated_protocol = CurrentProtocol,
+                              sni_guided_cert_selection = SNICertSelection} = HsEnv,
+           connection_env = CEnv,
+           session = #session{own_certificates = OwnCerts} = Session0,
+           ssl_options = SslOpts} = State,
+    SessionTracker = proplists:get_value(session_id_tracker, Trackers),
+    {Version, {Type, Session},
+     ConnectionStates, Protocol0, ServerHelloExt0, HashSign} =
+        tls_handshake:hello(Hello,
+                            SslOpts,
+                            {SessionTracker, Session0,
+                             ConnectionStates0, OwnCerts, KeyExAlg},
+                            Renegotiation),
+    Protocol = case Protocol0 of
+                   undefined -> CurrentProtocol;
+                   _ -> Protocol0
+               end,
+    ServerHelloExt =
+        case SNICertSelection of
+            true ->
+                ServerHelloExt0#{sni => #sni{hostname = ""}};
+            false ->
+                ServerHelloExt0
+        end,
+    {ServerHelloExt, Type, State#state{connection_states  = ConnectionStates,
+                                       connection_env = CEnv#connection_env{negotiated_version = Version},
+                                       handshake_env = HsEnv#handshake_env{
+                                                         hashsign_algorithm = HashSign,
+                                                         client_hello_version = ClientVersion,
+                                                         negotiated_protocol = Protocol},
+                                       session = Session
+                                      }}.
 
 
 gen_info(Event, connection = StateName, State) ->
diff --git a/lib/ssl/src/tls_dtls_connection.erl b/lib/ssl/src/tls_dtls_connection.erl
index 94e68c7045..5ee5c41b44 100644
--- a/lib/ssl/src/tls_dtls_connection.erl
+++ b/lib/ssl/src/tls_dtls_connection.erl
@@ -22,6 +22,8 @@
 %%----------------------------------------------------------------------
 %% Purpose: Common handling of a TLS/SSL/DTLS connection, see also
 %% tls_connection.erl and dtls_connection.erl
+%%
+%% NOTE: All alerts are thrown out of this module
 %%----------------------------------------------------------------------
 
 -module(tls_dtls_connection).
@@ -113,13 +115,11 @@ handle_session(#server_hello{cipher_suite = CipherSuite,
     
     PremasterSecret = make_premaster_secret(ReqVersion, KeyAlgorithm),
 
-    {ExpectNPN, Protocol} = case Protocol0 of
-				undefined -> 
-
-				    {false, CurrentProtocol};
-				_ -> 
-				    {ProtoExt =:= npn, Protocol0}
-			    end,
+    {ExpectNPN, Protocol} =
+        case Protocol0 of
+            undefined -> {false, CurrentProtocol};
+            _ -> {ProtoExt =:= npn, Protocol0}
+        end,
 
     State = State0#state{connection_states = ConnectionStates,
 			 handshake_env = HsEnv#handshake_env{kex_algorithm = KeyAlgorithm,
@@ -163,9 +163,9 @@ hello(Type, Event, State) ->
                  #hello_request{} | term(), #state{}) ->
           gen_statem:state_function_result().
 %%--------------------------------------------------------------------
-user_hello({call, From}, cancel, State) ->
+user_hello({call, From}, cancel, _State) ->
     gen_statem:reply(From, ok),
-    ssl_gen_statem:handle_own_alert(?ALERT_REC(?FATAL, ?USER_CANCELED, user_canceled), ?FUNCTION_NAME, State);
+    throw(?ALERT_REC(?FATAL, ?USER_CANCELED, user_canceled));
 user_hello({call, From}, {handshake_continue, NewOptions, Timeout},
            #state{static_env = #static_env{role = Role},
                   handshake_env = #handshake_env{hello = Hello},
@@ -208,7 +208,7 @@ abbreviated(internal, #finished{verify_data = Data} = Finished,
                                                       Connection),
 	    Connection:next_event(connection, Record, State, [{{timeout, handshake}, infinity, close}]);
 	#alert{} = Alert ->
-	    ssl_gen_statem:handle_own_alert(Alert, ?FUNCTION_NAME, State0)
+            throw(Alert)
     end;
 abbreviated(internal, #finished{verify_data = Data} = Finished,
 	    #state{static_env = #static_env{role = client,
@@ -231,7 +231,7 @@ abbreviated(internal, #finished{verify_data = Data} = Finished,
                                                       Connection),
 	    Connection:next_event(connection, Record, State, [{{timeout, handshake}, infinity, close} | Actions]);
 	#alert{} = Alert ->
-	    ssl_gen_statem:handle_own_alert(Alert, ?FUNCTION_NAME, State0)
+            throw(Alert)
     end;
 %% only allowed to send next_protocol message after change cipher spec
 %% & before finished message and it is not allowed during renegotiation
@@ -308,11 +308,8 @@ certify(info, Msg, State) ->
     handle_info(Msg, ?FUNCTION_NAME, State);
 certify(internal, #certificate{asn1_certificates = []},
 	#state{static_env = #static_env{role = server},
-	       ssl_options = #{verify := verify_peer,
-                               fail_if_no_peer_cert := true}} =
-	    State) ->
-    Alert =  ?ALERT_REC(?FATAL,?HANDSHAKE_FAILURE, no_client_certificate_provided),
-    ssl_gen_statem:handle_own_alert(Alert, ?FUNCTION_NAME, State);
+	       ssl_options = #{verify := verify_peer, fail_if_no_peer_cert := true}}) ->
+    throw(?ALERT_REC(?FATAL,?HANDSHAKE_FAILURE, no_client_certificate_provided));
 certify(internal, #certificate{asn1_certificates = []},
 	#state{static_env = #static_env{role = server,
                                         protocol_cb = Connection},
@@ -322,10 +319,8 @@ certify(internal, #certificate{asn1_certificates = []},
     Connection:next_event(?FUNCTION_NAME, no_record, State0#state{client_certificate_status = empty});
 certify(internal, #certificate{},
 	#state{static_env = #static_env{role = server},
-	       ssl_options = #{verify := verify_none}} =
-	    State) ->
-    Alert =  ?ALERT_REC(?FATAL,?UNEXPECTED_MESSAGE, unrequested_certificate),
-    ssl_gen_statem:handle_own_alert(Alert, ?FUNCTION_NAME, State);
+	       ssl_options = #{verify := verify_none}}) ->
+    throw(?ALERT_REC(?FATAL,?UNEXPECTED_MESSAGE, unrequested_certificate));
 certify(internal, #certificate{},
         #state{static_env = #static_env{protocol_cb = Connection},
                handshake_env = #handshake_env{
@@ -352,7 +347,7 @@ certify(internal, #certificate{asn1_certificates = [Peer|_]} = Cert,
                     end,
             handle_peer_cert(Role, PeerCert, PublicKeyInfo, State, Connection, []);
         #alert{} = Alert ->
-            ssl_gen_statem:handle_own_alert(Alert, ?FUNCTION_NAME, State0)
+            throw(Alert)
     end;
 certify(internal, #server_key_exchange{exchange_keys = Keys},
         #state{static_env = #static_env{role = client,
@@ -394,13 +389,12 @@ certify(internal, #server_key_exchange{exchange_keys = Keys},
                                                  session = session_handle_params(Params#server_key_params.params, Session)},
                     Connection);
 		false ->
-		    ssl_gen_statem:handle_own_alert(?ALERT_REC(?FATAL, ?DECRYPT_ERROR),
-						?FUNCTION_NAME, State)
+                    throw(?ALERT_REC(?FATAL, ?DECRYPT_ERROR))
 	    end
     end;
 certify(internal, #certificate_request{},
 	#state{static_env = #static_env{role = client},
-               handshake_env = #handshake_env{kex_algorithm = KexAlg}} = State)
+               handshake_env = #handshake_env{kex_algorithm = KexAlg}})
   when KexAlg == dh_anon; 
        KexAlg == ecdh_anon;
        KexAlg == psk; 
@@ -410,8 +404,7 @@ certify(internal, #certificate_request{},
        KexAlg == srp_dss; 
        KexAlg == srp_rsa; 
        KexAlg == srp_anon ->
-    ssl_gen_statem:handle_own_alert(?ALERT_REC(?FATAL, ?HANDSHAKE_FAILURE),
-                     ?FUNCTION_NAME, State);
+    throw(?ALERT_REC(?FATAL, ?HANDSHAKE_FAILURE));
 certify(internal, #certificate_request{},
 	#state{static_env = #static_env{role = client,
                                         protocol_cb = Connection},
@@ -439,7 +432,7 @@ certify(internal, #certificate_request{} = CertRequest,
            case ssl_handshake:select_hashsign(CertRequest, Cert,
                                               SupportedHashSigns, TLSVersion) of
                #alert {} = Alert ->
-                   ssl_gen_statem:handle_own_alert(Alert, ?FUNCTION_NAME, State);
+                   throw(Alert);
                SelectedHashSign ->
                    Connection:next_event(?FUNCTION_NAME, no_record,
                                          State#state{client_certificate_status = requested,
@@ -458,7 +451,7 @@ certify(internal, #server_hello_done{},
   when KexAlg == psk ->
     case ssl_handshake:premaster_secret({KexAlg, PSKIdentity}, PSKLookup) of
 	#alert{} = Alert ->
-	    ssl_gen_statem:handle_own_alert(Alert, ?FUNCTION_NAME, State0);
+            throw(Alert);
 	PremasterSecret ->
 	    State = master_secret(PremasterSecret,
 				  State0#state{handshake_env =
@@ -480,7 +473,7 @@ certify(internal, #server_hello_done{},
     case ssl_handshake:premaster_secret({KexAlg, PSKIdentity}, PSKLookup, 
 					RSAPremasterSecret) of
 	#alert{} = Alert ->
-	    ssl_gen_statem:handle_own_alert(Alert, ?FUNCTION_NAME, State0);
+            throw(Alert);
 	PremasterSecret ->
 	    State = master_secret(PremasterSecret, 
 				  State0#state{handshake_env = 
@@ -501,7 +494,7 @@ certify(internal, #server_hello_done{},
 	    State = State0#state{connection_states = ConnectionStates},
 	    client_certify_and_key_exchange(State, Connection);
 	#alert{} = Alert ->
-	    ssl_gen_statem:handle_own_alert(Alert, ?FUNCTION_NAME, State0)
+            throw(Alert)
     end;
 %% Master secret is calculated from premaster_secret
 certify(internal, #server_hello_done{},
@@ -519,7 +512,7 @@ certify(internal, #server_hello_done{},
 				 session = Session},
 	    client_certify_and_key_exchange(State, Connection);
 	#alert{} = Alert ->
-	    ssl_gen_statem:handle_own_alert(Alert, ?FUNCTION_NAME, State0)
+            throw(Alert)
     end;
 certify(internal, #client_key_exchange{exchange_keys = Keys},
 	State = #state{handshake_env = #handshake_env{kex_algorithm = KeyAlg}, 
@@ -537,7 +529,7 @@ certify(internal, #client_key_exchange{exchange_keys = Keys},
 				    State, Connection)
     catch
 	#alert{} = Alert ->
-	    ssl_gen_statem:handle_own_alert(Alert, ?FUNCTION_NAME, State)
+            throw(Alert)
     end;
 certify(internal, #hello_request{}, _) ->
     keep_state_and_data;
@@ -574,8 +566,8 @@ cipher(internal, #certificate_verify{signature = Signature,
 cipher(internal, #finished{},
        #state{static_env = #static_env{role = server},
               handshake_env = #handshake_env{expecting_next_protocol_negotiation = true,
-                                             negotiated_protocol = undefined}} = State0) ->
-    ssl_gen_statem:handle_own_alert(?ALERT_REC(?FATAL,?UNEXPECTED_MESSAGE), ?FUNCTION_NAME, State0);
+                                             negotiated_protocol = undefined}}) ->
+    throw(?ALERT_REC(?FATAL,?UNEXPECTED_MESSAGE));
 cipher(internal, #finished{verify_data = Data} = Finished,
        #state{static_env = #static_env{role = Role,
                                        host = Host,
@@ -603,7 +595,7 @@ cipher(internal, #finished{verify_data = Data} = Finished,
 	    cipher_role(Role, Data, Session,
 			State#state{handshake_env = HsEnv#handshake_env{expecting_finished = false}});
         #alert{} = Alert ->
-	    ssl_gen_statem:handle_own_alert(Alert, ?FUNCTION_NAME, State)
+            throw(Alert)
     end;
 %% only allowed to send next_protocol message after change cipher spec
 %% & before finished message and it is not allowed during renegotiation
@@ -682,13 +674,9 @@ downgrade(Type, Event, State) ->
     ssl_gen_statem:handle_common_event(Type, Event, ?FUNCTION_NAME, State).
 
 gen_handshake(StateName, Type, Event, State) ->
-    try
-        tls_dtls_connection:StateName(Type, Event, State)
-    catch
-        _:_ ->
-            ssl_gen_statem:handle_own_alert(?ALERT_REC(?FATAL, ?HANDSHAKE_FAILURE,
-                                                       malformed_handshake_data),
-                                            StateName, State)
+    try tls_dtls_connection:StateName(Type, Event, State)
+    catch error:_ ->
+            throw(?ALERT_REC(?FATAL, ?HANDSHAKE_FAILURE, malformed_handshake_data))
     end.
 
 %%--------------------------------------------------------------------
@@ -817,18 +805,12 @@ new_server_hello(#server_hello{cipher_suite = CipherSuite,
 			      session_id = SessionId},
                  #state{session = Session0,
                         static_env = #static_env{protocol_cb = Connection}} = State0, Connection) ->
-    try server_certify_and_key_exchange(State0, Connection) of
-        #state{} = State1 ->
-            {State, Actions} = server_hello_done(State1, Connection),
-	    Session =
-		Session0#session{session_id = SessionId,
-				 cipher_suite = CipherSuite,
-				 compression_method = Compression},
-	    Connection:next_event(certify, no_record, State#state{session = Session}, Actions)
-    catch
-        #alert{} = Alert ->
-	    ssl_gen_statem:handle_own_alert(Alert, hello, State0)
-    end.
+    #state{} = State1 = server_certify_and_key_exchange(State0, Connection),
+    {State, Actions} = server_hello_done(State1, Connection),
+    Session = Session0#session{session_id = SessionId,
+                               cipher_suite = CipherSuite,
+                               compression_method = Compression},
+    Connection:next_event(certify, no_record, State#state{session = Session}, Actions).
 
 resumed_server_hello(#state{session = Session,
 			    connection_states = ConnectionStates0,
@@ -844,7 +826,7 @@ resumed_server_hello(#state{session = Session,
 		finalize_handshake(State1, abbreviated, Connection),
 	    Connection:next_event(abbreviated, no_record, State, Actions);
 	#alert{} = Alert ->
-	    ssl_gen_statem:handle_own_alert(Alert, hello, State0)
+            throw(Alert)
     end.
 
 server_hello(ServerHello, State0, Connection) ->
@@ -914,17 +896,10 @@ verify_client_cert(#state{client_certificate_requested = false} = State, _) ->
     State.
 
 client_certify_and_key_exchange(State0, Connection) ->
-    try do_client_certify_and_key_exchange(State0, Connection) of
-        State1 = #state{} ->
-	    {State2, Actions} = finalize_handshake(State1, certify, Connection),
-            State = State2#state{
-                      %% Reinitialize
-                      client_certificate_status = not_requested},
-	    Connection:next_event(cipher, no_record, State, Actions)
-    catch
-        throw:#alert{} = Alert ->
-	    ssl_gen_statem:handle_own_alert(Alert, certify, State0)
-    end.
+    State1 = do_client_certify_and_key_exchange(State0, Connection),
+    {State2, Actions} = finalize_handshake(State1, certify, Connection),
+    State = State2#state{client_certificate_status = not_requested},     %% Reinitialize
+    Connection:next_event(cipher, no_record, State, Actions).
 
 do_client_certify_and_key_exchange(State0, Connection) ->
     State1 = certify_client(State0, Connection),
@@ -954,7 +929,7 @@ certify_client_key_exchange(#encrypted_premaster_secret{premaster_secret= EncPMS
                 end;
             _ -> %% erlang:byte_size(Secret) =/= ?NUM_OF_PREMASTERSECRET_BYTES
                 FakeSecret
-        catch 
+        catch
             #alert{description = ?DECRYPT_ERROR} ->
                 FakeSecret
         end,
@@ -1178,12 +1153,7 @@ key_exchange(#state{static_env = #static_env{role = server},
        KexAlg == srp_rsa;
        KexAlg == srp_anon ->
     SrpParams = handle_srp_identity(Username, LookupFun),
-    Keys = case generate_srp_server_keys(SrpParams, 0) of
-	       Alert = #alert{} ->
-		   throw(Alert);
-	       Keys0 = {_,_} ->
-		   Keys0
-	   end,
+    Keys = generate_srp_server_keys(SrpParams, 0),
     #{security_parameters := SecParams} =
 	ssl_record:pending_connection_state(ConnectionStates0, read),
     #security_parameters{client_random = ClientRandom,
@@ -1290,7 +1260,7 @@ rsa_key_exchange(Version, PremasterSecret, PublicKeyInfo = {Algorithm, _, _})
 			       {premaster_secret, PremasterSecret,
 				PublicKeyInfo});
 rsa_key_exchange(_, _, _) ->
-    throw (?ALERT_REC(?FATAL,?HANDSHAKE_FAILURE, pub_key_is_not_rsa)).
+    throw(?ALERT_REC(?FATAL,?HANDSHAKE_FAILURE, pub_key_is_not_rsa)).
 
 rsa_psk_key_exchange(Version, PskIdentity, PremasterSecret, 
 		     PublicKeyInfo = {Algorithm, _, _})
@@ -1307,7 +1277,7 @@ rsa_psk_key_exchange(Version, PskIdentity, PremasterSecret,
 			       {psk_premaster_secret, PskIdentity, PremasterSecret,
 				PublicKeyInfo});
 rsa_psk_key_exchange(_, _, _, _) ->
-    throw (?ALERT_REC(?FATAL,?HANDSHAKE_FAILURE, pub_key_is_not_rsa)).
+    throw(?ALERT_REC(?FATAL,?HANDSHAKE_FAILURE, pub_key_is_not_rsa)).
 
 request_client_cert(#state{handshake_env = #handshake_env{kex_algorithm = Alg}} = State, _)
   when Alg == dh_anon; 
@@ -1355,7 +1325,7 @@ calculate_master_secret(PremasterSecret,
 				  session = Session},
 	    Connection:next_event(Next, no_record, State);
 	#alert{} = Alert ->
-	    ssl_gen_statem:handle_own_alert(Alert, certify, State0)
+            throw(Alert)
     end.
 
 finalize_handshake(State0, StateName, Connection) ->
@@ -1469,7 +1439,7 @@ calculate_secret(#server_srp_params{srp_n = Prime, srp_g = Generator} = ServerKe
 			    certify, certify).
 
 master_secret(#alert{} = Alert, _) ->
-    Alert;
+    throw(Alert);
 master_secret(PremasterSecret, #state{static_env = #static_env{role = Role},
                                       connection_env = #connection_env{negotiated_version = Version},
                                       session = Session,
@@ -1482,11 +1452,11 @@ master_secret(PremasterSecret, #state{static_env = #static_env{role = Role},
 		  Session#session{master_secret = MasterSecret},
 	      connection_states = ConnectionStates};
 	#alert{} = Alert ->
-	    Alert
+	    throw(Alert)
     end.
 
 generate_srp_server_keys(_SrpParams, 10) ->
-    ?ALERT_REC(?FATAL, ?ILLEGAL_PARAMETER);
+    throw(?ALERT_REC(?FATAL, ?ILLEGAL_PARAMETER));
 generate_srp_server_keys(SrpParams =
 			     #srp_user{generator = Generator, prime = Prime,
 				       verifier = Verifier}, N) ->
@@ -1499,9 +1469,8 @@ generate_srp_server_keys(SrpParams =
     end.
 
 generate_srp_client_keys(_Generator, _Prime, 10) ->
-    ?ALERT_REC(?FATAL, ?ILLEGAL_PARAMETER);
+    throw(?ALERT_REC(?FATAL, ?ILLEGAL_PARAMETER));
 generate_srp_client_keys(Generator, Prime, N) ->
-
     try crypto:generate_key(srp, {user, [Generator, Prime, '6a']}) of
 	Keys ->
 	    Keys
@@ -1634,7 +1603,7 @@ handle_resumed_session(SessId, #state{static_env = #static_env{host = Host,
                                                             connection_states = ConnectionStates,
                                                             session = Session});
 	#alert{} = Alert ->
-	    ssl_gen_statem:handle_own_alert(Alert, hello, State)
+            throw(Alert)
     end.
 
 make_premaster_secret({MajVer, MinVer}, rsa) ->
@@ -1663,8 +1632,8 @@ handle_sni_extension(#state{static_env =
     case ssl_gen_statem:handle_sni_extension(PossibleSNI, State0) of
         {ok, State} ->
             State;
-        {error, Alert} ->
-            Alert
+        {error, #alert{}=Alert} ->
+            throw(Alert)
     end.
 
 ensure_tls({254, _} = Version) -> 
diff --git a/lib/ssl/src/tls_handshake.erl b/lib/ssl/src/tls_handshake.erl
index 05cf1a7339..cb00fa57a3 100644
--- a/lib/ssl/src/tls_handshake.erl
+++ b/lib/ssl/src/tls_handshake.erl
@@ -108,7 +108,8 @@ client_hello(_Host, _Port, ConnectionStates,
 	    boolean(), #session{}) ->
           {tls_record:tls_version(), ssl:session_id(), 
            ssl_record:connection_states(), alpn | npn, binary() | undefined, map()}|
-          {atom(), atom(), tls_record:tls_version(), map()} | #alert{}.
+          {atom(), atom(), tls_record:tls_version(), map()}.
+                                                % Otherwise Throws #alert{}
 %%
 %% Description: Handles a received hello message
 %%--------------------------------------------------------------------
@@ -128,7 +129,7 @@ hello(#server_hello{server_version = {Major, Minor},
        (M > 3 orelse M =:= 3 andalso N >= 4) andalso  %% TLS 1.3 client
        (Major =:= 3 andalso Minor < 3 andalso         %% Negotiating TLS 1.1 or prior
         Down =:= ?RANDOM_OVERRIDE_TLS11) ->
-    ?ALERT_REC(?FATAL, ?ILLEGAL_PARAMETER);
+    throw(?ALERT_REC(?FATAL, ?ILLEGAL_PARAMETER));
 
 %% TLS 1.2 clients SHOULD also check that the last eight bytes are not
 %% equal to the second value if the ServerHello indicates TLS 1.1 or below.
@@ -138,7 +139,7 @@ hello(#server_hello{server_version = {Major, Minor},
   when (M =:= 3 andalso N =:= 3) andalso              %% TLS 1.2 client
        (Major =:= 3 andalso Minor < 3 andalso         %% Negotiating TLS 1.1 or prior
         Down =:= ?RANDOM_OVERRIDE_TLS11) ->
-    ?ALERT_REC(?FATAL, ?ILLEGAL_PARAMETER);
+    throw(?ALERT_REC(?FATAL, ?ILLEGAL_PARAMETER));
 
 
 %% TLS 1.3 - 4.2.1.  Supported Versions
@@ -157,9 +158,8 @@ hello(#server_hello{server_version = LegacyVersion,
 		    compression_method = Compression,
 		    session_id = SessionId,
                     extensions = #{server_hello_selected_version :=
-                                       #server_hello_selected_version{selected_version = Version} = HelloExt}
-                   },
-      #{versions := SupportedVersions, 
+                                       #server_hello_selected_version{selected_version = Version}} = HelloExt},
+      #{versions := SupportedVersions,
         ocsp_stapling := Stapling} = SslOpt,
       ConnectionStates0, Renegotiation, OldId) ->
     %% In TLS 1.3, the TLS server indicates its version using the "supported_versions" extension
@@ -169,7 +169,7 @@ hello(#server_hello{server_version = LegacyVersion,
     case LegacyVersion > {3,3} orelse
         LegacyVersion =:= {3,3} andalso Version < {3,3} of
         true ->
-            ?ALERT_REC(?FATAL, ?ILLEGAL_PARAMETER);
+            throw(?ALERT_REC(?FATAL, ?ILLEGAL_PARAMETER));
         false ->
             case tls_record:is_acceptable_version(Version, SupportedVersions) of
                 true ->
@@ -186,7 +186,7 @@ hello(#server_hello{server_version = LegacyVersion,
                                                                      ocsp_expect => ocsp_expect(Stapling)}}
                     end;
                 false ->
-                    ?ALERT_REC(?FATAL, ?ILLEGAL_PARAMETER)
+                    throw(?ALERT_REC(?FATAL, ?ILLEGAL_PARAMETER))
             end
     end;
 
@@ -205,7 +205,7 @@ hello(#server_hello{server_version = Version,
 					   Compression, HelloExt, SslOpt, 
                                            ConnectionStates0, Renegotiation, IsNew);
 	false ->
-	    ?ALERT_REC(?FATAL, ?PROTOCOL_VERSION)
+	    throw(?ALERT_REC(?FATAL, ?PROTOCOL_VERSION))
     end.
 
 
@@ -219,7 +219,7 @@ hello(#server_hello{server_version = Version,
 		   {tls_record:tls_version(), {resumed | new, #session{}}, 
 		    ssl_record:connection_states(), binary() | undefined, 
                     HelloExt::map(), {ssl:hash(), ssl:sign_algo()} | 
-                    undefined} | {atom(), atom()} | {atom(), atom(), tuple()} | #alert{}.
+                    undefined} | {atom(), atom()} | {atom(), atom(), tuple()}.
 %% TLS 1.2 Server
 %% - If "supported_versions" is present (ClientHello):
 %%   - Select version from "supported_versions" (ignore ClientHello.legacy_version)
@@ -245,8 +245,8 @@ hello(#client_hello{client_version = _ClientVersion,
         SelectedVersion = ssl_handshake:select_supported_version(ClientVersions, Versions),
         do_hello(SelectedVersion, Versions, CipherSuites, Hello, SslOpts, Info, Renegotiation)
     catch
-	_:_ ->
-	    ?ALERT_REC(?FATAL, ?HANDSHAKE_FAILURE, malformed_handshake_data)
+	error:_ ->
+	    throw(?ALERT_REC(?FATAL, ?HANDSHAKE_FAILURE, malformed_handshake_data))
     end;
 
 hello(#client_hello{client_version = ClientVersion,
@@ -259,9 +259,9 @@ hello(#client_hello{client_version = ClientVersion,
     catch
         error:{case_clause,{asn1, Asn1Reason}} ->
             %% ASN-1 decode of certificate somehow failed
-            ?ALERT_REC(?FATAL, ?INTERNAL_ERROR, {failed_to_decode_own_certificate, Asn1Reason});
-        _:_ ->
-            ?ALERT_REC(?FATAL, ?HANDSHAKE_FAILURE, malformed_handshake_data)
+            throw(?ALERT_REC(?FATAL, ?INTERNAL_ERROR, {failed_to_decode_own_certificate, Asn1Reason}));
+        error:_ ->
+            throw(?ALERT_REC(?FATAL, ?HANDSHAKE_FAILURE, malformed_handshake_data))
     end.
 
 %%--------------------------------------------------------------------
@@ -337,13 +337,13 @@ handle_client_hello(Version,
 				   ClientHashSigns, SupportedHashSigns, OwnCert, Version),
 	    ECCCurve = ssl_handshake:select_curve(Curves, SupportedECCs, ECCOrder),
 	    {Type, #session{cipher_suite = CipherSuite} = Session1}
-		= ssl_handshake:select_session(SugesstedId, CipherSuites, 
+		= ssl_handshake:select_session(SugesstedId, CipherSuites,
                                                AvailableHashSigns, Compressions,
 					       SessIdTracker, Session0#session{ecc = ECCCurve},
                                                Version, SslOpts, OwnCert),
-	    case CipherSuite of 
+	    case CipherSuite of
 		no_suite ->
-                    ?ALERT_REC(?FATAL, ?INSUFFICIENT_SECURITY, no_suitable_ciphers);
+                    throw(?ALERT_REC(?FATAL, ?INSUFFICIENT_SECURITY, no_suitable_ciphers));
 		_ ->
 		    #{key_exchange := KeyExAlg} = ssl_cipher_format:suite_bin_to_map(CipherSuite),
 		    case ssl_handshake:select_hashsign({ClientHashSigns, ClientSignatureSchemes},
@@ -351,7 +351,7 @@ handle_client_hello(Version,
                                                        SupportedHashSigns,
                                                        Version) of
 			#alert{} = Alert ->
-			    Alert;
+			    throw(Alert);
 			HashSign ->
 			    handle_client_hello_extensions(Version, Type, Random, 
                                                            CipherSuites, HelloExt,
@@ -361,47 +361,38 @@ handle_client_hello(Version,
 		    end
 	    end;
 	false ->
-	    ?ALERT_REC(?FATAL, ?PROTOCOL_VERSION)
+	    throw(?ALERT_REC(?FATAL, ?PROTOCOL_VERSION))
     end.
 
 handle_client_hello_extensions(Version, Type, Random, CipherSuites,
                                HelloExt, SslOpts, Session0, ConnectionStates0, 
                                Renegotiation, HashSign) ->
-    try ssl_handshake:handle_client_hello_extensions(tls_record, Random, CipherSuites,
-						     HelloExt, Version, SslOpts,
-						     Session0, ConnectionStates0, 
+    {Session, ConnectionStates, Protocol, ServerHelloExt} =
+        ssl_handshake:handle_client_hello_extensions(tls_record, Random, CipherSuites,
+                                                     HelloExt, Version, SslOpts,
+                                                     Session0, ConnectionStates0,
                                                      Renegotiation,
-                                                     Session0#session.is_resumable) of
-	{Session, ConnectionStates, Protocol, ServerHelloExt} ->
-	    {Version, {Type, Session}, ConnectionStates, Protocol, 
-             ServerHelloExt, HashSign}
-    catch throw:Alert ->
-	    Alert
-    end.
-
+                                                     Session0#session.is_resumable),
+    {Version, {Type, Session}, ConnectionStates, Protocol, ServerHelloExt, HashSign}.
 
 handle_server_hello_extensions(Version, SessionId, Random, CipherSuite,
-			Compression, HelloExt, SslOpt, ConnectionStates0, Renegotiation, IsNew) ->
-    try ssl_handshake:handle_server_hello_extensions(tls_record, Random, CipherSuite,
-						      Compression, HelloExt, Version,
-						      SslOpt, ConnectionStates0, 
-                                                     Renegotiation, IsNew) of
-	{ConnectionStates, ProtoExt, Protocol, OcspState} ->
-	    {Version, SessionId, ConnectionStates, ProtoExt, Protocol, OcspState}
-    catch throw:Alert ->
-	    Alert
-    end.
-
+                               Compression, HelloExt, SslOpt, ConnectionStates0, Renegotiation, IsNew) ->
+    {ConnectionStates, ProtoExt, Protocol, OcspState} =
+        ssl_handshake:handle_server_hello_extensions(tls_record, Random, CipherSuite,
+                                                     Compression, HelloExt, Version,
+                                                     SslOpt, ConnectionStates0,
+                                                     Renegotiation, IsNew),
+    {Version, SessionId, ConnectionStates, ProtoExt, Protocol, OcspState}.
 
 do_hello(undefined, _Versions, _CipherSuites, _Hello, _SslOpts, _Info, _Renegotiation) ->
-    ?ALERT_REC(?FATAL, ?PROTOCOL_VERSION);
+    throw(?ALERT_REC(?FATAL, ?PROTOCOL_VERSION));
 do_hello(Version, Versions, CipherSuites, Hello, SslOpts, Info, Renegotiation) ->
     case ssl_cipher:is_fallback(CipherSuites) of
         true ->
             Highest = tls_record:highest_protocol_version(Versions),
             case tls_record:is_higher(Highest, Version) of
                 true ->
-                    ?ALERT_REC(?FATAL, ?INAPPROPRIATE_FALLBACK);
+                    throw(?ALERT_REC(?FATAL, ?INAPPROPRIATE_FALLBACK));
                 false ->
                     handle_client_hello(Version, Hello, SslOpts, Info, Renegotiation)
             end;
@@ -444,9 +435,7 @@ get_tls_handshake_aux(Version, <<?BYTE(Type), ?UINT24(Length),
             ssl_logger:debug(LogLevel, inbound, 'handshake', Handshake),
 	    get_tls_handshake_aux(Version, Rest, Opts, [{Handshake,Raw} | Acc])
     catch
-        throw:#alert{} = Alert ->
-            throw(Alert);
-	_:_ ->
+	error:_ ->
 	    throw(?ALERT_REC(?FATAL, ?HANDSHAKE_FAILURE, handshake_decode_error))
     end;
 get_tls_handshake_aux(_Version, Data, _, Acc) ->
-- 
2.31.1

openSUSE Build Service is sponsored by