Skip to content

Commit

Permalink
ssl: modernize timetrap handling
Browse files Browse the repository at this point in the history
Watchdog is legacy test_server use only ct:timetrap/1
  • Loading branch information
IngelaAndin committed Jun 22, 2015
1 parent 2be7b33 commit 287ab39
Show file tree
Hide file tree
Showing 17 changed files with 137 additions and 78 deletions.
1 change: 1 addition & 0 deletions lib/ssl/test/ssl_ECC_SUITE.erl
Expand Up @@ -144,6 +144,7 @@ init_per_testcase(TestCase, Config) ->
ct:log("Ciphers: ~p~n ", [ ssl:cipher_suites()]),
end_per_testcase(TestCase, Config),
ssl:start(),
ct:timetrap({seconds, 5}),
Config.

end_per_testcase(_TestCase, Config) ->
Expand Down
8 changes: 8 additions & 0 deletions lib/ssl/test/ssl_alpn_handshake_SUITE.erl
Expand Up @@ -104,6 +104,14 @@ init_per_group(GroupName, Config) ->
end_per_group(_GroupName, Config) ->
Config.

init_per_testcase(_TestCase, Config) ->
ct:log("TLS/SSL version ~p~n ", [tls_record:supported_protocol_versions()]),
ct:timetrap({seconds, 10}),
Config.

end_per_testcase(_TestCase, Config) ->
Config.

%%--------------------------------------------------------------------
%% Test Cases --------------------------------------------------------
%%--------------------------------------------------------------------
Expand Down
47 changes: 33 additions & 14 deletions lib/ssl/test/ssl_basic_SUITE.erl
Expand Up @@ -35,8 +35,7 @@
-include("tls_handshake.hrl").

-define('24H_in_sec', 86400).
-define(TIMEOUT, 60000).
-define(LONG_TIMEOUT, 600000).
-define(TIMEOUT, 20000).
-define(EXPIRE, 10).
-define(SLEEP, 500).
-define(RENEGOTIATION_DISABLE_TIME, 12000).
Expand Down Expand Up @@ -206,7 +205,6 @@ rizzo_tests() ->

%%--------------------------------------------------------------------
init_per_suite(Config0) ->
Dog = ct:timetrap(?LONG_TIMEOUT *2),
catch crypto:stop(),
try crypto:start() of
ok ->
Expand All @@ -219,9 +217,8 @@ init_per_suite(Config0) ->

Config1 = ssl_test_lib:make_dsa_cert(Config0),
Config2 = ssl_test_lib:make_ecdsa_cert(Config1),
Config3 = ssl_test_lib:make_ecdh_rsa_cert(Config2),
Config = ssl_test_lib:cert_options(Config3),
[{watchdog, Dog} | Config]
Config = ssl_test_lib:make_ecdh_rsa_cert(Config2),
ssl_test_lib:cert_options(Config)
catch _:_ ->
{skip, "Crypto did not start"}
end.
Expand Down Expand Up @@ -254,6 +251,7 @@ init_per_testcase(Case, Config) when Case == unordered_protocol_versions_client
Case == unordered_protocol_versions_server->
case proplists:get_value(supported, ssl:versions()) of
['tlsv1.2' | _] ->
ct:timetrap({seconds, 5}),
Config;
_ ->
{skip, "TLS 1.2 need but not supported on this platform"}
Expand All @@ -265,10 +263,11 @@ init_per_testcase(protocol_versions, Config) ->
%% For backwards compatibility sslv2 should be filtered out.
application:set_env(ssl, protocol_version, [sslv2, sslv3, tlsv1]),
ssl:start(),
ct:timetrap({seconds, 5}),
Config;

init_per_testcase(reuse_session_expired, Config0) ->
Config = lists:keydelete(watchdog, 1, Config0),
init_per_testcase(reuse_session_expired, Config) ->
ct:timetrap({seconds, 30}),
ssl:stop(),
application:load(ssl),
application:set_env(ssl, session_lifetime, ?EXPIRE),
Expand All @@ -281,24 +280,44 @@ init_per_testcase(empty_protocol_versions, Config) ->
application:load(ssl),
application:set_env(ssl, protocol_version, []),
ssl:start(),
ct:timetrap({seconds, 5}),
Config;

