Skip to content

Commit

Permalink
Deprecate crypto:start/stop()
Browse files Browse the repository at this point in the history
Use application:start/stop(crypto) instead.
  • Loading branch information
sverker committed Jun 18, 2024
1 parent fdcc857 commit 483acc1
Show file tree
Hide file tree
Showing 74 changed files with 142 additions and 128 deletions.
2 changes: 1 addition & 1 deletion .github/workflows/main.yaml
Original file line number Diff line number Diff line change
Expand Up @@ -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
Expand Down
4 changes: 2 additions & 2 deletions lib/common_test/src/ct_config.erl
Original file line number Diff line number Diff line change
Expand Up @@ -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} ->
Expand Down Expand Up @@ -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} ->
Expand Down
2 changes: 1 addition & 1 deletion lib/common_test/src/ct_ssh.erl
Original file line number Diff line number Diff line change
Expand Up @@ -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 ->
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -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) ->
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -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
Expand Down
2 changes: 1 addition & 1 deletion lib/compiler/src/compile.erl
Original file line number Diff line number Diff line change
Expand Up @@ -2511,7 +2511,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
Expand Down
6 changes: 3 additions & 3 deletions lib/compiler/test/compile_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -642,7 +642,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),
Expand Down Expand Up @@ -802,8 +802,8 @@ verify_abstract(Beam, Backend) ->

has_crypto() ->
try
crypto:start(),
crypto:stop(),
application:start(crypto),
application:stop(crypto),
true
catch
error:_ -> false
Expand Down
2 changes: 1 addition & 1 deletion lib/crypto/doc/guides/new_api.md
Original file line number Diff line number Diff line change
Expand Up @@ -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>>
Expand Down
16 changes: 12 additions & 4 deletions lib/crypto/src/crypto.erl
Original file line number Diff line number Diff line change
Expand Up @@ -196,7 +196,9 @@ end
-deprecated([{private_encrypt, 4, "use public_key:sign/3 instead"},
{private_decrypt, 4, "do not use"},
{public_encrypt, 4, "do not use"},
{public_decrypt, 4, "use public_key:verify/4 instead"}
{public_decrypt, 4, "use public_key:verify/4 instead"},
{start, 0, "use application:start(crypto) instead"},
{stop, 0, "use application:stop(crypto) instead"}
]).
%%%----------------------------------------------------------------
%% Removed functions.
Expand Down Expand Up @@ -793,13 +795,19 @@ format_error({Ex, {C_file,C_line}, Msg}, [{_M,_F,_Args,Opts} | _CallStack]) when
end
end.
-doc(#{title => <<"Utility Functions">>}).
-doc "Equivalent to [`application:start(crypto)`](`application:start/1`).".
-doc(#{title => <<"Deprecated API">>}).
-doc """
> #### Warning {: .warning }
>
> Using this function instead of [`application:start(crypto)`](`application:start/1`)
> will cause FIPS mode to be disabled even if application config parameter
>`fips_mode` is set to `true`.
""".
-spec start() -> ok | {error, Reason::term()}.
start() ->
application:start(crypto).
-doc(#{title => <<"Utility Functions">>}).
-doc(#{title => <<"Deprecated API">>}).
-doc "Equivalent to [`application:stop(crypto)`](`application:stop/1`).".
-spec stop() -> ok | {error, Reason::term()}.
stop() ->
Expand Down
8 changes: 4 additions & 4 deletions lib/crypto/test/crypto_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -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"
Expand Down Expand Up @@ -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",
Expand Down
2 changes: 1 addition & 1 deletion lib/crypto/test/crypto_bench_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -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]),
Expand Down
2 changes: 1 addition & 1 deletion lib/crypto/test/crypto_collect_labmachine_info_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -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
Expand Down
2 changes: 1 addition & 1 deletion lib/crypto/test/crypto_property_test_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -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;
Expand Down
2 changes: 1 addition & 1 deletion lib/crypto/test/engine_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -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}} ->
Expand Down
2 changes: 1 addition & 1 deletion lib/debugger/test/debugger_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -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
Expand Down
8 changes: 4 additions & 4 deletions lib/diameter/test/diameter_tls_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -128,7 +128,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}),
Config
catch
Expand All @@ -138,7 +138,7 @@ init_per_suite(Config) ->

end_per_suite(_Config) ->
ssl:stop(),
crypto:stop().
application:stop(crypto).

parallel(Config) ->
run(dir(Config), false).
Expand All @@ -157,14 +157,14 @@ run() ->
end.

run(Dir, B) ->
crypto:start(),
application:start(crypto),
ssl:start(),
try
?util:run([{[fun traffic/2, Dir, B], 60000}])
after
diameter:stop(),
ssl:stop(),
crypto:stop()
application:stop(crypto)
end.

traffic(Dir, true) ->
Expand Down
8 changes: 4 additions & 4 deletions lib/ftp/test/ftp_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -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 ->
Expand Down Expand Up @@ -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)
Expand Down
2 changes: 1 addition & 1 deletion lib/inets/examples/httpd_load_test/hdlt_client.erl
Original file line number Diff line number Diff line change
Expand Up @@ -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
Expand Down
2 changes: 1 addition & 1 deletion lib/inets/examples/httpd_load_test/hdlt_ctrl.erl
Original file line number Diff line number Diff line change
Expand Up @@ -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(),

Expand Down
2 changes: 1 addition & 1 deletion lib/inets/examples/httpd_load_test/hdlt_server.erl
Original file line number Diff line number Diff line change
Expand Up @@ -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
Expand Down
4 changes: 2 additions & 2 deletions lib/inets/test/httpc_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -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}],
Expand Down
4 changes: 2 additions & 2 deletions lib/inets/test/httpc_proxy_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -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),
Expand Down
4 changes: 2 additions & 2 deletions lib/inets/test/httpd_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -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
Expand Down
2 changes: 1 addition & 1 deletion lib/inets/test/inets_test_lib.erl
Original file line number Diff line number Diff line change
Expand Up @@ -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).

Expand Down
2 changes: 1 addition & 1 deletion lib/kernel/test/code_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -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 ->
Expand Down
2 changes: 1 addition & 1 deletion lib/public_key/test/pbe_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -66,7 +66,7 @@ groups() ->
%%--------------------------------------------------------------------
init_per_suite(Config) ->
application:stop(crypto),
try crypto:start() of
try application:start(crypto) of
ok ->
Config
catch _:_ ->
Expand Down
2 changes: 1 addition & 1 deletion lib/public_key/test/pkits_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -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)
Expand Down
2 changes: 1 addition & 1 deletion lib/public_key/test/public_key_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -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
Expand Down
2 changes: 1 addition & 1 deletion lib/snmp/test/snmp_manager_config_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -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
Expand Down
2 changes: 1 addition & 1 deletion lib/snmp/test/snmp_test_lib.erl
Original file line number Diff line number Diff line change
Expand Up @@ -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}} ->
Expand Down
2 changes: 1 addition & 1 deletion lib/ssh/examples/ssh_sample_cli.erl
Original file line number Diff line number Diff line change
Expand Up @@ -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]).

Expand Down
2 changes: 1 addition & 1 deletion lib/ssh/test/ssh_test_lib.hrl
Original file line number Diff line number Diff line change
Expand Up @@ -16,7 +16,7 @@
%%-------------------------------------------------------------------------
-define(CHECK_CRYPTO(UsersInitCode),
try
crypto:start(),
application:start(crypto),
ssh_test_lib:try_enable_fips_mode()
of
ok -> UsersInitCode;
Expand Down
Loading

0 comments on commit 483acc1

Please sign in to comment.