Skip to content

Commit

Permalink
Merge pull request #1398 from tburghart/rebar3_issue_1397
Browse files Browse the repository at this point in the history
Correct precedence of compile options merged from profiles.
  • Loading branch information
ferd authored Dec 5, 2016
2 parents 5f0658d + 1b422b9 commit 41d4002
Show file tree
Hide file tree
Showing 2 changed files with 162 additions and 35 deletions.
93 changes: 60 additions & 33 deletions src/rebar_opts.erl
Original file line number Diff line number Diff line change
Expand Up @@ -101,42 +101,69 @@ merge_opts(Profile, NewOpts, OldOpts) ->
end.

merge_opts(NewOpts, OldOpts) ->
dict:merge(fun(deps, _NewValue, OldValue) ->
OldValue;
({deps, _}, NewValue, _OldValue) ->
NewValue;
(plugins, NewValue, _OldValue) ->
NewValue;
({plugins, _}, NewValue, _OldValue) ->
NewValue;
(profiles, NewValue, OldValue) ->
dict:to_list(merge_opts(dict:from_list(NewValue), dict:from_list(OldValue)));
(mib_first_files, Value, Value) ->
Value;
(mib_first_files, NewValue, OldValue) ->
OldValue ++ NewValue;
(relx, NewValue, OldValue) ->
rebar_utils:tup_umerge(OldValue, NewValue);
(_Key, NewValue, OldValue) when is_list(NewValue) ->
case io_lib:printable_list(NewValue) of
true when NewValue =:= [] ->
case io_lib:printable_list(OldValue) of
true ->
NewValue;
false ->
OldValue
end;
true ->
NewValue;
false ->
rebar_utils:tup_umerge(NewValue, OldValue)
end;
(_Key, NewValue, _OldValue) ->
NewValue
end, NewOpts, OldOpts).
dict:merge(fun merge_opt/3, NewOpts, OldOpts).

%% Internal functions

%%
%% Function for dict:merge/3 (in merge_opts/2) to merge options by priority.
%%
merge_opt(deps, _NewValue, OldValue) ->
OldValue;
merge_opt({deps, _}, NewValue, _OldValue) ->
NewValue;
merge_opt(plugins, NewValue, _OldValue) ->
NewValue;
merge_opt({plugins, _}, NewValue, _OldValue) ->
NewValue;
merge_opt(profiles, NewValue, OldValue) ->
dict:to_list(merge_opts(dict:from_list(NewValue), dict:from_list(OldValue)));
merge_opt(mib_first_files, Value, Value) ->
Value;
merge_opt(mib_first_files, NewValue, OldValue) ->
OldValue ++ NewValue;
merge_opt(relx, NewValue, OldValue) ->
rebar_utils:tup_umerge(OldValue, NewValue);
merge_opt(Key, NewValue, OldValue)
when Key == erl_opts; Key == eunit_compile_opts; Key == ct_compile_opts ->
merge_erl_opts(lists:reverse(OldValue), NewValue);
merge_opt(_Key, NewValue, OldValue) when is_list(NewValue) ->
case io_lib:printable_list(NewValue) of
true when NewValue =:= [] ->
case io_lib:printable_list(OldValue) of
true ->
NewValue;
false ->
OldValue
end;
true ->
NewValue;
false ->
rebar_utils:tup_umerge(NewValue, OldValue)
end;
merge_opt(_Key, NewValue, _OldValue) ->
NewValue.

%%
%% Merge Erlang compiler options such that the result
%% a) Doesn't contain duplicates.
%% b) Resulting options are ordered by increasing precedence as expected by
%% the compiler.
%% The first parameter is the lower precedence options, in reverse order, to
%% be merged with the higher-precedence options in the second parameter.
%%
merge_erl_opts([Opt | Opts], []) ->
merge_erl_opts(Opts, [Opt]);
merge_erl_opts([Opt | Opts], Merged) ->
case lists:member(Opt, Merged) of
true ->
merge_erl_opts(Opts, Merged);
_ ->
merge_erl_opts(Opts, [Opt | Merged])
end;
merge_erl_opts([], Merged) ->
Merged.

%%
%% Filter a list of erl_opts platform_define options such that only
%% those which match the provided architecture regex are returned.
Expand Down
104 changes: 102 additions & 2 deletions test/rebar_profiles_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -20,7 +20,12 @@
test_profile_applied_at_completion/1,
test_profile_applied_before_compile/1,
test_profile_applied_before_eunit/1,
test_profile_applied_to_apps/1]).
test_profile_applied_to_apps/1,
test_profile_erl_opts_order_1/1,
test_profile_erl_opts_order_2/1,
test_profile_erl_opts_order_3/1,
test_profile_erl_opts_order_4/1,
test_profile_erl_opts_order_5/1]).

