Skip to content

Commit

Permalink
Merge pull request #1773 from ferd/otp-21-stacktrace-compat
Browse files Browse the repository at this point in the history
Work around OTP-21 deprecation of get_stacktrace() and other incompatible changes
  • Loading branch information
ferd authored May 3, 2018
2 parents a908284 + e321ca6 commit 048dfad
Show file tree
Hide file tree
Showing 14 changed files with 61 additions and 48 deletions.
1 change: 1 addition & 0 deletions bootstrap
Original file line number Diff line number Diff line change
Expand Up @@ -571,6 +571,7 @@ additional_defines() ->
[{d, D} || {Re, D} <- [{"^[0-9]+", namespaced_types},
{"^R1[4|5]", deprecated_crypto},
{"^2", unicode_str},
{"^(R|1|20)", fun_stacktrace},
{"^((1[8|9])|2)", rand_module}],
is_otp_release(Re)].

Expand Down
4 changes: 3 additions & 1 deletion rebar.config
Original file line number Diff line number Diff line change
@@ -1,7 +1,7 @@
%% -*- mode: erlang;erlang-indent-level: 4;indent-tabs-mode: nil -*-
%% ex: ts=4 sw=4 ft=erlang et

{deps, [{erlware_commons, "1.0.5"},
{deps, [{erlware_commons, "1.1.0"},
{ssl_verify_fun, "1.1.3"},
{certifi, "2.0.0"},
{providers, "1.7.0"},
Expand Down Expand Up @@ -31,6 +31,7 @@
{erl_opts, [{platform_define, "^[0-9]+", namespaced_types},
{platform_define, "^(19|2)", rand_only},
{platform_define, "^2", unicode_str},
{platform_define, "^(R|1|20)", fun_stacktrace},
warnings_as_errors]}.

%% Use OTP 18+ when dialyzing rebar3
Expand Down Expand Up @@ -59,6 +60,7 @@
{platform_define, "^R1[4|5]", deprecated_crypto},
{platform_define, "^((1[8|9])|2)", rand_module},
{platform_define, "^2", unicode_str},
{platform_define, "^(R|1|20)", fun_stacktrace},
no_debug_info,
warnings_as_errors]},
{deps, []}, {plugins, []}]},
Expand Down
4 changes: 2 additions & 2 deletions rebar.lock
Original file line number Diff line number Diff line change
Expand Up @@ -3,7 +3,7 @@
{<<"certifi">>,{pkg,<<"certifi">>,<<"2.0.0">>},0},
{<<"cf">>,{pkg,<<"cf">>,<<"0.2.2">>},0},
{<<"cth_readable">>,{pkg,<<"cth_readable">>,<<"1.3.4">>},0},
{<<"erlware_commons">>,{pkg,<<"erlware_commons">>,<<"1.0.5">>},0},
{<<"erlware_commons">>,{pkg,<<"erlware_commons">>,<<"1.1.0">>},0},
{<<"eunit_formatters">>,{pkg,<<"eunit_formatters">>,<<"0.5.0">>},0},
{<<"getopt">>,{pkg,<<"getopt">>,<<"1.0.1">>},0},
{<<"providers">>,{pkg,<<"providers">>,<<"1.7.0">>},0},
Expand All @@ -15,7 +15,7 @@
{<<"certifi">>, <<"A0C0E475107135F76B8C1D5BC7EFB33CD3815CB3CF3DEA7AEFDD174DABEAD064">>},
{<<"cf">>, <<"7F2913FFF90ABCABD0F489896CFEB0B0674F6C8DF6C10B17A83175448029896C">>},
{<<"cth_readable">>, <<"CB85DF77CEB7F05854AE241300DB36A72C371740EDD883D8BF75B5F652B7067D">>},
{<<"erlware_commons">>, <<"FC23D8E304140B65A811F653A76B2FB10B0CE744608CAF86E9125CEB349C9442">>},
{<<"erlware_commons">>, <<"F69F3D96044C2A9E735CCD76F469FEC5FC851797E5FE23115698B4EDC072191B">>},
{<<"eunit_formatters">>, <<"6A9133943D36A465D804C1C5B6E6839030434B8879C5600D7DDB5B3BAD4CCB59">>},
{<<"getopt">>, <<"C73A9FA687B217F2FF79F68A3B637711BB1936E712B521D8CE466B29CBF7808A">>},
{<<"providers">>, <<"BBF730563914328EC2511D205E6477A94831DB7297DE313B3872A2B26C562EAB">>},
Expand Down
6 changes: 6 additions & 0 deletions src/rebar.hrl
Original file line number Diff line number Diff line change
Expand Up @@ -52,6 +52,12 @@
-type rebar_set() :: set().
-endif.

