Skip to content

Commit

Permalink
Merge branch 'artempervin-master'
Browse files Browse the repository at this point in the history
  • Loading branch information
ferd committed Dec 1, 2016
2 parents 1766bc3 + 2c155ea commit 5f0658d
Show file tree
Hide file tree
Showing 5 changed files with 91 additions and 12 deletions.
30 changes: 25 additions & 5 deletions bootstrap
Original file line number Diff line number Diff line change
Expand Up @@ -99,8 +99,9 @@ fetch({pkg, Name, Vsn}, App) ->
{ok, Binary} ->
{ok, Contents} = extract(Binary),
ok = erl_tar:extract({binary, Contents}, [{cwd, Dir}, compressed]);
_ ->
io:format("Error: Unable to fetch package ~p ~p~n", [Name, Vsn])
{error, {Reason, _}} ->
ReasonText = re:replace(atom_to_list(Reason), "_", " ", [global,{return,list}]),
io:format("Error: Unable to fetch package ~s ~s: ~s~n", [Name, Vsn, ReasonText])
end;
true ->
io:format("Dependency ~s already exists~n", [Name])
Expand All @@ -112,8 +113,10 @@ extract(Binary) ->
{ok, Contents}.

request(Url) ->
HttpOptions = [{relaxed, true} | get_proxy_auth()],

case httpc:request(get, {Url, []},
[{relaxed, true}],
HttpOptions,
[{body_format, binary}],
rebar) of
{ok, {{_Version, 200, _Reason}, _Headers, Body}} ->
Expand Down Expand Up @@ -147,8 +150,9 @@ set_httpc_options(_, []) ->
ok;

set_httpc_options(Scheme, Proxy) ->
{ok, {_, _, Host, Port, _, _}} = http_uri:parse(Proxy),
httpc:set_options([{Scheme, {{Host, Port}, []}}], rebar).
{ok, {_, UserInfo, Host, Port, _, _}} = http_uri:parse(Proxy),
httpc:set_options([{Scheme, {{Host, Port}, []}}], rebar),
set_proxy_auth(UserInfo).

compile(App, FirstFiles) ->
Dir = filename:join(filename:absname("_build/default/lib/"), App),
Expand Down Expand Up @@ -402,3 +406,19 @@ otp_release1(Rel) ->
binary:bin_to_list(Vsn, {0, Size - 1})
end
end.

set_proxy_auth([]) ->
ok;
set_proxy_auth(UserInfo) ->
Idx = string:chr(UserInfo, $:),
Username = string:sub_string(UserInfo, 1, Idx-1),
Password = string:sub_string(UserInfo, Idx+1),
%% password may contain url encoded characters, need to decode them first
put(proxy_auth, [{proxy_auth, {Username, http_uri:decode(Password)}}]).

get_proxy_auth() ->
case get(proxy_auth) of
undefined -> [];
ProxyAuth -> ProxyAuth
end.

3 changes: 2 additions & 1 deletion src/rebar3.erl
Original file line number Diff line number Diff line change
Expand Up @@ -145,6 +145,8 @@ run_aux(State, RawArgs) ->
rebar_core:init_command(rebar_state:command_args(State10, Args), Task).

init_config() ->
rebar_utils:set_httpc_options(),

%% Initialize logging system
Verbosity = log_level(),
ok = rebar_log:init(command_line, Verbosity),
Expand Down Expand Up @@ -320,7 +322,6 @@ ensure_running(App, Caller) ->
end.

state_from_global_config(Config, GlobalConfigFile) ->
rebar_utils:set_httpc_options(),
GlobalConfigTerms = rebar_config:consult_file(GlobalConfigFile),
GlobalConfig = rebar_state:new(GlobalConfigTerms),

Expand Down
4 changes: 3 additions & 1 deletion src/rebar_pkg_resource.erl
Original file line number Diff line number Diff line change
Expand Up @@ -107,8 +107,10 @@ make_vsn(_) ->
{error, "Replacing version of type pkg not supported."}.

request(Url, ETag) ->
HttpOptions = [{ssl, ssl_opts(Url)}, {relaxed, true} | rebar_utils:get_proxy_auth()],