-include_lib("common_test/include/ct.hrl").
-include_lib("eunit/include/eunit.hrl").
Expand All @@ -36,7 +41,12 @@ all() ->
test_profile_applied_at_completion,
test_profile_applied_before_compile,
test_profile_applied_before_eunit,
test_profile_applied_to_apps].
test_profile_applied_to_apps,
test_profile_erl_opts_order_1,
test_profile_erl_opts_order_2,
test_profile_erl_opts_order_3,
test_profile_erl_opts_order_4,
test_profile_erl_opts_order_5].

init_per_suite(Config) ->
application:start(meck),
Expand Down Expand Up @@ -432,3 +442,93 @@ test_profile_applied_to_apps(Config) ->
ErlOpts = dict:fetch(erl_opts, Opts),
true = lists:member({d, 'TEST'}, ErlOpts)
end, Apps).

test_profile_erl_opts_order_1(Config) ->
Opts = get_compiled_profile_erl_opts([default], Config),
Opt = last_erl_opt(Opts, [warn_export_all, nowarn_export_all], undefined),
undefined = Opt.

test_profile_erl_opts_order_2(Config) ->
Opts = get_compiled_profile_erl_opts([strict], Config),
Opt = last_erl_opt(Opts, [warn_export_all, nowarn_export_all], undefined),
warn_export_all = Opt.

test_profile_erl_opts_order_3(Config) ->
Opts = get_compiled_profile_erl_opts([loose], Config),
Opt = last_erl_opt(Opts, [warn_export_all, nowarn_export_all], undefined),
nowarn_export_all = Opt.

test_profile_erl_opts_order_4(Config) ->
Opts = get_compiled_profile_erl_opts([strict, loose], Config),
Opt = last_erl_opt(Opts, [warn_export_all, nowarn_export_all], undefined),
nowarn_export_all = Opt.

test_profile_erl_opts_order_5(Config) ->
Opts = get_compiled_profile_erl_opts([loose, strict], Config),
Opt = last_erl_opt(Opts, [warn_export_all, nowarn_export_all], undefined),
warn_export_all = Opt.

get_compiled_profile_erl_opts(Profiles, Config) ->
AppDir = ?config(apps, Config),
PStrs = [atom_to_list(P) || P <- Profiles],

Name = rebar_test_utils:create_random_name(
lists:flatten(["erl_opts_order_" | [[S, $_] || S <- PStrs]])),
Vsn = rebar_test_utils:create_random_vsn(),
rebar_test_utils:create_app(AppDir, Name, Vsn, [kernel, stdlib]),

RebarConfig = [
{erl_opts, [warnings_as_errors, {d, profile_default}]},
{profiles, [
{strict, [{erl_opts, [warn_export_all, {d, profile_strict}]}]},
{loose, [{erl_opts, [nowarn_export_all, {d, profile_loose}]}]} ]}],
rebar_test_utils:create_config(AppDir, RebarConfig),

Command = case Profiles of
[] ->
["compile"];
[default] ->
["compile"];
_ ->
["as", string:join(PStrs, ","), "compile"]
end,
{ok, State} = rebar_test_utils:run_and_check(
Config, RebarConfig, Command, {ok, [{app, Name}]}),
code:add_paths(rebar_state:code_paths(State, all_deps)),
Mod = list_to_atom(Name),
proplists:get_value(options, Mod:module_info(compile), []).

% macro definitions get special handling
last_erl_opt([{d, Macro} = Opt | Opts], Targets, Last) ->
case lists:any(erl_opt_macro_match_fun(Macro), Targets) of
true ->
last_erl_opt(Opts, Targets, Opt);
_ ->
last_erl_opt(Opts, Targets, Last)
end;
last_erl_opt([{d, Macro, _} = Opt | Opts], Targets, Last) ->
case lists:any(erl_opt_macro_match_fun(Macro), Targets) of
true ->
last_erl_opt(Opts, Targets, Opt);
_ ->
last_erl_opt(Opts, Targets, Last)
end;
last_erl_opt([Opt | Opts], Targets, Last) ->
case lists:member(Opt, Targets) of
true ->
last_erl_opt(Opts, Targets, Opt);
_ ->
last_erl_opt(Opts, Targets, Last)
end;
last_erl_opt([], _, Last) ->
Last.

erl_opt_macro_match_fun(Macro) ->
fun({d, M}) ->
M == Macro;
({d, M, _}) ->
M == Macro;
(_) ->
false
end.

0 comments on commit 41d4002

Please sign in to comment.