Skip to content

Commit

Permalink
real bootstrapping
Browse files Browse the repository at this point in the history
  • Loading branch information
tsloughter committed Apr 23, 2015
1 parent 0537a06 commit 4374999
Show file tree
Hide file tree
Showing 21 changed files with 228 additions and 106 deletions.
4 changes: 2 additions & 2 deletions .gitignore
Original file line number Diff line number Diff line change
@@ -1,8 +1,9 @@
rebar3
_build
.depsolver_plt
*.beam
test/*_data
logs
rebar3
/rebar
*~
*.orig
Expand All @@ -13,6 +14,5 @@ rebar3
/.eunit
/deps
/.rebar
rebar.lock
priv/templates/*.dtl.erl
ebin
3 changes: 2 additions & 1 deletion .travis.yml
Original file line number Diff line number Diff line change
Expand Up @@ -3,7 +3,8 @@ otp_release:
- 17.0
- R16B03-1
- R15B03
script: make travis
before_script: "./bootstrap"
script: "./rebar3 ct"
branches:
only:
- master
Expand Down
129 changes: 129 additions & 0 deletions bootstrap
Original file line number Diff line number Diff line change
@@ -0,0 +1,129 @@
#!/usr/bin/env escript
%% -*- mode: erlang;erlang-indent-level: 4;indent-tabs-mode: nil -*-
%% ex: ft=erlang ts=4 sw=4 et

main(_Args) ->
%% Fetch and build deps required to build rebar3
BaseDeps = [{providers, []}
,{getopt, []}
,{erlware_commons, ["ec_dictionary.erl", "ec_vsn.erl"]}],
Deps = get_deps(),
[fetch_and_compile(Dep, Deps) || Dep <- BaseDeps],

%% Build rebar3 modules with compile:file
bootstrap_rebar3(),

%% Build rebar.app from rebar.app.src
{ok, App} = rebar_app_info:new(rebar, "3.0.0", filename:absname("_build/default/lib/rebar/")),
rebar_otp_app:compile(rebar_state:new(), App),

%% Because we are compiling files that are loaded already we want to silence
%% not_purged errors in rebar_erlc_compiler:opts_changed/1
error_logger:tty(false),

setup_env(),
os:putenv("REBAR_PROFILE", "bootstrap"),
{ok, State} = rebar3:run(["compile"]),
reset_env(),
os:unsetenv("REBAR_PROFILE"),
%% Build erlydtl files (a hook on compile in the default profile) and escript file
DepsPaths = rebar_state:code_paths(State, all_deps),
code:add_pathsa(DepsPaths),

rebar3:run(["clean", "-a"]),
rebar3:run(["escriptize"]),

%% Done with compile, can turn back on error logger
error_logger:tty(true),

%% Finally, update executable perms for our script on *nix,
%% or write out script files on win32.
ec_file:copy("_build/default/bin/rebar3", "./rebar3"),
case os:type() of
{unix,_} ->
[] = os:cmd("chmod u+x rebar3"),
ok;
{win32,_} ->
write_windows_scripts(),
ok;
_ ->
ok
end.

fetch_and_compile({Name, ErlFirstFiles}, Deps) ->
{Name, _, Repo} = lists:keyfind(Name, 1, Deps),
ok = fetch(Repo, Name),
compile(Name, ErlFirstFiles).

fetch({git, Url, Source}, App) ->
Dir = filename:join([filename:absname("_build/default/lib/"), App]),
case filelib:is_dir(Dir) of
true ->
true = code:add_path(filename:join(Dir, "ebin")),
ok;
false ->
fetch_source(Dir, Url, Source),
ok
end.

fetch_source(Dir, Url, {ref, Ref}) ->
ok = filelib:ensure_dir(Dir),
os:cmd(io_lib:format("git clone ~s ~s", [Url, Dir])),
{ok, Cwd} = file:get_cwd(),
file:set_cwd(Dir),
os:cmd(io_lib:format("git checkout -q ~s", [Ref])),
file:set_cwd(Cwd);
fetch_source(Dir, Url, {_, Branch}) ->
ok = filelib:ensure_dir(Dir),
os:cmd(io_lib:format("git clone ~s ~s -b ~s --single-branch",
[Url, Dir, Branch])).

compile(App, FirstFiles) ->
Dir = filename:join(filename:absname("_build/default/lib/"), App),
filelib:ensure_dir(filename:join([Dir, "ebin", "dummy.beam"])),
code:add_path(filename:join(Dir, "ebin")),
FirstFilesPaths = [filename:join([Dir, "src", Module]) || Module <- FirstFiles],
Sources = FirstFilesPaths ++ filelib:wildcard(filename:join([Dir, "src", "*.erl"])),
[compile:file(X, [{i, filename:join(Dir, "include")}
,{outdir, filename:join(Dir, "ebin")}
,return]) || X <- Sources].

bootstrap_rebar3() ->
filelib:ensure_dir("_build/default/lib/rebar/ebin/dummy.beam"),
filelib:ensure_dir("_build/default/lib/rebar/src/dummy.erl"),
ec_file:copy("src", "_build/default/lib/rebar/src", [recursive]),
Sources = filelib:wildcard("src/*.erl"),
[compile:file(X, [{outdir, "_build/default/lib/rebar/ebin/"}]) || X <- Sources],
code:add_path(filename:absname("_build/default/lib/rebar/ebin")).

setup_env() ->
%% We don't need or want erlydtl or relx providers loaded yet
application:load(rebar),
{ok, Providers} = application:get_env(rebar, providers),
Providers1 = Providers -- [rebar_prv_erlydtl_compiler,
rebar_prv_release,
rebar_prv_tar],
application:set_env(rebar, providers, Providers1).

reset_env() ->
%% Reset the env so we get all providers and can build erlydtl files
application:unset_env(rebar, providers),
application:unload(rebar),
application:load(rebar).

write_windows_scripts() ->
CmdScript=
"@echo off\r\n"
"setlocal\r\n"
"set rebarscript=%~f0\r\n"
"escript.exe \"%rebarscript:.cmd=%\" %*\r\n",
ok = file:write_file("rebar3.cmd", CmdScript).

get_deps() ->
case file:consult("rebar.lock") of
{ok, [Deps]} ->
[{binary_to_atom(Name, utf8), "", Source} || {Name, Source, _Level} <- Deps];
_ ->
{ok, Config} = file:consult("rebar.config"),
proplists:get_value(deps, Config)
end.
File renamed without changes.
66 changes: 0 additions & 66 deletions bootstrap/bootstrap

This file was deleted.

Binary file removed bootstrap/rebar
Binary file not shown.
65 changes: 46 additions & 19 deletions rebar.config
Original file line number Diff line number Diff line change
@@ -1,9 +1,22 @@
%% -*- mode: erlang;erlang-indent-level: 4;indent-tabs-mode: nil -*-
%% ex: ts=4 sw=4 ft=erlang et

%% escript_incl_extra is for internal rebar-private use only.
%% Do not use outside rebar. Config interface is not stable.
{escript_incl_extra, [{"priv/templates/*", "."}, {"rebar/include/*", "."}]}.
{deps, [
{erlware_commons, "",
{git, "https://github.com/erlware/erlware_commons.git",
{branch, "master"}}},
{providers, "",
{git, "https://github.com/tsloughter/providers.git",
{tag, "v1.3.1"}}},
{erlydtl, "",
{git, "https://github.com/erlydtl/erlydtl.git",
{branch, "master"}}},
{relx, "",
{git, "https://github.com/erlware/relx.git",
{branch, "master"}}},
{getopt, "",
{git, "https://github.com/jcomellas/getopt.git",
{branch, "master"}}}]}.

{escript_incl_apps,
[getopt, merl, erlydtl, erlware_commons, relx, providers, rebar]}.
Expand All @@ -18,23 +31,37 @@
debug_info,
warnings_as_errors]}.

{deps, [
{erlware_commons, ".*",
{git, "https://github.com/erlware/erlware_commons.git",
{branch, "master"}}},
{providers, "",
{git, "https://github.com/tsloughter/providers.git",
{tag, "v1.3.1"}}},
{erlydtl, ".*",
{git, "https://github.com/erlydtl/erlydtl.git",
{tag, "0.10.0"}}},
{relx, "",
{git, "https://github.com/erlware/relx.git",
{branch, "master"}}},
{getopt, "", {git, "https://github.com/jcomellas/getopt.git", {branch, "master"}}},
{meck, "", {git, "https://github.com/eproxus/meck.git", {tag, "0.8.2"}}}]}.

{erlydtl_opts, [{doc_root, "priv/templates"},
{compiler_options, [report, return, debug_info]}]}.

{dialyzer_plt_apps, [common_test, dialyzer, erlydtl, eunit, snmp]}.

{provider_hooks, [{post, [{compile, {erlydtl, compile}}]}]}.

%% Profiles
{profiles, [{test,
[{deps, [
{meck, "", {git, "https://github.com/eproxus/meck.git", {tag, "0.8.2"}}}
]}
]
},

%% We don't want erlydtl to attempt to run on the first compile pass to bootstrap
{bootstrap, [{overrides, [{override, relx, [{provider_hooks, [{post, []}]}]}]},
{provider_hooks, [{post, []}]}]}
]}.

%% Overrides
{overrides, [{override, erlware_commons, [{plugins, []}]},
{override, merl, [{pre_hooks, [{"(linux|darwin|solaris)", compile, "make -C \"$REBAR_DEPS_DIR/merl\" all -W test"},
{"(freebsd|netbsd|openbsd)", compile, "gmake -C \"$REBAR_DEPS_DIR/merl\" all"},
{"win32", compile, "make -C \"%REBAR_DEPS_DIR%/merl\" all -W test"},
{eunit,
"erlc -I include/erlydtl_preparser.hrl -o test"
" test/erlydtl_extension_testparser.yrl"},
{"(linux|darwin|solaris)", eunit, "make -C \"$REBAR_DEPS_DIR/merl\" test"},
{"(freebsd|netbsd|openbsd)", eunit, "gmake -C \"$REBAR_DEPS_DIR/merl\" test"},
{"win32", eunit, "make -C \"%REBAR_DEPS_DIR%/merl\" test"}
]}]},
{override, erlydtl, [{pre_hooks, []}]}
]}.
32 changes: 32 additions & 0 deletions rebar.lock
Original file line number Diff line number Diff line change
@@ -0,0 +1,32 @@
[{<<"rebar_vsn_plugin">>,
{git,"https://github.com/erlware/rebar_vsn_plugin.git",
{ref,"fd40c960c7912193631d948fe962e1162a8d1334"}},
1},
{<<"merl">>,
{git,"git://github.com/erlydtl/merl.git",
{ref,"750b09d44425f435ff579a4d28bf5844bb5b4ef1"}},
1},
{<<"eunit_formatters">>,
{git,"git://github.com/seancribbs/eunit_formatters",
{ref,"2c73eb6e46b0863f19507857b386a48a53aaf141"}},
1},
{<<"relx">>,
{git,"https://github.com/erlware/relx.git",
{ref,"3f2462807fe4afb82bc52dd3ff8ff9244aad3bd3"}},
0},
{<<"providers">>,
{git,"https://github.com/tsloughter/providers.git",
{ref,"7563ba7e916d5a35972b25b3aa1945ffe0a8e7a5"}},
0},
{<<"getopt">>,
{git,"https://github.com/jcomellas/getopt.git",
{ref,"626698975e63866156159661d100785d65eab6f9"}},
0},
{<<"erlydtl">>,
{git,"https://github.com/erlydtl/erlydtl.git",
{ref,"a4ac28680d6e066aabf86b3be9f073352a1a4d40"}},
0},
{<<"erlware_commons">>,
{git,"https://github.com/erlware/erlware_commons.git",
{ref,"05b956da26788f30b3cb793fa6ace02b75f481d0"}},
0}].
1 change: 1 addition & 0 deletions src/rebar3.erl
Original file line number Diff line number Diff line change
Expand Up @@ -27,6 +27,7 @@
-module(rebar3).

-export([main/1,
run/1,
run/2,
global_option_spec_list/0,
init_config/0,
Expand Down
2 changes: 1 addition & 1 deletion src/rebar_api.erl
Original file line number Diff line number Diff line change
Expand Up @@ -54,7 +54,7 @@ wordsize() ->

%% Add deps to the code path
add_deps_to_path(State) ->
code:add_paths(rebar_state:code_paths(State, all_deps)).
code:add_pathsa(rebar_state:code_paths(State, all_deps)).

%% Revert to only having the beams necessary for running rebar3 and plugins in the path
restore_code_path(State) ->
Expand Down
1 change: 0 additions & 1 deletion src/rebar_config.erl
Original file line number Diff line number Diff line change
Expand Up @@ -57,7 +57,6 @@ consult_file(File) ->
{ok, Terms} = consult_and_eval(File, Script),
Terms;
false ->
?DEBUG("Consult config file ~p", [File]),
try_consult(File)
end
end.
Expand Down
3 changes: 2 additions & 1 deletion src/rebar_erlc_compiler.erl
Original file line number Diff line number Diff line change
Expand Up @@ -148,7 +148,8 @@ doterl_compile(Config, Dir, OutDir, MoreSources, ErlOpts) ->

%% Make sure that ebin/ exists and is on the path
ok = filelib:ensure_dir(filename:join(OutDir, "dummy.beam")),
true = code:add_path(filename:absname(OutDir)),
true = code:add_patha(filename:absname(OutDir)),

OutDir1 = proplists:get_value(outdir, ErlOpts, OutDir),

G = init_erlcinfo(proplists:get_all_values(i, ErlOpts), AllErlFiles, Dir),
Expand Down
1 change: 0 additions & 1 deletion src/rebar_otp_app.erl
Original file line number Diff line number Diff line change
Expand Up @@ -128,7 +128,6 @@ preprocess(State, AppInfo, AppSrcFile) ->
load_app_vars(State) ->
case rebar_state:get(State, app_vars_file, undefined) of
undefined ->
?DEBUG("No app_vars_file defined.", []),
[];
Filename ->
?INFO("Loading app vars from ~p", [Filename]),
Expand Down
2 changes: 1 addition & 1 deletion src/rebar_prv_common_test.erl
Original file line number Diff line number Diff line change
Expand Up @@ -39,7 +39,7 @@ init(State) ->
do(State) ->
?INFO("Running Common Test suites...", []),

code:add_paths(rebar_state:code_paths(State, all_deps)),
code:add_pathsa(rebar_state:code_paths(State, all_deps)),

%% Run ct provider prehooks
Providers = rebar_state:providers(State),
Expand Down
Loading

0 comments on commit 4374999

Please sign in to comment.