Skip to content

Commit e15e024

Browse files
authored
Merge pull request #2974 from yoshi-monster/version-ranges
fix the version range parser to support and/or version constraints
2 parents 049f80c + f67f308 commit e15e024

File tree

10 files changed

+420
-277
lines changed

10 files changed

+420
-277
lines changed

apps/rebar/src/rebar.hrl

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -46,7 +46,7 @@
4646
-type ms_field() :: '$1' | '_' | {'$1', '$2'}.
4747

4848
%% TODO: change package and requirement keys to be required (:=) after dropping support for OTP-18
49-
-record(package, {key :: {unicode:unicode_binary() | ms_field(), unicode:unicode_binary() | ms_field() | ec_semver:semver(),
49+
-record(package, {key :: {unicode:unicode_binary() | ms_field(), unicode:unicode_binary() | ms_field() | rebar_semver:version(),
5050
unicode:unicode_binary() | ms_field()},
5151
inner_checksum :: binary() | ms_field(),
5252
outer_checksum :: binary() | ms_field(),

apps/rebar/src/rebar_app_utils.erl

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -328,7 +328,7 @@ update_source(AppInfo, {pkg, PkgName, PkgVsn, OldHash, Hash}, State) ->
328328
dependencies=Deps,
329329
retired=Retired} = Package,
330330
maybe_warn_retired(PkgName, PkgVsn1, Hash, Retired),
331-
PkgVsn2 = list_to_binary(lists:flatten(ec_semver:format(PkgVsn1))),
331+
PkgVsn2 = rebar_semver:format(PkgVsn1),
332332
AppInfo1 = rebar_app_info:source(AppInfo, {pkg, PkgName, PkgVsn2, OldHash1, Hash1, RepoConfig}),
333333
rebar_app_info:update_opts_deps(AppInfo1, Deps);
334334
not_found ->
@@ -364,7 +364,7 @@ maybe_warn_retired(_, _, Hash, _) when is_binary(Hash) ->
364364
maybe_warn_retired(Name, Vsn, _, R=#{reason := Reason}) ->
365365
Message = maps:get(message, R, ""),
366366
?WARN("Warning: package ~s-~s is retired: (~s) ~s",
367-
[Name, ec_semver:format(Vsn), retire_reason(Reason), Message]);
367+
[Name, rebar_semver:format(Vsn), retire_reason(Reason), Message]);
368368
maybe_warn_retired(_, _, _, _) ->
369369
ok.
370370

apps/rebar/src/rebar_packages.erl

Lines changed: 100 additions & 191 deletions
Original file line numberDiff line numberDiff line change
@@ -11,7 +11,7 @@
1111
,resolve_version/6]).
1212

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

1717
-export_type([package/0]).
@@ -55,16 +55,16 @@ get_all_names(State) ->
5555
_='_'},
5656
[], ['$1']}])).
5757

58-
-spec get_package_versions(unicode:unicode_binary(), ec_semver:semver(),
58+
-spec get_package_versions(unicode:unicode_binary(), boolean(),
5959
unicode:unicode_binary(),
6060
ets:tid(), rebar_state:t()) -> [vsn()].
61-
get_package_versions(Dep, {_, AlphaInfo}, Repo, Table, State) ->
61+
get_package_versions(Dep, AllowPreRelease, Repo, Table, State) ->
6262
?MODULE:verify_table(State),
63-
AllowPreRelease = rebar_state:get(State, deps_allow_prerelease, false)
64-
orelse AlphaInfo =/= {[],[]},
63+
AllowPreRelease2 = rebar_state:get(State, deps_allow_prerelease, false)
64+
orelse AllowPreRelease,
6565
ets:select(Table, [{#package{key={Dep, {'$1', '$2'}, Repo},
6666
_='_'},
67-
[{'==', '$2', {{[],[]}}} || not AllowPreRelease], [{{'$1', '$2'}}]}]).
67+
[{'==', '$2', {{[],[]}}} || not AllowPreRelease2], [{{'$1', '$2'}}]}]).
6868