-ifdef(fun_stacktrace).
-define(WITH_STACKTRACE(T, R, S), T:R -> S = erlang:get_stacktrace(),).
-else.
-define(WITH_STACKTRACE(T, R, S), T:R:S ->).
-endif.

-define(GRAPH_VSN, 2).
-type v() :: {digraph:vertex(), term()} | 'false'.
-type e() :: {digraph:vertex(), digraph:vertex()}.
Expand Down
21 changes: 10 additions & 11 deletions src/rebar3.erl
Original file line number Diff line number Diff line change
Expand Up @@ -67,10 +67,10 @@ main(Args) ->
{ok, _State} ->
erlang:halt(0);
Error ->
handle_error(Error)
handle_error(Error, [])
catch
_:Error ->
handle_error(Error)
?WITH_STACKTRACE(_,Error,Stacktrace)
handle_error(Error, Stacktrace)
end.

%% @doc Erlang-API entry point
Expand Down Expand Up @@ -299,29 +299,28 @@ global_option_spec_list() ->

%% @private translate unhandled errors and internal return codes into proper
%% erroneous program exits.
-spec handle_error(term()) -> no_return().
handle_error(rebar_abort) ->
-spec handle_error(term(), term()) -> no_return().
handle_error(rebar_abort, _) ->
erlang:halt(1);
handle_error({error, rebar_abort}) ->
handle_error({error, rebar_abort}, _) ->
erlang:halt(1);
handle_error({error, {Module, Reason}}) ->
handle_error({error, {Module, Reason}}, Stacktrace) ->
case code:which(Module) of
non_existing ->
?CRASHDUMP("~p: ~p~n~p~n~n", [Module, Reason, erlang:get_stacktrace()]),
?CRASHDUMP("~p: ~p~n~p~n~n", [Module, Reason, Stacktrace]),
?ERROR("Uncaught error in rebar_core. Run with DEBUG=1 to stacktrace or consult rebar3.crashdump", []),
?DEBUG("Uncaught error: ~p ~p", [Module, Reason]),
?INFO("When submitting a bug report, please include the output of `rebar3 report \"your command\"`", []);
_ ->
?ERROR("~ts", [Module:format_error(Reason)])
end,
erlang:halt(1);
handle_error({error, Error}) when is_list(Error) ->
handle_error({error, Error}, _) when is_list(Error) ->
?ERROR("~ts", [Error]),
erlang:halt(1);
handle_error(Error) ->
handle_error(Error, StackTrace) ->
%% Nothing should percolate up from rebar_core;
%% Dump this error to console
StackTrace = erlang:get_stacktrace(),
?CRASHDUMP("Error: ~p~n~p~n~n", [Error, StackTrace]),
?ERROR("Uncaught error in rebar_core. Run with DEBUG=1 to see stacktrace or consult rebar3.crashdump", []),
?DEBUG("Uncaught error: ~p", [Error]),
Expand Down
4 changes: 2 additions & 2 deletions src/rebar_agent.erl
Original file line number Diff line number Diff line change
Expand Up @@ -114,8 +114,8 @@ run(Namespace, Command, StrArgs, RState, Cwd) ->
{{error, cwd_changed}, RState}
end
catch
Type:Reason ->
?DEBUG("Agent Stacktrace: ~p", [erlang:get_stacktrace()]),
?WITH_STACKTRACE(Type, Reason, Stacktrace)
?DEBUG("Agent Stacktrace: ~p", [Stacktrace]),
{{error, {Type, Reason}}, RState}
end.

