Skip to content

Commit

Permalink
Add euint --test flag
Browse files Browse the repository at this point in the history
  • Loading branch information
eproxus committed Feb 23, 2022
1 parent 8b9b74a commit f54b658
Show file tree
Hide file tree
Showing 2 changed files with 57 additions and 14 deletions.
36 changes: 23 additions & 13 deletions src/rebar_prv_eunit.erl
Original file line number Diff line number Diff line change
Expand Up @@ -136,9 +136,11 @@ resolve_tests(State) ->
Dirs = resolve(dir, RawOpts),
Files = resolve(file, RawOpts),
Modules = resolve(module, RawOpts),
Tests = resolve(test, RawOpts),
Suites = resolve(suite, module, RawOpts),
Generator = resolve(generator, RawOpts),
Apps ++ Applications ++ Dirs ++ Files ++ Modules ++ Suites ++ Generator.
Generators = resolve(generator, RawOpts),
lists:append([Apps, Applications, Dirs, Files, Modules, Tests, Suites,
Generators]).

resolve(Flag, RawOpts) -> resolve(Flag, Flag, RawOpts).

Expand All @@ -149,22 +151,23 @@ resolve(Flag, EUnitKey, RawOpts) ->
rebar_string:lexemes(Args, [$,]))
end.

normalize(generator, Args) ->
lists:flatmap(fun(Value) -> normalize_(generator, Value) end, Args);
normalize(EUnitKey, Args) ->
lists:map(fun(Arg) -> normalize_(EUnitKey, Arg) end, Args).
lists:flatmap(fun(Arg) -> normalize_(EUnitKey, Arg) end, Args).

normalize_(generator, Value) ->
normalize_(generator, Value) -> tokenize(generator, Value);
normalize_(test, Value) -> tokenize(test, Value);
normalize_(Key, Value) when Key == dir; Key == file -> [{Key, Value}];
normalize_(Key, Value) -> [{Key, list_to_atom(Value)}].

tokenize(Type, Value) ->
case string:tokens(Value, [$:]) of
[Module0, Functions] ->
Module = list_to_atom(Module0),
lists:map(fun(F) -> {generator, Module, list_to_atom(F)} end,
string:tokens(Functions, [$;]));
lists:map(fun(F) -> {Type, Module, list_to_atom(F)} end,
string:tokens(Functions, [$;, $+]));
_ ->
?PRV_ERROR({generator, Value})
end;
normalize_(Key, Value) when Key == dir; Key == file -> {Key, Value};
normalize_(Key, Value) -> {Key, list_to_atom(Value)}.
?PRV_ERROR({Type, Value})
end.

cfg_tests(State) ->
case rebar_state:get(State, eunit_tests, []) of
Expand Down Expand Up @@ -369,6 +372,8 @@ validate(State, {file, File}) ->
validate_file(State, File);
validate(State, {module, Module}) ->
validate_module(State, Module);
validate(State, {test, Module, Function}) ->
validate_test(State, Module, Function);
validate(State, {suite, Module}) ->
validate_module(State, Module);
validate(State, {generator, Module, Function}) ->
Expand Down Expand Up @@ -418,6 +423,9 @@ validate_module(_State, Module) ->
validate_generator(State, Module, _Function) ->
validate_module(State, Module).

validate_test(State, Module, _Function) ->
validate_module(State, Module).

