Skip to content

Commit

Permalink
allow ct suites to be specified at root of project (or root of app)
Browse files Browse the repository at this point in the history
previously rebar3 dropped suites declared at the root of the project (via
`--suite=whatever_SUITE' probably) and warned. this was because the compiler
would recursively copy and compile everything in the directory indicated by
the test suite. this changes the copy mechanism to only copy erl source files
and directories that end with `_SUITE_data' into the `extras' dir in `_build'
  • Loading branch information
alisdair sullivan committed Dec 8, 2015
1 parent d76b25e commit 39c7ed2
Show file tree
Hide file tree
Showing 3 changed files with 78 additions and 8 deletions.
43 changes: 36 additions & 7 deletions src/rebar_prv_common_test.erl
Original file line number Diff line number Diff line change
Expand Up @@ -340,7 +340,7 @@ test_dirs(State, Apps, Opts) ->
{Suites, Dir} when is_integer(hd(Dir)) ->
set_compile_dirs(State, Apps, join(Suites, Dir));
{Suites, [Dir]} when is_integer(hd(Dir)) ->
set_compile_dirs(State, Apps, join(Suites, Dir));
set_compile_dirs(State, Apps, join(Suites, Dir));
{_Suites, _Dirs} -> {error, "Only a single directory may be specified when specifying suites"}
end.

Expand Down Expand Up @@ -375,6 +375,16 @@ find_suite_dirs(Suites) ->

maybe_inject_test_dir(State, AppAcc, [App|Rest], Dir) ->
case rebar_file_utils:path_from_ancestor(Dir, rebar_app_info:dir(App)) of
{ok, []} ->
%% normal operation involves copying the entire directory a
%% suite exists in but if the suite is in the app root directory
%% the current compiler tries to compile all subdirs including priv
%% instead copy only files ending in `.erl' and directories
%% ending in `_SUITE_data' into the `_build/PROFILE/extras' dir
ExtrasDir = filename:join([rebar_dir:base_dir(State), "extras"]),
ok = copy_bare_suites(Dir, ExtrasDir),
Opts = inject_test_dir(rebar_app_info:opts(App), ExtrasDir),
{State, AppAcc ++ [rebar_app_info:opts(App, Opts)] ++ Rest};
{ok, Path} ->
Opts = inject_test_dir(rebar_app_info:opts(App), Path),
{State, AppAcc ++ [rebar_app_info:opts(App, Opts)] ++ Rest};
Expand All @@ -384,8 +394,15 @@ maybe_inject_test_dir(State, AppAcc, [App|Rest], Dir) ->
maybe_inject_test_dir(State, AppAcc, [], Dir) ->
case rebar_file_utils:path_from_ancestor(Dir, rebar_state:dir(State)) of
{ok, []} ->
?WARN("Can't have suites in root of project dir, dropping from tests", []),
{State, AppAcc};
%% normal operation involves copying the entire directory a
%% suite exists in but if the suite is in the root directory
%% that results in a loop as we copy `_build' into itself
%% instead copy only files ending in `.erl' and directories
%% ending in `_SUITE_data' in the `_build/PROFILE/extras' dir
ExtrasDir = filename:join([rebar_dir:base_dir(State), "extras"]),
ok = copy_bare_suites(Dir, ExtrasDir),
Opts = inject_test_dir(rebar_state:opts(State), ExtrasDir),
{rebar_state:opts(State, Opts), AppAcc};
{ok, Path} ->
Opts = inject_test_dir(rebar_state:opts(State), Path),
{rebar_state:opts(State, Opts), AppAcc};
Expand All @@ -398,6 +415,14 @@ inject_test_dir(Opts, Dir) ->
ExtraSrcDirs = rebar_opts:get(Opts, extra_src_dirs, []),
rebar_opts:set(Opts, extra_src_dirs, ExtraSrcDirs ++ [Dir]).

copy_bare_suites(From, To) ->
filelib:ensure_dir(filename:join([To, "dummy.txt"])),
SrcFiles = rebar_utils:find_files(From, ".*\\.(erl|hrl|beam)\$", false),
DataDirs = lists:filter(fun filelib:is_dir/1,
filelib:wildcard(filename:join([From, "*_SUITE_data"]))),
ok = rebar_file_utils:cp_r(SrcFiles, To),
rebar_file_utils:cp_r(DataDirs, To).

translate_paths(State, Opts) ->
case {proplists:get_value(suite, Opts), proplists:get_value(dir, Opts)} of
{_Suites, undefined} -> translate_suites(State, Opts, []);
Expand Down Expand Up @@ -433,13 +458,17 @@ translate_suites(State, [Test|Rest], Acc) ->
translate_suites(State, Rest, [Test|Acc]).

translate(State, [App|Rest], Path) ->
case rebar_file_utils:path_from_ancestor(Path, rebar_app_info:dir(App)) of
{ok, P} -> filename:join([rebar_app_info:out_dir(App), P]);
case rebar_file_utils:path_from_ancestor(filename:dirname(Path), rebar_app_info:dir(App)) of
%% suite is in root dir, it should now be in `_build/PROFILE/extras'
{ok, []} -> filename:join([rebar_dir:base_dir(State), "extras", Path]);
{ok, P} -> filename:join([rebar_app_info:out_dir(App), P, filename:basename(Path)]);
{error, badparent} -> translate(State, Rest, Path)
end;
translate(State, [], Path) ->
case rebar_file_utils:path_from_ancestor(Path, rebar_state:dir(State)) of
{ok, P} -> filename:join([rebar_dir:base_dir(State), "extras", P]);
case rebar_file_utils:path_from_ancestor(filename:dirname(Path), rebar_state:dir(State)) of
%% suite is in root dir, it should now be in `_build/PROFILE/extras'
{ok, []} -> filename:join([rebar_dir:base_dir(State), "extras", Path]);
{ok, P} -> filename:join([rebar_dir:base_dir(State), "extras", P, filename:basename(Path)]);
%% not relative, leave as is
{error, badparent} -> Path
end.
Expand Down
3 changes: 3 additions & 0 deletions src/rebar_prv_compile.erl
Original file line number Diff line number Diff line change
Expand Up @@ -217,6 +217,9 @@ copy(OldAppDir, AppDir, Dir) ->

%% TODO: use ec_file:copy/2 to do this, it preserves timestamps and
%% may prevent recompilation of files in extra dirs
copy(Source, Source) ->
%% someone specified a src dir inside _build. weird but ok
ok;
copy(Source, Target) ->
%% important to do this so no files are copied onto themselves
%% which truncates them to zero length on some platforms
Expand Down
40 changes: 39 additions & 1 deletion test/rebar_ct_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -17,6 +17,7 @@
multi_suite/1,
all_suite/1,
single_dir_and_single_suite/1,
suite_at_root/1,
data_dir_correct/1,
cmd_label/1,
cmd_config/1,
Expand Down Expand Up @@ -72,7 +73,8 @@ groups() -> [{basic_app, [], [basic_app_default_dirs,
single_unmanaged_suite,
multi_suite,
all_suite,
single_dir_and_single_suite]},
single_dir_and_single_suite,
suite_at_root]},
{data_dirs, [], [data_dir_correct]},
{ct_opts, [], [cmd_label,
cmd_config,
Expand Down Expand Up @@ -177,6 +179,12 @@ init_per_group(dirs_and_suites, Config) ->
ok = filelib:ensure_dir(Suite3),
ok = file:write_file(Suite3, test_suite("extras")),

Suite4 = filename:join([AppDir, "root_SUITE.erl"]),
ok = file:write_file(Suite4, test_suite("root")),

ok = filelib:ensure_dir(filename:join([AppDir, "root_SUITE_data", "dummy.txt"])),
ok = file:write_file(filename:join([AppDir, "root_SUITE_data", "some_data.txt"]), <<>>),

{ok, State} = rebar_test_utils:run_and_check(C, [], ["as", "test", "lock"], return),

[{s, State}, {appnames, [Name1, Name2]}|C];
Expand Down Expand Up @@ -603,6 +611,36 @@ single_dir_and_single_suite(Config) ->
Suite = proplists:get_value(suite, Opts),
["extra_SUITE"] = Suite.

suite_at_root(Config) ->
AppDir = ?config(apps, Config),
State = ?config(s, Config),

LibDirs = rebar_dir:lib_dirs(State),
State1 = rebar_app_discover:do(State, LibDirs),

Providers = rebar_state:providers(State1),
Namespace = rebar_state:namespace(State1),
CommandProvider = providers:get_provider(ct, Providers, Namespace),
GetOptSpec = providers:opts(CommandProvider),
{ok, GetOptResult} = getopt:parse(GetOptSpec, ["--suite=" ++ filename:join([AppDir, "root_SUITE"])]),

State2 = rebar_state:command_parsed_args(State1, GetOptResult),

Tests = rebar_prv_common_test:prepare_tests(State2),
{ok, NewState} = rebar_prv_common_test:compile(State2, Tests),
{ok, T} = Tests,
Opts = rebar_prv_common_test:translate_paths(NewState, T),

Suite = proplists:get_value(suite, Opts),
Expected = filename:join([AppDir, "_build", "test", "extras", "root_SUITE"]),
[Expected] = Suite,

TestBeam = filename:join([AppDir, "_build", "test", "extras", "root_SUITE.beam"]),
true = filelib:is_file(TestBeam),

DataDir = filename:join([AppDir, "_build", "test", "extras", "root_SUITE_data"]),
true = filelib:is_dir(DataDir).

%% this test probably only fails when this suite is run via rebar3 with the --cover flag
data_dir_correct(Config) ->
DataDir = ?config(data_dir, Config),
Expand Down

0 comments on commit 39c7ed2

Please sign in to comment.