Skip to content

Commit

Permalink
Start integrating verl
Browse files Browse the repository at this point in the history
  • Loading branch information
filmor committed Apr 18, 2023
1 parent 3af3ed0 commit 5a3d307
Show file tree
Hide file tree
Showing 10 changed files with 128 additions and 189 deletions.
2 changes: 1 addition & 1 deletion apps/rebar/src/rebar.hrl
Original file line number Diff line number Diff line change
Expand Up @@ -44,7 +44,7 @@
-type ms_field() :: '$1' | '_' | {'$1', '$2'}.

%% 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() | ec_semver:semver(),
-record(package, {key :: {unicode:unicode_binary() | ms_field(), unicode:unicode_binary() | ms_field() | verl:version(),
unicode:unicode_binary() | ms_field()},
inner_checksum :: binary() | ms_field(),
outer_checksum :: binary() | ms_field(),
Expand Down
4 changes: 2 additions & 2 deletions apps/rebar/src/rebar_app_utils.erl
Original file line number Diff line number Diff line change
Expand Up @@ -328,7 +328,7 @@ update_source(AppInfo, {pkg, PkgName, PkgVsn, OldHash, Hash}, State) ->
dependencies=Deps,
retired=Retired} = Package,
maybe_warn_retired(PkgName, PkgVsn1, Hash, Retired),
PkgVsn2 = list_to_binary(lists:flatten(ec_semver:format(PkgVsn1))),
PkgVsn2 = list_to_binary(lists:flatten(rebar_verl:format_version(PkgVsn1))),
AppInfo1 = rebar_app_info:source(AppInfo, {pkg, PkgName, PkgVsn2, OldHash1, Hash1, RepoConfig}),
rebar_app_info:update_opts_deps(AppInfo1, Deps);
not_found ->
Expand Down Expand Up @@ -364,7 +364,7 @@ maybe_warn_retired(_, _, Hash, _) when is_binary(Hash) ->
maybe_warn_retired(Name, Vsn, _, R=#{reason := Reason}) ->
Message = maps:get(message, R, ""),
?WARN("Warning: package ~s-~s is retired: (~s) ~s",
[Name, ec_semver:format(Vsn), retire_reason(Reason), Message]);
[Name, rebar_verl:format_version(Vsn), retire_reason(Reason), Message]);
maybe_warn_retired(_, _, _, _) ->
ok.

Expand Down
179 changes: 48 additions & 131 deletions apps/rebar/src/rebar_packages.erl
Original file line number Diff line number Diff line change
Expand Up @@ -11,7 +11,7 @@
,resolve_version/6]).

-ifdef(TEST).
-export([new_package_table/0, find_highest_matching_/5, cmp_/4, cmpl_/4, valid_vsn/1]).
-export([new_package_table/0, find_highest_matching_/5, valid_vsn/1]).
-endif.

-export_type([package/0]).
Expand Down Expand Up @@ -55,31 +55,37 @@ get_all_names(State) ->
_='_'},
[], ['$1']}])).

