Skip to content

Commit

Permalink
Merge pull request #2335 from pablocostass/2334_improve_checkout_deps…
Browse files Browse the repository at this point in the history
…_warnings

Improve warnings about checkout dependencies when locking and upgrading
  • Loading branch information
tsloughter authored Aug 28, 2020
2 parents 7ccbc0b + aecbdcd commit 68dc4d2
Show file tree
Hide file tree
Showing 4 changed files with 36 additions and 11 deletions.
10 changes: 9 additions & 1 deletion src/rebar_prv_lock.erl
Original file line number Diff line number Diff line change
Expand Up @@ -38,9 +38,13 @@ do(State) ->
rebar_config:maybe_write_lock_file(filename:join(Dir, ?LOCK_FILE), Locks, OldLocks),
State1 = rebar_state:set(State, {locks, default}, Locks),

OldLockNames = [element(1,L) || L <- OldLocks],
Checkouts = [rebar_app_info:name(Dep) || Dep <- rebar_state:all_checkout_deps(State)],
%% Remove the checkout dependencies from the old lock info
%% so that they do not appear in the rebar_utils:info_useless/1 warning.
OldLockNames = [element(1,L) || L <- OldLocks] -- Checkouts,
NewLockNames = [element(1,L) || L <- Locks],
rebar_utils:info_useless(OldLockNames, NewLockNames),
info_checkout_deps(Checkouts),

{ok, State1};
_ ->
Expand All @@ -60,3 +64,7 @@ build_locks(State) ->
rebar_fetch:lock_source(Dep, State),
rebar_app_info:dep_level(Dep)}
end || Dep <- AllDeps, not(rebar_app_info:is_checkout(Dep))].

info_checkout_deps(Checkouts) ->
[?INFO("App ~ts is a checkout dependency and cannot be locked.", [CheckoutDep])
|| CheckoutDep <- Checkouts].
29 changes: 19 additions & 10 deletions src/rebar_prv_upgrade.erl
Original file line number Diff line number Diff line change
Expand Up @@ -86,7 +86,8 @@ do_(State) ->
DepsDict = deps_dict(rebar_state:all_deps(State)),
AltDeps = find_non_default_deps(Deps, State),
FilteredNames = cull_default_names_if_profiles(Names, Deps, State),
case prepare_locks(FilteredNames, Deps, Locks, [], DepsDict, AltDeps) of
Checkouts = [rebar_app_info:name(Dep) || Dep <- rebar_state:all_checkout_deps(State)],
case prepare_locks(FilteredNames, Deps, Locks, [], DepsDict, AltDeps, Checkouts) of
{error, Reason} ->
{error, Reason};
{Locks0, Unlocks0} ->
Expand Down Expand Up @@ -123,6 +124,9 @@ format_error({transitive_dependency, Name}) ->
io_lib:format("Dependency ~ts is transitive and cannot be safely upgraded. "
"Promote it to your top-level rebar.config file to upgrade it.",
[Name]);
format_error({checkout_dependency, Name}) ->
io_lib:format("Dependency ~ts is a checkout dependency under _checkouts/ and checkouts cannot be upgraded.",
[Name]);
format_error(Reason) ->
io_lib:format("~p", [Reason]).

Expand Down Expand Up @@ -190,20 +194,20 @@ cull_default_names_if_profiles(Names, Deps, State) ->
end, Names)
end.

prepare_locks([], _, Locks, Unlocks, _Dict, _AltDeps) ->
prepare_locks([], _, Locks, Unlocks, _Dict, _AltDeps, _Checkouts) ->
{Locks, Unlocks};
prepare_locks([Name|Names], Deps, Locks, Unlocks, Dict, AltDeps) ->
prepare_locks([Name|Names], Deps, Locks, Unlocks, Dict, AltDeps, Checkouts) ->
AtomName = binary_to_atom(Name, utf8),
case lists:keyfind(Name, 1, Locks) of
{_, _, 0} = Lock ->
case rebar_utils:tup_find(AtomName, Deps) of
false ->
?WARN("Dependency ~ts has been removed and will not be upgraded", [Name]),
prepare_locks(Names, Deps, Locks, Unlocks, Dict, AltDeps);
prepare_locks(Names, Deps, Locks, Unlocks, Dict, AltDeps, Checkouts);
Dep ->
{Source, NewLocks, NewUnlocks} = prepare_lock(Dep, Lock, Locks, Dict),
prepare_locks(Names, Deps, NewLocks,
[{Name, Source, 0} | NewUnlocks ++ Unlocks], Dict, AltDeps)
[{Name, Source, 0} | NewUnlocks ++ Unlocks], Dict, AltDeps, Checkouts)
end;
{_, _, Level} = Lock when Level > 0 ->
case rebar_utils:tup_find(AtomName, Deps) of
Expand All @@ -212,14 +216,19 @@ prepare_locks([Name|Names], Deps, Locks, Unlocks, Dict, AltDeps) ->
Dep -> % Dep has been promoted
{Source, NewLocks, NewUnlocks} = prepare_lock(Dep, Lock, Locks, Dict),
prepare_locks(Names, Deps, NewLocks,
[{Name, Source, 0} | NewUnlocks ++ Unlocks], Dict, AltDeps)
[{Name, Source, 0} | NewUnlocks ++ Unlocks], Dict, AltDeps, Checkouts)
end;
false ->
case rebar_utils:tup_find(AtomName, AltDeps) of
case lists:member(atom_to_binary(AtomName, utf8), Checkouts) of
true ->
?PRV_ERROR({checkout_dependency, Name});
false ->
?PRV_ERROR({unknown_dependency, Name});
_ -> % non-default profile dependency found, pass through
prepare_locks(Names, Deps, Locks, Unlocks, Dict, AltDeps)
case rebar_utils:tup_find(AtomName, AltDeps) of
false ->
?PRV_ERROR({unknown_dependency, Name});
_ -> % non-default profile dependency found, pass through
prepare_locks(Names, Deps, Locks, Unlocks, Dict, AltDeps, Checkouts)
end
end
end.

Expand Down
4 changes: 4 additions & 0 deletions src/rebar_state.erl
Original file line number Diff line number Diff line change
Expand Up @@ -32,6 +32,7 @@
deps_to_build/1, deps_to_build/2,
all_plugin_deps/1, all_plugin_deps/2, update_all_plugin_deps/2,
all_deps/1, all_deps/2, update_all_deps/2, merge_all_deps/2,
all_checkout_deps/1,
namespace/1, namespace/2,

deps_names/1,
Expand Down Expand Up @@ -342,6 +343,9 @@ all_deps(#state_t{all_deps=Apps}) ->
all_deps(State=#state_t{}, NewApps) ->
State#state_t{all_deps=NewApps}.

all_checkout_deps(#state_t{all_deps=Apps}) ->
[App || App <- Apps, rebar_app_info:is_checkout(App)].

all_plugin_deps(#state_t{all_plugin_deps=Apps}) ->
Apps.

Expand Down
4 changes: 4 additions & 0 deletions test/rebar_compile_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -461,6 +461,10 @@ paths_checkout_deps(Config) ->

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

[AppName2] = rebar_state:all_checkout_deps(State),
Name2Bin = binary:list_to_bin(Name2),
Name2Bin = rebar_app_info:name(AppName2),

code:add_paths(rebar_state:code_paths(State, all_deps)),
ok = application:load(list_to_atom(Name2)),
Loaded = application:loaded_applications(),
Expand Down

0 comments on commit 68dc4d2

Please sign in to comment.