Skip to content

Commit

Permalink
Introduce hex_core HTTP adapter for rebar3
Browse files Browse the repository at this point in the history
This will help add ways to increase observability, mocking for tests,
and future-proofing portability of browser options when talking to
hex.pm in the near future.

For the time being this is mostly a copy of the existing generated
adapter in hex_core.
  • Loading branch information
ferd committed May 24, 2021
1 parent e7f896a commit a4e54c1
Show file tree
Hide file tree
Showing 3 changed files with 51 additions and 10 deletions.
41 changes: 41 additions & 0 deletions src/rebar_httpc_adapter.erl
Original file line number Diff line number Diff line change
@@ -0,0 +1,41 @@
%% Derived from hex_core v0.7.1 for extra flexibility.

-module(rebar_httpc_adapter).
-behaviour(r3_hex_http).
-export([request/5]).

%%====================================================================
%% API functions
%%====================================================================

request(Method, URI, ReqHeaders, Body, AdapterConfig) ->
Profile = maps:get(profile, AdapterConfig, default),
Request = build_request(URI, ReqHeaders, Body),
SSLOpts = [{ssl, rebar_utils:ssl_opts(URI)}],
case httpc:request(Method, Request, SSLOpts, [{body_format, binary}], Profile) of
{ok, {{_, StatusCode, _}, RespHeaders, RespBody}} ->
RespHeaders2 = load_headers(RespHeaders),
{ok, {StatusCode, RespHeaders2, RespBody}};
{error, Reason} -> {error, Reason}
end.

%%====================================================================
%% Internal functions
%%====================================================================

build_request(URI, ReqHeaders, Body) ->
build_request2(binary_to_list(URI), dump_headers(ReqHeaders), Body).

build_request2(URI, ReqHeaders, undefined) ->
{URI, ReqHeaders};
build_request2(URI, ReqHeaders, {ContentType, Body}) ->
{URI, ReqHeaders, ContentType, Body}.

dump_headers(Map) ->
maps:fold(fun(K, V, Acc) ->
[{binary_to_list(K), binary_to_list(V)} | Acc] end, [], Map).