Expand Down
3 changes: 1 addition & 2 deletions src/rebar_core.erl
Original file line number Diff line number Diff line change
Expand Up @@ -157,8 +157,7 @@ do([ProviderName | Rest], State) ->
{error, Error} ->
{error, Error}
catch
error:undef ->
Stack = erlang:get_stacktrace(),
?WITH_STACKTRACE(error,undef,Stack)
case Stack of
[{ProviderName, do, [_], _}|_] ->
%% This should really only happen if a plugin provider doesn't export do/1
Expand Down
4 changes: 2 additions & 2 deletions src/rebar_dialyzer_format.erl
Original file line number Diff line number Diff line change
Expand Up @@ -53,9 +53,9 @@ format_warning_(Opts, Warning = {_Tag, {SrcFile, Line}, Msg}, {_LastFile, Acc})
String = message_to_string(Msg),
{SrcFile, [lists:flatten(fmt("~n~ts~n~!c~4w~!!: ~ts", [F, Line, String])) | Acc]}
catch
Error:Reason ->
?WITH_STACKTRACE(Error, Reason, Stacktrace)
?DEBUG("Failed to pretty format warning: ~p:~p~n~p",
[Error, Reason, erlang:get_stacktrace()]),
[Error, Reason, Stacktrace]),
{SrcFile, [dialyzer:format_warning(Warning, fullpath) | Acc]}
end.

Expand Down
4 changes: 2 additions & 2 deletions src/rebar_fetch.erl
Original file line number Diff line number Diff line change
Expand Up @@ -32,8 +32,8 @@ download_source(AppDir, Source, State) ->
Error ->
throw(?PRV_ERROR(Error))
catch
C:T ->
?DEBUG("rebar_fetch exception ~p ~p ~p", [C, T, erlang:get_stacktrace()]),
?WITH_STACKTRACE(C,T,S)
?DEBUG("rebar_fetch exception ~p ~p ~p", [C, T, S]),
throw(?PRV_ERROR({fetch_fail, Source}))
end.

Expand Down
4 changes: 2 additions & 2 deletions src/rebar_plugins.erl
Original file line number Diff line number Diff line change
Expand Up @@ -114,8 +114,8 @@ handle_plugin(Profile, Plugin, State, Upgrade) ->

{plugin_providers(Plugin), State4}
catch
C:T ->
?DEBUG("~p ~p ~p", [C, T, erlang:get_stacktrace()]),
?WITH_STACKTRACE(C,T,S)
?DEBUG("~p ~p ~p", [C, T, S]),
?WARN("Plugin ~p not available. It will not be used.", [Plugin]),
{[], State}
end.
Expand Down
33 changes: 20 additions & 13 deletions src/rebar_prv_shell.erl
Original file line number Diff line number Diff line change
Expand Up @@ -201,21 +201,28 @@ rewrite_leaders(OldUser, NewUser) ->
lists:member(proplists:get_value(group_leader, erlang:process_info(Pid)),
OldMasters)],
try
%% enable error_logger's tty output
error_logger:swap_handler(tty),
%% disable the simple error_logger (which may have been added multiple
%% times). removes at most the error_logger added by init and the
%% error_logger added by the tty handler
remove_error_handler(3),
%% reset the tty handler once more for remote shells
error_logger:swap_handler(tty)
case erlang:function_exported(logger, module_info, 0) of
false ->
%% Old style logger had a lock-up issue and other problems related
%% to group leader handling.
%% enable error_logger's tty output
error_logger:swap_handler(tty),
%% disable the simple error_logger (which may have been added
%% multiple times). removes at most the error_logger added by
%% init and the error_logger added by the tty handler
remove_error_handler(3),
%% reset the tty handler once more for remote shells
error_logger:swap_handler(tty);
true ->
%% This is no longer a problem with the logger interface
ok
end
catch
E:R -> % may fail with custom loggers
?DEBUG("Logger changes failed for ~p:~p (~p)", [E,R,erlang:get_stacktrace()]),
?WITH_STACKTRACE(E,R,S) % may fail with custom loggers
?DEBUG("Logger changes failed for ~p:~p (~p)", [E,R,S]),
hope_for_best
end.