init_per_testcase(fallback, Config) ->
case tls_record:highest_protocol_version([]) of
{3, N} when N > 1 ->
ct:timetrap({seconds, 5}),
Config;
_ ->
{skip, "Not relevant if highest supported version is less than 3.2"}
end;

%% init_per_testcase(different_ca_peer_sign, Config0) ->
%% ssl_test_lib:make_mix_cert(Config0);
init_per_testcase(TestCase, Config) when TestCase == client_renegotiate;
TestCase == server_renegotiate;
TestCase == client_secure_renegotiate;
TestCase == client_renegotiate_reused_session;
TestCase == server_renegotiate_reused_session;
TestCase == client_no_wrap_sequence_number;
TestCase == server_no_wrap_sequence_number;
TestCase == renegotiate_dos_mitigate_active;
TestCase == renegotiate_dos_mitigate_passive;
TestCase == renegotiate_dos_mitigate_absolute ->
ct:log("TLS/SSL version ~p~n ", [tls_record:supported_protocol_versions()]),
ct:timetrap({seconds, 30}),
Config;
init_per_testcase(ssl_accept_timeout, Config) ->
ct:log("TLS/SSL version ~p~n ", [tls_record:supported_protocol_versions()]),
ct:timetrap({seconds, 15}),
Config;
init_per_testcase(clear_pem_cache, Config) ->
ct:log("TLS/SSL version ~p~n ", [tls_record:supported_protocol_versions()]),
ct:timetrap({seconds, 20}),
Config;

init_per_testcase(_TestCase, Config0) ->
init_per_testcase(_TestCase, Config) ->
ct:log("TLS/SSL version ~p~n ", [tls_record:supported_protocol_versions()]),
Config = lists:keydelete(watchdog, 1, Config0),
Dog = ct:timetrap(?TIMEOUT),
[{watchdog, Dog} | Config].
ct:timetrap({seconds, 5}),
Config.

end_per_testcase(reuse_session_expired, Config) ->
application:unset_env(ssl, session_lifetime),
Expand Down
14 changes: 10 additions & 4 deletions lib/ssl/test/ssl_certificate_verify_SUITE.erl
Expand Up @@ -77,7 +77,6 @@ error_handling_tests()->
no_authority_key_identifier].

init_per_suite(Config0) ->
Dog = ct:timetrap(?LONG_TIMEOUT *2),
catch crypto:stop(),
try crypto:start() of
ok ->
Expand All @@ -88,9 +87,8 @@ init_per_suite(Config0) ->
?config(priv_dir, Config0))),
ct:log("Make certs ~p~n", [Result]),

Config1 = ssl_test_lib:make_dsa_cert(Config0),
Config = ssl_test_lib:cert_options(Config1),
[{watchdog, Dog} | Config]
Config = ssl_test_lib:make_dsa_cert(Config0),
ssl_test_lib:cert_options(Config)
catch _:_ ->
{skip, "Crypto did not start"}
end.
Expand All @@ -111,6 +109,14 @@ init_per_group(_, Config) ->
end_per_group(_GroupName, Config) ->
Config.

init_per_testcase(_TestCase, Config) ->
ct:log("TLS/SSL version ~p~n ", [tls_record:supported_protocol_versions()]),
ct:timetrap({seconds, 5}),
Config.

end_per_testcase(_TestCase, Config) ->
Config.

%%--------------------------------------------------------------------
%% Test Cases --------------------------------------------------------
%%--------------------------------------------------------------------
Expand Down
11 changes: 4 additions & 7 deletions lib/ssl/test/ssl_cipher_SUITE.erl
Expand Up @@ -29,8 +29,6 @@
-include("ssl_cipher.hrl").
-include("ssl_alert.hrl").

-define(TIMEOUT, 600000).

%%--------------------------------------------------------------------
%% Common Test interface functions -----------------------------------
%%--------------------------------------------------------------------
Expand Down Expand Up @@ -58,10 +56,9 @@ init_per_group(_GroupName, Config) ->
end_per_group(_GroupName, Config) ->
Config.