6969
-spec get_package(unicode:unicode_binary(), unicode:unicode_binary(),
7070
binary() | undefined | '_',
@@ -74,23 +74,29 @@ get_package(Dep, Vsn, undefined, Repos, Table, State) ->
7474
get_package(Dep, Vsn, '_', Repos, Table, State);
7575
get_package(Dep, Vsn, Hash, Repos, Table, State) ->
7676
?MODULE:verify_table(State),
77-
MatchingPackages = ets:select(Table, [{#package{key={Dep, ec_semver:parse(Vsn), Repo},
78-
_='_'}, [], ['$_']} || Repo <- Repos]),
79-
PackagesWithProperHash = lists:filter(
80-
fun(#package{key = {_Dep, _Vsn, Repo}, outer_checksum = PkgChecksum}) ->
81-
if (PkgChecksum =/= Hash) andalso (Hash =/= '_') ->
82-
?WARN("Checksum mismatch for package ~ts-~ts from repo ~ts", [Dep, Vsn, Repo]),
83-
false;
84-
true ->
85-
true
86-
end
87-
end, MatchingPackages
88-
),
89-
case PackagesWithProperHash of
90-
%% have to allow multiple matches in the list for cases that Repo is `_`
91-
[Package | _] ->
92-
{ok, Package};
93-
[] ->
77+
case rebar_semver:parse_version(Vsn) of
78+
{ok, Parsed} ->
79+
MatchingPackages = ets:select(Table, [{#package{key={Dep, Parsed, Repo},
80+
_='_'}, [], ['$_']} || Repo <- Repos]),
81+
PackagesWithProperHash = lists:filter(
82+
fun(#package{key = {_Dep, _Vsn, Repo}, outer_checksum = PkgChecksum}) ->
83+
if (PkgChecksum =/= Hash) andalso (Hash =/= '_') ->
84+
?WARN("Checksum mismatch for package ~ts-~ts from repo ~ts", [Dep, Vsn, Repo]),
85+
false;
86+
true ->
87+
true
88+
end
89+
end, MatchingPackages
90+
),
91+
case PackagesWithProperHash of
92+
%% have to allow multiple matches in the list for cases that Repo is `_`
93+
[Package | _] ->
94+
{ok, Package};
95+
[] ->
96+
not_found
97+
end;
98+
99+
_ ->
94100
not_found
95101
end.
96102

@@ -174,56 +180,26 @@ package_dir(Repo, State) ->
174180
%% `~> 2.1.3-dev` | `>= 2.1.3-dev and < 2.2.0`
175181
%% `~> 2.0` | `>= 2.0.0 and < 3.0.0`
176182
%% `~> 2.1` | `>= 2.1.0 and < 3.0.0`
177-
find_highest_matching(Dep, Constraint, Repo, Table, State) ->
178-
try find_highest_matching_(Dep, Constraint, Repo, Table, State) of
183+
find_highest_matching(Dep, DepVsn, Repo, Table, State) ->
184+
case find_highest_matching_(Dep, DepVsn, Repo, Table, State) of
179185
none ->
180186
handle_missing_package(Dep, Repo, State,
181187
fun(State1) ->
182-
find_highest_matching_(Dep, Constraint, Repo, Table, State1)
188+
find_highest_matching_(Dep, DepVsn, Repo, Table, State1)
183189
end);
184190
Result ->
185191
Result
186-
catch
187-
_:_ ->
188-
handle_missing_package(Dep, Repo, State,
189-
fun(State1) ->
190-
find_highest_matching_(Dep, Constraint, Repo, Table, State1)
191-
end)
192192
end.
193193

194-
find_highest_matching_(Dep, Constraint, #{name := Repo}, Table, State) ->
195-
try get_package_versions(Dep, Constraint, Repo, Table, State) of
196-
[Vsn] ->
197-
handle_single_vsn(Vsn, Constraint);
198-
Vsns ->
199-
case handle_vsns(Constraint, Vsns) of
200-
none ->
201-
none;
202-
FoundVsn ->
203-
{ok, FoundVsn}
204-
end
205-
catch
206-
error:badarg ->
207-
none
208-
end.
209-
210-
handle_vsns(Constraint, Vsns) ->
211-
lists:foldl(fun(Version, Highest) ->
212-
case ec_semver:pes(Version, Constraint) andalso
213-
(Highest =:= none orelse ec_semver:gt(Version, Highest)) of
214-
true ->
215-
Version;
216-
false ->
217-
Highest
218-
end
219-
end, none, Vsns).
220-
221-
handle_single_vsn(Vsn, Constraint) ->
222-
case ec_semver:pes(Vsn, Constraint) of
223-
true ->
224-
{ok, Vsn};
225-
false ->
226-
none
194+
find_highest_matching_(Dep, DepVsn, #{name := Repo}, Table, State) when is_tuple(DepVsn) ->
195+
find_highest_matching_(Dep, rebar_semver:format(DepVsn), Repo, Table, State);
196+
find_highest_matching_(Dep, DepVsn, #{name := Repo}, Table, State) when is_binary(DepVsn) ->
197+
case rebar_semver:parse_version(DepVsn) of
198+
{ok, _} ->
199+
resolve_version_(Dep, <<"~> "/utf8, DepVsn/binary>>, Repo, Table, State);
200+
201+
{error, _} ->
202+
resolve_version_(Dep, DepVsn, Repo, Table, State)
227203
end.
228204

229205
verify_table(State) ->
@@ -282,17 +258,24 @@ unverified_repo_message() ->
282258
"security reasons. The repository should be updated in order to be safer. "
283259
"You can disable this check by setting REBAR_NO_VERIFY_REPO_ORIGIN=1".
284260

285-
insert_releases(Name, Releases, Repo, Table) ->
286-
[true = ets:insert(Table,
287-
#package{key={Name, ec_semver:parse(Version), Repo},
288-
inner_checksum=parse_checksum(InnerChecksum),
289-
outer_checksum=parse_checksum(OuterChecksum),
290-
retired=maps:get(retired, Release, false),
291-
dependencies=parse_deps(Dependencies)})
292-
|| Release=#{inner_checksum := InnerChecksum,
293-
outer_checksum := OuterChecksum,
294-
version := Version,
295-
dependencies := Dependencies} <- Releases].
261+
insert_releases(_, [], _, _) -> nil;
262+
insert_releases(Name, [Release|Releases], Repo, Table) ->
263+
#{
264+
inner_checksum := InnerChecksum,
265+
outer_checksum := OuterChecksum,
266+
version := Version,
267+
dependencies := Dependencies
268+
} = Release,
269+
{ok, Parsed} = rebar_semver:parse_version(Version),
270+
Package = #package{
271+
key={Name, Parsed, Repo},
272+
inner_checksum=parse_checksum(InnerChecksum),
273+
outer_checksum=parse_checksum(OuterChecksum),
274+
retired=maps:get(retired, Release, false),
275+
dependencies=parse_deps(Dependencies)
276+
},
277+
true = ets:insert(Table, Package),
278+
insert_releases(Name, Releases, Repo, Table).
296279