resolve_eunit_opts(State) ->
{Opts, _} = rebar_state:command_parsed_args(State),
EUnitOpts = rebar_state:get(State, eunit_opts, []),
Expand Down Expand Up @@ -558,6 +566,7 @@ eunit_opts(_State) ->
{dir, $d, "dir", string, help(dir)},
{file, $f, "file", string, help(file)},
{module, $m, "module", string, help(module)},
{test, $t, "test", string, help(test)},
{suite, $s, "suite", string, help(module)},
{generator, $g, "generator", string, help(generator)},
{verbose, $v, "verbose", boolean, help(verbose)},
Expand All @@ -573,7 +582,8 @@ help(profile) -> "Show the slowest tests. Defaults to false.";
help(dir) -> "Comma separated list of dirs to load tests from. Equivalent to `[{dir, Dir}]`.";
help(file) -> "Comma separated list of files to load tests from. Equivalent to `[{file, File}]`.";
help(module) -> "Comma separated list of modules to load tests from. Equivalent to `[{module, Module}]`.";
help(generator) -> "Comma separated list of generators (the format is `module:function`) to load tests from. Equivalent to `[{generator, Module, Function}]`.";
help(test) -> "Comma separated list of tests to run. The format is `Module:Func1+Func2`. Equivalent to `[{test, Module, Function}]`.";
help(generator) -> "Comma separated list of generators to load tests from. The format is `Module:Func1+Func2`. Equivalent to `[{generator, Module, Function}]`.";
help(verbose) -> "Verbose output. Defaults to false.";
help(name) -> "Gives a long name to the node";
help(sname) -> "Gives a short name to the node";
Expand Down
35 changes: 34 additions & 1 deletion test/rebar_eunit_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -12,6 +12,7 @@
-export([eunit_tests/1, eunit_opts/1, eunit_first_files/1]).
-export([single_application_arg/1, multi_application_arg/1, missing_application_arg/1]).
-export([single_module_arg/1, multi_module_arg/1, missing_module_arg/1]).
-export([single_test_arg/1, multi_test_arg/1, missing_test_arg/1]).
-export([single_suite_arg/1, multi_suite_arg/1, missing_suite_arg/1]).
-export([single_generator_arg/1, multi_generator_arg/1, missing_generator_arg/1]).
-export([single_file_arg/1, multi_file_arg/1, missing_file_arg/1]).
Expand Down Expand Up @@ -48,6 +49,7 @@ groups() ->
{cmd_line_args, [], [eunit_tests, eunit_opts, eunit_first_files,
single_application_arg, multi_application_arg, missing_application_arg,
single_module_arg, multi_module_arg, missing_module_arg,
single_test_arg, multi_test_arg, missing_test_arg,
single_suite_arg, multi_suite_arg, missing_suite_arg,
single_generator_arg, multi_generator_arg, missing_generator_arg,
single_file_arg, multi_file_arg, missing_file_arg,
Expand Down Expand Up @@ -365,6 +367,37 @@ missing_module_arg(Config) ->
Error = {error, {rebar_prv_eunit, {eunit_test_errors, ["Module `missing_app' not found in project."]}}},
Error = Tests.

%% check that the --generator cmd line opt generates the correct test set
single_test_arg(Config) ->
S = ?config(result, Config),

{ok, Args} = getopt:parse(rebar_prv_eunit:eunit_opts(S), ["--test=module_name:function_name"]),
State = rebar_state:command_parsed_args(S, Args),

{ok, [{test, module_name, function_name}]} = rebar_prv_eunit:prepare_tests(State).

multi_test_arg(Config) ->
S = ?config(result, Config),

{ok, Args} = getopt:parse(rebar_prv_eunit:eunit_opts(S), ["--test=module1:func1+func2,module2:func1;func2"]),
State = rebar_state:command_parsed_args(S, Args),

Generators = [{test, module1, func1},
{test, module1, func2},
{test, module2, func1},
{test, module2, func2}],
{ok, Generators} = rebar_prv_eunit:prepare_tests(State).

%% check that an invalid --suite cmd line opt generates an error
missing_test_arg(Config) ->
S = ?config(result, Config),

{ok, Args} = getopt:parse(rebar_prv_eunit:eunit_opts(S), ["--test=missing_module:func1"]),
State = rebar_state:command_parsed_args(S, Args),

Error = {error, {rebar_prv_eunit, {eunit_test_errors, ["Module `missing_module' not found in project."]}}},
Error = rebar_prv_eunit:validate_tests(State, rebar_prv_eunit:prepare_tests(State)).

%% check that the --suite cmd line opt generates the correct test set
single_suite_arg(Config) ->
AppDir = ?config(apps, Config),
Expand Down Expand Up @@ -421,7 +454,7 @@ single_generator_arg(Config) ->
multi_generator_arg(Config) ->
S = ?config(result, Config),

{ok, Args} = getopt:parse(rebar_prv_eunit:eunit_opts(S), ["--generator=module1:func1;func2,module2:func1;func2"]),
{ok, Args} = getopt:parse(rebar_prv_eunit:eunit_opts(S), ["--generator=module1:func1+func2,module2:func1;func2"]),
State = rebar_state:command_parsed_args(S, Args),

Generators = [{generator, module1, func1},
Expand Down

0 comments on commit f54b658

Please sign in to comment.