load_headers(List) ->
lists:foldl(fun({K, V}, Acc) ->
maps:put(list_to_binary(K), list_to_binary(V), Acc) end, #{}, List).

2 changes: 1 addition & 1 deletion src/rebar_pkg_resource.erl
Original file line number Diff line number Diff line change
Expand Up @@ -29,7 +29,7 @@
-spec init(atom(), rebar_state:t()) -> {ok, rebar_resource_v2:resource()}.
init(Type, State) ->
{ok, Vsn} = application:get_key(rebar, vsn),
BaseConfig = #{http_adapter => {r3_hex_http_httpc, #{profile => rebar}},
BaseConfig = #{http_adapter => {rebar_httpc_adapter, #{profile => rebar}},
http_user_agent_fragment =>
<<"(rebar3/", (list_to_binary(Vsn))/binary, ") (httpc)">>},
Repos = rebar_hex_repos:from_state(BaseConfig, State),
Expand Down
18 changes: 9 additions & 9 deletions test/rebar_pkg_repos_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -382,14 +382,14 @@ use_first_repo_match(Config) ->
?assertMatch({ok,{package,{<<"B">>, {{2,0,0}, {[],[]}}, Repo2},
<<"inner checksum">>,<<"outer checksum">>, false, []},
#{name := Repo2,
http_adapter := {r3_hex_http_httpc, #{profile := rebar}}}},
http_adapter := {rebar_httpc_adapter, #{profile := rebar}}}},
rebar_packages:resolve_version(<<"B">>, <<"> 1.4.0">>, undefined, undefined,
?PACKAGE_TABLE, State)),

?assertMatch({ok,{package,{<<"B">>, {{1,4,0}, {[],[]}}, Repo3},
<<"inner checksum">>,<<"outer checksum">>, false, []},
#{name := Repo3,
http_adapter := {r3_hex_http_httpc, #{profile := rebar}}}},
http_adapter := {rebar_httpc_adapter, #{profile := rebar}}}},
rebar_packages:resolve_version(<<"B">>, <<"~> 1.4.0">>, undefined, undefined,
?PACKAGE_TABLE, State)).

Expand All @@ -400,7 +400,7 @@ use_exact_with_hash(Config) ->
?assertMatch({ok,{package,{<<"C">>, {{1,3,1}, {[],[]}}, Repo2},
<<"inner checksum">>, <<"good outer checksum">>, false, []},
#{name := Repo2,
http_adapter := {r3_hex_http_httpc, #{profile := rebar}}}},
http_adapter := {rebar_httpc_adapter, #{profile := rebar}}}},
rebar_packages:resolve_version(<<"C">>, <<"1.3.1">>, <<"inner checksum">>, <<"good outer checksum">>,
?PACKAGE_TABLE, State)).

Expand All @@ -410,7 +410,7 @@ fail_repo_update(Config) ->
?assertMatch({ok,{package,{<<"B">>, {{1,4,0}, {[],[]}}, Repo3},
<<"inner checksum">>,<<"outer checksum">>, false, []},
#{name := Repo3,
http_adapter := {r3_hex_http_httpc, #{profile := rebar}}}},
http_adapter := {rebar_httpc_adapter, #{profile := rebar}}}},
rebar_packages:resolve_version(<<"B">>, <<"~> 1.4.0">>, undefined, undefined,
?PACKAGE_TABLE, State)).

Expand All @@ -421,15 +421,15 @@ ignore_match_in_excluded_repo(Config) ->
?assertMatch({ok,{package,{<<"B">>, {{1,4,6}, {[],[]}}, Hexpm},
<<"inner checksum">>,<<"outer checksum">>, #{reason := 'RETIRED_INVALID'}, []},
#{name := Hexpm,
http_adapter := {r3_hex_http_httpc, #{profile := rebar}}}},
http_adapter := {rebar_httpc_adapter, #{profile := rebar}}}},
rebar_packages:resolve_version(<<"B">>, <<"~> 1.4.0">>, undefined, undefined,
?PACKAGE_TABLE, State)),

[_, Repo2 | _] = Repos,
?assertMatch({ok,{package,{<<"A">>, {{0,1,1}, {[],[]}}, Repo2},
<<"inner checksum">>, <<"good outer checksum">>, false, []},
#{name := Repo2,
http_adapter := {r3_hex_http_httpc, #{profile := rebar}}}},
http_adapter := {rebar_httpc_adapter, #{profile := rebar}}}},
rebar_packages:resolve_version(<<"A">>, <<"0.1.1">>, <<"inner checksum">>, <<"good outer checksum">>,
?PACKAGE_TABLE, State)).

Expand All @@ -439,14 +439,14 @@ optional_prereleases(Config) ->
?assertMatch({ok,{package,{<<"B">>, {{1,5,0}, {[],[]}}, Hexpm},
<<"inner checksum">>,<<"outer checksum">>, false, []},
#{name := Hexpm,
http_adapter := {r3_hex_http_httpc, #{profile := rebar}}}},
http_adapter := {rebar_httpc_adapter, #{profile := rebar}}}},
rebar_packages:resolve_version(<<"B">>, <<"~> 1.5.0">>, undefined, undefined,
?PACKAGE_TABLE, State)),

?assertMatch({ok,{package,{<<"B">>, {{1,5,6}, {[<<"rc">>,0],[]}}, Hexpm},
<<"inner checksum">>,<<"outer checksum">>, true, []},
#{name := Hexpm,
http_adapter := {r3_hex_http_httpc, #{profile := rebar}}}},
http_adapter := {rebar_httpc_adapter, #{profile := rebar}}}},
rebar_packages:resolve_version(<<"B">>, <<"1.5.6-rc.0">>, <<"inner checksum">>, <<"outer checksum">>,
?PACKAGE_TABLE, State)),

Expand All @@ -455,7 +455,7 @@ optional_prereleases(Config) ->
?assertMatch({ok,{package,{<<"B">>, {{1,5,6}, {[<<"rc">>,0],[]}}, Hexpm},
<<"inner checksum">>,<<"outer checksum">>, true, []},
#{name := Hexpm,
http_adapter := {r3_hex_http_httpc, #{profile := rebar}}}},
http_adapter := {rebar_httpc_adapter, #{profile := rebar}}}},
rebar_packages:resolve_version(<<"B">>, <<"~> 1.5.0">>, <<"inner checksum">>, <<"outer checksum">>,
?PACKAGE_TABLE, State1)).

Expand Down

0 comments on commit a4e54c1

Please sign in to comment.