Skip to content

Commit

Permalink
Merge pull request #1070 from project-fifo/hex-improvements
Browse files Browse the repository at this point in the history
Hex improvements
  • Loading branch information
tsloughter committed Feb 24, 2016
2 parents 2d2b8a7 + e9e6265 commit b9f058a
Show file tree
Hide file tree
Showing 4 changed files with 239 additions and 44 deletions.
40 changes: 29 additions & 11 deletions src/rebar_packages.erl
Original file line number Diff line number Diff line change
Expand Up @@ -7,7 +7,9 @@
,registry_dir/1
,package_dir/1
,registry_checksum/2
,find_highest_matching/6
,find_highest_matching/4
,find_all/3
,verify_table/1
,format_error/1]).

Expand Down Expand Up @@ -139,16 +141,26 @@ registry_checksum({pkg, Name, Vsn}, State) ->
%% `~> 2.0` | `>= 2.0.0 and < 3.0.0`
%% `~> 2.1` | `>= 2.1.0 and < 3.0.0`
find_highest_matching(Dep, Constraint, Table, State) ->
find_highest_matching(undefined, undefined, Dep, Constraint, Table, State).

find_highest_matching(Pkg, PkgVsn, Dep, Constraint, Table, State) ->
try find_all(Dep, Table, State) of
{ok, [Vsn]} ->
handle_single_vsn(Pkg, PkgVsn, Dep, Vsn, Constraint);
{ok, [HeadVsn | VsnTail]} ->
{ok, handle_vsns(Constraint, HeadVsn, VsnTail)}
catch
error:badarg ->
none
end.

find_all(Dep, Table, State) ->
?MODULE:verify_table(State),
try ets:lookup_element(Table, Dep, 2) of
[[HeadVsn | VsnTail]] ->
{ok, handle_vsns(Constraint, HeadVsn, VsnTail)};
[[Vsn]] ->
handle_single_vsn(Dep, Vsn, Constraint);
[Vsn] ->
handle_single_vsn(Dep, Vsn, Constraint);
[HeadVsn | VsnTail] ->
{ok, handle_vsns(Constraint, HeadVsn, VsnTail)}
[Vsns] when is_list(Vsns)->
{ok, Vsns};
Vsns ->
{ok, Vsns}
catch
error:badarg ->
none
Expand All @@ -165,13 +177,19 @@ handle_vsns(Constraint, HeadVsn, VsnTail) ->
end
end, HeadVsn, VsnTail).

handle_single_vsn(Dep, Vsn, Constraint) ->
handle_single_vsn(Pkg, PkgVsn, Dep, Vsn, Constraint) ->
case ec_semver:pes(Vsn, Constraint) of
true ->
{ok, Vsn};
false ->
?WARN("Only existing version of ~s is ~s which does not match constraint ~~> ~s. "
"Using anyway, but it is not guaranteed to work.", [Dep, Vsn, Constraint]),
case {Pkg, PkgVsn} of
{undefined, undefined} ->
?WARN("Only existing version of ~s is ~s which does not match constraint ~~> ~s. "
"Using anyway, but it is not guaranteed to work.", [Dep, Vsn, Constraint]);
_ ->
?WARN("[~s:~s] Only existing version of ~s is ~s which does not match constraint ~~> ~s. "
"Using anyway, but it is not guaranteed to work.", [Pkg, PkgVsn, Dep, Vsn, Constraint])
end,
{ok, Vsn}
end.

Expand Down
122 changes: 110 additions & 12 deletions src/rebar_prv_update.erl
Original file line number Diff line number Diff line change
Expand Up @@ -11,6 +11,10 @@

-export([hex_to_index/1]).

-ifdef(TEST).
-export([cmp_/6, cmpl_/6, valid_vsn/1]).
-endif.

-include("rebar.hrl").
-include_lib("providers/include/providers.hrl").

