Skip to content

Commit

Permalink
Merge pull request #2565 from nalundgaard/3.13.x-introduce-rebar_http…
Browse files Browse the repository at this point in the history
…_adapter

Introduce hex_core HTTP adapter for rebar3 (3.13.x)
  • Loading branch information
ferd authored May 26, 2021
2 parents 73c3613 + 24c5980 commit f850e7b
Show file tree
Hide file tree
Showing 3 changed files with 51 additions and 1 deletion.
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.5.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,
BaseConfig = #{http_adapter => rebar_httpc_adapter,
http_user_agent_fragment =>
<<"(rebar3/", (list_to_binary(Vsn))/binary, ") (httpc)">>,
http_adapter_config => #{profile => rebar}},
Expand Down
9 changes: 9 additions & 0 deletions test/rebar_pkg_repos_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -319,13 +319,15 @@ use_first_repo_match(Config) ->
?assertMatch({ok,{package,{<<"B">>, {{2,0,0}, {[],[]}}, Repo2},
<<"some checksum">>, false, []},
#{name := Repo2,
http_adapter := rebar_httpc_adapter,
http_adapter_config := #{profile := rebar}}},
rebar_packages:resolve_version(<<"B">>, <<"> 1.4.0">>, undefined,
?PACKAGE_TABLE, State)),

?assertMatch({ok,{package,{<<"B">>, {{1,4,0}, {[],[]}}, Repo3},
<<"some checksum">>, false, []},
#{name := Repo3,
http_adapter := rebar_httpc_adapter,
http_adapter_config := #{profile := rebar}}},
rebar_packages:resolve_version(<<"B">>, <<"~> 1.4.0">>, undefined,
?PACKAGE_TABLE, State)).
Expand All @@ -337,6 +339,7 @@ use_exact_with_hash(Config) ->
?assertMatch({ok,{package,{<<"C">>, {{1,3,1}, {[],[]}}, Repo2},
<<"good checksum">>, false, []},
#{name := Repo2,
http_adapter := rebar_httpc_adapter,
http_adapter_config := #{profile := rebar}}},
rebar_packages:resolve_version(<<"C">>, <<"1.3.1">>, <<"good checksum">>,
?PACKAGE_TABLE, State)).
Expand All @@ -347,6 +350,7 @@ fail_repo_update(Config) ->
?assertMatch({ok,{package,{<<"B">>, {{1,4,0}, {[],[]}}, Repo3},
<<"some checksum">>, false, []},
#{name := Repo3,
http_adapter := rebar_httpc_adapter,
http_adapter_config := #{profile := rebar}}},
rebar_packages:resolve_version(<<"B">>, <<"~> 1.4.0">>, undefined,
?PACKAGE_TABLE, State)).
Expand All @@ -358,6 +362,7 @@ ignore_match_in_excluded_repo(Config) ->
?assertMatch({ok,{package,{<<"B">>, {{1,4,6}, {[],[]}}, Hexpm},
<<"some checksum">>, #{reason := 'RETIRED_INVALID'}, []},
#{name := Hexpm,
http_adapter := rebar_httpc_adapter,
http_adapter_config := #{profile := rebar}}},
rebar_packages:resolve_version(<<"B">>, <<"~> 1.4.0">>, undefined,
?PACKAGE_TABLE, State)),
Expand All @@ -366,6 +371,7 @@ ignore_match_in_excluded_repo(Config) ->
?assertMatch({ok,{package,{<<"A">>, {{0,1,1}, {[],[]}}, Repo2},
<<"good checksum">>, false, []},
#{name := Repo2,
http_adapter := rebar_httpc_adapter,
http_adapter_config := #{profile := rebar}}},
rebar_packages:resolve_version(<<"A">>, <<"0.1.1">>, <<"good checksum">>,
?PACKAGE_TABLE, State)).
Expand All @@ -376,13 +382,15 @@ optional_prereleases(Config) ->
?assertMatch({ok,{package,{<<"B">>, {{1,5,0}, {[],[]}}, Hexpm},
<<"some checksum">>, false, []},
#{name := Hexpm,
http_adapter := rebar_httpc_adapter,
http_adapter_config := #{profile := rebar}}},
rebar_packages:resolve_version(<<"B">>, <<"~> 1.5.0">>, undefined,
?PACKAGE_TABLE, State)),

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

0 comments on commit f850e7b

Please sign in to comment.