setup_paths(State) ->
%% Add deps to path
code:add_pathsa(rebar_state:code_paths(State, all_deps)),
Expand All @@ -235,9 +242,9 @@ maybe_run_script(State) ->
File = filename:absname(RelFile),
try run_script_file(File)
catch
C:E ->
?WITH_STACKTRACE(C,E,S)
?ABORT("Couldn't run shell escript ~p - ~p:~p~nStack: ~p",
[File, C, E, erlang:get_stacktrace()])
[File, C, E, S])
end
end.

Expand Down
4 changes: 2 additions & 2 deletions src/rebar_prv_update.erl
Original file line number Diff line number Diff line change
Expand Up @@ -73,8 +73,8 @@ do(State) ->
?PRV_ERROR({package_parse_cdn, CDN})
end
catch
_E:C ->
?DEBUG("Error creating package index: ~p ~p", [C, erlang:get_stacktrace()]),
?WITH_STACKTRACE(_E, C, S)
?DEBUG("Error creating package index: ~p ~p", [C, S]),
throw(?PRV_ERROR(package_index_write))
end.

Expand Down
6 changes: 3 additions & 3 deletions src/rebar_state.erl
Original file line number Diff line number Diff line change
Expand Up @@ -418,9 +418,9 @@ create_logic_providers(ProviderModules, State0) ->
end
end, State0, ProviderModules)
catch
C:T ->
?DEBUG("~p: ~p ~p", [C, T, erlang:get_stacktrace()]),
?CRASHDUMP("~p: ~p~n~p~n~n~p", [C, T, erlang:get_stacktrace(), State0]),
?WITH_STACKTRACE(C,T,S)
?DEBUG("~p: ~p ~p", [C, T, S]),
?CRASHDUMP("~p: ~p~n~p~n~n~p", [C, T, S, State0]),
throw({error, "Failed creating providers. Run with DEBUG=1 for stacktrace or consult rebar3.crashdump."})
end.

Expand Down
11 changes: 5 additions & 6 deletions src/rebar_utils.erl
Original file line number Diff line number Diff line change
Expand Up @@ -506,11 +506,10 @@ otp_release1(Rel) ->
%% It's fine to rely on the binary module here because we can
%% be sure that it's available when the otp_release string does
%% not begin with $R.
Size = byte_size(Vsn),
%% The shortest vsn string consists of at least two digits
%% followed by "\n". Therefore, it's safe to assume Size >= 3.
case binary:part(Vsn, {Size, -3}) of
<<"**\n">> ->
case binary:match(Vsn, <<"**">>) of
{Pos, _} ->
%% The OTP documentation mentions that a system patched
%% using the otp_patch_apply tool available to licensed
%% customers will leave a '**' suffix in the version as a
Expand All @@ -519,9 +518,9 @@ otp_release1(Rel) ->
%% drop the suffix, given for all intents and purposes, we
%% cannot obtain relevant information from it as far as
%% tooling is concerned.
binary:bin_to_list(Vsn, {0, Size - 3});
_ ->
binary:bin_to_list(Vsn, {0, Size - 1})
binary:bin_to_list(Vsn, {0, Pos});
nomatch ->
rebar_string:trim(binary:bin_to_list(Vsn), trailing, "\n")
end
end.

Expand Down

0 comments on commit 048dfad

Please sign in to comment.