Expand Down Expand Up @@ -99,7 +103,7 @@ hex_to_index(State) ->
ets:foldl(fun({{Pkg, PkgVsn}, [Deps, Checksum, BuildTools | _]}, _) when is_list(BuildTools) ->
case lists:any(fun is_supported/1, BuildTools) of
true ->
DepsList = update_deps_list(Deps, Registry, State),
DepsList = update_deps_list(Pkg, PkgVsn, Deps, Registry, State),
ets:insert(?PACKAGE_TABLE, {{Pkg, PkgVsn}, DepsList, Checksum});
false ->
true
Expand Down Expand Up @@ -137,20 +141,114 @@ hex_to_index(State) ->
fail
end.

update_deps_list(Deps, HexRegistry, State) ->
update_deps_list(Pkg, PkgVsn, Deps, HexRegistry, State) ->
lists:foldl(fun([Dep, DepVsn, false, _AppName | _], DepsListAcc) ->
case DepVsn of
<<"~> ", Vsn/binary>> ->
case rebar_packages:find_highest_matching(Dep, Vsn, HexRegistry, State) of
{ok, HighestDepVsn} ->
[{Dep, HighestDepVsn} | DepsListAcc];
none ->
?WARN("Missing registry entry for package ~s. Try to fix with `rebar3 update`", [Dep]),
DepsListAcc
end;
Vsn ->
Dep1 = {Pkg, PkgVsn, Dep},
case {valid_vsn(DepVsn), DepVsn} of
%% Those are all not perfectly implemented!
%% and doubled since spaces seem not to be
%% enforced
{false, Vsn} ->
?WARN("[~s:~s], Bad dependency version for ~s: ~s.",
[Pkg, PkgVsn, Dep, Vsn]),
DepsListAcc;
{_, <<"~>", Vsn/binary>>} ->
highest_matching(Dep1, rm_ws(Vsn), HexRegistry,
State, DepsListAcc);
{_, <<">=", Vsn/binary>>} ->
cmp(Dep1, rm_ws(Vsn), HexRegistry, State,
DepsListAcc, fun ec_semver:gte/2);
{_, <<">", Vsn/binary>>} ->
cmp(Dep1, rm_ws(Vsn), HexRegistry, State,
DepsListAcc, fun ec_semver:gt/2);
{_, <<"<=", Vsn/binary>>} ->
cmpl(Dep1, rm_ws(Vsn), HexRegistry, State,
DepsListAcc, fun ec_semver:lte/2);
{_, <<"<", Vsn/binary>>} ->
cmpl(Dep1, rm_ws(Vsn), HexRegistry, State,
DepsListAcc, fun ec_semver:lt/2);
{_, <<"==", Vsn/binary>>} ->
[{Dep, Vsn} | DepsListAcc];
{_, Vsn} ->
[{Dep, Vsn} | DepsListAcc]
end;
([_Dep, _DepVsn, true, _AppName | _], DepsListAcc) ->
DepsListAcc
end, [], Deps).

rm_ws(<<" ", R/binary>>) ->
rm_ws(R);
rm_ws(R) ->
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) =/= nomatch.

highest_matching({Pkg, PkgVsn, Dep}, Vsn, HexRegistry, State, DepsListAcc) ->
case rebar_packages:find_highest_matching(Pkg, PkgVsn, Dep, Vsn, HexRegistry, State) of
{ok, HighestDepVsn} ->
[{Dep, HighestDepVsn} | DepsListAcc];
none ->
?WARN("[~s:~s] Missing registry entry for package ~s. Try to fix with `rebar3 update`",
[Pkg, PkgVsn, Dep]),
DepsListAcc
end.

cmp({_Pkg, _PkgVsn, Dep} = Dep1, Vsn, HexRegistry, State, DepsListAcc, CmpFun) ->
{ok, Vsns} = rebar_packages:find_all(Dep, HexRegistry, State),
cmp_(undefined, Vsn, Vsns, DepsListAcc, Dep1, CmpFun).


cmp_(undefined, _MinVsn, [], DepsListAcc, {Pkg, PkgVsn, Dep}, _CmpFun) ->
?WARN("[~s:~s] Missing registry entry for package ~s. Try to fix with `rebar3 update`",
[Pkg, PkgVsn, Dep]),
DepsListAcc;
cmp_(HighestDepVsn, _MinVsn, [], DepsListAcc, {_Pkg, _PkgVsn, Dep}, _CmpFun) ->
[{Dep, HighestDepVsn} | DepsListAcc];

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

%% We need to treat this differently since we want a version that is LOWER but
%% the higest possible one.
cmpl({_Pkg, _PkgVsn, Dep} = Dep1, Vsn, HexRegistry, State, DepsListAcc, CmpFun) ->
{ok, Vsns} = rebar_packages:find_all(Dep, HexRegistry, State),
cmpl_(undefined, Vsn, Vsns, DepsListAcc, Dep1, CmpFun).

cmpl_(undefined, _MaxVsn, [], DepsListAcc, {Pkg, PkgVsn, Dep}, _CmpFun) ->
?WARN("[~s:~s] Missing registry entry for package ~s. Try to fix with `rebar3 update`",
[Pkg, PkgVsn, Dep]),
DepsListAcc;

cmpl_(HighestDepVsn, _MaxVsn, [], DepsListAcc, {_Pkg, _PkgVsn, Dep}, _CmpFun) ->
[{Dep, HighestDepVsn} | DepsListAcc];

cmpl_(undefined, MaxVsn, [Vsn | R], DepsListAcc, Dep, CmpFun) ->
case CmpFun(Vsn, MaxVsn) of
true ->
cmpl_(Vsn, MaxVsn, R, DepsListAcc, Dep, CmpFun);
false ->
cmpl_(undefined, MaxVsn, R, DepsListAcc, Dep, CmpFun)
end;

cmpl_(BestMatch, MaxVsn, [Vsn | R], DepsListAcc, Dep, CmpFun) ->
case CmpFun(Vsn, MaxVsn) of
true ->
case ec_semver:gte(Vsn, BestMatch) of
true ->
cmpl_(Vsn, MaxVsn, R, DepsListAcc, Dep, CmpFun);
false ->
cmpl_(BestMatch, MaxVsn, R, DepsListAcc, Dep, CmpFun)
end;
false ->
cmpl_(BestMatch, MaxVsn, R, DepsListAcc, Dep, CmpFun)
end.
Loading

0 comments on commit b9f058a

Please sign in to comment.