File 0745-ssl-fix-test-code-compilation-warnings.patch of Package erlang

From a20816ad31b0c854393df62efcb6479d27b434f7 Mon Sep 17 00:00:00 2001
From: Jakub Witczak <kuba@erlang.org>
Date: Thu, 3 Oct 2024 10:58:20 +0200
Subject: [PATCH 1/2] ssl: fix test code compilation warnings

---
 .../test/openssl_tls_1_3_version_SUITE.erl    | 22 +++++++++----------
 lib/ssl/test/ssl_basic_SUITE.erl              |  4 ++--
 lib/ssl/test/ssl_cert_SUITE.erl               |  3 +--
 lib/ssl/test/ssl_renegotiate_SUITE.erl        | 12 +++++-----
 lib/ssl/test/tls_1_3_record_SUITE.erl         | 10 ++++-----
 5 files changed, 25 insertions(+), 26 deletions(-)

diff --git a/lib/ssl/test/openssl_tls_1_3_version_SUITE.erl b/lib/ssl/test/openssl_tls_1_3_version_SUITE.erl
index 9b95041064..f7032828ae 100644
--- a/lib/ssl/test/openssl_tls_1_3_version_SUITE.erl
+++ b/lib/ssl/test/openssl_tls_1_3_version_SUITE.erl
@@ -36,8 +36,8 @@
         ]).
 
 %% Test cases
--export([tls12_client_tls13_server/1
-        ]).
+-export([tls12_client_tls13_server/0,
+         tls12_client_tls13_server/1]).
 
 
 %%--------------------------------------------------------------------
@@ -124,15 +124,15 @@ end_per_group(GroupName, Config) ->
 %% In its ClientHello the supported_versions extension contains only one element
 %% [{3,4}] that the server does not accept if it is configured to not support
 %% TLS 1.3.
-tls13_client_tls12_server() ->
-    [{doc,"Test that a TLS 1.3 client can connect to a TLS 1.2 server."}].
-
-tls13_client_tls12_server(Config) when is_list(Config) ->
-    ClientOpts = [{versions,
-                   ['tlsv1.3', 'tlsv1.2']} | ssl_test_lib:ssl_options(client_cert_opts, Config)],
-    ServerOpts =  [{versions,
-                   ['tlsv1.1', 'tlsv1.2']} | ssl_test_lib:ssl_options(server_cert_opts, Config)],
-    ssl_test_lib:basic_test(ClientOpts, ServerOpts, Config).
+%% tls13_client_tls12_server() ->
+%%     [{doc,"Test that a TLS 1.3 client can connect to a TLS 1.2 server."}].
+
+%% tls13_client_tls12_server(Config) when is_list(Config) ->
+%%     ClientOpts = [{versions,
+%%                    ['tlsv1.3', 'tlsv1.2']} | ssl_test_lib:ssl_options(client_cert_opts, Config)],
+%%     ServerOpts =  [{versions,
+%%                    ['tlsv1.1', 'tlsv1.2']} | ssl_test_lib:ssl_options(server_cert_opts, Config)],
+%%     ssl_test_lib:basic_test(ClientOpts, ServerOpts, Config).
     
 %% tls13_client_with_ext_tls12_server() ->
 %%      [{doc,"Test basic connection between TLS 1.2 server and TLS 1.3 client when " 
diff --git a/lib/ssl/test/ssl_basic_SUITE.erl b/lib/ssl/test/ssl_basic_SUITE.erl
index d83427122c..c4851cc392 100644
--- a/lib/ssl/test/ssl_basic_SUITE.erl
+++ b/lib/ssl/test/ssl_basic_SUITE.erl
@@ -408,8 +408,8 @@ eccs() ->
     [{doc, "Test API functions eccs/0 and eccs/1"}].
 
 eccs(Config) when is_list(Config) ->
-    [_|_] = All = ssl:eccs(),
-    [_|_] = Tls = ssl:eccs(tlsv1),
+    [_|_] = _All = ssl:eccs(),
+    [_|_] = _Tls = ssl:eccs(tlsv1),
     [_|_] = Tls1 = ssl:eccs('tlsv1.1'),
     [_|_] = Tls2 = ssl:eccs('tlsv1.2'),
     [_|_] = Tls1 = ssl:eccs('dtlsv1'),
diff --git a/lib/ssl/test/ssl_cert_SUITE.erl b/lib/ssl/test/ssl_cert_SUITE.erl
index ef9e2cf759..a40a0514bd 100644
--- a/lib/ssl/test/ssl_cert_SUITE.erl
+++ b/lib/ssl/test/ssl_cert_SUITE.erl
@@ -1013,8 +1013,7 @@ key_auth_ext_sign_only(Config) when is_list(Config) ->
 cert_auth_in_first_ca() ->
     [{doc,"Test cert auth will be available in first ca in chain, make it happen by only having one"}].
 cert_auth_in_first_ca(Config) when is_list(Config) ->
-    #{server_config := ServerOpts0,
-      client_config := ClientOpts0} =
+    #{} =
         public_key:pkix_test_data(#{server_chain => #{root => [{key, ssl_test_lib:hardcode_rsa_key(1)}],
                                                       intermediates => [[]],
                                                       peer => [{key, ssl_test_lib:hardcode_rsa_key(5)}]},
diff --git a/lib/ssl/test/ssl_renegotiate_SUITE.erl b/lib/ssl/test/ssl_renegotiate_SUITE.erl
index 5ad0b8ceb2..bbe4746d62 100644
--- a/lib/ssl/test/ssl_renegotiate_SUITE.erl
+++ b/lib/ssl/test/ssl_renegotiate_SUITE.erl
@@ -323,7 +323,7 @@ client_no_wrap_sequence_number() ->
     [{doc,"Test that erlang client will renegotiate session when",
      "max sequence number celing is about to be reached. Although"
      "in the testcase we use the test option renegotiate_at"
-     " to lower treashold substantially."}].
+     " to lower treshold substantially."}].
 
 client_no_wrap_sequence_number(Config) when is_list(Config) ->
     ServerOpts = ssl_test_lib:ssl_options(server_rsa_verify_opts, Config),
