File 1551-Deprecate-crypto-start-stop.patch of Package erlang
From 2d3b3010c6649ed93b37eab91d12ee5a4f841616 Mon Sep 17 00:00:00 2001
From: Sverker Eriksson <sverker@erlang.org>
Date: Mon, 17 Jun 2024 18:28:44 +0200
Subject: [PATCH 1/3] Deprecate crypto:start/stop()
Use application:start/stop(crypto) instead.
---
.github/workflows/main.yaml | 2 +-
lib/common_test/src/ct_config.erl | 4 ++--
lib/common_test/src/ct_ssh.erl | 2 +-
.../test/ct_netconfc_SUITE_data/netconfc1_SUITE.erl | 2 +-
.../test/ct_netconfc_SUITE_data/netconfc_remote_SUITE.erl | 2 +-
lib/compiler/src/compile.erl | 2 +-
lib/compiler/test/compile_SUITE.erl | 6 +++---
lib/crypto/doc/guides/new_api.md | 2 +-
lib/crypto/src/crypto.erl | 8 +++++---
lib/crypto/test/crypto_SUITE.erl | 8 ++++----
lib/crypto/test/crypto_bench_SUITE.erl | 2 +-
lib/crypto/test/crypto_collect_labmachine_info_SUITE.erl | 2 +-
lib/crypto/test/crypto_property_test_SUITE.erl | 2 +-
lib/crypto/test/engine_SUITE.erl | 2 +-
lib/debugger/test/debugger_SUITE.erl | 2 +-
lib/diameter/test/diameter_tls_SUITE.erl | 8 ++++----
lib/ftp/test/ftp_SUITE.erl | 8 ++++----
lib/inets/examples/httpd_load_test/hdlt_client.erl | 2 +-
lib/inets/examples/httpd_load_test/hdlt_ctrl.erl | 2 +-
lib/inets/examples/httpd_load_test/hdlt_server.erl | 2 +-
lib/inets/test/httpc_SUITE.erl | 4 ++--
lib/inets/test/httpc_proxy_SUITE.erl | 4 ++--
lib/inets/test/httpd_SUITE.erl | 4 ++--
lib/inets/test/inets_test_lib.erl | 2 +-
lib/kernel/test/code_SUITE.erl | 2 +-
lib/public_key/test/pbe_SUITE.erl | 2 +-
lib/public_key/test/pkits_SUITE.erl | 2 +-
lib/public_key/test/public_key_SUITE.erl | 2 +-
lib/snmp/test/snmp_manager_config_SUITE.erl | 2 +-
lib/snmp/test/snmp_test_lib.erl | 2 +-
lib/ssh/examples/ssh_sample_cli.erl | 2 +-
lib/ssh/test/ssh_test_lib.hrl | 2 +-
lib/ssl/test/dtls_api_SUITE.erl | 4 ++--
lib/ssl/test/ssl_ECC_SUITE.erl | 2 +-
lib/ssl/test/ssl_alert_SUITE.erl | 4 ++--
lib/ssl/test/ssl_alpn_SUITE.erl | 4 ++--
lib/ssl/test/ssl_api_SUITE.erl | 4 ++--
lib/ssl/test/ssl_app_env_SUITE.erl | 4 ++--
lib/ssl/test/ssl_basic_SUITE.erl | 4 ++--
lib/ssl/test/ssl_cert_SUITE.erl | 4 ++--
lib/ssl/test/ssl_cipher_SUITE.erl | 2 +-
lib/ssl/test/ssl_cipher_suite_SUITE.erl | 4 ++--
lib/ssl/test/ssl_crl_SUITE.erl | 2 +-
lib/ssl/test/ssl_dist_SUITE.erl | 2 +-
lib/ssl/test/ssl_engine_SUITE.erl | 4 ++--
lib/ssl/test/ssl_eqc_SUITE.erl | 4 ++--
lib/ssl/test/ssl_handshake_SUITE.erl | 6 +++---
lib/ssl/test/ssl_key_update_SUITE.erl | 4 ++--
lib/ssl/test/ssl_npn_SUITE.erl | 4 ++--
lib/ssl/test/ssl_npn_hello_SUITE.erl | 4 ++--
lib/ssl/test/ssl_packet_SUITE.erl | 4 ++--
lib/ssl/test/ssl_payload_SUITE.erl | 4 ++--
lib/ssl/test/ssl_pem_cache_SUITE.erl | 4 ++--
lib/ssl/test/ssl_reject_SUITE.erl | 4 ++--
lib/ssl/test/ssl_renegotiate_SUITE.erl | 4 ++--
lib/ssl/test/ssl_rfc_5869_SUITE.erl | 4 ++--
lib/ssl/test/ssl_session_SUITE.erl | 4 ++--
lib/ssl/test/ssl_session_cache_SUITE.erl | 4 ++--
lib/ssl/test/ssl_session_cache_api_SUITE.erl | 4 ++--
lib/ssl/test/ssl_session_ticket_SUITE.erl | 4 ++--
lib/ssl/test/ssl_sni_SUITE.erl | 4 ++--
lib/ssl/test/ssl_socket_SUITE.erl | 4 ++--
lib/ssl/test/ssl_test_lib.erl | 2 +-
lib/ssl/test/ssl_trace_SUITE.erl | 4 ++--
lib/ssl/test/ssl_upgrade_SUITE.erl | 6 +++---
lib/ssl/test/ssl_use_srtp_SUITE.erl | 4 ++--
lib/ssl/test/tls_1_3_record_SUITE.erl | 4 ++--
lib/ssl/test/tls_1_3_version_SUITE.erl | 4 ++--
lib/ssl/test/tls_api_SUITE.erl | 4 ++--
lib/ssl/test/tls_server_session_ticket_SUITE.erl | 4 ++--
lib/stdlib/src/beam_lib.erl | 2 +-
lib/stdlib/test/beam_lib_SUITE.erl | 6 +++---
lib/tools/test/cover_SUITE.erl | 2 +-
system/doc/general_info/DEPRECATIONS | 6 ++++++
74 files changed, 135 insertions(+), 127 deletions(-)
diff --git a/.github/workflows/main.yaml b/.github/workflows/main.yaml
index 3dc2824f6e..7457316436 100644
--- a/.github/workflows/main.yaml
+++ b/.github/workflows/main.yaml
@@ -212,7 +212,7 @@ jobs:
cd otp/release
./Install -sasl $PWD
./bin/erl -noshell -eval 'io:format("~s", [erlang:system_info(system_version)]), halt().'
- ./bin/erl -noshell -eval 'ok = crypto:start(), io:format("crypto ok~n"), halt().'
+ ./bin/erl -noshell -eval 'ok = application:start(crypto), io:format("crypto ok~n"), halt().'
./bin/erl -noshell -eval '{wx_ref,_,_,_} = wx:new(), io:format("wx ok~n"), halt().'
- name: Upload tarball
diff --git a/lib/common_test/src/ct_config.erl b/lib/common_test/src/ct_config.erl
index 215f0d01c8..9fb56d5b8b 100644
--- a/lib/common_test/src/ct_config.erl
+++ b/lib/common_test/src/ct_config.erl
@@ -594,7 +594,7 @@ encrypt_config_file(SrcFileName, EncryptFileName, {file,KeyFile}) ->
end;
encrypt_config_file(SrcFileName, EncryptFileName, {key,Key}) ->
- _ = crypto:start(),
+ _ = application:start(crypto),
{CryptoKey,IVec} = make_crypto_key(Key),
case file:read_file(SrcFileName) of
{ok,Bin0} ->
@@ -633,7 +633,7 @@ decrypt_config_file(EncryptFileName, TargetFileName, {file,KeyFile}) ->
end;
decrypt_config_file(EncryptFileName, TargetFileName, {key,Key}) ->
- _ = crypto:start(),
+ _ = application:start(crypto),
{CryptoKey,IVec} = make_crypto_key(Key),
case file:read_file(EncryptFileName) of
{ok,Bin} ->
diff --git a/lib/common_test/src/ct_ssh.erl b/lib/common_test/src/ct_ssh.erl
index ef790cbf09..fa031b943f 100644
--- a/lib/common_test/src/ct_ssh.erl
+++ b/lib/common_test/src/ct_ssh.erl
@@ -1338,7 +1338,7 @@ init(KeyOrName, {ConnType,Addr,Port}, AllOpts) ->
end, [], AllOpts1),
FinalOptions = [{silently_accept_hosts,true},
{user_interaction,false} | Options],
- _ = crypto:start(),
+ _ = application:start(crypto),
_ = ssh:start(),
Result = case ConnType of
ssh ->
diff --git a/lib/common_test/test/ct_netconfc_SUITE_data/netconfc1_SUITE.erl b/lib/common_test/test/ct_netconfc_SUITE_data/netconfc1_SUITE.erl
index ff0909d725..c0cf74f3be 100644
--- a/lib/common_test/test/ct_netconfc_SUITE_data/netconfc1_SUITE.erl
+++ b/lib/common_test/test/ct_netconfc_SUITE_data/netconfc1_SUITE.erl
@@ -137,7 +137,7 @@ init_per_suite(Config) ->
end_per_suite(Config) ->
?NS:stop(?config(netconf_server,Config)),
ssh:stop(),
- crypto:stop(),
+ application:stop(crypto),
Config.
hello(Config) ->
diff --git a/lib/common_test/test/ct_netconfc_SUITE_data/netconfc_remote_SUITE.erl b/lib/common_test/test/ct_netconfc_SUITE_data/netconfc_remote_SUITE.erl
index c641704b10..06e3446e3d 100644
--- a/lib/common_test/test/ct_netconfc_SUITE_data/netconfc_remote_SUITE.erl
+++ b/lib/common_test/test/ct_netconfc_SUITE_data/netconfc_remote_SUITE.erl
@@ -70,7 +70,7 @@ init_per_suite(Config) ->
end_per_suite(Config) ->
ssh:stop(),
- crypto:stop(),
+ application:stop(crypto),
Config.
%% This test case is related to seq12645
diff --git a/lib/compiler/src/compile.erl b/lib/compiler/src/compile.erl
index d693937a89..b6825b057e 100644
--- a/lib/compiler/src/compile.erl
+++ b/lib/compiler/src/compile.erl
@@ -2523,7 +2523,7 @@ keep_compile_option(Option, _Deterministic) ->
effects_code_generation(Option).
start_crypto() ->
- try crypto:start() of
+ try application:start(crypto) of
{error,{already_started,crypto}} -> ok;
ok -> ok
catch
diff --git a/lib/compiler/test/compile_SUITE.erl b/lib/compiler/test/compile_SUITE.erl
index e4e0b98d82..c5c7107ad4 100644
--- a/lib/compiler/test/compile_SUITE.erl
+++ b/lib/compiler/test/compile_SUITE.erl
@@ -644,7 +644,7 @@ encrypted_abstr(Config) when is_list(Config) ->
OldPath = code:get_path(),
try
NewPath = OldPath -- [filename:dirname(code:which(crypto))],
- (catch crypto:stop()),
+ (catch application:stop(crypto)),
code:delete(crypto),
code:purge(crypto),
code:set_path(NewPath),
@@ -804,8 +804,8 @@ verify_abstract(Beam, Backend) ->
has_crypto() ->
try
- crypto:start(),
- crypto:stop(),
+ application:start(crypto),
+ application:stop(crypto),
true
catch
error:_ -> false
diff --git a/lib/crypto/doc/guides/new_api.md b/lib/crypto/doc/guides/new_api.md
index c1575afec2..fe5c431463 100644
--- a/lib/crypto/doc/guides/new_api.md
+++ b/lib/crypto/doc/guides/new_api.md
@@ -147,7 +147,7 @@ the cipher text, but divided into three blocks just to show that it is possible
to divide the plain text and cipher text differently for some ciphers:
```erlang
- 1> crypto:start().
+ 1> application:start(crypto).
ok
2> Key = <<1:128>>.
<<0,0,0,0,0,0,0,0,0,0,0,0,0,0,0,1>>
diff --git a/lib/crypto/src/crypto.erl b/lib/crypto/src/crypto.erl
index e956308add..6c42bc1591 100644
--- a/lib/crypto/src/crypto.erl
+++ b/lib/crypto/src/crypto.erl
@@ -196,6 +196,9 @@ end
%%%----------------------------------------------------------------
%% Deprecated functions
+-deprecated([{start, 0, "use application:start(crypto) instead"},
+ {stop, 0, "use application:stop(crypto) instead"}
+ ]).
%%%----------------------------------------------------------------
%% Removed functions.
%%
@@ -791,7 +794,7 @@ format_error({Ex, {C_file,C_line}, Msg}, [{_M,_F,_Args,Opts} | _CallStack]) when
end
end.
--doc(#{title => <<"Utility Functions">>}).
+-doc(#{title => <<"Deprecated API">>}).
-doc """
Use [`application:start(crypto)`](`application:start/1`) instead.
@@ -805,7 +808,7 @@ Use [`application:start(crypto)`](`appli
start() ->
application:start(crypto).
--doc(#{title => <<"Utility Functions">>}).
+-doc(#{title => <<"Deprecated API">>}).
-doc "Use [`application:stop(crypto)`](`application:stop/1`) instead.".
-spec stop() -> ok | {error, Reason::term()}.
stop() ->
diff --git a/lib/crypto/test/crypto_SUITE.erl b/lib/crypto/test/crypto_SUITE.erl
index 8149637bcf..bcb3490487 100644
--- a/lib/crypto/test/crypto_SUITE.erl
+++ b/lib/crypto/test/crypto_SUITE.erl
@@ -520,7 +520,7 @@ init_per_suite(Config) ->
{ok, _} = zip:unzip("cmactestvectors.zip"),
{ok, _} = zip:unzip("gcmtestvectors.zip"),
- try is_ok(crypto:start()) of
+ try is_ok(application:start(crypto)) of
ok ->
catch ct:comment("~s",[element(3,hd(crypto:info_lib()))]),
catch ct:log("crypto:info() -> ~p~n"
@@ -755,13 +755,13 @@ no_support(Config) when is_list(Config) ->
false = is_supported(Type).
%%--------------------------------------------------------------------
crypto_load(_Config) ->
- (catch crypto:stop()),
+ (catch application:stop(crypto)),
code:delete(crypto),
code:purge(crypto),
- crypto:start().
+ application:start(crypto).
%%--------------------------------------------------------------------
crypto_load_and_call(_Config) ->
- (catch crypto:stop()),
+ (catch application:stop(crypto)),
code:delete(crypto),
code:purge(crypto),
Key0 = "ablurf123BX#$;3",
diff --git a/lib/crypto/test/crypto_bench_SUITE.erl b/lib/crypto/test/crypto_bench_SUITE.erl
index 5ec2d085ab..683be4169e 100644
--- a/lib/crypto/test/crypto_bench_SUITE.erl
+++ b/lib/crypto/test/crypto_bench_SUITE.erl
@@ -74,7 +74,7 @@ groups() ->
%%%----------------------------------------------------------------
%%%
init_per_suite(Config0) ->
- try crypto:start() of
+ try application:start(crypto) of
_ ->
[{_,_,Info}] = crypto:info_lib(),
ct:comment("~s",[Info]),
diff --git a/lib/crypto/test/crypto_collect_labmachine_info_SUITE.erl b/lib/crypto/test/crypto_collect_labmachine_info_SUITE.erl
index 04ed7a1859..ad3d22289e 100644
--- a/lib/crypto/test/crypto_collect_labmachine_info_SUITE.erl
+++ b/lib/crypto/test/crypto_collect_labmachine_info_SUITE.erl
@@ -65,7 +65,7 @@ init_per_suite(Config) ->
Root = ct:get_config(collect_host_info),
RemoteFile = filename:join([Root, "crypto_info", hostname()++".data"]),
CryptoStarted =
- try crypto:start() of
+ try application:start(crypto) of
ok -> true;
{error, already_started} -> true;
_ -> false
diff --git a/lib/crypto/test/crypto_property_test_SUITE.erl b/lib/crypto/test/crypto_property_test_SUITE.erl
index 1c786c986a..a6ced25259 100644
--- a/lib/crypto/test/crypto_property_test_SUITE.erl
+++ b/lib/crypto/test/crypto_property_test_SUITE.erl
@@ -39,7 +39,7 @@ all() -> [encrypt_decrypt_one_time,
%%% First prepare Config and compile the property tests for the found tool:
init_per_suite(Config) ->
case
- try crypto:start() of
+ try application:start(crypto) of
ok -> true;
{error, already_started} -> true;
{error,{already_started,crypto}} -> true;
diff --git a/lib/crypto/test/engine_SUITE.erl b/lib/crypto/test/engine_SUITE.erl
index 4d74452183..81cbb71456 100644
--- a/lib/crypto/test/engine_SUITE.erl
+++ b/lib/crypto/test/engine_SUITE.erl
@@ -154,7 +154,7 @@ init_per_suite(Config) ->
{_,OS, Res} ->
ct:log("crypto:info_lib() -> ~p\nos:type() -> ~p", [Res,OS]),
- try crypto:start() of
+ try application:start(crypto) of
ok ->
Config;
{error,{already_started,crypto}} ->
diff --git a/lib/debugger/test/debugger_SUITE.erl b/lib/debugger/test/debugger_SUITE.erl
index 1d77232ad7..3435678012 100644
--- a/lib/debugger/test/debugger_SUITE.erl
+++ b/lib/debugger/test/debugger_SUITE.erl
@@ -91,7 +91,7 @@ no_abstract_code(Config) when is_list(Config) ->
ok.
encrypted_debug_info(Config) when is_list(Config) ->
- try begin crypto:start(), crypto:stop(), ok end of
+ try begin application:start(crypto), application:stop(crypto), ok end of
ok ->
encrypted_debug_info_1(Config)
catch
diff --git a/lib/diameter/test/diameter_tls_SUITE.erl b/lib/diameter/test/diameter_tls_SUITE.erl
index 6f21ceafce..575bbf3401 100644
--- a/lib/diameter/test/diameter_tls_SUITE.erl
+++ b/lib/diameter/test/diameter_tls_SUITE.erl
@@ -139,7 +139,7 @@ init_per_suite(Config) ->
try
[] == (catch make_certs(dir(Config)))
orelse throw({?MODULE, no_certs}),
- ok == crypto:start() orelse throw({?MODULE, no_crypto}),
+ ok == application:start(crypto) orelse throw({?MODULE, no_crypto}),
ok == ssl:start() orelse throw({?MODULE, no_ssl}),
?DUTIL:init_per_suite(Config)
catch
@@ -149,7 +149,7 @@ end_per_suite(Config) ->
?TL("end_per_suite -> entry with"
"~n Config: ~p", [Config]),
ssl:stop(),
- crypto:stop(),
+ application:stop(crypto),
?DUTIL:end_per_suite(Config).
%% This test case can take a *long* time, so if the machine is too slow, skip
@@ -175,7 +175,7 @@ run() ->
run(Dir, B) ->
?TL("run -> start crypto"),
- crypto:start(),
+ application:start(crypto),
?TL("run -> start ssl"),
ssl:start(),
try
@@ -187,7 +187,7 @@ run(Dir, B) ->
?TL("run(after) -> stop ssl"),
ssl:stop(),
?TL("run(after) -> stop crypto"),
- crypto:stop(),
+ application:stop(crypto),
?TL("run(after) -> done"),
ok
end.
diff --git a/lib/ftp/test/ftp_SUITE.erl b/lib/ftp/test/ftp_SUITE.erl
index c1284f6ff6..9a3fc6781a 100644
--- a/lib/ftp/test/ftp_SUITE.erl
+++ b/lib/ftp/test/ftp_SUITE.erl
@@ -276,8 +276,8 @@ init_per_group(Group, Config) when Group == ftpes_passive;
Group == ftpes_active_reuse;
Group == ftps_passive_reuse;
Group == ftps_active_reuse ->
- catch crypto:stop(),
- try crypto:start() of
+ catch application:stop(crypto),
+ try application:start(crypto) of
ok when Group == ftpes_passive; Group == ftpes_active ->
start_ftpd([{ftpd_ssl,true}|Config]);
ok when Group == ftps_passive; Group == ftps_active ->
@@ -305,8 +305,8 @@ init_per_testcase(Case, Config0) ->
application:ensure_started(ftp),
case Case of
error_datafail ->
- catch crypto:stop(),
- try crypto:start() of
+ catch application:stop(crypto),
+ try application:start(crypto) of
ok ->
Config = start_ftpd([{ftpd_ssl,true},{ftpd_ssl_reuse,true}|Config0]),
init_per_testcase2(Case, Config)
diff --git a/lib/inets/examples/httpd_load_test/hdlt_client.erl b/lib/inets/examples/httpd_load_test/hdlt_client.erl
index 56ca422a00..419a850ba5 100644
--- a/lib/inets/examples/httpd_load_test/hdlt_client.erl
+++ b/lib/inets/examples/httpd_load_test/hdlt_client.erl
@@ -208,7 +208,7 @@ client([SocketType, CertFile, URLBase, Sizes, Time, SendRate, Debug]) ->
(SocketType =:= ossl) orelse
(SocketType =:= essl) ->
%% Ensure crypto and ssl started:
- crypto:start(),
+ application:start(crypto),
ssl:start();
true ->
ok
diff --git a/lib/inets/examples/httpd_load_test/hdlt_ctrl.erl b/lib/inets/examples/httpd_load_test/hdlt_ctrl.erl
index 7ecf6c3876..790266cd5e 100644
--- a/lib/inets/examples/httpd_load_test/hdlt_ctrl.erl
+++ b/lib/inets/examples/httpd_load_test/hdlt_ctrl.erl
@@ -193,7 +193,7 @@ do_init(Config) ->
%% Start used applications
?DEBUG("ensure crypto started", []),
- crypto:start(),
+ application:start(crypto),
?DEBUG("ensure ssh started", []),
ssh:start(),
diff --git a/lib/inets/examples/httpd_load_test/hdlt_server.erl b/lib/inets/examples/httpd_load_test/hdlt_server.erl
index cd454c82cd..b65ccd7a77 100644
--- a/lib/inets/examples/httpd_load_test/hdlt_server.erl
+++ b/lib/inets/examples/httpd_load_test/hdlt_server.erl
@@ -146,7 +146,7 @@ maybe_start_crypto_and_ssl(Config) ->
(SocketType =:= ossl) orelse
(SocketType =:= essl)) ->
?LOG("maybe start crypto and ssl", []),
- (catch crypto:start()),
+ (catch application:start(crypto)),
ssl:start();
_ ->
ok
diff --git a/lib/inets/test/httpc_SUITE.erl b/lib/inets/test/httpc_SUITE.erl
index c570e35ec8..f33a8eb24e 100644
--- a/lib/inets/test/httpc_SUITE.erl
+++ b/lib/inets/test/httpc_SUITE.erl
@@ -250,8 +250,8 @@ init_per_group(misc = Group, Config) ->
[{httpc_options, [{ipfamily, Inet}]} | Config];
init_per_group(Group, Config0) when Group =:= sim_https; Group =:= https;
Group =:= sim_mixed ->
- catch crypto:stop(),
- try crypto:start() of
+ catch application:stop(crypto),
+ try application:start(crypto) of
ok ->
start_apps(Group),
HttpcOptions = [{keep_alive_timeout, 50000}, {max_keep_alive_length, 5}],
diff --git a/lib/inets/test/httpc_proxy_SUITE.erl b/lib/inets/test/httpc_proxy_SUITE.erl
index f7a97c09a9..639e144e0f 100644
--- a/lib/inets/test/httpc_proxy_SUITE.erl
+++ b/lib/inets/test/httpc_proxy_SUITE.erl
@@ -485,8 +485,8 @@ app_start(App, Config) ->
try
case App of
crypto ->
- crypto:stop(),
- ok = crypto:start();
+ application:stop(crypto),
+ ok = application:start(crypto);
inets ->
application:stop(App),
ok = application:start(App),
diff --git a/lib/inets/test/httpd_SUITE.erl b/lib/inets/test/httpd_SUITE.erl
index 1c751fe0cf..fea0d7db30 100644
--- a/lib/inets/test/httpd_SUITE.erl
+++ b/lib/inets/test/httpd_SUITE.erl
@@ -228,8 +228,8 @@ init_per_group(Group, Config0) when Group == https_basic;
Group == https_not_sup;
Group == https_alert
->
- catch crypto:stop(),
- try crypto:start() of
+ catch application:stop(crypto),
+ try application:start(crypto) of
ok ->
init_ssl(Group, [{http_version, "HTTP/1.0"} | Config0])
catch
diff --git a/lib/inets/test/inets_test_lib.erl b/lib/inets/test/inets_test_lib.erl
index fc28fbe303..c91be02819 100644
--- a/lib/inets/test/inets_test_lib.erl
+++ b/lib/inets/test/inets_test_lib.erl
@@ -176,7 +176,7 @@ ensure_started(crypto = App) ->
%% only this function ensures that the NIF lib is actually
%% loaded. And only by loading that lib can we know if it
%% is even possible to run crypto.
- do_ensure_started(App, fun() -> crypto:start() end);
+ do_ensure_started(App, fun() -> application:start(crypto) end);
ensure_started(App) when is_atom(App) ->
do_ensure_started(App, fun() -> application:start(App) end).
diff --git a/lib/kernel/test/code_SUITE.erl b/lib/kernel/test/code_SUITE.erl
index 12b2885d51..d05ed98ab6 100644
--- a/lib/kernel/test/code_SUITE.erl
+++ b/lib/kernel/test/code_SUITE.erl
@@ -111,7 +111,7 @@ end_per_suite(Config) ->
-define(TESTMODOBJ, ?TESTMODSTR ".beam").
init_per_testcase(big_boot_embedded, Config) ->
- case catch crypto:start() of
+ case catch application:start(crypto) of
ok ->
init_per_testcase(do_big_boot_embedded, Config);
_Else ->
diff --git a/lib/public_key/test/pbe_SUITE.erl b/lib/public_key/test/pbe_SUITE.erl
index f314eea64f..55e22724a0 100644
--- a/lib/public_key/test/pbe_SUITE.erl
+++ b/lib/public_key/test/pbe_SUITE.erl
@@ -66,7 +66,7 @@ groups() ->
%%--------------------------------------------------------------------
init_per_suite(Config) ->
application:stop(crypto),
- try crypto:start() of
+ try application:start(crypto) of
ok ->
Config
catch _:_ ->
diff --git a/lib/public_key/test/pkits_SUITE.erl b/lib/public_key/test/pkits_SUITE.erl
index 29a5e13bda..ef7aaba0d3 100644
--- a/lib/public_key/test/pkits_SUITE.erl
+++ b/lib/public_key/test/pkits_SUITE.erl
@@ -431,7 +431,7 @@ groups() ->
%%--------------------------------------------------------------------
init_per_suite(Config) ->
application:stop(crypto),
- try crypto:start() of
+ try application:start(crypto) of
ok ->
application:start(asn1),
crypto_support_check(Config)
diff --git a/lib/public_key/test/public_key_SUITE.erl b/lib/public_key/test/public_key_SUITE.erl
index 3db9c6ae37..cd95e7397e 100644
--- a/lib/public_key/test/public_key_SUITE.erl
+++ b/lib/public_key/test/public_key_SUITE.erl
@@ -204,7 +204,7 @@ groups() ->
%%-------------------------------------------------------------------
init_per_suite(Config) ->
application:stop(crypto),
- try crypto:start() of
+ try application:start(crypto) of
ok ->
application:start(asn1),
Config
diff --git a/lib/snmp/test/snmp_manager_config_SUITE.erl b/lib/snmp/test/snmp_manager_config_SUITE.erl
index 933be4e016..899902b121 100644
--- a/lib/snmp/test/snmp_manager_config_SUITE.erl
+++ b/lib/snmp/test/snmp_manager_config_SUITE.erl
@@ -3053,7 +3053,7 @@ maybe_stop_crypto() ->
case (catch crypto:version()) of
{'EXIT', {undef, _}} ->
%% This is the version of crypto before the NIFs...
- crypto:stop();
+ application:stop(crypto);
_ ->
%% There is nothing to stop in this version of crypto..
ok
diff --git a/lib/snmp/test/snmp_test_lib.erl b/lib/snmp/test/snmp_test_lib.erl
index 97b69dcfa5..dcb70db1ff 100644
--- a/lib/snmp/test/snmp_test_lib.erl
+++ b/lib/snmp/test/snmp_test_lib.erl
@@ -3034,7 +3034,7 @@ is_snmp_running() ->
is_app_running(snmp).
crypto_start() ->
- try crypto:start() of
+ try application:start(crypto) of
ok ->
ok;
{error, {already_started,crypto}} ->
diff --git a/lib/ssh/examples/ssh_sample_cli.erl b/lib/ssh/examples/ssh_sample_cli.erl
index f88aaf048a..5bfb8d4607 100644
--- a/lib/ssh/examples/ssh_sample_cli.erl
+++ b/lib/ssh/examples/ssh_sample_cli.erl
@@ -37,7 +37,7 @@ listen(Port) ->
listen(Port, []).
listen(Port, Options) ->
- crypto:start(),
+ application:start(crypto),
ssh:start(),
ssh:daemon(any, Port, [{shell, fun(U, H) -> start_our_shell(U, H) end} | Options]).
diff --git a/lib/ssh/test/ssh_test_lib.hrl b/lib/ssh/test/ssh_test_lib.hrl
index ade4174a71..6f782367ae 100644
--- a/lib/ssh/test/ssh_test_lib.hrl
+++ b/lib/ssh/test/ssh_test_lib.hrl
@@ -16,7 +16,7 @@
%%-------------------------------------------------------------------------
-define(CHECK_CRYPTO(UsersInitCode),
try
- crypto:start(),
+ application:start(crypto),
ssh_test_lib:try_enable_fips_mode()
of
ok -> UsersInitCode;
diff --git a/lib/ssl/test/dtls_api_SUITE.erl b/lib/ssl/test/dtls_api_SUITE.erl
index 5f05eb5f56..47ca3df3e0 100644
--- a/lib/ssl/test/dtls_api_SUITE.erl
+++ b/lib/ssl/test/dtls_api_SUITE.erl
@@ -94,8 +94,8 @@ api_tests() ->
].
init_per_suite(Config0) ->
- catch crypto:stop(),
- try crypto:start() of
+ catch application:stop(crypto),
+ try application:start(crypto) of
ok ->
ssl_test_lib:clean_start(),
ssl_test_lib:make_rsa_cert(Config0)
diff --git a/lib/ssl/test/ssl_ECC_SUITE.erl b/lib/ssl/test/ssl_ECC_SUITE.erl
index 42e200869e..c7832a4f32 100644
--- a/lib/ssl/test/ssl_ECC_SUITE.erl
+++ b/lib/ssl/test/ssl_ECC_SUITE.erl
@@ -112,7 +112,7 @@ ecc_negotiation() ->
%%--------------------------------------------------------------------
init_per_suite(Config0) ->
end_per_suite(Config0),
- try crypto:start() of
+ try application:start(crypto) of
ok ->
case ssl_test_lib:sufficient_crypto_support(cipher_ec) of
true ->
diff --git a/lib/ssl/test/ssl_alert_SUITE.erl b/lib/ssl/test/ssl_alert_SUITE.erl
index 9c45b70982..d8279d6828 100644
--- a/lib/ssl/test/ssl_alert_SUITE.erl
+++ b/lib/ssl/test/ssl_alert_SUITE.erl
@@ -58,8 +58,8 @@ all() ->
].
init_per_suite(Config0) ->
- catch crypto:stop(),
- try crypto:start() of
+ catch application:stop(crypto),
+ try application:start(crypto) of
ok ->
ssl_test_lib:clean_start(),
Config0
diff --git a/lib/ssl/test/ssl_alpn_SUITE.erl b/lib/ssl/test/ssl_alpn_SUITE.erl
index eb850c5d83..2954ef78e3 100644
--- a/lib/ssl/test/ssl_alpn_SUITE.erl
+++ b/lib/ssl/test/ssl_alpn_SUITE.erl
@@ -113,8 +113,8 @@ alpn_npn_coexist() ->
init_per_suite(Config0) ->
- catch crypto:stop(),
- try crypto:start() of
+ catch application:stop(crypto),
+ try application:start(crypto) of
ok ->
ssl_test_lib:clean_start(),
ssl_test_lib:make_rsa_cert(Config0)
diff --git a/lib/ssl/test/ssl_api_SUITE.erl b/lib/ssl/test/ssl_api_SUITE.erl
index 063f660f71..5417c89daa 100644
--- a/lib/ssl/test/ssl_api_SUITE.erl
+++ b/lib/ssl/test/ssl_api_SUITE.erl
@@ -381,8 +381,8 @@ tls13_group() ->
].
init_per_suite(Config0) ->
- catch crypto:stop(),
- try crypto:start() of
+ catch application:stop(crypto),
+ try application:start(crypto) of
ok ->
ssl_test_lib:clean_start(),
ssl_test_lib:make_rsa_cert(Config0)
diff --git a/lib/ssl/test/ssl_app_env_SUITE.erl b/lib/ssl/test/ssl_app_env_SUITE.erl
index 0004e43410..8981907118 100644
--- a/lib/ssl/test/ssl_app_env_SUITE.erl
+++ b/lib/ssl/test/ssl_app_env_SUITE.erl
@@ -81,8 +81,8 @@ tests() ->
init_per_suite(Config0) ->
- catch crypto:stop(),
- try crypto:start() of
+ catch application:stop(crypto),
+ try application:start(crypto) of
ok ->
ssl_test_lib:clean_start(),
ssl_test_lib:make_rsa_cert(Config0)
diff --git a/lib/ssl/test/ssl_basic_SUITE.erl b/lib/ssl/test/ssl_basic_SUITE.erl
index 98dc4dff00..db73684b4e 100644
--- a/lib/ssl/test/ssl_basic_SUITE.erl
+++ b/lib/ssl/test/ssl_basic_SUITE.erl
@@ -145,8 +145,8 @@ options_tests() ->
unordered_protocol_versions_client].
init_per_suite(Config0) ->
- catch crypto:stop(),
- try crypto:start() of
+ catch application:stop(crypto),
+ try application:start(crypto) of
ok ->
ssl_test_lib:clean_start(),
ssl_test_lib:make_rsa_cert(Config0)
diff --git a/lib/ssl/test/ssl_cert_SUITE.erl b/lib/ssl/test/ssl_cert_SUITE.erl
index 23bf6a21c5..f6bf4b7fa7 100644
--- a/lib/ssl/test/ssl_cert_SUITE.erl
+++ b/lib/ssl/test/ssl_cert_SUITE.erl
@@ -262,8 +262,8 @@ all_version_tests() ->
].
init_per_suite(Config) ->
- catch crypto:stop(),
- try crypto:start() of
+ catch application:stop(crypto),
+ try application:start(crypto) of
ok ->
Config
catch _:_ ->
diff --git a/lib/ssl/test/ssl_cipher_SUITE.erl b/lib/ssl/test/ssl_cipher_SUITE.erl
index 687bbd6f58..063a039fb3 100644
--- a/lib/ssl/test/ssl_cipher_SUITE.erl
+++ b/lib/ssl/test/ssl_cipher_SUITE.erl
@@ -57,7 +57,7 @@ groups() ->
[].
init_per_suite(Config) ->
- try crypto:start() of
+ try application:start(crypto) of
ok ->
Config
catch _:_ ->
diff --git a/lib/ssl/test/ssl_cipher_suite_SUITE.erl b/lib/ssl/test/ssl_cipher_suite_SUITE.erl
index e2a57cb14a..d65733e250 100644
--- a/lib/ssl/test/ssl_cipher_suite_SUITE.erl
+++ b/lib/ssl/test/ssl_cipher_suite_SUITE.erl
@@ -286,8 +286,8 @@ anonymous() ->
].
init_per_suite(Config) ->
- catch crypto:stop(),
- try crypto:start() of
+ catch application:stop(crypto),
+ try application:start(crypto) of
ok ->
ssl_test_lib:clean_start(),
Config
diff --git a/lib/ssl/test/ssl_dist_SUITE.erl b/lib/ssl/test/ssl_dist_SUITE.erl
index c2c721c8b9..f057f74bf2 100644
--- a/lib/ssl/test/ssl_dist_SUITE.erl
+++ b/lib/ssl/test/ssl_dist_SUITE.erl
@@ -135,7 +135,7 @@ all() ->
init_per_suite(Config0) ->
_ = end_per_suite(Config0),
- try crypto:start() of
+ try application:start(crypto) of
ok ->
%% Currently no ct function available for is_cover!
case test_server:is_cover() of
diff --git a/lib/ssl/test/ssl_engine_SUITE.erl b/lib/ssl/test/ssl_engine_SUITE.erl
index 5ae1452544..42bc327e10 100644
--- a/lib/ssl/test/ssl_engine_SUITE.erl
+++ b/lib/ssl/test/ssl_engine_SUITE.erl
@@ -47,8 +47,8 @@ all() ->
].
init_per_suite(Config) ->
- catch crypto:stop(),
- try crypto:start() of
+ catch application:stop(crypto),
+ try application:start(crypto) of
ok ->
case crypto:info_lib() of
[{_,_, <<"OpenSSL 1.0.1s-freebsd 1 Mar 2016">>}] ->
diff --git a/lib/ssl/test/ssl_eqc_SUITE.erl b/lib/ssl/test/ssl_eqc_SUITE.erl
index bbf28d47f4..a9428b1f95 100644
--- a/lib/ssl/test/ssl_eqc_SUITE.erl
+++ b/lib/ssl/test/ssl_eqc_SUITE.erl
@@ -69,8 +69,8 @@ all() ->
%%--------------------------------------------------------------------
init_per_suite(Config) ->
ct:timetrap({seconds, 20}),
- catch crypto:stop(),
- try crypto:start() of
+ catch application:stop(crypto),
+ try application:start(crypto) of
ok ->
ssl_test_lib:clean_start(),
ct_property_test:init_per_suite(Config)
diff --git a/lib/ssl/test/ssl_handshake_SUITE.erl b/lib/ssl/test/ssl_handshake_SUITE.erl
index 27c80c49a9..bc16a2779a 100644
--- a/lib/ssl/test/ssl_handshake_SUITE.erl
+++ b/lib/ssl/test/ssl_handshake_SUITE.erl
@@ -83,8 +83,8 @@ end_per_group(_,Config) ->
init_per_testcase(TC, Config0) when
TC =:= ignore_hassign_extension_pre_tls_1_2 orelse
TC =:= signature_algorithms ->
- catch crypto:stop(),
- try crypto:start() of
+ catch application:stop(crypto),
+ try application:start(crypto) of
ok ->
case is_supported(sha512) of
true ->
@@ -105,7 +105,7 @@ init_per_testcase(_, Config0) ->
Config0.
end_per_testcase(ignore_hassign_extension_pre_tls_1_2, _) ->
- crypto:stop();
+ application:stop(crypto);
end_per_testcase(_TestCase, Config) ->
Config.
diff --git a/lib/ssl/test/ssl_npn_SUITE.erl b/lib/ssl/test/ssl_npn_SUITE.erl
index 75154af652..a35f989bb8 100644
--- a/lib/ssl/test/ssl_npn_SUITE.erl
+++ b/lib/ssl/test/ssl_npn_SUITE.erl
@@ -99,8 +99,8 @@ next_protocol_tests() ->
].
init_per_suite(Config0) ->
- catch crypto:stop(),
- try crypto:start() of
+ catch application:stop(crypto),
+ try application:start(crypto) of
ok ->
ssl_test_lib:clean_start(),
ssl:clear_pem_cache(),
diff --git a/lib/ssl/test/ssl_npn_hello_SUITE.erl b/lib/ssl/test/ssl_npn_hello_SUITE.erl
index 227f7d104f..02e65ad49f 100644
--- a/lib/ssl/test/ssl_npn_hello_SUITE.erl
+++ b/lib/ssl/test/ssl_npn_hello_SUITE.erl
@@ -60,8 +60,8 @@ all() ->
create_server_hello_with_no_advertised_protocols_test].
init_per_suite(Config) ->
- catch crypto:stop(),
- try crypto:start() of
+ catch application:stop(crypto),
+ try application:start(crypto) of
ok ->
Config
catch _:_ ->
diff --git a/lib/ssl/test/ssl_packet_SUITE.erl b/lib/ssl/test/ssl_packet_SUITE.erl
index 5477626e51..9eb87700f8 100644
--- a/lib/ssl/test/ssl_packet_SUITE.erl
+++ b/lib/ssl/test/ssl_packet_SUITE.erl
@@ -353,8 +353,8 @@ protocol_active_packet_tests() ->
].
init_per_suite(Config) ->
- catch crypto:stop(),
- try crypto:start() of
+ catch application:stop(crypto),
+ try application:start(crypto) of
ok ->
ssl_test_lib:clean_start(),
ssl_test_lib:make_rsa_cert(Config)
diff --git a/lib/ssl/test/ssl_payload_SUITE.erl b/lib/ssl/test/ssl_payload_SUITE.erl
index 1585781521..152b325df0 100644
--- a/lib/ssl/test/ssl_payload_SUITE.erl
+++ b/lib/ssl/test/ssl_payload_SUITE.erl
@@ -152,8 +152,8 @@ payload_tests() ->
client_active_once_server_close].
init_per_suite(Config) ->
- catch crypto:stop(),
- try crypto:start() of
+ catch application:stop(crypto),
+ try application:start(crypto) of
ok ->
ssl_test_lib:clean_start(),
ssl_test_lib:make_rsa_cert(Config)
diff --git a/lib/ssl/test/ssl_pem_cache_SUITE.erl b/lib/ssl/test/ssl_pem_cache_SUITE.erl
index 9054d9d94a..4d2a370c31 100644
--- a/lib/ssl/test/ssl_pem_cache_SUITE.erl
+++ b/lib/ssl/test/ssl_pem_cache_SUITE.erl
@@ -96,8 +96,8 @@ all() ->
groups() -> [].
init_per_suite(Config0) ->
- catch crypto:stop(),
- try crypto:start() of
+ catch application:stop(crypto),
+ try application:start(crypto) of
ok ->
ssl_test_lib:clean_start(),
%% make rsa certs
diff --git a/lib/ssl/test/ssl_reject_SUITE.erl b/lib/ssl/test/ssl_reject_SUITE.erl
index 6222ba0399..0931be2145 100644
--- a/lib/ssl/test/ssl_reject_SUITE.erl
+++ b/lib/ssl/test/ssl_reject_SUITE.erl
@@ -87,8 +87,8 @@ all_tls_version_tests() ->
].
init_per_suite(Config0) ->
- catch crypto:stop(),
- try crypto:start() of
+ catch application:stop(crypto),
+ try application:start(crypto) of
ok ->
ssl_test_lib:clean_start(),
ssl_test_lib:make_rsa_cert(Config0)
diff --git a/lib/ssl/test/ssl_rfc_5869_SUITE.erl b/lib/ssl/test/ssl_rfc_5869_SUITE.erl
index d77298ebec..5fe5604189 100644
--- a/lib/ssl/test/ssl_rfc_5869_SUITE.erl
+++ b/lib/ssl/test/ssl_rfc_5869_SUITE.erl
@@ -65,8 +65,8 @@ all() ->
%%--------------------------------------------------------------------
init_per_suite(Config) ->
- catch crypto:stop(),
- try crypto:start() of
+ catch application:stop(crypto),
+ try application:start(crypto) of
ok ->
Config
catch _:_ ->
diff --git a/lib/ssl/test/ssl_session_SUITE.erl b/lib/ssl/test/ssl_session_SUITE.erl
index 29248be7bd..de20dd931c 100644
--- a/lib/ssl/test/ssl_session_SUITE.erl
+++ b/lib/ssl/test/ssl_session_SUITE.erl
@@ -105,8 +105,8 @@ tls_session_tests() ->
[session_table_stable_size_on_tcp_close].
init_per_suite(Config0) ->
- catch crypto:stop(),
- try crypto:start() of
+ catch application:stop(crypto),
+ try application:start(crypto) of
ok ->
ssl_test_lib:clean_start(),
Config = ssl_test_lib:make_rsa_cert(Config0),
diff --git a/lib/ssl/test/ssl_session_cache_SUITE.erl b/lib/ssl/test/ssl_session_cache_SUITE.erl
index f40b868e07..e2559b156e 100644
--- a/lib/ssl/test/ssl_session_cache_SUITE.erl
+++ b/lib/ssl/test/ssl_session_cache_SUITE.erl
@@ -99,8 +99,8 @@ session_tests() ->
].
init_per_suite(Config0) ->
- catch crypto:stop(),
- try crypto:start() of
+ catch application:stop(crypto),
+ try application:start(crypto) of
ok ->
ssl_test_lib:clean_start(),
%% make rsa certs using
diff --git a/lib/ssl/test/ssl_session_cache_api_SUITE.erl b/lib/ssl/test/ssl_session_cache_api_SUITE.erl
index 0f775ea7ba..8b8a193920 100644
--- a/lib/ssl/test/ssl_session_cache_api_SUITE.erl
+++ b/lib/ssl/test/ssl_session_cache_api_SUITE.erl
@@ -47,8 +47,8 @@ all() ->
client_cb].
init_per_suite(Config0) ->
- catch crypto:stop(),
- try crypto:start() of
+ catch application:stop(crypto),
+ try application:start(crypto) of
ok ->
ssl_test_lib:clean_start(),
Config0
diff --git a/lib/ssl/test/ssl_session_ticket_SUITE.erl b/lib/ssl/test/ssl_session_ticket_SUITE.erl
index dcebd5f0c3..0480911fc4 100644
--- a/lib/ssl/test/ssl_session_ticket_SUITE.erl
+++ b/lib/ssl/test/ssl_session_ticket_SUITE.erl
@@ -144,8 +144,8 @@ mixed_tests() ->
].
init_per_suite(Config0) ->
- catch crypto:stop(),
- try crypto:start() of
+ catch application:stop(crypto),
+ try application:start(crypto) of
ok ->
ssl_test_lib:clean_start(),
ssl_test_lib:make_rsa_cert(Config0)
diff --git a/lib/ssl/test/ssl_sni_SUITE.erl b/lib/ssl/test/ssl_sni_SUITE.erl
index 8489c59a82..db2e18a44b 100644
--- a/lib/ssl/test/ssl_sni_SUITE.erl
+++ b/lib/ssl/test/ssl_sni_SUITE.erl
@@ -103,8 +103,8 @@ sni_tests() ->
hostname_trailing_dot].
init_per_suite(Config0) ->
- catch crypto:stop(),
- try crypto:start() of
+ catch application:stop(crypto),
+ try application:start(crypto) of
ok ->
ssl_test_lib:clean_start(),
Hostname = net_adm:localhost(),
diff --git a/lib/ssl/test/ssl_socket_SUITE.erl b/lib/ssl/test/ssl_socket_SUITE.erl
index 781f9b6e79..6cfd111f35 100644
--- a/lib/ssl/test/ssl_socket_SUITE.erl
+++ b/lib/ssl/test/ssl_socket_SUITE.erl
@@ -103,8 +103,8 @@ raw_inet_opt() ->
init_per_suite(Config0) ->
- catch crypto:stop(),
- try crypto:start() of
+ catch application:stop(crypto),
+ try application:start(crypto) of
ok ->
ssl_test_lib:clean_start(),
ssl_test_lib:make_rsa_cert(Config0)
diff --git a/lib/ssl/test/ssl_test_lib.erl b/lib/ssl/test/ssl_test_lib.erl
index d4ce937185..ff57e4aa9d 100644
--- a/lib/ssl/test/ssl_test_lib.erl
+++ b/lib/ssl/test/ssl_test_lib.erl
@@ -321,7 +321,7 @@ get_client_opts(Config) ->
init_per_suite(Config0, Type) ->
end_per_suite(Config0),
- try crypto:start() of
+ try application:start(crypto) of
ok ->
clean_start(),
ssl:clear_pem_cache(),
diff --git a/lib/ssl/test/ssl_trace_SUITE.erl b/lib/ssl/test/ssl_trace_SUITE.erl
index d4cd4abf1a..06f6caf58a 100644
--- a/lib/ssl/test/ssl_trace_SUITE.erl
+++ b/lib/ssl/test/ssl_trace_SUITE.erl
@@ -60,8 +60,8 @@ all() -> [tc_basic, tc_no_trace, tc_api_profile, tc_rle_profile,
tc_budget_option, tc_write, tc_file_option, tc_check_profiles].
init_per_suite(Config) ->
- catch crypto:stop(),
- try crypto:start() of
+ catch application:stop(crypto),
+ try application:start(crypto) of
ok ->
ssl_test_lib:clean_start(),
ssl_test_lib:make_rsa_cert(Config)
diff --git a/lib/ssl/test/ssl_upgrade_SUITE.erl b/lib/ssl/test/ssl_upgrade_SUITE.erl
index e768964a38..9a5f2b8e0c 100644
--- a/lib/ssl/test/ssl_upgrade_SUITE.erl
+++ b/lib/ssl/test/ssl_upgrade_SUITE.erl
@@ -62,8 +62,8 @@ all() ->
].
init_per_suite(Config0) ->
- catch crypto:stop(),
- try crypto:start() of
+ catch application:stop(crypto),
+ try application:start(crypto) of
ok ->
ssl_test_lib:clean_start(),
case ct_release_test:init(Config0) of
@@ -78,7 +78,7 @@ init_per_suite(Config0) ->
end_per_suite(Config) ->
ct_release_test:cleanup(Config),
- crypto:stop().
+ application:stop(crypto).
init_per_testcase(_TestCase, Config) ->
ssl_test_lib:ct_log_supported_protocol_versions(Config),
diff --git a/lib/ssl/test/ssl_use_srtp_SUITE.erl b/lib/ssl/test/ssl_use_srtp_SUITE.erl
index a3397ce403..64ebd3ccf2 100644
--- a/lib/ssl/test/ssl_use_srtp_SUITE.erl
+++ b/lib/ssl/test/ssl_use_srtp_SUITE.erl
@@ -67,8 +67,8 @@ use_srtp_tests() ->
].
init_per_suite(Config0) ->
- catch crypto:stop(),
- try crypto:start() of
+ catch application:stop(crypto),
+ try application:start(crypto) of
ok ->
ssl_test_lib:clean_start(),
{#{server_config := _ServerConf,
diff --git a/lib/ssl/test/tls_1_3_record_SUITE.erl b/lib/ssl/test/tls_1_3_record_SUITE.erl
index cae89e7439..4524fe3848 100644
--- a/lib/ssl/test/tls_1_3_record_SUITE.erl
+++ b/lib/ssl/test/tls_1_3_record_SUITE.erl
@@ -55,8 +55,8 @@ all() ->
'0_RTT_handshake'].
init_per_suite(Config) ->
- catch crypto:stop(),
- try (ok == crypto:start()) andalso ssl_test_lib:sufficient_crypto_support('tlsv1.3') of
+ catch application:stop(crypto),
+ try (ok == application:start(crypto)) andalso ssl_test_lib:sufficient_crypto_support('tlsv1.3') of
true ->
ssl_test_lib:clean_start(),
Config;
diff --git a/lib/ssl/test/tls_api_SUITE.erl b/lib/ssl/test/tls_api_SUITE.erl
index a2f4e1d5a7..080a802ce8 100644
--- a/lib/ssl/test/tls_api_SUITE.erl
+++ b/lib/ssl/test/tls_api_SUITE.erl
@@ -189,8 +189,8 @@ api_tests() ->
].
init_per_suite(Config0) ->
- catch crypto:stop(),
- try crypto:start() of
+ catch application:stop(crypto),
+ try application:start(crypto) of
ok ->
ssl_test_lib:clean_start(),
Config1 = ssl_test_lib:make_rsa_cert_with_protected_keyfile(Config0,
diff --git a/lib/ssl/test/tls_server_session_ticket_SUITE.erl b/lib/ssl/test/tls_server_session_ticket_SUITE.erl
index 283f91b734..518cbaca1c 100644
--- a/lib/ssl/test/tls_server_session_ticket_SUITE.erl
+++ b/lib/ssl/test/tls_server_session_ticket_SUITE.erl
@@ -79,8 +79,8 @@ groups() ->
].
init_per_suite(Config0) ->
- catch crypto:stop(),
- try crypto:start() of
+ catch application:stop(crypto),
+ try application:start(crypto) of
ok ->
ssl_test_lib:clean_start(),
Config0
diff --git a/lib/stdlib/src/beam_lib.erl b/lib/stdlib/src/beam_lib.erl
index 27aa88fa37..95c3d3d7b5 100644
--- a/lib/stdlib/src/beam_lib.erl
+++ b/lib/stdlib/src/beam_lib.erl
@@ -1376,7 +1376,7 @@ anno_from_forms(Forms0) ->
[erl_parse:anno_from_term(Form) || Form <- Forms].
start_crypto() ->
- case crypto:start() of
+ case application:start(crypto) of
{error, {already_started, _}} ->
ok;
ok ->
diff --git a/lib/stdlib/test/beam_lib_SUITE.erl b/lib/stdlib/test/beam_lib_SUITE.erl
index c8c1a65484..3413fee6fd 100644
--- a/lib/stdlib/test/beam_lib_SUITE.erl
+++ b/lib/stdlib/test/beam_lib_SUITE.erl
@@ -654,7 +654,7 @@ encrypted_abstr_1(Conf) ->
do_encrypted_abstr(BeamFile, Key),
do_encrypted_abstr(Binary, Key),
- ok = crypto:stop(), %To get rid of extra ets tables.
+ ok = application:stop(crypto), %To get rid of extra ets tables.
file:delete(BeamFile),
file:delete(Source),
NoOfTables = erlang:system_info(ets_count),
@@ -780,7 +780,7 @@ encrypted_abstr_file_1(Conf) ->
do_encrypted_abstr_file(Binary, Key),
ok = file:set_cwd(OldCwd),
- ok = crypto:stop(), %To get rid of extra ets tables.
+ ok = application:stop(crypto), %To get rid of extra ets tables.
file:delete(filename:join(PrivDir, ".erlang.crypt")),
file:delete(BeamFile),
file:delete(Source),
@@ -991,7 +991,7 @@ simple_file(File, Module, F) ->
ok = file:write_file(File, B).
run_if_crypto_works(Test) ->
- try begin crypto:start(), crypto:stop(), ok end of
+ try begin application:start(crypto), application:stop(crypto), ok end of
ok ->
Test()
catch
diff --git a/lib/tools/test/cover_SUITE.erl b/lib/tools/test/cover_SUITE.erl
index 489c35d24d..3e4c3bc6fc 100644
--- a/lib/tools/test/cover_SUITE.erl
+++ b/lib/tools/test/cover_SUITE.erl
@@ -204,7 +204,7 @@ compile(Config) when is_list(Config) ->
remove(files(Files, ".beam")).
crypto_works() ->
- try crypto:start() of
+ try application:start(crypto) of
{error,{already_started,crypto}} -> true;
ok -> true
catch
diff --git a/system/doc/general_info/DEPRECATIONS b/system/doc/general_info/DEPRECATIONS
index 92058c204f..c0b3948043 100644
--- a/system/doc/general_info/DEPRECATIONS
+++ b/system/doc/general_info/DEPRECATIONS
@@ -17,6 +17,12 @@
# is scheduled to be removed in OTP 25.
#
+#
+# Added in OTP 28.
+#
+crypto:start/0 since=28
+crypto:stop/0 since=28
+
#
# Added in OTP 27.
#
--
2.35.3