Skip to content

Commit

Permalink
backward compat locks
Browse files Browse the repository at this point in the history
  • Loading branch information
Bryan Paxton committed Jan 30, 2020
1 parent 812e0ce commit c734db9
Show file tree
Hide file tree
Showing 7 changed files with 68 additions and 48 deletions.
12 changes: 12 additions & 0 deletions rebar.lock
Original file line number Diff line number Diff line change
Expand Up @@ -12,6 +12,18 @@
{<<"ssl_verify_fun">>,{pkg,<<"ssl_verify_fun">>,<<"1.1.5">>},0}]}.
[
{pkg_hash,[
{<<"bbmustache">>, <<"A268D256B3D5C7CF9FD14ECED58977BC71AADB7CE412E883C3A2CD0A10F3CF27">>},
{<<"certifi">>, <<"867CE347F7C7D78563450A18A6A28A8090331E77FA02380B4A21962A65D36EE5">>},
{<<"cf">>, <<"7F2913FFF90ABCABD0F489896CFEB0B0674F6C8DF6C10B17A83175448029896C">>},
{<<"cth_readable">>, <<"29DF6430584389B30D14B7D68D0EB7BC837ED31E2DF6E9D93598D4EC63B1E3BD">>},
{<<"erlware_commons">>, <<"0CE192AD69BC6FD0880246D852D0ECE17631E234878011D1586E053641ED4C04">>},
{<<"eunit_formatters">>, <<"6A9133943D36A465D804C1C5B6E6839030434B8879C5600D7DDB5B3BAD4CCB59">>},
{<<"getopt">>, <<"C73A9FA687B217F2FF79F68A3B637711BB1936E712B521D8CE466B29CBF7808A">>},
{<<"parse_trans">>, <<"09765507A3C7590A784615CFD421D101AEC25098D50B89D7AA1D66646BC571C1">>},
{<<"providers">>, <<"70B4197869514344A8A60E2B2A4EF41CA03DEF43CFB1712ECF076A0F3C62F083">>},
{<<"relx">>, <<"AFC019320BB69881718576B3E4E1EB548C1FA3270717BA66A78004C98A77CD17">>},
{<<"ssl_verify_fun">>, <<"6EAF7AD16CB568BB01753DBBD7A95FF8B91C7979482B95F38443FE2C8852A79B">>}]},
{pkg_hash_ext,[
{<<"bbmustache">>, <<"190EA2206128BDFABF5D9200B8DF97F6511D9C62953655828E28C2BC79161252">>},
{<<"certifi">>, <<"805ABD97539CAF89EC6D4732C91E62BA9DA0CDA51AC462380BBD28EE697A8C42">>},
{<<"cf">>, <<"48283B3019BC7FAD56E7B23028A5DA4D3E6CD598A553AB2A99A2153BF5F19B21">>},
Expand Down
1 change: 1 addition & 0 deletions src/rebar.hrl
Original file line number Diff line number Diff line change
Expand Up @@ -45,6 +45,7 @@
%% TODO: change package and requirement keys to be required (:=) after dropping support for OTP-18
-record(package, {key :: {unicode:unicode_binary() | ms_field(), unicode:unicode_binary() | ms_field(),
unicode:unicode_binary() | ms_field()},
inner_checksum :: binary() | ms_field(),
outer_checksum :: binary() | ms_field(),
retired :: boolean() | ms_field(),
dependencies :: [#{package => unicode:unicode_binary(),
Expand Down
17 changes: 9 additions & 8 deletions src/rebar_app_utils.erl
Original file line number Diff line number Diff line change
Expand Up @@ -207,15 +207,15 @@ parse_dep(Dep, Parent, DepsDir, State, Locks, Level) ->
parse_dep(Parent, {Name, Vsn, {pkg, PkgName}}, DepsDir, IsLock, State) ->
{PkgName1, PkgVsn} = {rebar_utils:to_binary(PkgName),
rebar_utils:to_binary(Vsn)},
dep_to_app(Parent, DepsDir, Name, PkgVsn, {pkg, PkgName1, PkgVsn, undefined}, IsLock, State);
dep_to_app(Parent, DepsDir, Name, PkgVsn, {pkg, PkgName1, PkgVsn, undefined ,undefined}, IsLock, State);
parse_dep(Parent, {Name, {pkg, PkgName}}, DepsDir, IsLock, State) ->
%% Package dependency with different package name from app name
dep_to_app(Parent, DepsDir, Name, undefined, {pkg, rebar_utils:to_binary(PkgName), undefined, undefined}, IsLock, State);
parse_dep(Parent, {Name, Vsn}, DepsDir, IsLock, State) when is_list(Vsn); is_binary(Vsn) ->
%% Versioned Package dependency
{PkgName, PkgVsn} = {rebar_utils:to_binary(Name),
rebar_utils:to_binary(Vsn)},
dep_to_app(Parent, DepsDir, PkgName, PkgVsn, {pkg, PkgName, PkgVsn, undefined}, IsLock, State);
dep_to_app(Parent, DepsDir, PkgName, PkgVsn, {pkg, PkgName, PkgVsn, undefined, undefined}, IsLock, State);
parse_dep(Parent, Name, DepsDir, IsLock, State) when is_atom(Name); is_binary(Name) ->
%% Unversioned package dependency
dep_to_app(Parent, DepsDir, rebar_utils:to_binary(Name), undefined, {pkg, rebar_utils:to_binary(Name), undefined, undefined}, IsLock, State);
Expand All @@ -232,9 +232,9 @@ parse_dep(Parent, {Name, Source, Opts}, DepsDir, IsLock, State) when is_tuple(So
?WARN("Dependency option list ~p in ~p is not supported and will be ignored", [Opts, Name]),
dep_to_app(Parent, DepsDir, Name, [], Source, IsLock, State);
parse_dep(Parent, {Name, {pkg, PkgName, Vsn}, Level}, DepsDir, IsLock, State) when is_integer(Level) ->
dep_to_app(Parent, DepsDir, Name, Vsn, {pkg, PkgName, Vsn, undefined}, IsLock, State);
parse_dep(Parent, {Name, {pkg, PkgName, Vsn, Hash}, Level}, DepsDir, IsLock, State) when is_integer(Level) ->
dep_to_app(Parent, DepsDir, Name, Vsn, {pkg, PkgName, Vsn, Hash}, IsLock, State);
dep_to_app(Parent, DepsDir, Name, Vsn, {pkg, PkgName, Vsn, undefined, undefined}, IsLock, State);
parse_dep(Parent, {Name, {pkg, PkgName, Vsn, OldHash, Hash}, Level}, DepsDir, IsLock, State) when is_integer(Level) ->
dep_to_app(Parent, DepsDir, Name, Vsn, {pkg, PkgName, Vsn, OldHash, Hash}, IsLock, State);
parse_dep(Parent, {Name, Source, Level}, DepsDir, IsLock, State) when is_tuple(Source)
, is_integer(Level) ->
dep_to_app(Parent, DepsDir, Name, [], Source, IsLock, State);
Expand Down Expand Up @@ -286,17 +286,18 @@ expand_deps_sources(Dep, State) ->
-spec update_source(rebar_app_info:t(), Source, rebar_state:t()) ->
rebar_app_info:t() when
Source :: rebar_resource_v2:source().
update_source(AppInfo, {pkg, PkgName, PkgVsn, Hash}, State) ->
case rebar_packages:resolve_version(PkgName, PkgVsn, Hash,
update_source(AppInfo, {pkg, PkgName, PkgVsn, OldHash, Hash}, State) ->
case rebar_packages:resolve_version(PkgName, PkgVsn, OldHash, Hash,
?PACKAGE_TABLE, State) of
{ok, Package, RepoConfig} ->
#package{key={_, PkgVsn1, _},
inner_checksum=OldHash1,
outer_checksum=Hash1,
dependencies=Deps,
retired=Retired} = Package,
maybe_warn_retired(PkgName, PkgVsn1, Hash, Retired),
PkgVsn2 = list_to_binary(lists:flatten(ec_semver:format(PkgVsn1))),
AppInfo1 = rebar_app_info:source(AppInfo, {pkg, PkgName, PkgVsn2, Hash1, RepoConfig}),
AppInfo1 = rebar_app_info:source(AppInfo, {pkg, PkgName, PkgVsn2, OldHash1, Hash1, RepoConfig}),
rebar_app_info:update_opts_deps(AppInfo1, Deps);
not_found ->
throw(?PRV_ERROR({missing_package, PkgName, PkgVsn}));
Expand Down
55 changes: 29 additions & 26 deletions src/rebar_config.erl
Original file line number Diff line number Diff line change
Expand Up @@ -82,7 +82,7 @@ consult_lock_file(File) ->
%% Make sure the warning below is to be shown whenever a version
%% newer than the current one is being used, as we can't parse
%% all the contents of the lock file properly.
warn_vsn_once(Vsn)
warn_vsn_once()
end,
read_attrs(Vsn, Locks, Attrs)
end.
Expand All @@ -91,25 +91,19 @@ consult_lock_file(File) ->
%% at most once.
%% The warning can also be cancelled by configuring the `warn_config_vsn'
%% OTP env variable.
-spec warn_vsn_once(string()) -> ok.
warn_vsn_once(Vsn) ->
-spec warn_vsn_once() -> ok.
warn_vsn_once() ->
Warn = application:get_env(rebar, warn_config_vsn) =/= {ok, false},
application:set_env(rebar, warn_config_vsn, false),
case Warn of
false -> ok;
true ->
warning_for_vsn(Vsn)
?WARN("Rebar3 detected a lock file from a newer version. "
"It will be loaded in compatibility mode, but important "
"information may be missing or lost. It is recommended to "
"upgrade Rebar3.", [])
end.

warning_for_vsn([Maj, _dot, Min, _dot, _Patch]) when Maj =:= $1 andalso Min =< $1 ->
?WARN("Rebar3 detected a lock file incompatible with this version of rebar3. "
"You will need to unlock and relock your dependencies via rebar3 unlock and rebar3 lock", []);
warning_for_vsn(_) ->
?WARN("Rebar3 detected a lock file from a newer version. "
"It will be loaded in compatibility mode, but important "
"information may be missing or lost. It is recommended to "
"upgrade Rebar3.", []).

%% @doc Converts the internal format for locks into the multi-version
%% compatible one used within rebar3 lock files.
%% @end
Expand All @@ -136,6 +130,9 @@ write_lock_file(LockFile, Locks) ->
format_attrs([]) -> [];
format_attrs([{pkg_hash, Vals}|T]) ->
[io_lib:format("{pkg_hash,[~n",[]), format_hashes(Vals), "]}",
maybe_comma(T) | format_attrs(T)];
format_attrs([{pkg_hash_ext, Vals}|T]) ->
[io_lib:format("{pkg_hash_ext,[~n",[]), format_hashes(Vals), "]}",
maybe_comma(T) | format_attrs(T)].

%% @private format hashing in order to disturb source diffing as little
Expand Down Expand Up @@ -178,7 +175,11 @@ extract_pkg_hashes(Attrs) ->
-spec expand_locks(list(), list()) -> list().
expand_locks([], _Hashes) ->
[];
expand_locks([{Name, {pkg,PkgName,Vsn}, Lvl} | Locks], Hashes) ->

expand_locks([{Name, {pkg_hash,PkgName,Vsn}, Lvl} | Locks], Hashes) ->
Hash = proplists:get_value(Name, Hashes),
[{Name, {old_pkg,PkgName,Vsn,Hash}, Lvl} | expand_locks(Locks, Hashes)];
expand_locks([{Name, {pkg_hash_ext,PkgName,Vsn}, Lvl} | Locks], Hashes) ->
Hash = proplists:get_value(Name, Hashes),
[{Name, {pkg,PkgName,Vsn,Hash}, Lvl} | expand_locks(Locks, Hashes)];
expand_locks([Lock|Locks], Hashes) ->
Expand All @@ -190,23 +191,25 @@ expand_locks([Lock|Locks], Hashes) ->
write_attrs(Locks) ->
%% No attribute known that needs to be taken out of the structure,
%% just return terms as is.
{NewLocks, Hashes} = split_locks(Locks, [], []),
case Hashes of
{NewLocks, OldHashes, NewHashes} = split_locks(Locks, [], [], []),
case OldHashes of
[] -> {NewLocks, []};
_ -> {NewLocks, [{pkg_hash, lists:sort(Hashes)}]}
_ -> {NewLocks, [{pkg_hash, lists:sort(OldHashes)}, {pkg_hash_ext, lists:sort(NewHashes)}]}
end.

%% @private split up extra attributes for locks out of the internal lock
%% structure for backwards compatibility reasons
-spec split_locks(list(), list(), [{_,binary()}]) -> {list(), list()}.
split_locks([], Locks, Hashes) ->
{lists:reverse(Locks), Hashes};
split_locks([{Name, {pkg,PkgName,Vsn,undefined}, Lvl} | Locks], LAcc, HAcc) ->
split_locks(Locks, [{Name,{pkg,PkgName,Vsn},Lvl}|LAcc], HAcc);
split_locks([{Name, {pkg,PkgName,Vsn,Hash}, Lvl} | Locks], LAcc, HAcc) ->
split_locks(Locks, [{Name,{pkg,PkgName,Vsn},Lvl}|LAcc], [{Name, Hash}|HAcc]);
split_locks([Lock|Locks], LAcc, HAcc) ->
split_locks(Locks, [Lock|LAcc], HAcc).
-spec split_locks(list(), list(), [{_,binary()}], [{_,binary()}]) -> {list(), list(), list()}.
split_locks([], Locks, OldHashes, NewHashes) ->
{lists:reverse(Locks), OldHashes, NewHashes};
split_locks([{Name, {pkg,PkgName,Vsn,undefined}, Lvl} | Locks], LAcc, OldHAcc, NewHAcc) ->
split_locks(Locks, [{Name,{pkg,PkgName,Vsn},Lvl}|LAcc], OldHAcc, NewHAcc);
split_locks([{Name, {pkg,PkgName,Vsn,undefined, undefined}, Lvl} | Locks], LAcc, OldHAcc, NewHAcc) ->
split_locks(Locks, [{Name,{pkg,PkgName,Vsn},Lvl}|LAcc], OldHAcc, NewHAcc);
split_locks([{Name, {pkg,PkgName,Vsn, OldHash, NewHash}, Lvl} | Locks], LAcc, OldHAcc, NewHAcc) ->
split_locks(Locks, [{Name,{pkg,PkgName,Vsn},Lvl}|LAcc], [{Name, OldHash}|OldHAcc], [{Name, NewHash}|NewHAcc]);
split_locks([Lock|Locks], LAcc, OldHAcc, NewHAcc) ->
split_locks(Locks, [Lock|LAcc], OldHAcc, NewHAcc).

%% @doc reads a given config file, including the `.script' variations,
%% if any can be found, and asserts that the config format is in
Expand Down
17 changes: 10 additions & 7 deletions src/rebar_packages.erl
Original file line number Diff line number Diff line change
Expand Up @@ -8,7 +8,7 @@
,verify_table/1
,format_error/1
,update_package/3
,resolve_version/5]).
,resolve_version/6]).

-ifdef(TEST).
-export([new_package_table/0, find_highest_matching_/5, cmp_/4, cmpl_/4, valid_vsn/1]).
Expand Down Expand Up @@ -230,7 +230,7 @@ verify_table(State) ->
ets:info(?PACKAGE_TABLE, named_table) =:= true orelse load_and_verify_version(State).

parse_deps(Deps) ->
[{maps:get(app, D, Name), {pkg, Name, Constraint, undefined}}
[{maps:get(app, D, Name), {pkg, Name, Constraint, undefined, undefined}}
|| D=#{package := Name,
requirement := Constraint} <- Deps].

Expand Down Expand Up @@ -280,21 +280,24 @@ unverified_repo_message() ->
insert_releases(Name, Releases, Repo, Table) ->
[true = ets:insert(Table,
#package{key={Name, ec_semver:parse(Version), Repo},
outer_checksum=parse_checksum(Checksum),
inner_checksum=parse_checksum(InnerChecksum),
outer_checksum=parse_checksum(OuterChecksum),
retired=maps:get(retired, Release, false),
dependencies=parse_deps(Dependencies)})
|| Release=#{outer_checksum := Checksum,
|| Release=#{inner_checksum := InnerChecksum,
outer_checksum := OuterChecksum,
version := Version,
dependencies := Dependencies} <- Releases].

-spec resolve_version(unicode:unicode_binary(), unicode:unicode_binary() | undefined,
binary() | undefined,
binary() | undefined,
ets:tab(), rebar_state:t())
-> {error, {invalid_vsn, unicode:unicode_binary()}} |
not_found |
{ok, #package{}, map()}.
%% if checksum is defined search for any matching repo matching pkg-vsn and checksum
resolve_version(Dep, DepVsn, Hash, HexRegistry, State) when is_binary(Hash) ->
resolve_version(Dep, DepVsn, _OldHash, Hash, HexRegistry, State) when is_binary(Hash) ->
Resources = rebar_state:resources(State),
#{repos := RepoConfigs} = rebar_resource_v2:find_resource_state(pkg, Resources),
RepoNames = [RepoName || #{name := RepoName} <- RepoConfigs],
Expand All @@ -315,7 +318,7 @@ resolve_version(Dep, DepVsn, Hash, HexRegistry, State) when is_binary(Hash) ->
end,
handle_missing_no_exception(Fun, Dep, State)
end;
resolve_version(Dep, undefined, Hash, HexRegistry, State) ->
resolve_version(Dep, undefined, _OldHash, Hash, HexRegistry, State) ->
Fun = fun(Repo) ->
case highest_matching(Dep, {0,{[],[]}}, Repo, HexRegistry, State) of
none ->
Expand All @@ -325,7 +328,7 @@ resolve_version(Dep, undefined, Hash, HexRegistry, State) ->
end
end,
handle_missing_no_exception(Fun, Dep, State);
resolve_version(Dep, DepVsn, Hash, HexRegistry, State) ->
resolve_version(Dep, DepVsn, _OldHash, Hash, HexRegistry, State) ->
case valid_vsn(DepVsn) of
false ->
{error, {invalid_vsn, DepVsn}};
Expand Down
12 changes: 6 additions & 6 deletions src/rebar_pkg_resource.erl
Original file line number Diff line number Diff line change
Expand Up @@ -45,8 +45,8 @@ init(Type, State) ->
ResourceState :: rebar_resource_v2:resource_state(),
Res :: {atom(), string(), any(), binary()}.
lock(AppInfo, _) ->
{pkg, Name, Vsn, Hash, _RepoConfig} = rebar_app_info:source(AppInfo),
{pkg, Name, Vsn, Hash}.
{pkg, Name, Vsn, OldHash, Hash, _RepoConfig} = rebar_app_info:source(AppInfo),
{pkg, Name, Vsn, OldHash, Hash}.

%%------------------------------------------------------------------------------
%% @doc
Expand All @@ -59,7 +59,7 @@ lock(AppInfo, _) ->
ResourceState :: rebar_resource_v2:resource_state(),
Res :: boolean().
needs_update(AppInfo, _) ->
{pkg, _Name, Vsn, _Hash, _} = rebar_app_info:source(AppInfo),
{pkg, _Name, Vsn, _OldHash, _Hash, _} = rebar_app_info:source(AppInfo),
case rebar_utils:to_binary(rebar_app_info:original_vsn(AppInfo)) =:= rebar_utils:to_binary(Vsn) of
true ->
false;
Expand Down Expand Up @@ -101,7 +101,7 @@ download(TmpDir, AppInfo, State, ResourceState) ->
UpdateETag :: boolean(),
Res :: ok | {error,_} | {unexpected_hash, string(), integer(), integer()} |
{fetch_fail, binary(), binary()}.
download(TmpDir, Pkg={pkg, Name, Vsn, _Hash, Repo}, State, _ResourceState, UpdateETag) ->
download(TmpDir, Pkg={pkg, Name, Vsn, _OldHash, _Hash, Repo}, State, _ResourceState, UpdateETag) ->
{ok, PackageDir} = rebar_packages:package_dir(Repo, State),
Package = binary_to_list(<<Name/binary, "-", Vsn/binary, ".tar">>),
ETagFile = binary_to_list(<<Name/binary, "-", Vsn/binary, ".etag">>),
Expand Down Expand Up @@ -214,7 +214,7 @@ store_etag_in_cache(Path, ETag) ->
ETagPath :: file:name(),
UpdateETag :: boolean(),
Res :: ok | {unexpected_hash, integer(), integer()} | {fetch_fail, binary(), binary()}.
cached_download(TmpDir, CachePath, Pkg={pkg, Name, Vsn, _Hash, RepoConfig}, ETag,
cached_download(TmpDir, CachePath, Pkg={pkg, Name, Vsn, _OldHash, _Hash, RepoConfig}, ETag,
ETagPath, UpdateETag) ->
case request(RepoConfig, Name, Vsn, ETag) of
{ok, cached} ->
Expand Down Expand Up @@ -246,7 +246,7 @@ serve_from_cache(TmpDir, CachePath, Pkg) ->
Tarball :: binary(),
Package :: package(),
Res :: ok | {error,_} | {bad_registry_checksum, integer(), integer()}.
serve_from_memory(TmpDir, Binary, {pkg, _Name, _Vsn, Hash, _RepoConfig}) ->
serve_from_memory(TmpDir, Binary, {pkg, _Name, _Vsn, _OldHash, Hash, _RepoConfig}) ->
RegistryChecksum = list_to_integer(binary_to_list(Hash), 16),
case r3_hex_tarball:unpack(Binary, TmpDir) of
{ok, #{outer_checksum := <<Checksum:256/big-unsigned>>}} when RegistryChecksum =/= Checksum ->
Expand Down
2 changes: 1 addition & 1 deletion src/rebar_resource_v2.erl
Original file line number Diff line number Diff line change
Expand Up @@ -139,7 +139,7 @@ get_resource_type({Type, Location, _}, Resources) ->
get_resource(Type, Location, Resources);
get_resource_type({Type, _, _, Location}, Resources) ->
get_resource(Type, Location, Resources);
get_resource_type(Location={Type, _, _, _, _}, Resources) ->
get_resource_type(Location={Type, _, _, _, _, _}, Resources) ->
get_resource(Type, Location, Resources);
get_resource_type(Source, _) ->
throw(?PRV_ERROR({no_resource, Source})).
Expand Down

0 comments on commit c734db9

Please sign in to comment.