File 4591-ssl-Cleanup-remove-Version-argument.patch of Package erlang

From a0b638051e767b056c559827b3d812a9376c668c Mon Sep 17 00:00:00 2001
From: Dan Gudmundsson <dgud@erlang.org>
Date: Fri, 24 Sep 2021 11:18:36 +0200
Subject: [PATCH 01/10] ssl: Cleanup, remove Version argument

Not used (and available in state if needed later).
---
 lib/ssl/src/dtls_connection.erl     | 26 +++++-----
 lib/ssl/src/dtls_gen_connection.erl | 22 ++++-----
 lib/ssl/src/ssl_gen_statem.erl      | 17 +++----
 lib/ssl/src/tls_connection.erl      | 32 ++++++------
 lib/ssl/src/tls_connection_1_3.erl  | 29 ++++++-----
 lib/ssl/src/tls_dtls_connection.erl | 77 +++++++++++++----------------
 lib/ssl/src/tls_gen_connection.erl  | 16 +++---
 7 files changed, 98 insertions(+), 121 deletions(-)

diff --git a/lib/ssl/src/dtls_connection.erl b/lib/ssl/src/dtls_connection.erl
index 1a4f001273..32ccb18176 100644
--- a/lib/ssl/src/dtls_connection.erl
+++ b/lib/ssl/src/dtls_connection.erl
@@ -287,7 +287,7 @@ hello(internal, #client_hello{cookie = <<>>,
                                                                              ssl_handshake:init_handshake_history()}},
                        Actions);
         #alert{} = Alert ->
