Skip to content

Commit

Permalink
Merge pull request #2720 from ferd/vendor-structure
Browse files Browse the repository at this point in the history
Vendor structure
  • Loading branch information
ferd authored Jul 19, 2022
2 parents 017c7fc + f24df6a commit a2ea0c5
Show file tree
Hide file tree
Showing 400 changed files with 26,053 additions and 199 deletions.
2 changes: 1 addition & 1 deletion .gitignore
Original file line number Diff line number Diff line change
Expand Up @@ -24,4 +24,4 @@ ebin
env

# hex_core artifact
src/vendored/r3_safe_erl_term.erl
apps/rebar/src/vendored/r3_safe_erl_term.erl
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
90 changes: 90 additions & 0 deletions apps/rebar/rebar.config
Original file line number Diff line number Diff line change
@@ -0,0 +1,90 @@
%% -*- mode: erlang;erlang-indent-level: 4;indent-tabs-mode: nil -*-
%% ex: ts=4 sw=4 ft=erlang et

{deps, [{erlware_commons, "1.5.0"},
{ssl_verify_fun, "1.1.6"},
{certifi, "2.9.0"},
{providers, "1.9.0"},
{getopt, "1.0.1"},
{bbmustache, "1.12.2"},
{relx, "4.7.0"},
{cf, "0.3.1"},
{cth_readable, "1.5.1"},
{eunit_formatters, "0.5.0"}]}.

{post_hooks, [{"(linux|darwin|solaris|freebsd|netbsd|openbsd)",
escriptize,
"cp \"$REBAR_BUILD_DIR/bin/rebar3\" ./rebar3"},
{"win32",
escriptize,
"robocopy \"%REBAR_BUILD_DIR%/bin/\" ./ rebar3* "
"/njs /njh /nfl /ndl & exit /b 0"} % silence things
]}.

{escript_name, rebar3}.
{escript_wrappers_windows, ["cmd", "powershell"]}.
{escript_comment, "%%Rebar3 3.19.0\n"}.
{escript_emu_args, "%%! +sbtu +A1\n"}.
%% escript_incl_priv is for internal rebar-private use only.
%% Do not use outside rebar. Config interface is not stable.
{escript_incl_priv, [{relx, "templates/*"},
{rebar, "templates/*"}]}.

{overrides, [{add, relx, [{erl_opts, [{d, 'RLX_LOG', rebar_log}]}]}]}.

{erl_opts, [warnings_as_errors,
{platform_define, "^(2[1-9])|(20\\\\.3)", filelib_find_source},
{platform_define, "^(1|(20))", no_customize_hostname_check},
{platform_define, "^(20)", fun_stacktrace}
]}.

{edoc_opts, [preprocess]}.

%% Use OTP 23+ when dialyzing rebar3
{dialyzer, [
{warnings, [unknown]},
{plt_extra_apps, [parsetools, public_key]}
]}.

%% Keep only the logs of the last 5 runs
{ct_opts, [{keep_logs, 5}]}.

%% Profiles
{profiles, [{test, [
{deps, [{meck, "0.8.13"}]},
{erl_opts, [debug_info, nowarn_export_all]}
]
},

{dialyzer, [
{erl_opts, [debug_info, nowarn_export_all]}
]},

{bootstrap, []},

{prod, [
{erl_opts, [no_debug_info]},
{overrides, [
{override, erlware_commons, [
{erl_opts, [{platform_define, "^[0-9]+", namespaced_types},
{platform_define, "^R1[4|5]", deprecated_crypto},
{platform_define, "^((1[8|9])|2)", rand_module},
{platform_define, "^2", unicode_str},
{platform_define, "^(R|1|20)", fun_stacktrace},
no_debug_info,
warnings_as_errors]},
{deps, []}, {plugins, []}]},
{add, ssl_verify_hostname, [{erl_opts, [no_debug_info]}]},
{add, certifi, [{erl_opts, [no_debug_info]}]},
{add, cf, [{erl_opts, [no_debug_info]}]},
{add, cth_readable, [{erl_opts, [no_debug_info]}]},
{add, eunit_formatters, [{erl_opts, [no_debug_info]}]},
{override, bbmustache, [
{erl_opts, [no_debug_info, {platform_define, "^[0-9]+", namespaced_types}]},
{deps, []}, {plugins, []}]},
{add, getopt, [{erl_opts, [no_debug_info]}]},
{add, providers, [{erl_opts, [no_debug_info]}]},
{add, relx, [{erl_opts, [no_debug_info]}]}]}
]}
]}.

