Skip to content

Commit

Permalink
Migrate to an umbrella structure
Browse files Browse the repository at this point in the history
This is a prerequisite for vendoring and demands that we move all source
files around, and update the helper scripts (like bootstrap) to work
with it.

This should have no consequence on rebar3 users aside from needing to
fetch a git_subdir if they need the content for it.
  • Loading branch information
ferd committed Jul 19, 2022
1 parent 017c7fc commit 7a97040
Show file tree
Hide file tree
Showing 262 changed files with 107 additions and 91 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.
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.
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.
13 changes: 7 additions & 6 deletions bootstrap
Original file line number Diff line number Diff line change
Expand Up @@ -194,8 +194,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 +242,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 @@ -641,12 +642,12 @@ get_deps() ->
%% 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"),
{ok, Config} = file:consult("apps/rebar/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"),
{ok, Config} = file:consult("apps/rebar/rebar.config"),
proplists:get_value(deps, Config)
end.

Expand Down
83 changes: 4 additions & 79 deletions rebar.config
Original file line number Diff line number Diff line change
@@ -1,26 +1,8 @@
%% -*- 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
]}.

%% The rest of the config is in apps/rebar/
{escript_main_app, rebar}.
{escript_name, rebar3}.
{escript_wrappers_windows, ["cmd", "powershell"]}.
{escript_comment, "%%Rebar3 3.19.0\n"}.
Expand All @@ -30,65 +12,8 @@
{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]}
]
},
{systest, [
{ profiles, [{systest, [
{erl_opts, [debug_info, nowarn_export_all]},
{ct_opts, [{dir, "systest"}]}
]},

{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]}]}]}
]}
]}.

]}.
4 changes: 2 additions & 2 deletions systest/all_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -72,10 +72,10 @@ grisp_explode() ->
[{doc, "Don't force purge a plugin that runs the compile job itself"}].
grisp_explode(Config) ->
%% When the purge handling is wrong, the run fails violently.
{error, {_,Output}} = rebar3("grisp deploy -n robot -v 0.1.0", Config),
{error, {_,Output}} = rebar3("grisp deploy -n mygrispproject -v 0.1.0", Config),
ct:pal("Rebar3 Output:~n~s",[Output]),
?assertNotEqual(nomatch,
re:run(Output, "No releases exist in the system for robot:0.1.0!")
re:run(Output, "No releases exist in the system for mygrispproject:0.1.0!")
),
ok.

Expand Down
4 changes: 2 additions & 2 deletions systest/all_SUITE_data/grisp_explode/rebar.config
Original file line number Diff line number Diff line change
@@ -1,11 +1,11 @@
{deps, [grisp]}.

{plugins, [{rebar3_grisp, "0.1.0"}]}.
{plugins, [{rebar3_grisp, "2.3.0"}]}.

{erl_opts, [debug_info]}.

{grisp, [
{otp_release, "19"},
{otp, [{version, "23.0"}]},
{deploy, [
{destination, "/path/to/SD-card"}
]}
Expand Down
2 changes: 1 addition & 1 deletion vendor_hex_core.sh
Original file line number Diff line number Diff line change
Expand Up @@ -6,7 +6,7 @@ if [[ -z "$1" ]]; then
exit 1
fi

REBAR3_TOP=$(pwd)
REBAR3_TOP=$(pwd)/apps/rebar
export REBAR3_TOP
pushd "$1"
touch proto/* # force re-generation of protobuf elements
Expand Down

0 comments on commit 7a97040

Please sign in to comment.