Skip to content

Commit

Permalink
add support for passing a sys_config to common test
Browse files Browse the repository at this point in the history
  • Loading branch information
tsloughter committed Jun 11, 2016
1 parent e337793 commit 854abc1
Show file tree
Hide file tree
Showing 5 changed files with 101 additions and 33 deletions.
15 changes: 15 additions & 0 deletions src/rebar_file_utils.erl
Original file line number Diff line number Diff line change
Expand Up @@ -27,6 +27,7 @@
-module(rebar_file_utils).

-export([try_consult/1,
consult_config/2,
format_error/1,
symlink_or_copy/2,
rm_rf/1,
Expand Down Expand Up @@ -61,6 +62,20 @@ try_consult(File) ->
throw(?PRV_ERROR({bad_term_file, File, Reason}))
end.

-spec consult_config(rebar_state:t(), string()) -> [[tuple()]].
consult_config(State, Filename) ->
Fullpath = filename:join(rebar_dir:root_dir(State), Filename),
?DEBUG("Loading configuration from ~p", [Fullpath]),
Config = case try_consult(Fullpath) of
[T] -> T;
[] -> []
end,
SubConfigs = [consult_config(State, Entry ++ ".config") ||
Entry <- Config, is_list(Entry)
],

[Config | lists:merge(SubConfigs)].

format_error({bad_term_file, AppFile, Reason}) ->
io_lib:format("Error reading file ~s: ~s", [AppFile, file:format_error(Reason)]).

Expand Down
25 changes: 24 additions & 1 deletion src/rebar_prv_common_test.erl
Original file line number Diff line number Diff line change
Expand Up @@ -116,6 +116,7 @@ prepare_tests(State) ->
%% rebar.config test options
CfgOpts = cfgopts(State),
ProjectApps = rebar_state:project_apps(State),

%% prioritize tests to run first trying any command line specified
%% tests falling back to tests specified in the config file finally
%% running a default set if no other tests are present
Expand Down Expand Up @@ -215,6 +216,14 @@ add_hooks(Opts, State) ->
select_tests(_, _, {error, _} = Error, _) -> Error;
select_tests(_, _, _, {error, _} = Error) -> Error;
select_tests(State, ProjectApps, CmdOpts, CfgOpts) ->
%% set application env if sys_config argument is provided
SysConfigs = sys_config_list(CmdOpts, CfgOpts),
Configs = lists:flatmap(fun(Filename) ->
rebar_file_utils:consult_config(State, Filename)
end, SysConfigs),
[application:load(Application) || Config <- SysConfigs, {Application, _} <- Config],
rebar_utils:reread_config(Configs),

Merged = lists:ukeymerge(1,
lists:ukeysort(1, CmdOpts),
lists:ukeysort(1, CfgOpts)),
Expand All @@ -229,6 +238,17 @@ select_tests(State, ProjectApps, CmdOpts, CfgOpts) ->
end,
discover_tests(State, ProjectApps, Opts).

sys_config_list(CmdOpts, CfgOpts) ->
CmdSysConfigs = split_string(proplists:get_value(sys_config, CmdOpts, "")),
case proplists:get_value(sys_config, CfgOpts, []) of
[H | _]=Configs when is_list(H) ->
Configs ++ CmdSysConfigs;
[] ->
CmdSysConfigs;
Configs ->
[Configs | CmdSysConfigs]
end.

discover_tests(State, ProjectApps, Opts) ->
case {proplists:get_value(suite, Opts), proplists:get_value(dir, Opts)} of
%% no dirs or suites defined, try using `$APP/test` and `$ROOT/test`
Expand Down Expand Up @@ -647,7 +667,8 @@ ct_opts(_State) ->
{verbose, $v, "verbose", boolean, help(verbose)},
{name, undefined, "name", atom, help(name)},
{sname, undefined, "sname", atom, help(sname)},
{setcookie, undefined, "setcookie", atom, help(setcookie)}
{setcookie, undefined, "setcookie", atom, help(setcookie)},
{sys_config, undefined, "sys_config", string, help(sys_config)} %% comma-seperated list
].

help(dir) ->
Expand All @@ -662,6 +683,8 @@ help(label) ->
"Test label";
help(config) ->
"List of config files";
help(sys_config) ->
"List of application config files";
help(allow_user_terms) ->
"Allow user defined config values in config files";
help(logdir) ->
Expand Down
32 changes: 4 additions & 28 deletions src/rebar_prv_shell.erl
Original file line number Diff line number Diff line change
Expand Up @@ -111,7 +111,7 @@ shell(State) ->
%% Hack to fool the init process into thinking we have stopped and the normal
%% node start process can go on. Without it, init:get_status() always return
%% '{starting, started}' instead of '{started, started}'
init ! {'EXIT', self(), normal},
init ! {'EXIT', self(), normal},
gen_server:enter_loop(rebar_agent, [], GenState, {local, rebar_agent}, hibernate).

info() ->
Expand Down Expand Up @@ -332,16 +332,7 @@ reread_config(State) ->
no_config ->
ok;
ConfigList ->
try
[application:set_env(Application, Key, Val)
|| Config <- ConfigList,
{Application, Items} <- Config,
{Key, Val} <- Items]
catch _:_ ->
?ERROR("The configuration file submitted could not be read "
"and will be ignored.", [])
end,
ok
rebar_utils:reread_config(ConfigList)
end.

boot_apps(Apps) ->
Expand Down Expand Up @@ -406,15 +397,15 @@ find_config(State) ->
no_value ->
no_config;
Filename when is_list(Filename) ->
consult_config(State, Filename)
rebar_file_utils:consult_config(State, Filename)
end.

-spec first_value([Fun], State) -> no_value | Value when
Value :: any(),
State :: rebar_state:t(),
Fun :: fun ((State) -> no_value | Value).
first_value([], _) -> no_value;
first_value([Fun | Rest], State) ->
first_value([Fun | Rest], State) ->
case Fun(State) of
no_value ->
first_value(Rest, State);
Expand Down Expand Up @@ -445,18 +436,3 @@ find_config_rebar(State) ->
find_config_relx(State) ->
debug_get_value(sys_config, rebar_state:get(State, relx, []), no_value,
"Found config from relx.").

-spec consult_config(rebar_state:t(), string()) -> [[tuple()]].
consult_config(State, Filename) ->
Fullpath = filename:join(rebar_dir:root_dir(State), Filename),
?DEBUG("Loading configuration from ~p", [Fullpath]),
Config = case rebar_file_utils:try_consult(Fullpath) of
[T] -> T;
[] -> []
end,
SubConfigs = [consult_config(State, Entry ++ ".config") ||
Entry <- Config, is_list(Entry)
],

[Config | lists:merge(SubConfigs)].

14 changes: 13 additions & 1 deletion src/rebar_utils.erl
Original file line number Diff line number Diff line change
Expand Up @@ -69,7 +69,8 @@
check_blacklisted_otp_versions/1,
info_useless/2,
list_dir/1,
user_agent/0]).
user_agent/0,
reread_config/1]).