-spec get_package_versions(unicode:unicode_binary(), ec_semver:semver(),
-spec get_package_versions(unicode:unicode_binary(), verl:semver(),
unicode:unicode_binary(),
ets:tid(), rebar_state:t()) -> [vsn()].
get_package_versions(Dep, {_, AlphaInfo}, Repo, Table, State) ->
?MODULE:verify_table(State),
AllowPreRelease = rebar_state:get(State, deps_allow_prerelease, false)
orelse AlphaInfo =/= {[],[]},
ets:select(Table, [{#package{key={Dep, {'$1', '$2'}, Repo},
_='_'},
[{'==', '$2', {{[],[]}}} || not AllowPreRelease], [{{'$1', '$2'}}]}]).
get_package_versions(Dep, DepVsn, Repo, Table, State) ->
_AllowPreRelease = rebar_state:get(State, deps_allow_prerelease, false),
case rebar_verl:parse_requirement(DepVsn) of
{error, _} ->
none;
{ok, #{matchspec := [{Head, [Match], _}]}} ->
?MODULE:verify_table(State),
Vsns = ets:select(Table, [{#package{key={Dep, Head, Repo}, _='_'},
[Match], [{Head}]}]),
handle_vsns(Vsns)
end.

-spec get_package(unicode:unicode_binary(), unicode:unicode_binary(),
binary() | undefined | '_',
[unicode:unicode_binary()] | ['_'], ets:tab(), rebar_state:t())
-> {ok, #package{}} | not_found.
get_package(Dep, Vsn, undefined, Repos, Table, State) ->
get_package(Dep, Vsn, '_', Repos, Table, State);
get_package(Dep, Vsn, Hash, Repos, Table, State) when is_binary(Vsn) ->
get_package(Dep, r3_verl:parse(Vsn), Hash, Repos, Table, State);
get_package(Dep, Vsn, Hash, Repos, Table, State) ->
?MODULE:verify_table(State),
MatchingPackages = ets:select(Table, [{#package{key={Dep, ec_semver:parse(Vsn), Repo},
MatchingPackages = ets:select(Table, [{#package{key={Dep, Vsn, Repo},
_='_'}, [], ['$_']} || Repo <- Repos]),
PackagesWithProperHash = lists:filter(
fun(#package{key = {_Dep, _Vsn, Repo}, outer_checksum = PkgChecksum}) ->
if (PkgChecksum =/= Hash) andalso (Hash =/= '_') ->
?WARN("Checksum mismatch for package ~ts-~ts from repo ~ts", [Dep, Vsn, Repo]),
?WARN("Checksum mismatch for package ~ts-~ts from repo ~ts", [Dep, rebar_verl:format_version(Vsn), Repo]),
false;
true ->
true
Expand Down Expand Up @@ -174,7 +180,8 @@ package_dir(Repo, State) ->
%% `~> 2.1.3-dev` | `>= 2.1.3-dev and < 2.2.0`
%% `~> 2.0` | `>= 2.0.0 and < 3.0.0`
%% `~> 2.1` | `>= 2.1.0 and < 3.0.0`
find_highest_matching(Dep, Constraint, Repo, Table, State) ->
find_highest_matching(Dep, Version, Repo, Table, State) ->
Constraint = verl:add_highest_matching_prefix(Version),
try find_highest_matching_(Dep, Constraint, Repo, Table, State) of
none ->
handle_missing_package(Dep, Repo, State,
Expand All @@ -192,39 +199,26 @@ find_highest_matching(Dep, Constraint, Repo, Table, State) ->
end.

find_highest_matching_(Dep, Constraint, #{name := Repo}, Table, State) ->
try get_package_versions(Dep, Constraint, Repo, Table, State) of
[Vsn] ->
handle_single_vsn(Vsn, Constraint);
Vsns ->
case handle_vsns(Constraint, Vsns) of
none ->
none;
FoundVsn ->
{ok, FoundVsn}
end
try
get_package_versions(Dep, Constraint, Repo, Table, State)
catch
error:badarg ->
none
end.

handle_vsns(Constraint, Vsns) ->
lists:foldl(fun(Version, Highest) ->
case ec_semver:pes(Version, Constraint) andalso
(Highest =:= none orelse ec_semver:gt(Version, Highest)) of
true ->
Version;
false ->
Highest
end
end, none, Vsns).

handle_single_vsn(Vsn, Constraint) ->
case ec_semver:pes(Vsn, Constraint) of
true ->
{ok, Vsn};
false ->
none
end.
handle_vsns([]) -> none;
handle_vsns(Vsns) ->
Vsn =
lists:foldl(
fun(Version, Highest) ->
case (Highest =:= none orelse r3_verl:compare(Version, Highest) =:= gt) of
true ->
Version;
false ->
Highest
end
end, none, Vsns),
{ok, Vsn}.

verify_table(State) ->
ets:info(?PACKAGE_TABLE, named_table) =:= true orelse load_and_verify_version(State).
Expand Down Expand Up @@ -282,8 +276,12 @@ unverified_repo_message() ->
"You can disable this check by setting REBAR_NO_VERIFY_REPO_ORIGIN=1".

insert_releases(Name, Releases, Repo, Table) ->
Parse = fun (V) ->
{ok, Res} = verl:parse(V),
Res
end,
[true = ets:insert(Table,
#package{key={Name, ec_semver:parse(Version), Repo},
#package{key={Name, Parse(Version), Repo},
inner_checksum=parse_checksum(InnerChecksum),
outer_checksum=parse_checksum(OuterChecksum),
retired=maps:get(retired, Release, false),
Expand Down Expand Up @@ -313,7 +311,7 @@ resolve_version(Dep, DepVsn, _OldHash, Hash, HexRegistry, State) when is_binary(
{ok, Package, RepoConfig};
_ ->
Fun = fun(Repo) ->
case resolve_version_(Dep, DepVsn, Repo, HexRegistry, State) of
case get_package_versions(Dep, DepVsn, Repo, HexRegistry, State) of
none ->
not_found;
{ok, Vsn} ->
Expand All @@ -324,7 +322,7 @@ resolve_version(Dep, DepVsn, _OldHash, Hash, HexRegistry, State) when is_binary(
end;
resolve_version(Dep, undefined, _OldHash, Hash, HexRegistry, State) ->
Fun = fun(Repo) ->
case highest_matching(Dep, {0,{[],[]}}, Repo, HexRegistry, State) of
case get_latest_version(Dep, Repo, HexRegistry, State) of
none ->
not_found;
{ok, Vsn} ->
Expand All @@ -338,7 +336,7 @@ resolve_version(Dep, DepVsn, _OldHash, Hash, HexRegistry, State) ->
{error, {invalid_vsn, DepVsn}};
_ ->
Fun = fun(Repo) ->
case resolve_version_(Dep, DepVsn, Repo, HexRegistry, State) of
case get_package_versions(Dep, DepVsn, Repo, HexRegistry, State) of
none ->
not_found;
{ok, Vsn} ->
Expand Down Expand Up @@ -373,92 +371,11 @@ handle_missing_no_exception(Fun, Dep, State) ->
Result
end.

resolve_version_(Dep, DepVsn, Repo, HexRegistry, State) ->
case DepVsn of
<<"~>", Vsn/binary>> ->
highest_matching(Dep, rm_ws(Vsn), Repo, HexRegistry, State);
<<">=", Vsn/binary>> ->
cmp(Dep, rm_ws(Vsn), Repo, HexRegistry, State, fun ec_semver:gte/2);
<<">", Vsn/binary>> ->
cmp(Dep, rm_ws(Vsn), Repo, HexRegistry, State, fun ec_semver:gt/2);
<<"<=", Vsn/binary>> ->
cmpl(Dep, rm_ws(Vsn), Repo, HexRegistry, State, fun ec_semver:lte/2);
<<"<", Vsn/binary>> ->
cmpl(Dep, rm_ws(Vsn), Repo, HexRegistry, State, fun ec_semver:lt/2);
<<"==", Vsn/binary>> ->
{ok, Vsn};
Vsn ->
{ok, Vsn}
end.

rm_ws(<<" ", R/binary>>) ->
ec_semver:parse(rm_ws(R));
rm_ws(R) ->
ec_semver:parse(R).

valid_vsn(Vsn) ->
%% Regepx from https://github.com/sindresorhus/semver-regex/blob/master/index.js
SemVerRegExp = "v?(0|[1-9][0-9]*)\\.(0|[1-9][0-9]*)(\\.(0|[1-9][0-9]*))?"
"(-[0-9a-z-]+(\\.[0-9a-z-]+)*)?(\\+[0-9a-z-]+(\\.[0-9a-z-]+)*)?",
SupportedVersions = "^(>=?|<=?|~>|==)?\\s*" ++ SemVerRegExp ++ "$",
re:run(Vsn, SupportedVersions, [unicode]) =/= nomatch.

highest_matching(Dep, Vsn, Repo, HexRegistry, State) ->
find_highest_matching_(Dep, Vsn, #{name => Repo}, HexRegistry, State).

cmp(Dep, Vsn, Repo, HexRegistry, State, CmpFun) ->
case get_package_versions(Dep, Vsn, Repo, HexRegistry, State) of
[] ->
none;
Vsns ->
cmp_(undefined, Vsn, Vsns, CmpFun)
end.

cmp_(undefined, MinVsn, [], _CmpFun) ->
{ok, MinVsn};
cmp_(HighestDepVsn, _MinVsn, [], _CmpFun) ->
{ok, HighestDepVsn};

cmp_(BestMatch, MinVsn, [Vsn | R], CmpFun) ->
case CmpFun(Vsn, MinVsn) of
true ->
cmp_(Vsn, Vsn, R, CmpFun);
false ->
cmp_(BestMatch, MinVsn, R, CmpFun)
end.

%% We need to treat this differently since we want a version that is LOWER but
%% the highest possible one.
cmpl(Dep, Vsn, Repo, HexRegistry, State, CmpFun) ->
case get_package_versions(Dep, Vsn, Repo, HexRegistry, State) of
[] ->
none;
Vsns ->
cmpl_(undefined, Vsn, Vsns, CmpFun)
end.

cmpl_(undefined, MaxVsn, [], _CmpFun) ->
{ok, MaxVsn};
cmpl_(HighestDepVsn, _MaxVsn, [], _CmpFun) ->
{ok, HighestDepVsn};

cmpl_(undefined, MaxVsn, [Vsn | R], CmpFun) ->
case CmpFun(Vsn, MaxVsn) of
true ->
cmpl_(Vsn, MaxVsn, R, CmpFun);
false ->
cmpl_(undefined, MaxVsn, R, CmpFun)
end;
rebar_verl:valid_requirement(Vsn).

cmpl_(BestMatch, MaxVsn, [Vsn | R], CmpFun) ->
case CmpFun(Vsn, MaxVsn) of
true ->
case ec_semver:gte(Vsn, BestMatch) of
true ->
cmpl_(Vsn, MaxVsn, R, CmpFun);
false ->
cmpl_(BestMatch, MaxVsn, R, CmpFun)
end;
false ->
cmpl_(BestMatch, MaxVsn, R, CmpFun)
end.
get_latest_version(Dep, Repo, HexRegistry, State) ->
verify_table(State),
Vsns = ets:select(HexRegistry, [{#package{key={'$1', '$2', '$3'}, _='_'},
[{'==', '$1', Dep}, {'==', '$3', Repo}], ['$2']}]),
handle_vsns(Vsns).
55 changes: 55 additions & 0 deletions apps/rebar/src/rebar_verl.erl
Original file line number Diff line number Diff line change
@@ -0,0 +1,55 @@
%% -*- erlang-indent-level: 4;indent-tabs-mode: nil -*-
%% ex: ts=4 sw=4 et
-module(rebar_verl).

-export([
parse_requirement/1,
valid_requirement/1,
parse_version/1,
format_version/1
]).

parse_requirement(Vsn) ->
Vsn1 =
case verl:parse(Vsn) of
{ok, _} ->
list_to_binary([<<"=> ">>, Vsn]);
_ ->
Vsn
end,

verl:parse_requirement(Vsn1).

valid_requirement(Vsn) ->
case verl:parse(Vsn) of
{ok, _} ->
true;
_ ->
case verl:parse_requirement(Vsn) of
{ok, _} ->
true;
_ ->
false
end
end.

parse_version(Vsn) ->
{ok, Res} = verl:parse(Vsn),
Res.

format_version(#{major := Major, minor := Minor, patch := Patch, pre := Pre, build := Build}) ->
Base = io_lib:format("~p.~p.~p", [Major, Minor, Patch]),
WithPre = case Pre of
[] ->
Base;
_ ->
[Base, [$-, Pre]]
end,
WithBuild = case Build of
undefined ->
WithPre;
_ ->
[WithPre, io_lib:format("+~p", [Build])]
end,
WithBuild.

8 changes: 5 additions & 3 deletions apps/rebar/test/mock_pkg_resource.erl
Original file line number Diff line number Diff line change
Expand Up @@ -173,21 +173,23 @@ to_index(AllDeps, Dict, Repos) ->
DKB <- [ec_cnv:to_binary(DK)],
DVB <- [ec_cnv:to_binary(DV)]],
Repo = rebar_test_utils:random_element(Repos),
{ok, ParsedV} = verl:parse(V),

ets:insert(?PACKAGE_TABLE, #package{key={N, ec_semver:parse(V), Repo},
ets:insert(?PACKAGE_TABLE, #package{key={N, ParsedV, Repo},
dependencies=parse_deps(DepsList),
retired=false,
inner_checksum = <<"inner_checksum">>,
outer_checksum = <<"checksum">>})
end, ok, Dict),

lists:foreach(fun({{Name, Vsn}, _}) ->
{ok, ParsedV} = verl:parse(Vsn),
case lists:any(fun(R) ->
ets:member(?PACKAGE_TABLE, {ec_cnv:to_binary(Name), ec_semver:parse(Vsn), R})
ets:member(?PACKAGE_TABLE, {ec_cnv:to_binary(Name), ParsedV, R})
end, Repos) of
false ->
Repo = rebar_test_utils:random_element(Repos),
ets:insert(?PACKAGE_TABLE, #package{key={ec_cnv:to_binary(Name), ec_semver:parse(Vsn), Repo},
ets:insert(?PACKAGE_TABLE, #package{key={ec_cnv:to_binary(Name), ParsedV, Repo},
dependencies=[],
retired=false,
inner_checksum = <<"inner_checksum">>,
Expand Down

0 comments on commit 5a3d307

Please sign in to comment.