Skip to content

Commit f6422f9

Browse files
authored
Merge branch 'master' into relx-upgrade-xref
2 parents 53f9a41 + 68dc4d2 commit f6422f9

File tree

4 files changed

+36
-12
lines changed

4 files changed

+36
-12
lines changed

src/rebar_prv_lock.erl

Lines changed: 9 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -38,11 +38,15 @@ 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) || Dep <- rebar_state:all_checkout_deps(State)],
42+
%% Remove the checkout dependencies from the old lock info
43+
%% so that they do not appear in the rebar_utils:info_useless/1 warning.
44+
OldLockNames = [element(1,L) || L <- OldLocks] -- Checkouts,
4245
NewLockNames = [element(1,L) || L <- Locks],
4346

4447
%% TODO: don't output this message if the dep is now a checkout
4548
rebar_utils:info_useless(OldLockNames, NewLockNames),
49+
info_checkout_deps(Checkouts),
4650

4751
{ok, State1};
4852
_ ->
@@ -62,3 +66,7 @@ build_locks(State) ->
6266
rebar_fetch:lock_source(Dep, State),
6367
rebar_app_info:dep_level(Dep)}
6468
end || Dep <- AllDeps, not(rebar_app_info:is_checkout(Dep))].
69+
70+
info_checkout_deps(Checkouts) ->
71+
[?INFO("App ~ts is a checkout dependency and cannot be locked.", [CheckoutDep])
72+
|| CheckoutDep <- Checkouts].

src/rebar_prv_upgrade.erl

Lines changed: 19 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -86,7 +86,8 @@ 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) || Dep <- rebar_state:all_checkout_deps(State)],
90+
case prepare_locks(FilteredNames, Deps, Locks, [], DepsDict, AltDeps, Checkouts) of
9091
{error, Reason} ->
9192
{error, Reason};
9293
{Locks0, Unlocks0} ->
@@ -123,6 +124,9 @@ format_error({transitive_dependency, Name}) ->
123124
io_lib:format("Dependency ~ts is transitive and cannot be safely upgraded. "
124125
"Promote it to your top-level rebar.config file to upgrade it.",
125126
[Name]);
127+
format_error({checkout_dependency, Name}) ->
128+
io_lib:format("Dependency ~ts is a checkout dependency under _checkouts/ and checkouts cannot be upgraded.",
129+
[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,15 +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-
%% TODO: output a different error if the app is a checkout
221-
?PRV_ERROR({unknown_dependency, Name});
222-
_ -> % non-default profile dependency found, pass through
223-
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
224232
end
225233
end.
226234

src/rebar_state.erl

Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -32,6 +32,7 @@
3232
deps_to_build/1, deps_to_build/2,
3333
all_plugin_deps/1, all_plugin_deps/2, update_all_plugin_deps/2,
3434
all_deps/1, all_deps/2, update_all_deps/2, merge_all_deps/2,
35+
all_checkout_deps/1,
3536
namespace/1, namespace/2,
3637

3738
deps_names/1,
@@ -342,6 +343,9 @@ all_deps(#state_t{all_deps=Apps}) ->
342343
all_deps(State=#state_t{}, NewApps) ->
343344
State#state_t{all_deps=NewApps}.
344345

346+
all_checkout_deps(#state_t{all_deps=Apps}) ->
347+
[App || App <- Apps, rebar_app_info:is_checkout(App)].
348+
345349
all_plugin_deps(#state_t{all_plugin_deps=Apps}) ->
346350
Apps.
347351

test/rebar_compile_SUITE.erl

Lines changed: 4 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -461,6 +461,10 @@ paths_checkout_deps(Config) ->
461461

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

464+
[AppName2] = rebar_state:all_checkout_deps(State),
465+
Name2Bin = binary:list_to_bin(Name2),
466+
Name2Bin = rebar_app_info:name(AppName2),
467+
464468
code:add_paths(rebar_state:code_paths(State, all_deps)),
465469
ok = application:load(list_to_atom(Name2)),
466470
Loaded = application:loaded_applications(),

0 commit comments

Comments
 (0)