mirror of
https://github.com/erlang/rebar3.git
synced 2025-04-19 02:04:00 +03:00
Bump cth_readable version for OTP-28 readiness
This commit is contained in:
parent
942875e517
commit
0a2cf9fba7
@ -11,7 +11,7 @@
|
||||
{bbmustache, "1.12.2"},
|
||||
{relx, "4.10.0"},
|
||||
{cf, "0.3.1"},
|
||||
{cth_readable, "1.5.1"},
|
||||
{cth_readable, "1.6.1"},
|
||||
{eunit_formatters, "0.5.0"}]}.
|
||||
|
||||
{post_hooks, [{"(linux|darwin|solaris|freebsd|netbsd|openbsd)",
|
||||
|
9
vendor/cth_readable/README.md
vendored
9
vendor/cth_readable/README.md
vendored
@ -34,7 +34,7 @@ Add the following to your `rebar.config`:
|
||||
|
||||
```erlang
|
||||
{deps, [
|
||||
{cth_readable, {git, "https://github.com/ferd/cth_readable.git", {tag, "v1.5.1"}}}
|
||||
{cth_readable, {git, "https://github.com/ferd/cth_readable.git", {tag, "v1.6.0"}}}
|
||||
]}.
|
||||
|
||||
{ct_compile_opts, [{parse_transform, cth_readable_transform}]}.
|
||||
@ -70,6 +70,13 @@ It will let you have both proper formatting and support for arbitrary
|
||||
configurations.
|
||||
|
||||
## Changelog
|
||||
|
||||
1.6.1:
|
||||
- Cleaning up some code for OTP-28, mostly around type usage
|
||||
|
||||
1.6.0:
|
||||
- Adding support for less verbose test skipping (thanks @paulo-ferraz-oliveira)
|
||||
|
||||
1.5.1:
|
||||
- Adding support for `cthr:pal/5` (thanks @ashleyjlive)
|
||||
|
||||
|
4
vendor/cth_readable/hex_metadata.config
vendored
4
vendor/cth_readable/hex_metadata.config
vendored
@ -3,7 +3,7 @@
|
||||
{<<"description">>,<<"Common Test hooks for more readable logs">>}.
|
||||
{<<"files">>,
|
||||
[<<"LICENSE">>,<<"README.md">>,<<"rebar.config">>,<<"rebar.config.script">>,
|
||||
<<"rebar.lock">>,<<"src/cth_readable.app.src">>,
|
||||
<<"rebar.lock">>,<<"src">>,<<"src/cth_readable.app.src">>,
|
||||
<<"src/cth_readable_compact_shell.erl">>,
|
||||
<<"src/cth_readable_failonly.erl">>,<<"src/cth_readable_helpers.erl">>,
|
||||
<<"src/cth_readable_lager_backend.erl">>,<<"src/cth_readable_nosasl.erl">>,
|
||||
@ -17,4 +17,4 @@
|
||||
[{<<"app">>,<<"cf">>},
|
||||
{<<"optional">>,false},
|
||||
{<<"requirement">>,<<"~>0.2.1">>}]}]}.
|
||||
{<<"version">>,<<"1.5.1">>}.
|
||||
{<<"version">>,<<"1.6.1">>}.
|
||||
|
7
vendor/cth_readable/rebar.config
vendored
7
vendor/cth_readable/rebar.config
vendored
@ -15,6 +15,11 @@
|
||||
|
||||
{profiles, [
|
||||
{test, [
|
||||
{deps, [{lager, "3.6.10"}]}
|
||||
{deps, [{lager, "3.9.2"}]},
|
||||
{erl_opts, [debug_info, nowarn_export_all]}
|
||||
]}
|
||||
]}.
|
||||
|
||||
{dialyzer, [
|
||||
{warnings, [no_unknown]}
|
||||
]}.
|
||||
|
4
vendor/cth_readable/src/cth_readable.app.src
vendored
4
vendor/cth_readable/src/cth_readable.app.src
vendored
@ -1,8 +1,8 @@
|
||||
{application,cth_readable,
|
||||
[{description,"Common Test hooks for more readable logs"},
|
||||
{vsn,"1.5.1"},
|
||||
{vsn,"1.6.1"},
|
||||
{registered,[cth_readable_failonly,cth_readable_logger]},
|
||||
{applications,[kernel,stdlib,syntax_tools,cf]},
|
||||
{applications,[kernel,stdlib,syntax_tools,common_test,cf]},
|
||||
{env,[]},
|
||||
{modules,[]},
|
||||
{licenses,["BSD"]},
|
||||
|
@ -5,22 +5,6 @@
|
||||
-define(FAILC, red).
|
||||
-define(SKIPC, magenta).
|
||||
|
||||
-define(OK(Suite, CasePat, CaseArgs),
|
||||
?CASE(Suite, CasePat, ?OKC, "OK", CaseArgs)).
|
||||
-define(SKIP(Suite, CasePat, CaseArgs, Reason),
|
||||
?STACK(Suite, CasePat, CaseArgs, Reason, ?SKIPC, "SKIPPED")).
|
||||
-define(FAIL(Suite, CasePat, CaseArgs, Reason),
|
||||
?STACK(Suite, CasePat, CaseArgs, Reason, ?FAILC, "FAILED")).
|
||||
-define(STACK(Suite, CasePat, CaseArgs, Reason, Color, Label),
|
||||
begin
|
||||
?CASE(Suite, CasePat, Color, Label, CaseArgs),
|
||||
io:format(user, "%%% ~p ==> "++colorize(Color, maybe_eunit_format(Reason))++"~n", [Suite])
|
||||
end).
|
||||
-define(CASE(Suite, CasePat, Color, Res, Args),
|
||||
case Res of
|
||||
"OK" -> io:format(user, colorize(Color, "."), []);
|
||||
_ -> io:format(user, "~n%%% ~p ==> "++CasePat++": "++colorize(Color, Res)++"~n", [Suite | Args])
|
||||
end).
|
||||
|
||||
%% Callbacks
|
||||
-export([id/1]).
|
||||
@ -44,7 +28,7 @@
|
||||
|
||||
-export([terminate/1]).
|
||||
|
||||
-record(state, {id, suite, groups}).
|
||||
-record(state, {id, suite, groups, opts}).
|
||||
|
||||
%% @doc Return a unique id for this CTH.
|
||||
id(_Opts) ->
|
||||
@ -52,8 +36,8 @@ id(_Opts) ->
|
||||
|
||||
%% @doc Always called before any other callback function. Use this to initiate
|
||||
%% any common state.
|
||||
init(Id, _Opts) ->
|
||||
{ok, #state{id=Id}}.
|
||||
init(Id, Opts) ->
|
||||
{ok, #state{id=Id, opts=Opts}}.
|
||||
|
||||
%% @doc Called before init_per_suite is called.
|
||||
pre_init_per_suite(Suite,Config,State) ->
|
||||
@ -95,13 +79,13 @@ pre_init_per_testcase(_TC,Config,State) ->
|
||||
|
||||
%% @doc Called after each test case.
|
||||
post_end_per_testcase(TC,_Config,ok,State=#state{suite=Suite, groups=Groups}) ->
|
||||
?OK(Suite, "~s", [format_path(TC,Groups)]),
|
||||
format_ok(Suite, "~s", [format_path(TC,Groups)]),
|
||||
{ok, State};
|
||||
post_end_per_testcase(TC,Config,Error,State=#state{suite=Suite, groups=Groups}) ->
|
||||
case lists:keyfind(tc_status, 1, Config) of
|
||||
{tc_status, ok} ->
|
||||
%% Test case passed, but we still ended in an error
|
||||
?STACK(Suite, "~s", [format_path(TC,Groups)], Error, ?SKIPC, "end_per_testcase FAILED");
|
||||
format_stack(Suite, "~s", [format_path(TC,Groups)], Error, ?SKIPC, "end_per_testcase FAILED");
|
||||
_ ->
|
||||
%% Test case failed, in which case on_tc_fail already reports it
|
||||
ok
|
||||
@ -111,30 +95,65 @@ post_end_per_testcase(TC,Config,Error,State=#state{suite=Suite, groups=Groups})
|
||||
%% @doc Called after post_init_per_suite, post_end_per_suite, post_init_per_group,
|
||||
%% post_end_per_group and post_end_per_testcase if the suite, group or test case failed.
|
||||
on_tc_fail({TC,_Group}, Reason, State=#state{suite=Suite, groups=Groups}) ->
|
||||
?FAIL(Suite, "~s", [format_path(TC,Groups)], Reason),
|
||||
format_fail(Suite, "~s", [format_path(TC,Groups)], Reason),
|
||||
State;
|
||||
on_tc_fail(TC, Reason, State=#state{suite=Suite, groups=Groups}) ->
|
||||
?FAIL(Suite, "~s", [format_path(TC,Groups)], Reason),
|
||||
format_fail(Suite, "~s", [format_path(TC,Groups)], Reason),
|
||||
State.
|
||||
|
||||
%% @doc Called when a test case is skipped by either user action
|
||||
%% or due to an init function failing. (>= 19.3)
|
||||
on_tc_skip(Suite, {TC,_Group}, Reason, State=#state{groups=Groups}) ->
|
||||
?SKIP(Suite, "~s", [format_path(TC,Groups)], Reason),
|
||||
on_tc_skip(Suite, {TC,_Group}, Reason, State=#state{groups=Groups, opts=Opts}) ->
|
||||
skip(Suite, TC, Groups, Reason, Opts),
|
||||
State#state{suite=Suite};
|
||||
on_tc_skip(Suite, TC, Reason, State=#state{groups=Groups}) ->
|
||||
?SKIP(Suite, "~s", [format_path(TC,Groups)], Reason),
|
||||
on_tc_skip(Suite, TC, Reason, State=#state{groups=Groups, opts=Opts}) ->
|
||||
skip(Suite, TC, Groups, Reason, Opts),
|
||||
State#state{suite=Suite}.
|
||||
|
||||
skip(Suite, TC, Groups, Reason, Opts) ->
|
||||
Verbose = proplists:get_value(verbose, Opts, true),
|
||||
format_skip(Suite, "~s", [format_path(TC,Groups)], Reason, Verbose).
|
||||
|
||||
%% @doc Called when a test case is skipped by either user action
|
||||
%% or due to an init function failing. (Pre-19.3)
|
||||
on_tc_skip({TC,Group}, Reason, State=#state{suite=Suite}) ->
|
||||
?SKIP(Suite, "~p (group ~p)", [TC, Group], Reason),
|
||||
format_skip(Suite, "~p (group ~p)", [TC, Group], Reason, true),
|
||||
State;
|
||||
on_tc_skip(TC, Reason, State=#state{suite=Suite}) ->
|
||||
?SKIP(Suite, "~p", [TC], Reason),
|
||||
format_skip(Suite, "~p", [TC], Reason, true),
|
||||
State.
|
||||
|
||||
%% @doc Called when the scope of the CTH is done
|
||||
terminate(_State) ->
|
||||
ok.
|
||||
|
||||
%%%%%%%%%%%%%%%
|
||||
%%% HELPERS %%%
|
||||
%%%%%%%%%%%%%%%
|
||||
|
||||
format_ok(Suite, CasePat, CaseArgs) ->
|
||||
format_case(Suite, CasePat, ?OKC, "OK", CaseArgs).
|
||||
|
||||
format_skip(Suite, CasePat, CaseArgs, Reason, Verbose) ->
|
||||
format_stack(Suite, CasePat, CaseArgs, Reason, ?SKIPC, "SKIPPED", Verbose).
|
||||
|
||||
format_fail(Suite, CasePat, CaseArgs, Reason) ->
|
||||
format_stack(Suite, CasePat, CaseArgs, Reason, ?FAILC, "FAILED").
|
||||
|
||||
format_stack(Suite, CasePat, CaseArgs, Reason, Color, Label) ->
|
||||
format_stack(Suite, CasePat, CaseArgs, Reason, Color, Label, true).
|
||||
|
||||
format_stack(Suite, CasePat, CaseArgs, Reason, Color, Label, Verbose) ->
|
||||
case Verbose of
|
||||
true ->
|
||||
format_case(Suite, CasePat, Color, Label, CaseArgs),
|
||||
io:format(user, "%%% ~p ==> ~ts~n", [Suite,colorize(Color, maybe_eunit_format(Reason))]);
|
||||
false ->
|
||||
io:format(user, colorize(Color, "*"), [])
|
||||
end.
|
||||
|
||||
format_case(Suite, CasePat, Color, Res, Args) ->
|
||||
case Res of
|
||||
"OK" -> io:put_chars(user, colorize(Color, "."));
|
||||
_ -> io:format(user, lists:flatten(["~n%%% ~p ==> ",CasePat,": ",colorize(Color, Res),"~n"]), [Suite | Args])
|
||||
end.
|
||||
|
@ -1,5 +1,13 @@
|
||||
-module(cth_readable_failonly).
|
||||
|
||||
%% We use configuration patterns for older versions of Erlang/OTP
|
||||
%% that do not exist anymore in the modern versions scanned by
|
||||
%% Dialyzer, so turn off the warnings for those.
|
||||
%%
|
||||
%% Also we create an idle fun we know never returns, so turn
|
||||
%% that off too.
|
||||
-dialyzer([no_return]).
|
||||
|
||||
-record(state, {id,
|
||||
sasl_reset,
|
||||
lager_reset,
|
||||
@ -109,11 +117,13 @@ init(Id, Opts) ->
|
||||
{ok, #state{id=Id, sasl_reset={reset, tty}, lager_reset=LagerReset,
|
||||
handlers=[?MODULE], named=Named, has_logger=HasLogger}};
|
||||
{ok, tty} when HasLogger ->
|
||||
logger:add_handler(?MODULE, ?MODULE, Cfg#{sasl => true, max_events => MaxEvents}),
|
||||
SubCfg = maps:get(config, Cfg, #{}),
|
||||
logger:add_handler(?MODULE, ?MODULE, Cfg#{config => SubCfg#{sasl => true, max_events => MaxEvents}}),
|
||||
{ok, #state{id=Id, lager_reset=LagerReset, handlers=[?MODULE],
|
||||
named=Named, has_logger=HasLogger}};
|
||||
_ when HasLogger ->
|
||||
logger:add_handler(?MODULE, ?MODULE, Cfg#{sasl => false, max_events => MaxEvents}),
|
||||
SubCfg = maps:get(config, Cfg, #{}),
|
||||
logger:add_handler(?MODULE, ?MODULE, Cfg#{config => SubCfg#{sasl => false, max_events => MaxEvents}}),
|
||||
{ok, #state{id=Id, lager_reset=LagerReset, handlers=[?MODULE],
|
||||
named=Named, has_logger=HasLogger}};
|
||||
_ ->
|
||||
@ -309,7 +319,7 @@ flush(Buf, Cfg, ShowSASL, SASLType) ->
|
||||
|
||||
|
||||
%%%%%%%%%%%%%%%% LOGGER %%%%%%%%%%%%%%%%%%%
|
||||
adding_handler(Config = #{sasl := SASL, max_events := MaxEvents}) ->
|
||||
adding_handler(Config = #{config := #{sasl := SASL, max_events := MaxEvents}}) ->
|
||||
{ok, Pid} = gen_event:start({local, cth_readable_logger}, []),
|
||||
gen_event:add_handler(cth_readable_logger, ?MODULE, [{sasl, SASL}, {max_events, MaxEvents}]),
|
||||
{ok, Config#{cth_readable_logger => Pid}}.
|
||||
@ -340,12 +350,8 @@ maybe_steal_logger_config() ->
|
||||
false ->
|
||||
#{};
|
||||
true ->
|
||||
case logger:get_handler_config(default) of
|
||||
{ok, {_,Cfg}} -> %% OTP-21.0-rc2 result
|
||||
maps:with([formatter], Cfg); % only keep the essential
|
||||
{ok, Cfg} -> %% OTP-21.0 result
|
||||
maps:with([formatter], Cfg) % only keep the essential
|
||||
end
|
||||
{ok, Cfg} = logger:get_handler_config(default),
|
||||
maps:with([formatter], Cfg) % only keep the essential
|
||||
end.
|
||||
|
||||
sasl_running() ->
|
||||
|
74
vendor/cth_readable/src/cth_readable_shell.erl
vendored
74
vendor/cth_readable/src/cth_readable_shell.erl
vendored
@ -5,20 +5,6 @@
|
||||
-define(FAILC, red).
|
||||
-define(SKIPC, magenta).
|
||||
|
||||
-define(OK(Suite, CasePat, CaseArgs),
|
||||
?CASE(Suite, CasePat, ?OKC, "OK", CaseArgs)).
|
||||
-define(SKIP(Suite, CasePat, CaseArgs, Reason),
|
||||
?STACK(Suite, CasePat, CaseArgs, Reason, ?SKIPC, "SKIPPED")).
|
||||
-define(FAIL(Suite, CasePat, CaseArgs, Reason),
|
||||
?STACK(Suite, CasePat, CaseArgs, Reason, ?FAILC, "FAILED")).
|
||||
-define(STACK(Suite, CasePat, CaseArgs, Reason, Color, Label),
|
||||
begin
|
||||
?CASE(Suite, CasePat, Color, Label, CaseArgs),
|
||||
io:format(user, "%%% ~p ==> "++colorize(Color, maybe_eunit_format(Reason))++"~n", [Suite])
|
||||
end).
|
||||
-define(CASE(Suite, CasePat, Color, Res, Args),
|
||||
io:format(user, "%%% ~p ==> "++CasePat++": "++colorize(Color, Res)++"~n", [Suite | Args])).
|
||||
|
||||
%% Callbacks
|
||||
-export([id/1]).
|
||||
-export([init/2]).
|
||||
@ -41,7 +27,7 @@
|
||||
|
||||
-export([terminate/1]).
|
||||
|
||||
-record(state, {id, suite, groups}).
|
||||
-record(state, {id, suite, groups, opts}).
|
||||
|
||||
%% @doc Return a unique id for this CTH.
|
||||
id(_Opts) ->
|
||||
@ -49,8 +35,8 @@ id(_Opts) ->
|
||||
|
||||
%% @doc Always called before any other callback function. Use this to initiate
|
||||
%% any common state.
|
||||
init(Id, _Opts) ->
|
||||
{ok, #state{id=Id}}.
|
||||
init(Id, Opts) ->
|
||||
{ok, #state{id=Id, opts=Opts}}.
|
||||
|
||||
%% @doc Called before init_per_suite is called.
|
||||
pre_init_per_suite(Suite,Config,State) ->
|
||||
@ -90,13 +76,13 @@ pre_init_per_testcase(_TC,Config,State) ->
|
||||
|
||||
%% @doc Called after each test case.
|
||||
post_end_per_testcase(TC,_Config,ok,State=#state{suite=Suite, groups=Groups}) ->
|
||||
?OK(Suite, "~s", [format_path(TC,Groups)]),
|
||||
format_ok(Suite, "~s", [format_path(TC,Groups)]),
|
||||
{ok, State};
|
||||
post_end_per_testcase(TC,Config,Error,State=#state{suite=Suite, groups=Groups}) ->
|
||||
case lists:keyfind(tc_status, 1, Config) of
|
||||
{tc_status, ok} ->
|
||||
%% Test case passed, but we still ended in an error
|
||||
?STACK(Suite, "~s", [format_path(TC,Groups)], Error, ?SKIPC, "end_per_testcase FAILED");
|
||||
format_stack(Suite, "~s", [format_path(TC,Groups)], Error, ?SKIPC, "end_per_testcase FAILED");
|
||||
_ ->
|
||||
%% Test case failed, in which case on_tc_fail already reports it
|
||||
ok
|
||||
@ -106,30 +92,64 @@ post_end_per_testcase(TC,Config,Error,State=#state{suite=Suite, groups=Groups})
|
||||
%% @doc Called after post_init_per_suite, post_end_per_suite, post_init_per_group,
|
||||
%% post_end_per_group and post_end_per_testcase if the suite, group or test case failed.
|
||||
on_tc_fail({TC,_Group}, Reason, State=#state{suite=Suite, groups=Groups}) ->
|
||||
?FAIL(Suite, "~s", [format_path(TC,Groups)], Reason),
|
||||
format_fail(Suite, "~s", [format_path(TC,Groups)], Reason),
|
||||
State;
|
||||
on_tc_fail(TC, Reason, State=#state{suite=Suite, groups=Groups}) ->
|
||||
?FAIL(Suite, "~s", [format_path(TC,Groups)], Reason),
|
||||
format_fail(Suite, "~s", [format_path(TC,Groups)], Reason),
|
||||
State.
|
||||
|
||||
%% @doc Called when a test case is skipped by either user action
|
||||
%% or due to an init function failing. (>= 19.3)
|
||||
on_tc_skip(Suite, {TC,_Group}, Reason, State=#state{groups=Groups}) ->
|
||||
?SKIP(Suite, "~s", [format_path(TC,Groups)], Reason),
|
||||
on_tc_skip(Suite, {TC,_Group}, Reason, State=#state{groups=Groups, opts=Opts}) ->
|
||||
skip(Suite, TC, Groups, Reason, Opts),
|
||||
State#state{suite=Suite};
|
||||
on_tc_skip(Suite, TC, Reason, State=#state{groups=Groups}) ->
|
||||
?SKIP(Suite, "~s", [format_path(TC,Groups)], Reason),
|
||||
on_tc_skip(Suite, TC, Reason, State=#state{groups=Groups, opts=Opts}) ->
|
||||
skip(Suite, TC, Groups, Reason, Opts),
|
||||
State#state{suite=Suite}.
|
||||
|
||||
skip(Suite, TC, Groups, Reason, Opts) ->
|
||||
Verbose = proplists:get_value(verbose, Opts, true),
|
||||
format_skip(Suite, "~s", [format_path(TC,Groups)], Reason, Verbose).
|
||||
|
||||
%% @doc Called when a test case is skipped by either user action
|
||||
%% or due to an init function failing. (Pre-19.3)
|
||||
on_tc_skip({TC,Group}, Reason, State=#state{suite=Suite}) ->
|
||||
?SKIP(Suite, "~p (group ~p)", [TC, Group], Reason),
|
||||
format_skip(Suite, "~p (group ~p)", [TC, Group], Reason, true),
|
||||
State;
|
||||
on_tc_skip(TC, Reason, State=#state{suite=Suite}) ->
|
||||
?SKIP(Suite, "~p", [TC], Reason),
|
||||
format_skip(Suite, "~p", [TC], Reason, true),
|
||||
State.
|
||||
|
||||
%% @doc Called when the scope of the CTH is done
|
||||
terminate(_State) ->
|
||||
ok.
|
||||
|
||||
%%%%%%%%%%%%%%%%
|
||||
%%% Helpers %%%
|
||||
%%%%%%%%%%%%%%%%
|
||||
format_ok(Suite, CasePat, CaseArgs) ->
|
||||
format_case(Suite, CasePat, ?OKC, "OK", CaseArgs).
|
||||
|
||||
format_skip(Suite, CasePat, CaseArgs, Reason, Verbose) ->
|
||||
format_stack(Suite, CasePat, CaseArgs, Reason, ?SKIPC, "SKIPPED", Verbose).
|
||||
|
||||
format_fail(Suite, CasePat, CaseArgs, Reason) ->
|
||||
format_stack(Suite, CasePat, CaseArgs, Reason, ?FAILC, "FAILED").
|
||||
|
||||
format_case(Suite, CasePat, Color, Res, Args) ->
|
||||
case Res of
|
||||
"OK" -> io:put_chars(user, colorize(Color, "."));
|
||||
_ -> io:format(user, lists:flatten(["~n%%% ~p ==> ",CasePat,": ",colorize(Color, Res),"~n"]), [Suite | Args])
|
||||
end.
|
||||
|
||||
format_stack(Suite, CasePat, CaseArgs, Reason, Color, Label) ->
|
||||
format_stack(Suite, CasePat, CaseArgs, Reason, Color, Label, true).
|
||||
|
||||
format_stack(Suite, CasePat, CaseArgs, Reason, Color, Label, Verbose) ->
|
||||
case Verbose of
|
||||
true ->
|
||||
format_case(Suite, CasePat, Color, Label, CaseArgs),
|
||||
io:format(user, "%%% ~p ==> ~ts~n", [Suite,colorize(Color, maybe_eunit_format(Reason))]);
|
||||
false ->
|
||||
io:format(user, colorize(Color, "*"), [])
|
||||
end.
|
||||
|
Loading…
x
Reference in New Issue
Block a user