File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
Original file line number Diff line number Diff line change
Expand Up @@ -246,6 +246,8 @@ get_files(State, Apps, SkipApps, Mods, SkipMods, ExtraDirs) ->
Files1 = extras_files(BaseDir, ExtraDirs, Files0),
ExcludeMods = get_config(State, exclude_mods, []),
Files2 = mods_files(Mods, ExcludeMods ++ SkipMods, Files1),
?DEBUG("{dialyzer, [{exclude_apps, ~p}, {exclude_mods, ~p}]}.",
[ExcludeApps, ExcludeMods]),
dict:fold(fun(_, File, Acc) -> [File | Acc] end, [], Files2).

apps_files([], _, _ExtraDirs, Files) ->
Expand Down
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
16 changes: 10 additions & 6 deletions src/rebar_prv_vendor.erl → apps/rebar/src/rebar_prv_vendor.erl
Original file line number Diff line number Diff line change
Expand Up @@ -137,9 +137,13 @@ check_project_layout(State) ->

vendor_plugins(State, PluginVDir) ->
PluginDir = rebar_dir:plugins_dir(State),
{ok, Files} = file:list_dir_all(PluginDir),
[rebar_file_utils:mv(Path, filename:join(PluginVDir, PathPart))
|| PathPart <- Files,
Path <- [filename:join(PluginDir, PathPart)],
filelib:is_dir(Path)],
ok.
case file:list_dir_all(PluginDir) of
{ok, Files} ->
[rebar_file_utils:mv(Path, filename:join(PluginVDir, PathPart))
|| PathPart <- Files,
Path <- [filename:join(PluginDir, PathPart)],
filelib:is_dir(Path)],
ok;
{error, enoent} ->
ok
end.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.
91 changes: 18 additions & 73 deletions bootstrap
Original file line number Diff line number Diff line change
Expand Up @@ -89,12 +89,12 @@ ensure_app(App) ->
end.

fetch_and_compile({Name, ErlFirstFiles}, Deps) ->
case lists:keyfind(Name, 1, Deps) of
{Name, Vsn} ->
ok = fetch({pkg, atom_to_binary(Name, utf8), list_to_binary(Vsn)}, Name);
{Name, _, Source} ->
ok = fetch(Source, Name)
end,
%% Use vendored dependencies, don't hit the network; to update
%% dependencies first bootstrap, then use the escript to do
%% fancier dep management.
filelib:ensure_dir("_build/default/lib/.touch"),
[cp_r([DepDir], "_build/default/lib/")
|| {Dep, DepDir} <- Deps, atom_to_list(Name) =:= Dep],

%% Hack: erlware_commons depends on a .script file to check if it is being built with
%% rebar2 or rebar3. But since rebar3 isn't built yet it can't get the vsn with get_key.
Expand All @@ -103,51 +103,6 @@ fetch_and_compile({Name, ErlFirstFiles}, Deps) ->

compile(Name, ErlFirstFiles).

fetch({pkg, Name, Vsn}, App) ->
Dir = filename:join([filename:absname("_build/default/lib/"), App]),
case filelib:is_dir(Dir) of
false ->
CDN = "https://repo.hex.pm/tarballs",
Package = binary_to_list(<<Name/binary, "-", Vsn/binary, ".tar">>),
Url = join([CDN, Package], "/"),
case request(Url) of
{ok, Binary} ->
{ok, Contents} = extract(Binary),
ok = erl_tar:extract({binary, Contents}, [{cwd, Dir}, compressed]);
{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])
end.

