Skip to content

Commit

Permalink
Merge pull request #2898 from ferd/bump-hex-core-and-deps
Browse files Browse the repository at this point in the history
Bump hex_core and certifi dependency
  • Loading branch information
ferd authored Jun 12, 2024
2 parents cea518c + e1a1c70 commit d055c3a
Show file tree
Hide file tree
Showing 29 changed files with 3,325 additions and 3,132 deletions.
4 changes: 3 additions & 1 deletion apps/rebar/rebar.config
Original file line number Diff line number Diff line change
@@ -1,9 +1,11 @@
%% -*- mode: erlang;erlang-indent-level: 4;indent-tabs-mode: nil -*-
%% ex: ts=4 sw=4 ft=erlang et

%% Upgrade by calling 'rebar3 experimental vendor' and making sure
%% any manual patches (Eg. erlware_commons or relx) are kept.
{deps, [{erlware_commons, "1.7.0"},
{ssl_verify_fun, "1.1.6"},
{certifi, "2.11.0"},
{certifi, "2.13.0"},
{providers, "1.9.0"},
{getopt, "1.0.2"},
{bbmustache, "1.12.2"},
Expand Down
3 changes: 2 additions & 1 deletion apps/rebar/src/rebar_packages.erl
Original file line number Diff line number Diff line change
Expand Up @@ -246,7 +246,8 @@ update_package(Name, RepoConfig=#{name := Repo}, State) ->
?DEBUG("Getting definition for package ~ts from repo ~ts",
[Name, rebar_hex_repos:format_repo(RepoConfig)]),
try r3_hex_repo:get_package(get_package_repo_config(RepoConfig), Name) of
{ok, {200, _Headers, Releases}} ->
{ok, {200, _Headers, Package}} ->
#{releases := Releases} = Package,
_ = insert_releases(Name, Releases, Repo, ?PACKAGE_TABLE),
{ok, RegistryDir} = rebar_packages:registry_dir(State),
PackageIndex = filename:join(RegistryDir, ?INDEX_FILE),
Expand Down
51 changes: 37 additions & 14 deletions apps/rebar/src/vendored/r3_hex_api.erl
Original file line number Diff line number Diff line change
@@ -1,7 +1,7 @@
%% Vendored from hex_core v0.7.1, do not edit manually

%% @hidden
%% Vendored from hex_core v0.10.1, do not edit manually

%% @doc
%% Hex HTTP API
-module(r3_hex_api).

-export([
Expand All @@ -16,35 +16,40 @@
]).
-define(ERL_CONTENT_TYPE, <<"application/vnd.hex+erlang">>).

-export_type([body/0, response/0]).
-export_type([response/0]).

-type response() :: {ok, {r3_hex_http:status(), r3_hex_http:headers(), body() | nil}} | {error, term()}.
-type body() :: [body()] | #{binary() => body() | binary()}.

%% @private
get(Config, Path) ->
request(Config, get, Path, undefined).

%% @private
post(Config, Path, Body) ->
request(Config, post, Path, encode_body(Body)).

%% @private
put(Config, Path, Body) ->
request(Config, put, Path, encode_body(Body)).

%% @private
delete(Config, Path) ->
request(Config, delete, Path, undefined).

%% @private
encode_query_string(List) ->
Pairs = lists:map(fun ({K, V}) -> {to_list(K), to_list(V)} end, List),
Pairs = lists:map(fun({K, V}) -> {to_list(K), to_list(V)} end, List),
list_to_binary(compose_query(Pairs)).

%% OTP 21+
-ifdef (OTP_RELEASE).
%% @private
-ifdef(OTP_RELEASE).
compose_query(Pairs) ->
uri_string:compose_query(Pairs).
-else.
compose_query(Pairs) ->
String = join("&", lists:map(fun ({K, V}) -> K ++ "=" ++ V end, Pairs)),
String = join("&", lists:map(fun({K, V}) -> K ++ "=" ++ V end, Pairs)),
http_uri:encode(String).
-endif.

Expand All @@ -65,7 +70,8 @@ join_path_segments(Segments) ->
iolist_to_binary(recompose(Segments)).

%% OTP 21+
-ifdef (OTP_RELEASE).
%% @private
-ifdef(OTP_RELEASE).
recompose(Segments) ->
Concatenated = join(<<"/">>, Segments),
%% uri_string:recompose/1 accepts path segments as a list,
Expand All @@ -75,6 +81,7 @@ recompose(Segments) ->
recompose(Segments) ->
join(<<"/">>, lists:map(fun encode_segment/1, Segments)).

%% @private
encode_segment(Binary) when is_binary(Binary) ->
encode_segment(binary_to_list(Binary));
encode_segment(String) when is_list(String) ->
Expand All @@ -99,43 +106,59 @@ request(Config, Method, Path, Body) when is_binary(Path) and is_map(Config) ->
case binary:match(ContentType, ?ERL_CONTENT_TYPE) of
{_, _} ->
{ok, {Status, RespHeaders, binary_to_term(RespBody)}};

nomatch ->
{ok, {Status, RespHeaders, nil}}
end;

Other ->
Other
end.

%% TODO: not needed after exdoc is fixed
%% @private
build_url(Path, #{api_url := URI}) ->
<<URI/binary, "/", Path/binary>>.

%% TODO: not needed after exdoc is fixed
%% @private
encode_body({_ContentType, _Body} = Body) ->
Body;
encode_body(Body) ->
{binary_to_list(?ERL_CONTENT_TYPE), term_to_binary(Body)}.

%% TODO: not needed after exdoc is fixed
%% @private
%% TODO: copy-pasted from r3_hex_repo
make_headers(Config) ->
maps:fold(fun set_header/3, #{}, Config).

set_header(api_key, Token, Headers) when is_binary(Token) -> maps:put(<<"authorization">>, Token, Headers);
set_header(_, _, Headers) -> Headers.
%% TODO: not needed after exdoc is fixed
%% @private
set_header(api_key, Token, Headers) when is_binary(Token) ->
maps:put(<<"authorization">>, Token, Headers);
set_header(_, _, Headers) ->
Headers.

%% TODO: not needed after exdoc is fixed
%% @private
put_new(Key, Value, Map) ->
case maps:find(Key, Map) of
{ok, _} -> Map;
error -> maps:put(Key, Value, Map)
end.

%% TODO: not needed after exdoc is fixed
%% @private
%% https://github.com/erlang/otp/blob/OTP-20.3/lib/stdlib/src/lists.erl#L1449:L1453
join(_Sep, []) -> [];
join(Sep, [H|T]) -> [H|join_prepend(Sep, T)].
join(Sep, [H | T]) -> [H | join_prepend(Sep, T)].

%% TODO: not needed after exdoc is fixed
%% @private
join_prepend(_Sep, []) -> [];
join_prepend(Sep, [H|T]) -> [Sep,H|join_prepend(Sep,T)].
join_prepend(Sep, [H | T]) -> [Sep, H | join_prepend(Sep, T)].

%% TODO: not needed after exdoc is fixed
%% @private
to_list(A) when is_atom(A) -> atom_to_list(A);
to_list(B) when is_binary(B) -> unicode:characters_to_list(B);
to_list(I) when is_integer(I) -> integer_to_list(I);
Expand Down
21 changes: 10 additions & 11 deletions apps/rebar/src/vendored/r3_hex_api_key.erl
Original file line number Diff line number Diff line change
@@ -1,5 +1,7 @@
%% Vendored from hex_core v0.7.1, do not edit manually
%% Vendored from hex_core v0.10.1, do not edit manually

%% @doc
%% Hex HTTP API - Keys.
-module(r3_hex_api_key).
-export([
list/1,
Expand All @@ -11,16 +13,7 @@

-export_type([permission/0]).

-type permission() :: api_permission() | repo_permission() | repos_permission().
-ifdef(OTP_19).
-type api_permission() :: #{domain := api, resource => read | write}.
-type repo_permission() :: #{domain := repository, resource := binary()}.
-type repos_permission() :: #{domain := repositories}.
-else.
-type api_permission() :: #{domain => api, resource => read | write}.
-type repo_permission() :: #{domain => repository, resource => binary()}.
-type repos_permission() :: #{domain => repositories}.
-endif.
-type permission() :: #{binary() := binary()}.

%% @doc
%% Lists the user's or organization's API and repository keys.
Expand Down Expand Up @@ -79,6 +72,12 @@ get(Config, Name) when is_map(Config) and is_binary(Name) ->
%% @doc
%% Adds a new API or repository key.
%%
%% A permission is a map of `#{<<"domain">> => Domain, <<"resource"> => Resource}'.
%%
%% Valid `Domain' values: `<<"api">> | <<"repository">> | <<"repositories">>'.
%%
%% Valid `Resource' values: `<<"read">> | <<"write">>'.
%%
%% Examples:
%%
%% ```
Expand Down
14 changes: 9 additions & 5 deletions apps/rebar/src/vendored/r3_hex_api_package.erl
Original file line number Diff line number Diff line change
@@ -1,5 +1,7 @@
%% Vendored from hex_core v0.7.1, do not edit manually
%% Vendored from hex_core v0.10.1, do not edit manually

%% @doc
%% Hex HTTP API - Packages.
-module(r3_hex_api_package).
-export([get/2, search/3]).

Expand Down Expand Up @@ -27,7 +29,7 @@
%% '''
%% @end
-spec get(r3_hex_core:config(), binary()) -> r3_hex_api:response().
get(Config, Name) when is_map(Config) and is_binary(Name)->
get(Config, Name) when is_map(Config) and is_binary(Name) ->
Path = r3_hex_api:build_repository_path(Config, ["packages", Name]),
r3_hex_api:get(Config, Path).

Expand All @@ -37,14 +39,16 @@ get(Config, Name) when is_map(Config) and is_binary(Name)->
%% Examples:
%%
%% ```
%% > r3_hex_api_package:search(r3_hex_core:default_config(), <<"package">>, []).
%% > r3_hex_api_package:search(r3_hex_core:default_config(), <<"package">>, [{page, 1}]).
%% {ok, {200, ..., [
%% #{<<"name">> => <<"package1">>, ...},
%% ...
%% ]}}
%% '''
-spec search(r3_hex_core:config(), binary(), list(binary())) -> r3_hex_api:response().
search(Config, Query, SearchParams) when is_map(Config) and is_binary(Query) and is_list(SearchParams) ->
-spec search(r3_hex_core:config(), binary(), [{term(), term()}]) -> r3_hex_api:response().
search(Config, Query, SearchParams) when
is_map(Config) and is_binary(Query) and is_list(SearchParams)
->
QueryString = r3_hex_api:encode_query_string([{search, Query} | SearchParams]),
Path = r3_hex_api:join_path_segments(r3_hex_api:build_repository_path(Config, ["packages"])),
PathQuery = <<Path/binary, "?", QueryString/binary>>,
Expand Down
31 changes: 22 additions & 9 deletions apps/rebar/src/vendored/r3_hex_api_package_owner.erl
Original file line number Diff line number Diff line change
@@ -1,5 +1,7 @@
%% Vendored from hex_core v0.7.1, do not edit manually
%% Vendored from hex_core v0.10.1, do not edit manually

%% @doc
%% Hex HTTP API - Package Owners.
-module(r3_hex_api_package_owner).
-export([
add/5,
Expand Down Expand Up @@ -52,8 +54,12 @@ list(Config, PackageName) when is_binary(PackageName) ->
%% '''
%% @end
-spec get(r3_hex_core:config(), binary(), binary()) -> r3_hex_api:response().
get(Config, PackageName, UsernameOrEmail) when is_map(Config) and is_binary(PackageName) and is_binary(UsernameOrEmail) ->
Path = r3_hex_api:build_repository_path(Config, ["packages", PackageName, "owners", UsernameOrEmail]),
get(Config, PackageName, UsernameOrEmail) when
is_map(Config) and is_binary(PackageName) and is_binary(UsernameOrEmail)
->
Path = r3_hex_api:build_repository_path(Config, [
"packages", PackageName, "owners", UsernameOrEmail
]),
r3_hex_api:get(Config, Path).

%% @doc
Expand All @@ -76,12 +82,15 @@ get(Config, PackageName, UsernameOrEmail) when is_map(Config) and is_binary(Pack
%% '''
%% @end
-spec add(r3_hex_core:config(), binary(), binary(), binary(), boolean()) -> r3_hex_api:response().
add(Config, PackageName, UsernameOrEmail, Level, Transfer)
when is_binary(PackageName) and is_binary(UsernameOrEmail) and is_map(Config) and is_binary(Level) and is_boolean(Transfer) ->
Path = r3_hex_api:build_repository_path(Config, ["packages", PackageName, "owners", UsernameOrEmail]),
add(Config, PackageName, UsernameOrEmail, Level, Transfer) when
is_binary(PackageName) and is_binary(UsernameOrEmail) and is_map(Config) and is_binary(Level) and
is_boolean(Transfer)
->
Path = r3_hex_api:build_repository_path(Config, [
"packages", PackageName, "owners", UsernameOrEmail
]),
r3_hex_api:put(Config, Path, #{<<"level">> => Level, <<"transfer">> => Transfer}).


%% @doc
%% Deletes a packages owner.
%%
Expand All @@ -93,6 +102,10 @@ when is_binary(PackageName) and is_binary(UsernameOrEmail) and is_map(Config) an
%% '''
%% @end
-spec delete(r3_hex_core:config(), binary(), binary()) -> r3_hex_api:response().
delete(Config, PackageName, UsernameOrEmail) when is_map(Config) and is_binary(PackageName) and is_binary(UsernameOrEmail) ->
Path = r3_hex_api:build_repository_path(Config, ["packages", PackageName, "owners", UsernameOrEmail]),
delete(Config, PackageName, UsernameOrEmail) when
is_map(Config) and is_binary(PackageName) and is_binary(UsernameOrEmail)
->
Path = r3_hex_api:build_repository_path(Config, [
"packages", PackageName, "owners", UsernameOrEmail
]),
r3_hex_api:delete(Config, Path).
22 changes: 13 additions & 9 deletions apps/rebar/src/vendored/r3_hex_api_release.erl
Original file line number Diff line number Diff line change
@@ -1,5 +1,7 @@
%% Vendored from hex_core v0.7.1, do not edit manually
%% Vendored from hex_core v0.10.1, do not edit manually

%% @doc
%% Hex HTTP API - Releases.
-module(r3_hex_api_release).
-export([
delete/3,
Expand All @@ -16,11 +18,7 @@

-type retirement_reason() :: other | invalid | security | deprecated | renamed.

-ifdef(OTP_19).
-type retirement_params() :: #{reason := retirement_reason(), message => binary()}.
-else.
-type retirement_params() :: #{reason => retirement_reason(), message => binary()}.
-endif.
%% @doc
%% Gets a package release.
%%
Expand Down Expand Up @@ -79,7 +77,6 @@ get(Config, Name, Version) when is_map(Config) and is_binary(Name) and is_binary
-spec publish(r3_hex_core:config(), binary()) -> r3_hex_api:response().
publish(Config, Tarball) -> publish(Config, Tarball, []).


%% @doc
%% Publishes a new package release with query parameters.
%%
Expand Down Expand Up @@ -109,8 +106,12 @@ publish(Config, Tarball) -> publish(Config, Tarball, []).
%% '''
%% @end
-spec publish(r3_hex_core:config(), binary(), publish_params()) -> r3_hex_api:response().
publish(Config, Tarball, Params) when is_map(Config) andalso is_binary(Tarball) andalso is_list(Params)->
QueryString = r3_hex_api:encode_query_string([{replace, proplists:get_value(replace, Params, false)}]),
publish(Config, Tarball, Params) when
is_map(Config) andalso is_binary(Tarball) andalso is_list(Params)
->
QueryString = r3_hex_api:encode_query_string([
{replace, proplists:get_value(replace, Params, false)}
]),
Path = r3_hex_api:join_path_segments(r3_hex_api:build_repository_path(Config, ["publish"])),
PathWithQuery = <<Path/binary, "?", QueryString/binary>>,
TarballContentType = "application/octet-stream",
Expand Down Expand Up @@ -144,7 +145,9 @@ delete(Config, Name, Version) when is_map(Config) and is_binary(Name) and is_bin
%% '''
%% @end
-spec retire(r3_hex_core:config(), binary(), binary(), retirement_params()) -> r3_hex_api:response().
retire(Config, Name, Version, Params) when is_map(Config) and is_binary(Name) and is_binary(Version) ->
retire(Config, Name, Version, Params) when
is_map(Config) and is_binary(Name) and is_binary(Version)
->
Path = r3_hex_api:build_repository_path(Config, ["packages", Name, "releases", Version, "retire"]),
r3_hex_api:post(Config, Path, Params).

Expand All @@ -167,6 +170,7 @@ unretire(Config, Name, Version) when is_map(Config) and is_binary(Name) and is_b
%% Internal functions
%%====================================================================

%% @private
put_header(Name, Value, Config) ->
Headers = maps:get(http_headers, Config, #{}),
Headers2 = maps:put(Name, Value, Headers),
Expand Down
15 changes: 9 additions & 6 deletions apps/rebar/src/vendored/r3_hex_api_user.erl
Original file line number Diff line number Diff line change
@@ -1,5 +1,7 @@
%% Vendored from hex_core v0.7.1, do not edit manually
%% Vendored from hex_core v0.10.1, do not edit manually

%% @doc
%% Hex HTTP API - Users.
-module(r3_hex_api_user).
-export([
create/4,
Expand Down Expand Up @@ -51,12 +53,13 @@ me(Config) when is_map(Config) ->
%% '''
%% @end
-spec create(r3_hex_core:config(), binary(), binary(), binary()) -> r3_hex_api:response().
create(Config, Username, Password, Email)
when is_map(Config) and is_binary(Username) and is_binary(Password) and is_binary(Email) ->
create(Config, Username, Password, Email) when
is_map(Config) and is_binary(Username) and is_binary(Password) and is_binary(Email)
->
Params = #{
<<"username">> => Username,
<<"password">> => Password,
<<"email">> => Email
<<"username">> => Username,
<<"password">> => Password,
<<"email">> => Email
},
r3_hex_api:post(Config, ["users"], Params).

Expand Down
Loading

0 comments on commit d055c3a

Please sign in to comment.