Skip to content

Commit

Permalink
only print skip warning if version is different (#1886)
Browse files Browse the repository at this point in the history
  • Loading branch information
tsloughter authored Sep 17, 2018
1 parent cd858a4 commit 43769ae
Show file tree
Hide file tree
Showing 2 changed files with 31 additions and 8 deletions.
24 changes: 18 additions & 6 deletions src/rebar_prv_install_deps.erl
Original file line number Diff line number Diff line change
Expand Up @@ -259,9 +259,21 @@ update_seen_dep(AppInfo, _Profile, _Level, Deps, Apps, State, Upgrade, Seen, Loc
%% If seen from lock file or user requested an upgrade
%% don't print warning about skipping
case lists:keymember(Name, 1, Locks) of
false when Upgrade -> ok;
false when not Upgrade -> warn_skip_deps(AppInfo, State);
true -> ok
false when Upgrade ->
ok;
false when not Upgrade ->
{ok, SeenApp} = rebar_app_utils:find(Name, Apps),
Source = rebar_app_info:source(AppInfo),
case rebar_app_info:source(SeenApp) of
Source ->
%% dep is the same version and checksum as the one we already saw.
%% meaning there is no conflict, so don't warn about it.
skip;
_ ->
warn_skip_deps(Name, Source, State)
end;
true ->
ok
end,
{Deps, Apps, State, Seen}.

Expand Down Expand Up @@ -395,11 +407,11 @@ maybe_upgrade(AppInfo, _AppDir, Upgrade, State) ->
AppInfo
end.

warn_skip_deps(AppInfo, State) ->
warn_skip_deps(Name, Source, State) ->
Msg = "Skipping ~ts (from ~p) as an app of the same name "
"has already been fetched",
Args = [rebar_app_info:name(AppInfo),
rebar_resource_v2:format_source(rebar_app_info:source(AppInfo))],
Args = [Name,
rebar_resource_v2:format_source(Source)],
case rebar_state:get(State, deps_error_on_conflict, false) of
false ->
case rebar_state:get(State, deps_warning_on_conflict, true) of
Expand Down
15 changes: 13 additions & 2 deletions test/rebar_install_deps_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -17,7 +17,7 @@ groups() ->
{mixed, [], [
m_flat1, m_flat2, m_circular1, m_circular2,
m_pick_source1, m_pick_source2, m_pick_source3,
m_pick_source4, m_pick_source5, m_source_to_pkg,
m_pick_source4, m_pick_source5, m_pick_source6, m_source_to_pkg,
m_pkg_level1, m_pkg_level2, m_pkg_level3, m_pkg_level3_alpha_order
]}
].
Expand Down Expand Up @@ -93,6 +93,8 @@ format_expected_mdeps(Deps) ->
[{dep, N}, {lock, src, N, "0.0.0"}]
end || Dep <- Deps]).

format_expected_mixed_warnings(none) ->
none;
format_expected_mixed_warnings(Warnings) ->
[case W of
{N, Vsn} when hd(N) >= $a, hd(N) =< $z -> {pkg, rebar_string:uppercase(N), Vsn};
Expand Down Expand Up @@ -225,6 +227,11 @@ mdeps(m_pick_source5) ->
{"C", [{"D", "1.0.0", []}]}],
[{"D", "1.0.0"}],
{ok, ["B", "C", {"d", "1.0.0"}]}};
mdeps(m_pick_source6) ->
{[{"B", [{"D", "1.0.0", []}]},
{"C", [{"D", "1.0.0", []}]}],
none,
{ok, ["B", "C", {"D", "1.0.0"}]}};
mdeps(m_source_to_pkg) ->
{[{"B", [{"c",[{"d", []}]}]}],
[],
Expand Down Expand Up @@ -436,6 +443,7 @@ m_pick_source2(Config) -> run(Config).
m_pick_source3(Config) -> run(Config).
m_pick_source4(Config) -> run(Config).
m_pick_source5(Config) -> run(Config).
m_pick_source6(Config) -> run(Config).
m_source_to_pkg(Config) -> run(Config).
m_pkg_level1(Config) -> run(Config).
m_pkg_level2(Config) -> run(Config).
Expand Down Expand Up @@ -466,7 +474,10 @@ check_warnings(Warns, [{Type, Name, Vsn} | Rest], mixed) ->
check_warnings(Warns, [{Name, Vsn} | Rest], Type) ->
ct:pal("Checking for warning ~p in ~p", [{Name,Vsn},Warns]),
?assert(in_warnings(Type, Warns, Name, Vsn)),
check_warnings(Warns, Rest, Type).
check_warnings(Warns, Rest, Type);
check_warnings(Warns, none, _Type) ->
ct:pal("Checking that there were no warnings", []),
?assert(Warns == []).

in_warnings(git, Warns, NameRaw, VsnRaw) ->
Name = iolist_to_binary(NameRaw),
Expand Down

0 comments on commit 43769ae

Please sign in to comment.