extract(Binary) ->
{ok, Files} = erl_tar:extract({binary, Binary}, [memory]),
{"contents.tar.gz", Contents} = lists:keyfind("contents.tar.gz", 1, Files),
{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, []},
HttpOptions,
[{body_format, binary}],
rebar) of
{ok, {{_Version, 200, _Reason}, _Headers, Body}} ->
{ok, Body};
Error ->
Error
end.

get_rebar_config() ->
{ok, [[Home]]} = init:get_argument(home),
ConfDir = filename:join(Home, ".config/rebar3"),
Expand Down Expand Up @@ -194,8 +149,8 @@ maybe_set_ipfamily(_, _Family) ->
ok.

compile_vendored() ->
compile_xrl_file("src/vendored/r3_safe_erl_term.xrl"),
Sources = filelib:wildcard(filename:join(["src/vendored", "*.erl"])),
compile_xrl_file("apps/rebar/src/vendored/r3_safe_erl_term.xrl"),
Sources = filelib:wildcard(filename:join(["apps/rebar/src/vendored", "*.erl"])),
OutDir = filename:absname("_build/bootstrap/lib/rebar/ebin"),
code:add_patha(OutDir),
Opts = [debug_info,{outdir, OutDir}, return | additional_defines()],
Expand Down Expand Up @@ -242,10 +197,11 @@ compile_erl_file(File, Opts) ->
bootstrap_rebar3() ->
filelib:ensure_dir("_build/default/lib/rebar/ebin/dummy.beam"),
code:add_path("_build/default/lib/rebar/ebin/"),
Res = symlink_or_copy(filename:absname("src"),
Res = symlink_or_copy(filename:absname("apps/rebar/src"),
filename:absname("_build/default/lib/rebar/src")),
true = Res == ok orelse Res == exists,
Sources = ["src/rebar_resource_v2.erl", "src/rebar_resource.erl" | filelib:wildcard("src/*.erl") ],
Sources = ["apps/rebar/src/rebar_resource_v2.erl", "apps/rebar/src/rebar_resource.erl"
| filelib:wildcard("apps/rebar/src/*.erl") ],
[compile_erl_file(X, [{outdir, "_build/default/lib/rebar/ebin/"}
,return | additional_defines()]) || X <- Sources],
code:add_patha(filename:absname("_build/default/lib/rebar/ebin")).
Expand Down Expand Up @@ -636,19 +592,8 @@ reset_env() ->
application:load(rebar).

get_deps() ->
case file:consult("rebar.lock") of
{ok, [[]]} ->
%% Something went wrong in a previous build, lock file shouldn't be empty
io:format("Empty list in lock file, deleting rebar.lock~n"),
ok = file:delete("rebar.lock"),
{ok, Config} = file:consult("rebar.config"),
proplists:get_value(deps, Config);
{ok, [Deps]} ->
[{binary_to_atom(Name, utf8), "", Source} || {Name, Source, _Level} <- Deps];
_ ->
{ok, Config} = file:consult("rebar.config"),
proplists:get_value(deps, Config)
end.
{ok, Deps} = file:list_dir("vendor"),
[{Dep, filename:join("vendor", Dep)} || Dep <- Deps].

format_errors(Source, Errors) ->
format_errors(Source, "", Errors).
Expand Down Expand Up @@ -740,11 +685,11 @@ set_proxy_auth(UserInfo) ->
%% password may contain url encoded characters, need to decode them first
put(proxy_auth, [{proxy_auth, {Username, rebar_uri_percent_decode(Password)}}]).

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


%% string:join/2 copy; string:join/2 is getting obsoleted
Expand Down
Loading

0 comments on commit a2ea0c5

Please sign in to comment.