Skip to content

Commit

Permalink
Merge pull request #2643 from zuiderkwast/offline-mode
Browse files Browse the repository at this point in the history
Add --offline option and REBAR_OFFLINE environment variable
  • Loading branch information
ferd authored Jun 6, 2022
2 parents f934571 + 4f3bb00 commit fc52e08
Show file tree
Hide file tree
Showing 5 changed files with 91 additions and 17 deletions.
29 changes: 24 additions & 5 deletions bootstrap
Original file line number Diff line number Diff line change
Expand Up @@ -2,14 +2,25 @@
%% -*- mode: erlang;erlang-indent-level: 4;indent-tabs-mode: nil -*-
%% ex: ft=erlang ts=4 sw=4 et

main(_) ->
main(Args) ->
case lists:member("--offline", Args) of
true ->
os:putenv("REBAR_OFFLINE", "1");
false ->
ok
end,
ensure_app(crypto),
ensure_app(asn1),
ensure_app(public_key),
ensure_app(ssl),
inets:start(),
inets:start(httpc, [{profile, rebar}]),
set_httpc_options(),
case os:getenv("REBAR_OFFLINE") of
"1" ->
ok;
_ ->
ensure_app(ssl),
inets:start(),
inets:start(httpc, [{profile, rebar}]),
set_httpc_options()
end,

%% Clear directories for builds since bootstrapping may require
%% a changed structure from an older one
Expand Down Expand Up @@ -117,6 +128,14 @@ extract(Binary) ->
{ok, Contents}.

request(Url) ->
case os:getenv("REBAR_OFFLINE") of
"1" ->
{error, {offline, Url}};
_ ->
request_online(Url)
end.

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

case httpc:request(get, {Url, []},
Expand Down
31 changes: 23 additions & 8 deletions src/rebar3.erl
Original file line number Diff line number Diff line change
Expand Up @@ -177,17 +177,27 @@ run_aux(State, RawArgs) ->
State9 = rebar_state:default(State8, rebar_state:opts(State8)),

{Task, Args} = parse_args(RawArgs),
Offline = case lists:member("--offline", Args) of
true ->
%% We store this redundantly in env, because some APIs
%% don't get a state.
os:putenv("REBAR_OFFLINE", "1"),
true;
false ->
os:getenv("REBAR_OFFLINE") =:= "1"
end,
State10 = rebar_state:set(State9, offline, Offline),

State10 = rebar_state:code_paths(State9, default, code:get_path()),
State11 = rebar_state:code_paths(State10, default, code:get_path()),

case rebar_core:init_command(rebar_state:command_args(State10, Args), Task) of
{ok, State11} ->
case rebar_core:init_command(rebar_state:command_args(State11, Args), Task) of
{ok, State12} ->
case rebar_state:get(State11, caller, command_line) of
api ->
rebar_paths:unset_paths([deps, plugins], State11),
{ok, State11};
{ok, State12};
_ ->
{ok, State11}
{ok, State12}
end;
Other ->
Other
Expand Down Expand Up @@ -377,9 +387,14 @@ start_and_load_apps(Caller) ->
ensure_running(crypto, Caller),
ensure_running(asn1, Caller),
ensure_running(public_key, Caller),
ensure_running(ssl, Caller),
ensure_running(inets, Caller),
inets:start(httpc, [{profile, rebar}]).
case os:getenv("REBAR_OFFLINE") of
"1" ->
ok;
_ ->
ensure_running(ssl, Caller),
ensure_running(inets, Caller),
inets:start(httpc, [{profile, rebar}])
end.

%% @doc Make sure a required app is running, or display an error message
%% and abort if there's a problem.
Expand Down
19 changes: 19 additions & 0 deletions src/rebar_fetch.erl
Original file line number Diff line number Diff line change
Expand Up @@ -50,6 +50,14 @@ download_source(AppInfo, State) ->
end.

download_source_(AppInfo, State) ->
case rebar_state:get(State, offline, false) of
true ->
{error, {?MODULE, offline}};
false ->
download_source_online(AppInfo, State)
end.

download_source_online(AppInfo, State) ->
AppDir = rebar_app_info:dir(AppInfo),
TmpDir = ec_file:insecure_mkdtemp(),
AppDir1 = rebar_utils:to_list(AppDir),
Expand All @@ -68,6 +76,17 @@ download_source_(AppInfo, State) ->
-spec needs_update(rebar_app_info:t(), rebar_state:t())
-> boolean() | {error, string()}.
needs_update(AppInfo, State) ->
case rebar_state:get(State, offline, false) of
true ->
?DEBUG("Can't check if dependency needs updates in offline mode", []),
false;
false ->
needs_update_online(AppInfo, State)
end.

-spec needs_update_online(rebar_app_info:t(), rebar_state:t())
-> boolean() | {error, string()}.
needs_update_online(AppInfo, State) ->
try
rebar_resource_v2:needs_update(AppInfo, State)
catch
Expand Down
16 changes: 12 additions & 4 deletions src/rebar_httpc_adapter.erl
Original file line number Diff line number Diff line change
Expand Up @@ -9,6 +9,18 @@
%%====================================================================

request(Method, URI, ReqHeaders, Body, AdapterConfig) ->
case os:getenv("REBAR_OFFLINE") of
"1" ->
{error, {offline, URI}};
_ ->
request_online(Method, URI, ReqHeaders, Body, AdapterConfig)
end.

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

request_online(Method, URI, ReqHeaders, Body, AdapterConfig) ->
Profile = maps:get(profile, AdapterConfig, default),
Request = build_request(URI, ReqHeaders, Body),
SSLOpts = [{ssl, rebar_utils:ssl_opts(URI)}],
Expand All @@ -19,10 +31,6 @@ request(Method, URI, ReqHeaders, Body, AdapterConfig) ->
{error, Reason} -> {error, Reason}
end.

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

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

Expand Down
13 changes: 13 additions & 0 deletions src/rebar_prv_local_upgrade.erl
Original file line number Diff line number Diff line change
Expand Up @@ -120,6 +120,19 @@ etag(Path) ->
ETag :: false | string(),
Res :: 'error' | {ok, cached} | {ok, any(), string()}.
request(Url, ETag) ->
case os:getenv("REBAR_OFFLINE") of
"1" ->
?DEBUG("Rebar is in offline mode", []),
error;
_ ->
request_online(Url, ETag)
end.

-spec request_online(Url, ETag) -> Res when
Url :: string(),
ETag :: false | string(),
Res :: 'error' | {ok, cached} | {ok, any(), string()}.
request_online(Url, ETag) ->
HttpOptions = [{ssl, rebar_utils:ssl_opts(Url)},
{relaxed, true} | rebar_utils:get_proxy_auth()],
case httpc:request(get, {Url, [{"if-none-match", "\"" ++ ETag ++ "\""}
Expand Down

0 comments on commit fc52e08

Please sign in to comment.