297280
-spec resolve_version(unicode:unicode_binary(), unicode:unicode_binary() | undefined,
298281
binary() | undefined,
@@ -313,42 +296,30 @@ resolve_version(Dep, DepVsn, _OldHash, Hash, HexRegistry, State) when is_binary(
313296
{ok, RepoConfig} = rebar_hex_repos:get_repo_config(RepoName, RepoConfigs),
314297
{ok, Package, RepoConfig};
315298
_ ->
316-
Fun = fun(Repo) ->
317-
case resolve_version_(Dep, DepVsn, Repo, HexRegistry, State) of
318-
none ->
319-
not_found;
320-
{ok, Vsn} ->
321-
get_package(Dep, Vsn, Hash, [Repo], HexRegistry, State)
322-
end
323-
end,
324-
handle_missing_no_exception(Fun, Dep, State)
299+
resolve_version_no_package(Dep, DepVsn, Hash, HexRegistry, State)
325300
end;
326-
resolve_version(Dep, undefined, _OldHash, Hash, HexRegistry, State) ->
327-
Fun = fun(Repo) ->
328-
case highest_matching(Dep, {0,{[],[]}}, Repo, HexRegistry, State) of
329-
none ->
330-
not_found;
331-
{ok, Vsn} ->
332-
get_package(Dep, Vsn, Hash, [Repo], HexRegistry, State)
333-
end
334-
end,
335-
handle_missing_no_exception(Fun, Dep, State);
301+
336302
resolve_version(Dep, DepVsn, _OldHash, Hash, HexRegistry, State) ->
337-
case valid_vsn(DepVsn) of
338-
false ->
339-
{error, {invalid_vsn, DepVsn}};
340-
_ ->
303+
resolve_version_no_package(Dep, DepVsn, Hash, HexRegistry, State).
304+
305+
resolve_version_no_package(Dep, DepVsn, Hash, HexRegistry, State) ->
306+
case rebar_semver:parse_constraint(DepVsn) of
307+
{ok, _} ->
341308
Fun = fun(Repo) ->
342-
case resolve_version_(Dep, DepVsn, Repo, HexRegistry, State) of
343-
none ->
344-
not_found;
345-
{ok, Vsn} ->
346-
get_package(Dep, Vsn, Hash, [Repo], HexRegistry, State)
347-
end
348-
end,
349-
handle_missing_no_exception(Fun, Dep, State)
309+
case resolve_version_(Dep, DepVsn, Repo, HexRegistry, State) of
310+
none ->
311+
not_found;
312+
{ok, Vsn} ->
313+
get_package(Dep, Vsn, Hash, [Repo], HexRegistry, State)
314+
end
315+
end,
316+
handle_missing_no_exception(Fun, Dep, State);
317+
318+
Error ->
319+
Error
350320
end.
351321

322+
352323
check_all_repos(Fun, RepoConfigs) ->
353324
ec_lists:search(fun(#{name := R}) ->
354325
Fun(R)
@@ -374,92 +345,30 @@ handle_missing_no_exception(Fun, Dep, State) ->
374345
Result
375346
end.
376347

377-
resolve_version_(Dep, DepVsn, Repo, HexRegistry, State) ->
378-
case DepVsn of
379-
<<"~>", Vsn/binary>> ->
380-
highest_matching(Dep, process_vsn(Vsn), Repo, HexRegistry, State);
381-
<<">=", Vsn/binary>> ->
382-
cmp(Dep, process_vsn(Vsn), Repo, HexRegistry, State, fun ec_semver:gte/2);
383-
<<">", Vsn/binary>> ->
384-
cmp(Dep, process_vsn(Vsn), Repo, HexRegistry, State, fun ec_semver:gt/2);
385-
<<"<=", Vsn/binary>> ->
386-
cmpl(Dep, process_vsn(Vsn), Repo, HexRegistry, State, fun ec_semver:lte/2);
387-
<<"<", Vsn/binary>> ->
388-
cmpl(Dep, process_vsn(Vsn), Repo, HexRegistry, State, fun ec_semver:lt/2);
389-
<<"==", Vsn/binary>> ->
390-
{ok, Vsn};
391-
Vsn ->
392-
{ok, Vsn}
393-
end.
394-
395-
process_vsn(Vsn) ->
396-
[Vsn1|_] = string:split(Vsn, <<" or ">>),
397-
Vsn2 = string:trim(Vsn1),
398-
ec_semver:parse(Vsn2).
399-
400-
valid_vsn(Vsn) ->
401-
%% Regepx from https://github.com/sindresorhus/semver-regex/blob/master/index.js
402-
SemVerRegExp = "v?(0|[1-9][0-9]*)\\.(0|[1-9][0-9]*)(\\.(0|[1-9][0-9]*))?"
403-
"(-[0-9a-z-]+(\\.[0-9a-z-]+)*)?(\\+[0-9a-z-]+(\\.[0-9a-z-]+)*)?",
404-
SupportedVersions = "^(>=?|<=?|~>|==)?\\s*" ++ SemVerRegExp ++ "( or .*)?$",
405-
re:run(Vsn, SupportedVersions, [unicode]) =/= nomatch.
406-
407-
highest_matching(Dep, Vsn, Repo, HexRegistry, State) ->
408-
find_highest_matching_(Dep, Vsn, #{name => Repo}, HexRegistry, State).
409-
410-
cmp(Dep, Vsn, Repo, HexRegistry, State, CmpFun) ->
411-
case get_package_versions(Dep, Vsn, Repo, HexRegistry, State) of
412-
[] ->
413-
none;
414-
Vsns ->
415-
cmp_(undefined, Vsn, Vsns, CmpFun)
416-
end.
417-
418-
cmp_(undefined, MinVsn, [], _CmpFun) ->
419-
{ok, MinVsn};
420-
cmp_(HighestDepVsn, _MinVsn, [], _CmpFun) ->
421-
{ok, HighestDepVsn};
422-
423-
cmp_(BestMatch, MinVsn, [Vsn | R], CmpFun) ->
424-
case CmpFun(Vsn, MinVsn) of
425-
true ->
426-
cmp_(Vsn, Vsn, R, CmpFun);
427-
false ->
428-
cmp_(BestMatch, MinVsn, R, CmpFun)
429-
end.
430-
431-
%% We need to treat this differently since we want a version that is LOWER but
432-
%% the highest possible one.
433-
cmpl(Dep, Vsn, Repo, HexRegistry, State, CmpFun) ->
434-
case get_package_versions(Dep, Vsn, Repo, HexRegistry, State) of
435-
[] ->
436-
none;
437-
Vsns ->
438-
cmpl_(undefined, Vsn, Vsns, CmpFun)
348+
resolve_version_(Dep, Constraint, Repo, HexRegistry, State) ->
349+
case rebar_semver:parse_constraint(Constraint) of
350+
{ok, Match} ->
351+
AllowPreRelease = rebar_semver:is_prerelease_or_build(Constraint),
352+
AllVersions = get_package_versions(Dep, AllowPreRelease, Repo, HexRegistry, State),
353+
resolve_version_loop(Match, AllVersions, none);
354+
355+
Error ->
356+
Error
439357
end.
440-
441-
cmpl_(undefined, MaxVsn, [], _CmpFun) ->
442-
{ok, MaxVsn};
443-
cmpl_(HighestDepVsn, _MaxVsn, [], _CmpFun) ->
444-
{ok, HighestDepVsn};
445-
446-
cmpl_(undefined, MaxVsn, [Vsn | R], CmpFun) ->
447-
case CmpFun(Vsn, MaxVsn) of
448-
true ->
449-
cmpl_(Vsn, MaxVsn, R, CmpFun);
450-
false ->
451-
cmpl_(undefined, MaxVsn, R, CmpFun)
358+
359+
resolve_version_loop(_Constraint, [], none) -> none;
360+
resolve_version_loop(_Constraint, [], BestMatch) -> {ok, BestMatch};
361+
resolve_version_loop(Constraint, [Vsn|R], none) ->
362+
case rebar_semver:match(Vsn, Constraint) of
363+
true -> resolve_version_loop(Constraint, R, Vsn);
364+
_ -> resolve_version_loop(Constraint, R, none)
452365
end;
453-
454-
cmpl_(BestMatch, MaxVsn, [Vsn | R], CmpFun) ->
455-
case CmpFun(Vsn, MaxVsn) of
366+
resolve_version_loop(Constraint, [Vsn|R], BestMatch) ->
367+
case rebar_semver:match(Vsn, Constraint) of
456368
true ->
457-
case ec_semver:gte(Vsn, BestMatch) of
458-
true ->
459-
cmpl_(Vsn, MaxVsn, R, CmpFun);
460-
false ->
461-
cmpl_(BestMatch, MaxVsn, R, CmpFun)
369+
case rebar_semver:cmp(Vsn, BestMatch) of
370+
gt -> resolve_version_loop(Constraint, R, Vsn);
371+
_ -> resolve_version_loop(Constraint, R, BestMatch)
462372
end;
463-
false ->
464-
cmpl_(BestMatch, MaxVsn, R, CmpFun)
373+
_ -> resolve_version_loop(Constraint, R, BestMatch)
465374
end.

0 commit comments

Comments
 (0)