@@ -347,7 +347,7 @@ client_no_wrap_sequence_number(Config) when is_list(Config) ->
 					{host, Hostname},
 					{from, self()},
 					{mfa, {ssl_test_lib,
-					       trigger_renegotiate, [[ErlData, treashold(N, Version)]]}},
+					       trigger_renegotiate, [[ErlData, treshold(N, Version)]]}},
 					{options, [{reuse_sessions, false},
 						   {renegotiate_at, N} | ClientOpts]}]),
 
@@ -360,7 +360,7 @@ server_no_wrap_sequence_number() ->
     [{doc, "Test that erlang server will renegotiate session when",
      "max sequence number celing is about to be reached. Although"
      "in the testcase we use the test option renegotiate_at"
-     " to lower treashold substantially."}].
+     " to lower treshold substantially."}].
 
 server_no_wrap_sequence_number(Config) when is_list(Config) ->
     ServerOpts = ssl_test_lib:ssl_options(server_rsa_verify_opts, Config),
@@ -477,7 +477,7 @@ active_error_disallowed_client_renegotiate(Config) when is_list(Config) ->
     ServerOpts = ssl_test_lib:ssl_options(server_rsa_verify_opts, Config),
     ClientOpts = ssl_test_lib:ssl_options(client_rsa_verify_opts, Config),
 
-    {ClientNode, ServerNode, Hostname} = ssl_test_lib:run_where(Config),
+    {_ClientNode, ServerNode, Hostname} = ssl_test_lib:run_where(Config),
 
     Server =
 	ssl_test_lib:start_server([{node, ServerNode}, {port, 0},
@@ -546,11 +546,11 @@ renegotiate_rejected(Socket) ->
     ok.
 
 %% First two clauses handles 1/n-1 splitting countermeasure Rizzo/Duong-Beast
-treashold(N, {3,0}) ->
+treshold(N, {3,0}) ->
     (N div 2) + 1;
-treashold(N, {3,1}) ->
+treshold(N, {3,1}) ->
     (N div 2) + 1;
-treashold(N, _) ->
+treshold(N, _) ->
     N + 1.
 
 erlang_ssl_receive(Socket, Data) ->
diff --git a/lib/ssl/test/tls_1_3_record_SUITE.erl b/lib/ssl/test/tls_1_3_record_SUITE.erl
index 3f3cc76564..7db47144f0 100644
--- a/lib/ssl/test/tls_1_3_record_SUITE.erl
+++ b/lib/ssl/test/tls_1_3_record_SUITE.erl
@@ -1429,11 +1429,11 @@ finished_verify_data(_Config) ->
 %% Internal functions ------------------------------------------------
 %%--------------------------------------------------------------------
 
-hexstr2int(S) ->
-    B = hexstr2bin(S),
-    Bits = byte_size(B) * 8,
-    <<Integer:Bits/integer>> = B,
-    Integer.
+%% hexstr2int(S) ->
+%%     B = hexstr2bin(S),
+%%     Bits = byte_size(B) * 8,
+%%     <<Integer:Bits/integer>> = B,
+%%     Integer.
 
 hexstr2bin(S) when is_binary(S) ->
     hexstr2bin(S, <<>>);
-- 
2.43.0

openSUSE Build Service is sponsored by