Skip to content

Commit c9fa733

Browse files
committed
Improve warnings about checkout dependencies when locking and upgrading
1 parent 7ccbc0b commit c9fa733

File tree

2 files changed

+29
-11
lines changed

2 files changed

+29
-11
lines changed

src/rebar_prv_lock.erl

Lines changed: 10 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -38,9 +38,14 @@ do(State) ->
3838
rebar_config:maybe_write_lock_file(filename:join(Dir, ?LOCK_FILE), Locks, OldLocks),
3939
State1 = rebar_state:set(State, {locks, default}, Locks),
4040

41-
OldLockNames = [element(1,L) || L <- OldLocks],
41+
Checkouts = [rebar_app_info:name(Dep)
42+
|| Dep <- rebar_state:all_deps(State), rebar_app_info:is_checkout(Dep)],
43+
%% Remove the checkout dependencies from the old lock info
44+
%% so that they do not appear in the rebar_utils:info_useless/1 warning.
45+
OldLockNames = [element(1,L) || L <- OldLocks] -- Checkouts,
4246
NewLockNames = [element(1,L) || L <- Locks],
4347
rebar_utils:info_useless(OldLockNames, NewLockNames),
48+
info_checkout_deps(Checkouts),
4449

4550
{ok, State1};
4651
_ ->
@@ -60,3 +65,7 @@ build_locks(State) ->
6065
rebar_fetch:lock_source(Dep, State),
6166
rebar_app_info:dep_level(Dep)}
6267
end || Dep <- AllDeps, not(rebar_app_info:is_checkout(Dep))].
68+
69+
info_checkout_deps(Checkouts) ->
70+
[?INFO("App ~ts is a checkout dependency and cannot be locked.", [CheckoutDep])
71+
|| CheckoutDep <- Checkouts].

src/rebar_prv_upgrade.erl

Lines changed: 19 additions & 10 deletions
Original file line numberDiff line numberDiff line change
@@ -86,7 +86,9 @@ do_(State) ->
8686
DepsDict = deps_dict(rebar_state:all_deps(State)),
8787
AltDeps = find_non_default_deps(Deps, State),
8888
FilteredNames = cull_default_names_if_profiles(Names, Deps, State),
89-
case prepare_locks(FilteredNames, Deps, Locks, [], DepsDict, AltDeps) of
89+
Checkouts = [rebar_app_info:name(Dep)
90+
|| Dep <- rebar_state:all_deps(State), rebar_app_info:is_checkout(Dep)],
91+
case prepare_locks(FilteredNames, Deps, Locks, [], DepsDict, AltDeps, Checkouts) of
9092
{error, Reason} ->
9193
{error, Reason};
9294
{Locks0, Unlocks0} ->
@@ -123,6 +125,8 @@ format_error({transitive_dependency, Name}) ->
123125
io_lib:format("Dependency ~ts is transitive and cannot be safely upgraded. "
124126
"Promote it to your top-level rebar.config file to upgrade it.",
125127
[Name]);
128+
format_error({checkout_dependency, Name}) ->
129+
io_lib:format("Dependency ~ts is a checkout dependency and cannot be upgraded.", [Name]);
126130
format_error(Reason) ->
127131
io_lib:format("~p", [Reason]).
128132

@@ -190,20 +194,20 @@ cull_default_names_if_profiles(Names, Deps, State) ->
190194
end, Names)
191195
end.
192196

193-
prepare_locks([], _, Locks, Unlocks, _Dict, _AltDeps) ->
197+
prepare_locks([], _, Locks, Unlocks, _Dict, _AltDeps, _Checkouts) ->
194198
{Locks, Unlocks};
195-
prepare_locks([Name|Names], Deps, Locks, Unlocks, Dict, AltDeps) ->
199+
prepare_locks([Name|Names], Deps, Locks, Unlocks, Dict, AltDeps, Checkouts) ->
196200
AtomName = binary_to_atom(Name, utf8),
197201
case lists:keyfind(Name, 1, Locks) of
198202
{_, _, 0} = Lock ->
199203
case rebar_utils:tup_find(AtomName, Deps) of
200204
false ->
201205
?WARN("Dependency ~ts has been removed and will not be upgraded", [Name]),
202-
prepare_locks(Names, Deps, Locks, Unlocks, Dict, AltDeps);
206+
prepare_locks(Names, Deps, Locks, Unlocks, Dict, AltDeps, Checkouts);
203207
Dep ->
204208
{Source, NewLocks, NewUnlocks} = prepare_lock(Dep, Lock, Locks, Dict),
205209
prepare_locks(Names, Deps, NewLocks,
206-
[{Name, Source, 0} | NewUnlocks ++ Unlocks], Dict, AltDeps)
210+
[{Name, Source, 0} | NewUnlocks ++ Unlocks], Dict, AltDeps, Checkouts)
207211
end;
208212
{_, _, Level} = Lock when Level > 0 ->
209213
case rebar_utils:tup_find(AtomName, Deps) of
@@ -212,14 +216,19 @@ prepare_locks([Name|Names], Deps, Locks, Unlocks, Dict, AltDeps) ->
212216
Dep -> % Dep has been promoted
213217
{Source, NewLocks, NewUnlocks} = prepare_lock(Dep, Lock, Locks, Dict),
214218
prepare_locks(Names, Deps, NewLocks,
215-
[{Name, Source, 0} | NewUnlocks ++ Unlocks], Dict, AltDeps)
219+
[{Name, Source, 0} | NewUnlocks ++ Unlocks], Dict, AltDeps, Checkouts)
216220
end;
217221
false ->
218-
case rebar_utils:tup_find(AtomName, AltDeps) of
222+
case lists:member(atom_to_binary(AtomName, utf8), Checkouts) of
223+
true ->
224+
?PRV_ERROR({checkout_dependency, Name});
219225
false ->
220-
?PRV_ERROR({unknown_dependency, Name});
221-
_ -> % non-default profile dependency found, pass through
222-
prepare_locks(Names, Deps, Locks, Unlocks, Dict, AltDeps)
226+
case rebar_utils:tup_find(AtomName, AltDeps) of
227+
false ->
228+
?PRV_ERROR({unknown_dependency, Name});
229+
_ -> % non-default profile dependency found, pass through
230+
prepare_locks(Names, Deps, Locks, Unlocks, Dict, AltDeps, Checkouts)
231+
end
223232
end
224233
end.
225234

0 commit comments

Comments
 (0)