Skip to content

Commit

Permalink
Merge pull request #1606 from ferd/recurive-profile-merge
Browse files Browse the repository at this point in the history
Fix recursive profile merging, particularly for umbrella apps
  • Loading branch information
ferd authored Aug 13, 2017
2 parents d906476 + bed661a commit 9c4e40d
Show file tree
Hide file tree
Showing 3 changed files with 63 additions and 4 deletions.
4 changes: 2 additions & 2 deletions src/rebar3.erl
Original file line number Diff line number Diff line change
Expand Up @@ -396,8 +396,8 @@ safe_define_test_macro(Opts) ->
%% defining a compile macro twice results in an exception so
%% make sure 'TEST' is only defined once
case test_defined(Opts) of
true -> [];
false -> [{d, 'TEST'}]
true -> Opts;
false -> [{d, 'TEST'}|Opts]
end.

test_defined([{d, 'TEST'}|_]) -> true;
Expand Down
30 changes: 29 additions & 1 deletion src/rebar_opts.erl
Original file line number Diff line number Diff line change
Expand Up @@ -117,7 +117,12 @@ merge_opt(plugins, NewValue, _OldValue) ->
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 up sparse pairs of {Profile, Opts} into a joined up
%% {Profile, OptsNew, OptsOld} list.
ToMerge = normalise_profile_pairs(lists:sort(NewValue),
lists:sort(OldValue)),
[{K,dict:to_list(merge_opts(dict:from_list(New), dict:from_list(Old)))}
|| {K,New,Old} <- ToMerge];
merge_opt(erl_first_files, Value, Value) ->
Value;
merge_opt(erl_first_files, NewValue, OldValue) ->
Expand Down Expand Up @@ -190,3 +195,26 @@ filter_defines([{platform_define, ArchRegex, Key, Value} | Rest], Acc) ->
end;
filter_defines([Opt | Rest], Acc) ->
filter_defines(Rest, [Opt | Acc]).

%% @private takes two lists of profile tuples and merges them
%% into one list of 3-tuples containing the values of either
%% profiles.
%% Any missing profile in one of the keys is replaced by an
%% empty one.
-spec normalise_profile_pairs([Profile], [Profile]) -> [Pair] when
Profile :: {Name, Opts},
Pair :: {Name, Opts, Opts},
Name :: atom(),
Opts :: [term()].
normalise_profile_pairs([], []) ->
[];
normalise_profile_pairs([{P,V}|Ps], []) ->
[{P,V,[]} | normalise_profile_pairs(Ps, [])];
normalise_profile_pairs([], [{P,V}|Ps]) ->
[{P,[],V} | normalise_profile_pairs([], Ps)];
normalise_profile_pairs([{P,VA}|PAs], [{P,VB}|PBs]) ->
[{P,VA,VB} | normalise_profile_pairs(PAs, PBs)];
normalise_profile_pairs([{PA,VA}|PAs], [{PB,VB}|PBs]) when PA < PB ->
[{PA,VA,[]} | normalise_profile_pairs(PAs, [{PB, VB}|PBs])];
normalise_profile_pairs([{PA,VA}|PAs], [{PB,VB}|PBs]) when PA > PB ->
[{PB,[],VB} | normalise_profile_pairs([{PA,VA}|PAs], PBs)].
33 changes: 32 additions & 1 deletion test/rebar_profiles_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -7,6 +7,7 @@
all/0,
profile_new_key/1,
profile_merge_keys/1,
profile_merge_umbrella_keys/1,
explicit_profile_deduplicate_deps/1,
implicit_profile_deduplicate_deps/1,
all_deps_code_paths/1,
Expand All @@ -33,7 +34,8 @@
-include_lib("kernel/include/file.hrl").

all() ->
[profile_new_key, profile_merge_keys, all_deps_code_paths, profile_merges,
[profile_new_key, profile_merge_keys, profile_merge_umbrella_keys,
all_deps_code_paths, profile_merges,
explicit_profile_deduplicate_deps, implicit_profile_deduplicate_deps,
same_profile_deduplication, stack_deduplication,
add_to_profile, add_to_existing_profile,
Expand Down Expand Up @@ -118,6 +120,35 @@ profile_merge_keys(Config) ->
,{dep, "a", "1.0.0"}
,{dep, "b", "2.0.0"}]}).

profile_merge_umbrella_keys(Config) ->
AppDir = ?config(apps, Config),
ct:pal("Path: ~s", [AppDir]),
Name = rebar_test_utils:create_random_name("profile_merge_umbrella_keys"),
Vsn = rebar_test_utils:create_random_vsn(),
SubAppDir = filename:join([AppDir, "apps", Name]),

RebarConfig = [{vals, [{a,1},{b,1}]},
{profiles,
[{ct,
[{vals, [{a,1},{b,2}]}]}]}],

SubRebarConfig = [{vals, []},
{profiles, [{ct, [{vals, [{c,1}]}]}]}],

rebar_test_utils:create_app(SubAppDir, Name, Vsn, [kernel, stdlib]),
rebar_test_utils:create_config(SubAppDir, SubRebarConfig),
{ok, RebarConfigRead} = file:consult(rebar_test_utils:create_config(AppDir, RebarConfig)),

{ok, State} = rebar_test_utils:run_and_check(
Config, RebarConfigRead, ["as", "ct", "compile"], return
),

[ProjectApp] = rebar_state:project_apps(State),
?assertEqual(Name, binary_to_list(rebar_app_info:name(ProjectApp))),
Opts = rebar_app_info:opts(ProjectApp),
?assertEqual([{a,1},{b,2},{b,1},{c,1}], dict:fetch(vals, Opts)),
ok.

explicit_profile_deduplicate_deps(Config) ->
AppDir = ?config(apps, Config),

Expand Down

0 comments on commit 9c4e40d

Please sign in to comment.