init_per_testcase(_TestCase, Config0) ->
Config = lists:keydelete(watchdog, 1, Config0),
Dog = ct:timetrap(?TIMEOUT),
[{watchdog, Dog} | Config].
init_per_testcase(_TestCase, Config) ->
ct:timetrap({seconds, 5}),
Config.

end_per_testcase(_TestCase, Config) ->
Config.
Expand Down Expand Up @@ -105,7 +102,7 @@ padding_test(Config) when is_list(Config) ->
% Internal functions --------------------------------------------------------
%%--------------------------------------------------------------------
decipher_check_good(HashSz, CipherState, Version) ->
{Content, NextIV, Mac} = content_nextiv_mac(Version),
{Content, _NextIV, Mac} = content_nextiv_mac(Version),
{Content, Mac, _} =
ssl_cipher:decipher(?AES_CBC, HashSz, CipherState, aes_fragment(Version), Version, true).

Expand Down
8 changes: 3 additions & 5 deletions lib/ssl/test/ssl_crl_SUITE.erl
Expand Up @@ -26,8 +26,6 @@
-include_lib("common_test/include/ct.hrl").
-include_lib("public_key/include/public_key.hrl").

-define(LONG_TIMEOUT, 600000).

%%--------------------------------------------------------------------
%% Common Test interface functions -----------------------------------
%%--------------------------------------------------------------------
Expand Down Expand Up @@ -57,8 +55,7 @@ basic_tests() ->
[crl_verify_valid, crl_verify_revoked].


init_per_suite(Config0) ->
Dog = ct:timetrap(?LONG_TIMEOUT *2),
init_per_suite(Config) ->
case os:find_executable("openssl") of
false ->
{skip, "Openssl not found"};
Expand All @@ -77,7 +74,7 @@ init_per_suite(Config0) ->
true -> inet6;
false -> inet
end,
[{ipfamily,IPfamily}, {watchdog, Dog}, {openssl_version,OpenSSL_version} | Config0]
[{ipfamily,IPfamily}, {openssl_version,OpenSSL_version} | Config]
catch _:_ ->
{skip, "Crypto did not start"}
end
Expand Down Expand Up @@ -130,6 +127,7 @@ init_per_testcase(Case, Config0) ->
CertDir = filename:join(?config(priv_dir, Config0), idp_crl),
{CertOpts, Config} = init_certs(CertDir, idp_crl, Config),
Result = make_certs:all(DataDir, CertDir, CertOpts),
ct:timetrap({seconds, 6}),
[{make_cert_result, Result}, {cert_dir, CertDir} | Config];
false ->
end_per_testcase(Case, Config0),
Expand Down
8 changes: 3 additions & 5 deletions lib/ssl/test/ssl_dist_SUITE.erl
Expand Up @@ -86,17 +86,15 @@ init_per_testcase(Case, Config) when is_list(Config) ->
common_init(Case, Config).

common_init(Case, Config) ->
Dog = ?t:timetrap(?t:seconds(?DEFAULT_TIMETRAP_SECS)),
[{watchdog, Dog},{testcase, Case}|Config].
ct:timetrap({seconds, ?DEFAULT_TIMETRAP_SECS}),
[{testcase, Case}|Config].

end_per_testcase(Case, Config) when is_list(Config) ->
Flags = proplists:get_value(old_flags, Config),
catch os:putenv("ERL_FLAGS", Flags),
common_end(Case, Config).

common_end(_, Config) ->
Dog = ?config(watchdog, Config),
?t:timetrap_cancel(Dog),
common_end(_, _Config) ->
ok.

%%--------------------------------------------------------------------
Expand Down
4 changes: 3 additions & 1 deletion lib/ssl/test/ssl_handshake_SUITE.erl
Expand Up @@ -65,7 +65,9 @@ init_per_testcase(ignore_hassign_extension_pre_tls_1_2, Config0) ->
(catch make_certs:all(?config(data_dir, Config0),
?config(priv_dir, Config0))),
ct:log("Make certs ~p~n", [Result]),
ssl_test_lib:cert_options(Config0);
Config = ssl_test_lib:cert_options(Config0),
ct:timetrap({seconds, 5}),
Config;
false ->
{skip, "Crypto did not support sha512"}
end
Expand Down
9 changes: 9 additions & 0 deletions lib/ssl/test/ssl_npn_handshake_SUITE.erl
Expand Up @@ -100,6 +100,15 @@ init_per_group(GroupName, Config) ->
end_per_group(_GroupName, Config) ->
Config.