case httpc:request(get, {Url, [{"if-none-match", ETag} || ETag =/= false]++[{"User-Agent", rebar_utils:user_agent()}]},
[{ssl, ssl_opts(Url)}, {relaxed, true}],
HttpOptions,
[{body_format, binary}],
rebar) of
{ok, {{_Version, 200, _Reason}, Headers, Body}} ->
Expand Down
24 changes: 21 additions & 3 deletions src/rebar_utils.erl
Original file line number Diff line number Diff line change
Expand Up @@ -70,7 +70,9 @@
info_useless/2,
list_dir/1,
user_agent/0,
reread_config/1]).
reread_config/1,
get_proxy_auth/0]).


%% for internal use only
-export([otp_release/0]).
Expand Down Expand Up @@ -825,8 +827,9 @@ set_httpc_options(_, []) ->
ok;

set_httpc_options(Scheme, Proxy) ->
{ok, {_, _, Host, Port, _, _}} = http_uri:parse(Proxy),
httpc:set_options([{Scheme, {{Host, Port}, []}}], rebar).
{ok, {_, UserInfo, Host, Port, _, _}} = http_uri:parse(Proxy),
httpc:set_options([{Scheme, {{Host, Port}, []}}], rebar),
set_proxy_auth(UserInfo).

url_append_path(Url, ExtraPath) ->
case http_uri:parse(Url) of
Expand Down Expand Up @@ -865,3 +868,18 @@ list_dir(Dir) ->
true -> file:list_dir_all(Dir);
false -> file:list_dir(Dir)
end.

set_proxy_auth([]) ->
ok;
set_proxy_auth(UserInfo) ->
Idx = string:chr(UserInfo, $:),
Username = string:sub_string(UserInfo, 1, Idx-1),
Password = string:sub_string(UserInfo, Idx+1),
%% password may contain url encoded characters, need to decode them first
application:set_env(rebar, proxy_auth, [{proxy_auth, {Username, http_uri:decode(Password)}}]).

get_proxy_auth() ->
case application:get_env(rebar, proxy_auth) of
undefined -> [];
{ok, ProxyAuth} -> ProxyAuth
end.
42 changes: 40 additions & 2 deletions test/rebar_utils_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -31,7 +31,8 @@
nonblacklisted_otp_version/1,
blacklisted_otp_version/1,
sh_does_not_miss_messages/1,
tup_merge/1]).
tup_merge/1,
proxy_auth/1]).

-include_lib("common_test/include/ct.hrl").
-include_lib("eunit/include/eunit.hrl").
Expand All @@ -46,7 +47,8 @@ end_per_testcase(_, _Config) ->
all() ->
[{group, args_to_tasks},
sh_does_not_miss_messages,
tup_merge].
tup_merge,
proxy_auth].

groups() ->
[{args_to_tasks, [], [empty_arglist,
Expand Down Expand Up @@ -272,3 +274,39 @@ tup_merge(_Config) ->
rebar_utils:tup_sort([{a,a},{a,a,a},a,{b,a,a},b,{z,a},{z,a,a},{b,a},z])
)
).

proxy_auth(_Config) ->
proxy_auth(_Config, "http_proxy"),
proxy_auth(_Config, "https_proxy").

proxy_auth(_Config, ProxyEnvKey) ->
Host = "host:",
Port = "1234",

%% remember current proxy specification
OldProxySpec = os:getenv(ProxyEnvKey),

%% proxy auth not set
application:unset_env(rebar, proxy_auth),
?assertEqual([], rebar_utils:get_proxy_auth()),

%% proxy auth with regular username/password
os:putenv(ProxyEnvKey, "http://Username:Password@" ++ Host ++ Port),
rebar_utils:set_httpc_options(),
?assertEqual([{proxy_auth, {"Username", "Password"}}],
rebar_utils:get_proxy_auth()),

%% proxy auth with username missing and url encoded password
os:putenv(ProxyEnvKey, "http://:%3F!abc%23%24@" ++ Host ++ Port),
rebar_utils:set_httpc_options(),
?assertEqual([{proxy_auth, {"", "?!abc#$"}}],
rebar_utils:get_proxy_auth()),

%% restore original proxy specification if any
restore_proxy_env(ProxyEnvKey, OldProxySpec),
application:unset_env(rebar, proxy_auth).

restore_proxy_env(ProxyEnvKey, false) ->
os:putenv(ProxyEnvKey, "");
restore_proxy_env(ProxyEnvKey, ProxySpec) ->
os:putenv(ProxyEnvKey, ProxySpec).

0 comments on commit 5f0658d

Please sign in to comment.