%% for internal use only
-export([otp_release/0]).
Expand Down Expand Up @@ -412,6 +413,17 @@ user_agent() ->
{ok, Vsn} = application:get_key(rebar, vsn),
?FMT("Rebar/~s (OTP/~s)", [Vsn, otp_release()]).

reread_config(ConfigList) ->
try
[application:set_env(Application, Key, Val)
|| Config <- ConfigList,
{Application, Items} <- Config,
{Key, Val} <- Items]
catch _:_ ->
?ERROR("The configuration file submitted could not be read "
"and will be ignored.", [])
end.

%% ====================================================================
%% Internal functions
%% ====================================================================
Expand Down
48 changes: 45 additions & 3 deletions test/rebar_ct_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -41,6 +41,7 @@
cmd_scale_timetraps/1,
cmd_create_priv_dir/1,
cmd_include_dir/1,
cmd_sys_config/1,
cfg_opts/1,
cfg_arbitrary_opts/1,
cfg_test_spec/1,
Expand All @@ -51,6 +52,7 @@
misspecified_ct_compile_opts/1,
misspecified_ct_first_files/1]).

-include_lib("eunit/include/eunit.hrl").
-include_lib("common_test/include/ct.hrl").

all() -> [{group, basic_app},
Expand Down Expand Up @@ -102,7 +104,8 @@ groups() -> [{basic_app, [], [basic_app_default_dirs,
cmd_multiply_timetraps,
cmd_scale_timetraps,
cmd_create_priv_dir,
cmd_include_dir]},
cmd_include_dir,
cmd_sys_config]},
{cover, [], [cover_compiled]}].

