Skip to content

Commit

Permalink
Merge branch 'kuba/ssl/fix_test_compile_warnings' into maint-27
Browse files Browse the repository at this point in the history
* kuba/ssl/fix_test_compile_warnings:
  Apply suggestions from code review
  ssl: fix test code compilation warnings
  • Loading branch information
Erlang/OTP committed Oct 17, 2024
2 parents 7691102 + 6437496 commit 2164f02
Show file tree
Hide file tree
Showing 5 changed files with 25 additions and 26 deletions.
22 changes: 11 additions & 11 deletions lib/ssl/test/openssl_tls_1_3_version_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -36,8 +36,8 @@
]).

%% Test cases
-export([tls12_client_tls13_server/1
]).
-export([tls12_client_tls13_server/0,
tls12_client_tls13_server/1]).


%%--------------------------------------------------------------------
Expand Down Expand Up @@ -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 "
Expand Down
4 changes: 2 additions & 2 deletions lib/ssl/test/ssl_basic_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -414,8 +414,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'),
Expand Down
3 changes: 1 addition & 2 deletions lib/ssl/test/ssl_cert_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -1021,8 +1021,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)}]},
Expand Down
12 changes: 6 additions & 6 deletions lib/ssl/test/ssl_renegotiate_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -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 threshold substantially."}].

client_no_wrap_sequence_number(Config) when is_list(Config) ->
ServerOpts = ssl_test_lib:ssl_options(server_rsa_verify_opts, Config),
Expand All @@ -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, threshold(N, Version)]]}},
{options, [{reuse_sessions, false},
{renegotiate_at, N} | ClientOpts]}]),

Expand All @@ -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 threshold substantially."}].

server_no_wrap_sequence_number(Config) when is_list(Config) ->
ServerOpts = ssl_test_lib:ssl_options(server_rsa_verify_opts, Config),
Expand Down Expand Up @@ -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},
Expand Down Expand Up @@ -536,9 +536,9 @@ renegotiate_rejected(Socket) ->
ok.

%% First two clauses handles 1/n-1 splitting countermeasure Rizzo/Duong-Beast
treashold(N, ?TLS_1_0) ->
threshold(N, ?TLS_1_0) ->
(N div 2) + 1;
treashold(N, _) ->
threshold(N, _) ->
N + 1.

erlang_ssl_receive(Socket, Data) ->
Expand Down
10 changes: 5 additions & 5 deletions lib/ssl/test/tls_1_3_record_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -1435,11 +1435,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, <<>>);
Expand Down

0 comments on commit 2164f02

Please sign in to comment.