-            ssl_gen_statem:handle_own_alert(Alert, Version,?FUNCTION_NAME, State0)
+            ssl_gen_statem:handle_own_alert(Alert,?FUNCTION_NAME, State0)
     end;
 hello(internal, #hello_verify_request{cookie = Cookie}, 
       #state{static_env = #static_env{role = client,
@@ -317,7 +317,7 @@ hello(internal, #hello_verify_request{cookie = Cookie},
 			 protocol_specific = PS#{current_cookie_secret => Cookie}
                         },
     dtls_gen_connection:next_event(?FUNCTION_NAME, no_record, State, Actions);
-hello(internal, #client_hello{extensions = Extensions, client_version = ClientVersion} = Hello,
+hello(internal, #client_hello{extensions = Extensions} = Hello,
       #state{ssl_options = #{handshake := hello},
              handshake_env = HsEnv,
              start_or_recv_from = From} = State0) ->
@@ -327,7 +327,7 @@ hello(internal, #client_hello{extensions = Extensions, client_version = ClientVe
                                                  handshake_env = HsEnv#handshake_env{hello = Hello}},
              [{reply, From, {ok, Extensions}}]};
         #alert{} = Alert ->
-            ssl_gen_statem:handle_own_alert(Alert, ClientVersion, ?FUNCTION_NAME, State0)
+            ssl_gen_statem:handle_own_alert(Alert, ?FUNCTION_NAME, State0)
     end;
 hello(internal, #server_hello{extensions = Extensions} = Hello, 
       #state{ssl_options = #{
@@ -363,13 +363,12 @@ hello(internal, #server_hello{} = Hello,
          handshake_env = #handshake_env{
              renegotiation = {Renegotiation, _},
              ocsp_stapling_state = OcspState0} = HsEnv,
-         connection_env = #connection_env{negotiated_version = ReqVersion},
          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, ReqVersion, ?FUNCTION_NAME, State);
+            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,
@@ -478,10 +478,10 @@ wait_cert_verify(info, Event, State) ->
     gen_info(Event, ?FUNCTION_NAME, State);
 wait_cert_verify(state_timeout, Event, State) ->
     handle_state_timeout(Event, ?FUNCTION_NAME, State);
-wait_cert_verify(Type, Event, #state{connection_env = #connection_env{negotiated_version = Version}} = State) ->
+wait_cert_verify(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, Version, ?FUNCTION_NAME, State)
+            ssl_gen_statem:handle_own_alert(Alert, ?FUNCTION_NAME, State)
     end.
 
 %%--------------------------------------------------------------------
@@ -638,7 +637,7 @@ handle_client_hello(#client_hello{client_version = ClientVersion} = Hello, State
             case dtls_handshake:hello(Hello, SslOpts, {SessionTracker, Session0,
                                                        ConnectionStates0, OwnCerts, KeyExAlg}, Renegotiation) of
                 #alert{} = Alert ->
-                    ssl_gen_statem:handle_own_alert(Alert, ClientVersion, hello, State1);
+                    ssl_gen_statem:handle_own_alert(Alert, hello, State1);
                 {Version, {Type, Session},
                  ConnectionStates, Protocol0, ServerHelloExt, HashSign} ->
                     Protocol = case Protocol0 of
@@ -656,7 +655,7 @@ handle_client_hello(#client_hello{client_version = ClientVersion} = Hello, State
                     {next_state, hello, State, [{next_event, internal, {common_client_hello, Type, ServerHelloExt}}]}
             end;
         #alert{} = Alert ->
-             ssl_gen_statem:handle_own_alert(Alert, ClientVersion, hello, State0)
+             ssl_gen_statem:handle_own_alert(Alert, hello, State0)
         end.
 
 
@@ -672,8 +671,7 @@ handle_state_timeout(flight_retransmission_timeout, StateName,
 
 
 
-gen_handshake(StateName, Type, Event, 
-	      #state{connection_env = #connection_env{negotiated_version = Version}} = State) ->
+gen_handshake(StateName, Type, Event, State) ->
     try tls_dtls_connection:StateName(Type, Event, State) of
 	Result ->
 	    Result
@@ -681,10 +679,10 @@ gen_handshake(StateName, Type, Event,
 	_:_ ->
 	    ssl_gen_statem:handle_own_alert(?ALERT_REC(?FATAL, ?HANDSHAKE_FAILURE,
 						       malformed_handshake_data),
-					    Version, StateName, State)  
+					    StateName, State)  
     end.
 
-gen_info(Event, connection = StateName,  #state{connection_env = #connection_env{negotiated_version = Version}} = State) ->
+gen_info(Event, connection = StateName, State) ->
     try dtls_gen_connection:handle_info(Event, StateName, State) of
 	Result ->
 	    Result
@@ -692,10 +690,10 @@ gen_info(Event, connection = StateName,  #state{connection_env = #connection_env
 	_:_ ->
 	    ssl_gen_statem:handle_own_alert(?ALERT_REC(?FATAL, ?INTERNAL_ERROR,
 						       malformed_data), 
-					    Version, StateName, State)  
+					    StateName, State)  
     end;
 
-gen_info(Event, StateName, #state{connection_env = #connection_env{negotiated_version = Version}} = State) ->
+gen_info(Event, StateName, State) ->
     try dtls_gen_connection:handle_info(Event, StateName, State) of
 	Result ->
 	    Result
@@ -703,7 +701,7 @@ gen_info(Event, StateName, #state{connection_env = #connection_env{negotiated_ve
         _:_ ->
 	    ssl_gen_statem:handle_own_alert(?ALERT_REC(?FATAL, ?HANDSHAKE_FAILURE,
 						       malformed_handshake_data), 
-					    Version, StateName, State)  
+					    StateName, State)  
     end.
 
 prepare_flight(#state{flight_buffer = Flight,
diff --git a/lib/ssl/src/dtls_gen_connection.erl b/lib/ssl/src/dtls_gen_connection.erl
index 2032d77074..4b402f6841 100644
--- a/lib/ssl/src/dtls_gen_connection.erl
+++ b/lib/ssl/src/dtls_gen_connection.erl
@@ -182,8 +182,7 @@ next_event(StateName, no_record,
 	    %% TODO maybe buffer later epoch
             next_event(StateName, no_record, State, Actions); 
 	{#alert{} = Alert, State} ->
-            Version = State#state.connection_env#connection_env.negotiated_version,
-            handle_own_alert(Alert, Version, StateName, State)
+            handle_own_alert(Alert, StateName, State)
     end;
 next_event(connection = StateName, Record,
 	   #state{connection_states = #{current_read := #{epoch := CurrentEpoch}}} = State0, Actions) ->
@@ -223,8 +222,7 @@ next_event(StateName, Record,
 	    %% TODO maybe buffer later epoch
             next_event(StateName, no_record, State0, Actions); 
 	#alert{} = Alert ->
-	    Version = State0#state.connection_env#connection_env.negotiated_version,
-            handle_own_alert(Alert, Version, StateName, State0)
+            handle_own_alert(Alert, StateName, State0)
     end.
 
 initial_flight_state(udp)->
@@ -352,19 +350,18 @@ handle_protocol_record(#ssl_tls{type = ?HANDSHAKE,
                                                      = unprocessed_events(Events)}}, Events}
 	end
     catch throw:#alert{} = Alert ->
-	    handle_own_alert(Alert, Version, StateName, State)
+	    handle_own_alert(Alert, StateName, State)
     end;
 %%% DTLS record protocol level change cipher messages
 handle_protocol_record(#ssl_tls{type = ?CHANGE_CIPHER_SPEC, fragment = Data}, StateName, State) ->
     {next_state, StateName, State, [{next_event, internal, #change_cipher_spec{type = Data}}]};
 %%% DTLS record protocol level Alert messages
-handle_protocol_record(#ssl_tls{type = ?ALERT, fragment = EncAlerts}, StateName,
-                       #state{connection_env = #connection_env{negotiated_version = Version}} = State) ->
+handle_protocol_record(#ssl_tls{type = ?ALERT, fragment = EncAlerts}, StateName, State) ->
     case decode_alerts(EncAlerts) of
 	Alerts = [_|_] ->
 	    handle_alerts(Alerts,  {next_state, StateName, State});
 	#alert{} = Alert ->
-	    handle_own_alert(Alert, Version, StateName, State)
+	    handle_own_alert(Alert, StateName, State)
     end;
 %% Ignore unknown TLS record level protocol messages
 handle_protocol_record(#ssl_tls{type = _Unknown}, StateName, State) ->
@@ -626,7 +623,7 @@ handle_alerts([Alert | Alerts], {next_state, StateName, State}) ->
 handle_alerts([Alert | Alerts], {next_state, StateName, State, _Actions}) ->
      handle_alerts(Alerts, ssl_gen_statem:handle_alert(Alert, StateName, State)).
 
-handle_own_alert(Alert, Version, StateName,
+handle_own_alert(Alert, StateName,
                  #state{static_env = #static_env{data_tag = udp,
                                                  role = Role},
                         ssl_options = #{log_level := LogLevel}} = State0) ->
@@ -635,10 +632,11 @@ handle_own_alert(Alert, Version, StateName,
             log_ignore_alert(LogLevel, StateName, Alert, Role),
             {next_state, StateName, State};
         {false, State} ->
-            ssl_gen_statem:handle_own_alert(Alert, Version, StateName, State)
+            ssl_gen_statem:handle_own_alert(Alert, StateName, State)
     end;
-handle_own_alert(Alert, Version, StateName, State) ->
-    ssl_gen_statem:handle_own_alert(Alert, Version, StateName, State).
+handle_own_alert(Alert, StateName, State) ->
+    ssl_gen_statem:handle_own_alert(Alert, StateName, State).
+
 ignore_alert(#alert{level = ?FATAL}, #state{protocol_specific = #{ignored_alerts := N,
                                                   max_ignored_alerts := N}} = State) ->
     {false, State};
diff --git a/lib/ssl/src/ssl_gen_statem.erl b/lib/ssl/src/ssl_gen_statem.erl
index a68f9e0836..d8573f06dc 100644
--- a/lib/ssl/src/ssl_gen_statem.erl
+++ b/lib/ssl/src/ssl_gen_statem.erl
@@ -87,7 +87,7 @@
 
 %% Alert and close handling
 -export([send_alert/3,
-         handle_own_alert/4,
+         handle_own_alert/3,
          handle_alert/3,
 	 handle_normal_shutdown/3,
          handle_trusted_certs_db/1,
@@ -515,8 +515,7 @@ initial_hello({call, From}, {start, Timeout},
                               [{{timeout, handshake}, Timeout, close}])
     catch
         {Ref, #alert{} = Alert} ->
-            handle_own_alert(Alert, RequestedVersion, init,
-                             State0#state{start_or_recv_from = From})
+            handle_own_alert(Alert, init, State0#state{start_or_recv_from = From})
     end;
 initial_hello({call, From}, {start, Timeout}, #state{static_env = #static_env{role = Role,
                                                                               protocol_cb = Connection},
@@ -718,10 +716,9 @@ handle_common_event({timeout, recv}, timeout, StateName, #state{start_or_recv_fr
 handle_common_event(internal, {recv, RecvFrom}, StateName, #state{start_or_recv_from = RecvFrom}) when
       StateName =/= connection ->
     {keep_state_and_data, [postpone]};
-handle_common_event(Type, Msg, StateName, #state{connection_env =
-                                                     #connection_env{negotiated_version = Version}} = State) ->
+handle_common_event(Type, Msg, StateName, State) ->
     Alert =  ?ALERT_REC(?FATAL,?UNEXPECTED_MESSAGE, {unexpected_msg, {Type, Msg}}),
-    handle_own_alert(Alert, Version, StateName, State).
+    handle_own_alert(Alert, StateName, State).
 
 handle_call({application_data, _Data}, _, _, _) ->
     %% In renegotiation priorities handshake, send data when handshake is finished
@@ -939,7 +936,7 @@ send_alert(Alert, connection, #state{static_env = #static_env{protocol_cb = Conn
 send_alert(Alert, _, #state{static_env = #static_env{protocol_cb = Connection}} = State) ->
     Connection:send_alert(Alert, State).
 
-handle_own_alert(Alert0, _, StateName,
+handle_own_alert(Alert0, StateName,
 		 #state{static_env = #static_env{role = Role,
                                                  protocol_cb = Connection},
                         ssl_options = #{log_level := LogLevel}} = State) ->
diff --git a/lib/ssl/src/tls_connection.erl b/lib/ssl/src/tls_connection.erl
index ff06b5dc71..f4786e3c6a 100644
--- a/lib/ssl/src/tls_connection.erl
+++ b/lib/ssl/src/tls_connection.erl
@@ -233,7 +233,7 @@ hello(internal, #client_hello{client_version = ClientVersion} = Hello, #state{ss
                 {ServerHelloExt, Type, State} ->
                     {next_state, hello, State, [{next_event, internal, {common_client_hello, Type, ServerHelloExt}}]};
                 Alert ->
-                    ssl_gen_statem:handle_own_alert(Alert, ClientVersion, hello,
+                    ssl_gen_statem:handle_own_alert(Alert, hello,
                                                         State0#state{connection_env = CEnv#connection_env{negotiated_version
                                                                                                           = ClientVersion}})
             end
@@ -249,7 +249,7 @@ hello(internal, #server_hello{} = Hello,
 	     ssl_options = SslOptions} = State) ->   
     case tls_handshake:hello(Hello, SslOptions, ConnectionStates0, Renegotiation, OldId) of
         #alert{} = Alert -> 
-            ssl_gen_statem:handle_own_alert(Alert, ReqVersion, hello,
+            ssl_gen_statem:handle_own_alert(Alert, hello,
                                             State#state{connection_env =
                                                             CEnv#connection_env{negotiated_version = ReqVersion}
                                                        });
@@ -314,10 +314,10 @@ certify(Type, Event, State) ->
 %%--------------------------------------------------------------------
 wait_cert_verify(info, Event, State) ->
     gen_info(Event, ?FUNCTION_NAME, State);
-wait_cert_verify(Type, Event, #state{connection_env = #connection_env{negotiated_version = Version}} = State) ->
+wait_cert_verify(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, Version, ?FUNCTION_NAME, State)
+            ssl_gen_statem:handle_own_alert(Alert, ?FUNCTION_NAME, State)
     end.
 
 %%--------------------------------------------------------------------
@@ -520,28 +520,26 @@ handle_client_hello(#client_hello{client_version = ClientVersion} = Hello, State
     end.
 
 
-gen_info(Event, connection = StateName,  #state{connection_env = #connection_env{negotiated_version = Version}} = State) ->
-    try tls_gen_connection:handle_info(Event, StateName, State) of
-	Result ->
-	    Result
-    catch 
+gen_info(Event, connection = StateName, State) ->
+    try
+        tls_gen_connection:handle_info(Event, StateName, State)
+    catch
         _:_ ->
 	    ssl_gen_statem:handle_own_alert(?ALERT_REC(?FATAL, ?INTERNAL_ERROR,
-						       malformed_data), 
-					    Version, StateName, State)  
+						       malformed_data),
+					    StateName, State)
     end;
 
-gen_info(Event, StateName, #state{connection_env = #connection_env{negotiated_version = Version}} = State) ->
-    try tls_gen_connection:handle_info(Event, StateName, State) of
-	Result ->
-	    Result
-    catch 
+gen_info(Event, StateName, State) ->
+    try
+        tls_gen_connection:handle_info(Event, StateName, State)
+    catch
         _:_ ->
 	    ssl_gen_statem:handle_own_alert(?ALERT_REC(?FATAL, ?HANDSHAKE_FAILURE,
-						       malformed_handshake_data), 
-					    Version, StateName, State)  
+						       malformed_handshake_data),
+					    StateName, State)
     end.
-	    
+
 ensure_sender_terminate(downgrade, _) ->
     ok; %% Do not terminate sender during downgrade phase 
 ensure_sender_terminate(_,  #state{protocol_specific = #{sender := Sender}}) ->
diff --git a/lib/ssl/src/tls_connection_1_3.erl b/lib/ssl/src/tls_connection_1_3.erl
index 2d123bab43..d251bde34b 100644
--- a/lib/ssl/src/tls_connection_1_3.erl
+++ b/lib/ssl/src/tls_connection_1_3.erl
@@ -232,11 +232,10 @@ config_error(Type, Event, State) ->
     ssl_gen_statem:?FUNCTION_NAME(Type, Event, State).
 
 
-user_hello({call, From}, cancel, #state{connection_env = #connection_env{negotiated_version = Version}} 
-           = 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),
-                     Version, ?FUNCTION_NAME, State);
+                                    ?FUNCTION_NAME, State);
 user_hello({call, From}, {handshake_continue, NewOptions, Timeout},
            #state{static_env = #static_env{role = Role},
                   handshake_env = #handshake_env{hello = Hello},
@@ -269,7 +268,7 @@ start(internal, #client_hello{extensions = Extensions} = Hello,
 start(internal, #client_hello{} = Hello, State0) ->
     case tls_handshake_1_3:do_start(Hello, State0) of
         #alert{} = Alert ->
-            ssl_gen_statem:handle_own_alert(Alert, {3,4}, start, State0);
+            ssl_gen_statem:handle_own_alert(Alert, start, State0);
         {State, start} ->
             {next_state, start, State, []};
         {State, negotiated} ->
@@ -289,7 +288,7 @@ start(internal, #server_hello{extensions = Extensions} = ServerHello,
 start(internal, #server_hello{} = ServerHello, State0) ->
     case tls_handshake_1_3:do_start(ServerHello, State0) of
         #alert{} = Alert ->
-            ssl_gen_statem:handle_own_alert(Alert, {3,4}, start, State0);
+            ssl_gen_statem:handle_own_alert(Alert, start, State0);
         {State, NextState} ->
             {next_state, NextState, State, []}
     end;
@@ -303,7 +302,7 @@ negotiated(internal, #change_cipher_spec{}, State) ->
 negotiated(internal, Message, State0) ->
     case tls_handshake_1_3:do_negotiated(Message, State0) of
         #alert{} = Alert ->
-            ssl_gen_statem:handle_own_alert(Alert, {3,4}, negotiated, State0);
+            ssl_gen_statem:handle_own_alert(Alert, negotiated, State0);
         {State, NextState} ->
             {next_state, NextState, State, []}
     end;
@@ -316,7 +315,7 @@ wait_cert(internal,
           #certificate_1_3{} = Certificate, State0) ->
     case tls_handshake_1_3:do_wait_cert(Certificate, State0) of
         {#alert{} = Alert, State} ->
-            ssl_gen_statem:handle_own_alert(Alert, {3,4}, wait_cert, State);
+            ssl_gen_statem:handle_own_alert(Alert, wait_cert, State);
         {State, NextState} ->
             tls_gen_connection:next_event(NextState, no_record, State)
     end;
@@ -331,7 +330,7 @@ wait_cv(internal,
           #certificate_verify_1_3{} = CertificateVerify, State0) ->
     case tls_handshake_1_3:do_wait_cv(CertificateVerify, State0) of
         {#alert{} = Alert, State} ->
-            ssl_gen_statem:handle_own_alert(Alert, {3,4}, wait_cv, State);
+            ssl_gen_statem:handle_own_alert(Alert, wait_cv, State);
         {State, NextState} ->
             tls_gen_connection:next_event(NextState, no_record, State)
     end;
@@ -346,7 +345,7 @@ wait_finished(internal,
              #finished{} = Finished, State0) ->
     case tls_handshake_1_3:do_wait_finished(Finished, State0) of
         #alert{} = Alert ->
-            ssl_gen_statem:handle_own_alert(Alert, {3,4}, finished, State0);
+            ssl_gen_statem:handle_own_alert(Alert, finished, State0);
         State1 ->
             {Record, State} = ssl_gen_statem:prepare_connection(State1, tls_gen_connection),
             tls_gen_connection:next_event(connection, Record, State,
@@ -370,7 +369,7 @@ wait_sh(internal, #server_hello{extensions = Extensions} = Hello,  #state{ssl_op
 wait_sh(internal, #server_hello{} = Hello, State0) ->
     case tls_handshake_1_3:do_wait_sh(Hello, State0) of
         #alert{} = Alert ->
-            ssl_gen_statem:handle_own_alert(Alert, {3,4}, wait_sh, State0);
+            ssl_gen_statem:handle_own_alert(Alert, wait_sh, State0);
         {State1, start, ServerHello} ->
             %% hello_retry_request: go to start
             {next_state, start, State1, [{next_event, internal, ServerHello}]};
@@ -388,7 +387,7 @@ wait_ee(internal, #change_cipher_spec{}, State) ->
 wait_ee(internal, #encrypted_extensions{} = EE, State0) ->
     case tls_handshake_1_3:do_wait_ee(EE, State0) of
         #alert{} = Alert ->
-            ssl_gen_statem:handle_own_alert(Alert, {3,4}, wait_ee, State0);
+            ssl_gen_statem:handle_own_alert(Alert, wait_ee, State0);
         {State1, NextState} ->
             tls_gen_connection:next_event(NextState, no_record, State1)
     end;
@@ -403,14 +402,14 @@ wait_cert_cr(internal, #change_cipher_spec{}, State) ->
 wait_cert_cr(internal, #certificate_1_3{} = Certificate, State0) ->
     case tls_handshake_1_3:do_wait_cert_cr(Certificate, State0) of
         {#alert{} = Alert, State} ->
-            ssl_gen_statem:handle_own_alert(Alert, {3,4}, wait_cert_cr, State);
+            ssl_gen_statem:handle_own_alert(Alert, wait_cert_cr, State);
         {State1, NextState} ->
             tls_gen_connection:next_event(NextState, no_record, State1)
     end;
 wait_cert_cr(internal, #certificate_request_1_3{} = CertificateRequest, State0) ->
     case tls_handshake_1_3:do_wait_cert_cr(CertificateRequest, State0) of
         #alert{} = Alert ->
-            ssl_gen_statem:handle_own_alert(Alert, {3,4}, wait_cert_cr, State0);
+            ssl_gen_statem:handle_own_alert(Alert, wait_cert_cr, State0);
         {State1, NextState} ->
             tls_gen_connection:next_event(NextState, no_record, State1)
     end;
@@ -424,7 +423,7 @@ wait_eoed(internal, #change_cipher_spec{}, State) ->
 wait_eoed(internal, #end_of_early_data{} = EOED, State0) ->
     case tls_handshake_1_3:do_wait_eoed(EOED, State0) of
         {#alert{} = Alert, State} ->
-            ssl_gen_statem:handle_own_alert(Alert, {3,4}, wait_eoed, State);
+            ssl_gen_statem:handle_own_alert(Alert, wait_eoed, State);
         {State1, NextState} ->
             tls_gen_connection:next_event(NextState, no_record, State1)
     end;
@@ -442,7 +441,7 @@ connection(internal, #key_update{} = KeyUpdate, State0) ->
         {ok, State} ->
             tls_gen_connection:next_event(?FUNCTION_NAME, no_record, State);
         {error, State, Alert} ->
-            ssl_gen_statem:handle_own_alert(Alert, {3,4}, connection, State),
+            ssl_gen_statem:handle_own_alert(Alert, connection, State),
             tls_gen_connection:next_event(?FUNCTION_NAME, no_record, State)
     end;
 connection({call, From}, negotiated_protocol,
diff --git a/lib/ssl/src/tls_dtls_connection.erl b/lib/ssl/src/tls_dtls_connection.erl
index bb138b035b..94e68c7045 100644
--- a/lib/ssl/src/tls_dtls_connection.erl
+++ b/lib/ssl/src/tls_dtls_connection.erl
@@ -163,10 +163,9 @@ hello(Type, Event, State) ->
                  #hello_request{} | term(), #state{}) ->
           gen_statem:state_function_result().
 %%--------------------------------------------------------------------
-user_hello({call, From}, cancel, #state{connection_env = #connection_env{negotiated_version = Version}} = 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),
-                     Version, ?FUNCTION_NAME, State);
+    ssl_gen_statem:handle_own_alert(?ALERT_REC(?FATAL, ?USER_CANCELED, user_canceled), ?FUNCTION_NAME, State);
 user_hello({call, From}, {handshake_continue, NewOptions, Timeout},
            #state{static_env = #static_env{role = Role},
                   handshake_env = #handshake_env{hello = Hello},
@@ -209,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, Version, ?FUNCTION_NAME, State0)
+	    ssl_gen_statem:handle_own_alert(Alert, ?FUNCTION_NAME, State0)
     end;
 abbreviated(internal, #finished{verify_data = Data} = Finished,
 	    #state{static_env = #static_env{role = client,
@@ -232,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, Version, ?FUNCTION_NAME, State0)
+	    ssl_gen_statem:handle_own_alert(Alert, ?FUNCTION_NAME, State0)
     end;
 %% only allowed to send next_protocol message after change cipher spec
 %% & before finished message and it is not allowed during renegotiation
@@ -309,12 +308,11 @@ certify(info, Msg, State) ->
     handle_info(Msg, ?FUNCTION_NAME, State);
 certify(internal, #certificate{asn1_certificates = []},
 	#state{static_env = #static_env{role = server},
-               connection_env = #connection_env{negotiated_version = Version},
 	       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, Version, ?FUNCTION_NAME, State);
+    ssl_gen_statem:handle_own_alert(Alert, ?FUNCTION_NAME, State);
 certify(internal, #certificate{asn1_certificates = []},
 	#state{static_env = #static_env{role = server,
                                         protocol_cb = Connection},
@@ -324,11 +322,10 @@ 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},
-               connection_env = #connection_env{negotiated_version = Version},
 	       ssl_options = #{verify := verify_none}} =
 	    State) ->
     Alert =  ?ALERT_REC(?FATAL,?UNEXPECTED_MESSAGE, unrequested_certificate),
-    ssl_gen_statem:handle_own_alert(Alert, Version, ?FUNCTION_NAME, State);
+    ssl_gen_statem:handle_own_alert(Alert, ?FUNCTION_NAME, State);
 certify(internal, #certificate{},
         #state{static_env = #static_env{protocol_cb = Connection},
                handshake_env = #handshake_env{
@@ -355,7 +352,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, Version, ?FUNCTION_NAME, State0)
+            ssl_gen_statem:handle_own_alert(Alert, ?FUNCTION_NAME, State0)
     end;
 certify(internal, #server_key_exchange{exchange_keys = Keys},
         #state{static_env = #static_env{role = client,
@@ -398,13 +395,12 @@ certify(internal, #server_key_exchange{exchange_keys = Keys},
                     Connection);
 		false ->
 		    ssl_gen_statem:handle_own_alert(?ALERT_REC(?FATAL, ?DECRYPT_ERROR),
-						Version, ?FUNCTION_NAME, State)
+						?FUNCTION_NAME, State)
 	    end
     end;
 certify(internal, #certificate_request{},
 	#state{static_env = #static_env{role = client},
-               handshake_env = #handshake_env{kex_algorithm = KexAlg},
-               connection_env = #connection_env{negotiated_version = Version}} = State)
+               handshake_env = #handshake_env{kex_algorithm = KexAlg}} = State)
   when KexAlg == dh_anon; 
        KexAlg == ecdh_anon;
        KexAlg == psk; 
@@ -415,7 +411,7 @@ certify(internal, #certificate_request{},
        KexAlg == srp_rsa; 
        KexAlg == srp_anon ->
     ssl_gen_statem:handle_own_alert(?ALERT_REC(?FATAL, ?HANDSHAKE_FAILURE),
-                     Version, ?FUNCTION_NAME, State);
+                     ?FUNCTION_NAME, State);
 certify(internal, #certificate_request{},
 	#state{static_env = #static_env{role = client,
                                         protocol_cb = Connection},
@@ -443,7 +439,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, Version, ?FUNCTION_NAME, State);
+                   ssl_gen_statem:handle_own_alert(Alert, ?FUNCTION_NAME, State);
                SelectedHashSign ->
                    Connection:next_event(?FUNCTION_NAME, no_record,
                                          State#state{client_certificate_status = requested,
@@ -455,7 +451,6 @@ certify(internal, #server_hello_done{},
 	#state{static_env = #static_env{role = client,
                                         protocol_cb = Connection},
                session = #session{master_secret = undefined},
-               connection_env = #connection_env{negotiated_version = Version},
                handshake_env = #handshake_env{kex_algorithm = KexAlg,
                                               premaster_secret = undefined,
                                               server_psk_identity = PSKIdentity} = HsEnv,
@@ -463,7 +458,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, Version, ?FUNCTION_NAME, State0);
+	    ssl_gen_statem:handle_own_alert(Alert, ?FUNCTION_NAME, State0);
 	PremasterSecret ->
 	    State = master_secret(PremasterSecret,
 				  State0#state{handshake_env =
@@ -473,7 +468,7 @@ certify(internal, #server_hello_done{},
 certify(internal, #server_hello_done{},
 	#state{static_env = #static_env{role = client,
                                        protocol_cb = Connection},
-               connection_env = #connection_env{negotiated_version = {Major, Minor}} = Version,
+               connection_env = #connection_env{negotiated_version = {Major, Minor}},
                handshake_env = #handshake_env{kex_algorithm = KexAlg,
                                               premaster_secret = undefined,
                                               server_psk_identity = PSKIdentity} = HsEnv,
@@ -485,7 +480,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, Version, ?FUNCTION_NAME, State0);
+	    ssl_gen_statem:handle_own_alert(Alert, ?FUNCTION_NAME, State0);
 	PremasterSecret ->
 	    State = master_secret(PremasterSecret, 
 				  State0#state{handshake_env = 
@@ -506,7 +501,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, Version, ?FUNCTION_NAME, State0)
+	    ssl_gen_statem:handle_own_alert(Alert, ?FUNCTION_NAME, State0)
     end;
 %% Master secret is calculated from premaster_secret
 certify(internal, #server_hello_done{},
@@ -524,7 +519,7 @@ certify(internal, #server_hello_done{},
 				 session = Session},
 	    client_certify_and_key_exchange(State, Connection);
 	#alert{} = Alert ->
-	    ssl_gen_statem:handle_own_alert(Alert, Version, ?FUNCTION_NAME, State0)
+	    ssl_gen_statem:handle_own_alert(Alert, ?FUNCTION_NAME, State0)
     end;
 certify(internal, #client_key_exchange{exchange_keys = Keys},
 	State = #state{handshake_env = #handshake_env{kex_algorithm = KeyAlg}, 
@@ -543,7 +537,7 @@ certify(internal, #client_key_exchange{exchange_keys = Keys},
 				    State, Connection)
     catch
 	#alert{} = Alert ->
-	    ssl_gen_statem:handle_own_alert(Alert, Version, ?FUNCTION_NAME, State)
+	    ssl_gen_statem:handle_own_alert(Alert, ?FUNCTION_NAME, State)
     end;
 certify(internal, #hello_request{}, _) ->
     keep_state_and_data;
@@ -580,9+574,8 @@ cipher(info, Msg, State) ->
 cipher(internal, #finished{},
        #state{static_env = #static_env{role = server},
               handshake_env = #handshake_env{expecting_next_protocol_negotiation = true,
-                                             negotiated_protocol = undefined},
-              connection_env = #connection_env{negotiated_version = Version}} = State0) ->
-    ssl_gen_statem:handle_own_alert(?ALERT_REC(?FATAL,?UNEXPECTED_MESSAGE), Version, ?FUNCTION_NAME, State0);
+                                             negotiated_protocol = undefined}} = State0) ->
+    ssl_gen_statem:handle_own_alert(?ALERT_REC(?FATAL,?UNEXPECTED_MESSAGE), ?FUNCTION_NAME, State0);
 cipher(internal, #finished{verify_data = Data} = Finished,
        #state{static_env = #static_env{role = Role,
                                        host = Host,
@@ -610,7 +603,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, Version, ?FUNCTION_NAME, State)
+	    ssl_gen_statem:handle_own_alert(Alert, ?FUNCTION_NAME, State)
     end;
 %% only allowed to send next_protocol message after change cipher spec
 %% & before finished message and it is not allowed during renegotiation
@@ -688,16 +681,14 @@ connection(Type, Event, State) ->
 downgrade(Type, Event, State) ->
     ssl_gen_statem:handle_common_event(Type, Event, ?FUNCTION_NAME, State).
 
-gen_handshake(StateName, Type, Event,
-	      #state{connection_env = #connection_env{negotiated_version = Version}} = State) ->
-    try tls_dtls_connection:StateName(Type, Event, State) of
-	Result ->
-	    Result
+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),
-                                            Version, StateName, State)
+                                            StateName, State)
     end.
 
 %%--------------------------------------------------------------------
@@ -825,8 +816,7 @@ new_server_hello(#server_hello{cipher_suite = CipherSuite,
 			      compression_method = Compression,
 			      session_id = SessionId},
                  #state{session = Session0,
-                        static_env = #static_env{protocol_cb = Connection},
-                        connection_env = #connection_env{negotiated_version = Version}} = State0, Connection) ->
+                        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),
@@ -837,7 +827,7 @@ new_server_hello(#server_hello{cipher_suite = CipherSuite,
 	    Connection:next_event(certify, no_record, State#state{session = Session}, Actions)
     catch
         #alert{} = Alert ->
-	    ssl_gen_statem:handle_own_alert(Alert, Version, hello, State0)
+	    ssl_gen_statem:handle_own_alert(Alert, hello, State0)
     end.
 
 resumed_server_hello(#state{session = Session,
@@ -854,7 +844,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, Version, hello, State0)
+	    ssl_gen_statem:handle_own_alert(Alert, hello, State0)
     end.
 
 server_hello(ServerHello, State0, Connection) ->
@@ -923,8 +913,7 @@ verify_client_cert(#state{static_env = #static_env{role = client},
 verify_client_cert(#state{client_certificate_status = not_requested} = State, _) ->
     State.
 
-client_certify_and_key_exchange(#state{connection_env = #connection_env{negotiated_version = Version}} =
-                                    State0, Connection) ->
+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),
@@ -934,7 +923,7 @@ client_certify_and_key_exchange(#state{connection_env = #connection_env{negotiat
 	    Connection:next_event(cipher, no_record, State, Actions)
     catch
         throw:#alert{} = Alert ->
-	    ssl_gen_statem:handle_own_alert(Alert, Version, certify, State0)
+	    ssl_gen_statem:handle_own_alert(Alert, certify, State0)
     end.
 
 do_client_certify_and_key_exchange(State0, Connection) ->
@@ -1366,7 +1355,7 @@ calculate_master_secret(PremasterSecret,
 				  session = Session},
 	    Connection:next_event(Next, no_record, State);
 	#alert{} = Alert ->
-	    ssl_gen_statem:handle_own_alert(Alert, Version, certify, State0)
+	    ssl_gen_statem:handle_own_alert(Alert, certify, State0)
     end.
 
 finalize_handshake(State0, StateName, Connection) ->
@@ -1645,7 +1634,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, Version, hello, State)
+	    ssl_gen_statem:handle_own_alert(Alert, hello, State)
     end.
 
 make_premaster_secret({MajVer, MinVer}, rsa) ->
diff --git a/lib/ssl/src/tls_gen_connection.erl b/lib/ssl/src/tls_gen_connection.erl
index 217620f62e..dfb67a8f65 100644
--- a/lib/ssl/src/tls_gen_connection.erl
+++ b/lib/ssl/src/tls_gen_connection.erl
@@ -241,13 +241,12 @@ getopts(Transport, Socket, Tag) ->
 
 %% raw data from socket, upack records
 handle_info({Protocol, _, Data}, StateName,
-            #state{static_env = #static_env{data_tag = Protocol},
-                   connection_env = #connection_env{negotiated_version = Version}} = State0) ->
+            #state{static_env = #static_env{data_tag = Protocol}} = State0) ->
     case next_tls_record(Data, StateName, State0) of
 	{Record, State} ->
 	    next_event(StateName, Record, State);
 	#alert{} = Alert ->
-	    ssl_gen_statem:handle_own_alert(Alert, Version, StateName, State0)
+	    ssl_gen_statem:handle_own_alert(Alert, StateName, State0)
     end;
 handle_info({PassiveTag, Socket},  StateName, 
             #state{static_env = #static_env{socket = Socket,
@@ -350,7 +350,6 @@ next_event(StateName,  #alert{} = Alert,
 %%% TLS record protocol level application data messages 
 handle_protocol_record(#ssl_tls{type = ?APPLICATION_DATA}, StateName,
                        #state{static_env = #static_env{role = server},
-                              connection_env = #connection_env{negotiated_version = Version},
                               handshake_env = #handshake_env{renegotiation = {false, first}}
                              } = State) when StateName == initial_hello;
                                              StateName == hello;
@@ -362,13 +361,12 @@ handle_protocol_record(#ssl_tls{type = ?
                                              ->
     %% Application data can not be sent before initial handshake pre TLS-1.3.
     Alert = ?ALERT_REC(?FATAL, ?UNEXPECTED_MESSAGE, application_data_before_initial_handshake),
-    ssl_gen_statem:handle_own_alert(Alert, Version, StateName, State);
+    ssl_gen_statem:handle_own_alert(Alert, StateName, State);
 handle_protocol_record(#ssl_tls{type = ?APPLICATION_DATA}, start = StateName,
-                       #state{static_env = #static_env{role = server},
-                              connection_env = #connection_env{negotiated_version = Version}
+                       #state{static_env = #static_env{role = server}
                              } = State) ->
     Alert = ?ALERT_REC(?FATAL, ?DECODE_ERROR, invalid_tls_13_message),
-    ssl_gen_statem:handle_own_alert(Alert, Version, StateName, State);
+    ssl_gen_statem:handle_own_alert(Alert, StateName, State);
 handle_protocol_record(#ssl_tls{type = ?APPLICATION_DATA, fragment = Data}, StateName,
                        #state{start_or_recv_from = From,
                               socket_options = #socket_options{active = false}} = State0) when From =/= undefined ->
@@ -404,26 +403,25 @@ handle_protocol_record(#ssl_tls{type = ?HANDSHAKE, fragment = Data},
                 end
         end
     catch throw:#alert{} = Alert ->
-            ssl_gen_statem:handle_own_alert(Alert, Version, StateName, State0)
+            ssl_gen_statem:handle_own_alert(Alert, StateName, State0)
     end;
 %%% TLS record protocol level change cipher messages
 handle_protocol_record(#ssl_tls{type = ?CHANGE_CIPHER_SPEC, fragment = Data}, StateName, State) ->
     {next_state, StateName, State, [{next_event, internal, #change_cipher_spec{type = Data}}]};
 %%% TLS record protocol level Alert messages
-handle_protocol_record(#ssl_tls{type = ?ALERT, fragment = EncAlerts}, StateName,
-                       #state{connection_env = #connection_env{negotiated_version = Version}} = State) ->
+handle_protocol_record(#ssl_tls{type = ?ALERT, fragment = EncAlerts}, StateName,State) ->
     try decode_alerts(EncAlerts) of	
 	Alerts = [_|_] ->
 	    handle_alerts(Alerts,  {next_state, StateName, State});
 	[] ->
 	    ssl_gen_statem:handle_own_alert(?ALERT_REC(?FATAL, ?HANDSHAKE_FAILURE, empty_alert),
-					    Version, StateName, State);
+					    StateName, State);
         #alert{} = Alert ->
-            ssl_gen_statem:handle_own_alert(Alert, Version, StateName, State)
+            ssl_gen_statem:handle_own_alert(Alert, StateName, State)
     catch
 	_:_ ->
 	    ssl_gen_statem:handle_own_alert(?ALERT_REC(?FATAL, ?HANDSHAKE_FAILURE, alert_decode_error),
-					    Version, StateName, State)  
+					    StateName, State)
 
     end;
 %% Ignore unknown TLS record level protocol messages
-- 
2.31.1

openSUSE Build Service is sponsored by