init_per_group(basic_app, Config) ->
Expand Down Expand Up @@ -1020,7 +1023,41 @@ cmd_include_dir(Config) ->
CompileOpts = proplists:get_value(options, Info),
true = lists:member({i, "foo/bar/baz"}, CompileOpts),
true = lists:member({i, "qux"}, CompileOpts).


cmd_sys_config(Config) ->
State = ?config(result, Config),
AppDir = ?config(apps, Config),
Name = ?config(name, Config),
AppName = list_to_atom(Name),

{ok, _} = rebar_prv_common_test:prepare_tests(State),
?assertEqual(undefined, application:get_env(AppName, key)),

CfgFile = filename:join([AppDir, "config", "cfg_sys.config"]),
ok = filelib:ensure_dir(CfgFile),
ok = file:write_file(CfgFile, cfg_sys_config_file(AppName)),
RebarConfig = [{ct_opts, [{sys_config, CfgFile}]}],
{ok, State1} = rebar_test_utils:run_and_check(Config, RebarConfig, ["as", "test", "lock"], return),

{ok, _} = rebar_prv_common_test:prepare_tests(State1),
?assertEqual({ok, cfg_value}, application:get_env(AppName, key)),

Providers = rebar_state:providers(State1),
Namespace = rebar_state:namespace(State1),
CommandProvider = providers:get_provider(ct, Providers, Namespace),
GetOptSpec = providers:opts(CommandProvider),

CmdFile = filename:join([AppDir, "config", "cmd_sys.config"]),
ok = filelib:ensure_dir(CmdFile),
ok = file:write_file(CmdFile, cmd_sys_config_file(AppName)),
{ok, GetOptResult} = getopt:parse(GetOptSpec, ["--sys_config="++CmdFile]),
State2 = rebar_state:command_parsed_args(State1, GetOptResult),

{ok, _} = rebar_prv_common_test:prepare_tests(State2),

?assertEqual({ok ,cmd_value}, application:get_env(AppName, key)).


cfg_opts(Config) ->
C = rebar_test_utils:init_rebar_state(Config, "ct_cfg_opts_"),

Expand Down Expand Up @@ -1181,10 +1218,15 @@ misspecified_ct_first_files(Config) ->

{badconfig, {"Value `~p' of option `~p' must be a list", {some_file, ct_first_files}}} = Error.


%% helper for generating test data
test_suite(Name) ->
io_lib:format("-module(~ts_SUITE).\n"
"-compile(export_all).\n"
"all() -> [some_test].\n"
"some_test(_) -> ok.\n", [Name]).

cmd_sys_config_file(AppName) ->
io_lib:format("[{~s, [{key, cmd_value}]}].", [AppName]).

cfg_sys_config_file(AppName) ->
io_lib:format("[{~s, [{key, cfg_value}]}].", [AppName]).

0 comments on commit 854abc1

Please sign in to comment.