init_per_testcase(_TestCase, Config) ->
ct:log("TLS/SSL version ~p~n ", [tls_record:supported_protocol_versions()]),
ct:log("Ciphers: ~p~n ", [ ssl:cipher_suites()]),
ct:timetrap({seconds, 10}),
Config.

end_per_testcase(_TestCase, Config) ->
Config.

%%--------------------------------------------------------------------
%% Test Cases --------------------------------------------------------
%%--------------------------------------------------------------------
Expand Down
8 changes: 8 additions & 0 deletions lib/ssl/test/ssl_npn_hello_SUITE.erl
Expand Up @@ -40,6 +40,14 @@ all() ->
create_server_hello_with_advertised_protocols_test,
create_server_hello_with_no_advertised_protocols_test].

init_per_testcase(_TestCase, Config) ->
ct:log("TLS/SSL version ~p~n ", [tls_record:supported_protocol_versions()]),
ct:timetrap({seconds, 5}),
Config.

end_per_testcase(_TestCase, Config) ->
Config.

%%--------------------------------------------------------------------
%% Test Cases --------------------------------------------------------
%%--------------------------------------------------------------------
Expand Down
8 changes: 3 additions & 5 deletions lib/ssl/test/ssl_packet_SUITE.erl
Expand Up @@ -37,7 +37,6 @@
-define(uint24(X), << ?UINT24(X) >> ).
-define(uint32(X), << ?UINT32(X) >> ).
-define(uint64(X), << ?UINT64(X) >> ).
-define(TIMEOUT, 120000).

-define(MANY, 1000).
-define(SOME, 50).
Expand Down Expand Up @@ -169,10 +168,9 @@ init_per_group(GroupName, Config) ->
end_per_group(_GroupName, Config) ->
Config.

init_per_testcase(_TestCase, Config0) ->
Config = lists:keydelete(watchdog, 1, Config0),
Dog = ct:timetrap(?TIMEOUT),
[{watchdog, Dog} | Config].
init_per_testcase(_TestCase, Config) ->
ct:timetrap({seconds, 15}),
Config.


end_per_testcase(_TestCase, Config) ->
Expand Down
16 changes: 12 additions & 4 deletions lib/ssl/test/ssl_payload_SUITE.erl
Expand Up @@ -98,10 +98,18 @@ init_per_group(GroupName, Config) ->
end_per_group(_GroupName, Config) ->
Config.

init_per_testcase(_TestCase, Config0) ->
Config = lists:keydelete(watchdog, 1, Config0),
Dog = ct:timetrap(?TIMEOUT),
[{watchdog, Dog} | Config].
init_per_testcase(TestCase, Config) when TestCase == server_echos_passive_huge;
TestCase == server_echos_active_once_huge;
TestCase == server_echos_active_huge;
TestCase == client_echos_passive_huge;
TestCase == client_echos_active_once_huge;
TestCase == client_echos_active_huge ->
ct:timetrap({seconds, 30}),
Config;

init_per_testcase(_TestCase, Config) ->
ct:timetrap({seconds, 15}),
Config.

end_per_testcase(_TestCase, Config) ->
Config.
Expand Down
7 changes: 4 additions & 3 deletions lib/ssl/test/ssl_pem_cache_SUITE.erl
Expand Up @@ -64,15 +64,16 @@ init_per_group(_GroupName, Config) ->
end_per_group(_GroupName, Config) ->
Config.

init_per_testcase(pem_cleanup, Config) ->
ssl:stop(),
init_per_testcase(pem_cleanup = Case, Config) ->
end_per_testcase(Case, Config) ,
application:load(ssl),
application:set_env(ssl, ssl_pem_cache_clean, ?CLEANUP_INTERVAL),
ssl:start(),
ct:timetrap({minutes, 1}),
Config.

end_per_testcase(_TestCase, Config) ->
%%ssl:stop(),
ssl:stop(),
Config.

%%--------------------------------------------------------------------
Expand Down

0 comments on commit 287ab39

Please sign in to comment.