mirror of
https://github.com/erlang/rebar3.git
synced 2025-04-19 02:04:00 +03:00
real bootstrapping
This commit is contained in:
parent
0537a0699d
commit
4374999d95
4
.gitignore
vendored
4
.gitignore
vendored
@ -1,8 +1,9 @@
|
||||
rebar3
|
||||
_build
|
||||
.depsolver_plt
|
||||
*.beam
|
||||
test/*_data
|
||||
logs
|
||||
rebar3
|
||||
/rebar
|
||||
*~
|
||||
*.orig
|
||||
@ -13,6 +14,5 @@ rebar3
|
||||
/.eunit
|
||||
/deps
|
||||
/.rebar
|
||||
rebar.lock
|
||||
priv/templates/*.dtl.erl
|
||||
ebin
|
||||
|
@ -3,7 +3,8 @@ otp_release:
|
||||
- 17.0
|
||||
- R16B03-1
|
||||
- R15B03
|
||||
script: make travis
|
||||
before_script: "./bootstrap"
|
||||
script: "./rebar3 ct"
|
||||
branches:
|
||||
only:
|
||||
- master
|
||||
|
129
bootstrap
Executable file
129
bootstrap
Executable file
@ -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.
|
@ -1,66 +0,0 @@
|
||||
#!/usr/bin/env escript
|
||||
%% -*- mode: erlang;erlang-indent-level: 4;indent-tabs-mode: nil -*-
|
||||
%% ex: ft=erlang ts=4 sw=4 et
|
||||
|
||||
main(Args) ->
|
||||
case lists:member("--help", Args) of
|
||||
true ->
|
||||
usage(),
|
||||
halt(0);
|
||||
false ->
|
||||
ok
|
||||
end,
|
||||
|
||||
%% Check for force=1 flag to force a rebuild
|
||||
case lists:member("force=1", Args) of
|
||||
true ->
|
||||
rm("ebin/*.beam");
|
||||
false ->
|
||||
rm("ebin/rebar.beam")
|
||||
end,
|
||||
|
||||
%% Extract the system info of the version of OTP we use to compile rebar
|
||||
|
||||
os:cmd("./bootstrap/rebar get-deps compile escriptize"),
|
||||
|
||||
%% Finally, update executable perms for our script on *nix,
|
||||
%% or write out script files on win32.
|
||||
case os:type() of
|
||||
{unix,_} ->
|
||||
[] = os:cmd("chmod u+x rebar3"),
|
||||
ok;
|
||||
{win32,_} ->
|
||||
write_windows_scripts(),
|
||||
ok;
|
||||
_ ->
|
||||
ok
|
||||
end,
|
||||
|
||||
%% Add a helpful message
|
||||
io:format("Congratulations! You now have a self-contained script called"
|
||||
" \"rebar3\" in\n"
|
||||
"your current working directory. "
|
||||
"Place this script anywhere in your path\n"
|
||||
"and you can use rebar to build OTP-compliant apps.\n").
|
||||
|
||||
usage() ->
|
||||
io:format("Usage: bootstrap [OPTION]...~n"),
|
||||
io:format(" force=1 unconditional build~n"),
|
||||
io:format(" debug add debug information~n").
|
||||
|
||||
rm(Path) ->
|
||||
NativePath = filename:nativename(Path),
|
||||
Cmd = case os:type() of
|
||||
{unix,_} -> "rm -f ";
|
||||
{win32,_} -> "del /q "
|
||||
end,
|
||||
[] = os:cmd(Cmd ++ NativePath),
|
||||
ok.
|
||||
|
||||
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("rebar.cmd", CmdScript).
|
BIN
bootstrap/rebar
BIN
bootstrap/rebar
Binary file not shown.
65
rebar.config
65
rebar.config
@ -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]}.
|
||||
@ -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
rebar.lock
Normal file
32
rebar.lock
Normal file
@ -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}].
|
@ -27,6 +27,7 @@
|
||||
-module(rebar3).
|
||||
|
||||
-export([main/1,
|
||||
run/1,
|
||||
run/2,
|
||||
global_option_spec_list/0,
|
||||
init_config/0,
|
||||
|
@ -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) ->
|
||||
|
@ -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.
|
||||
|
@ -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),
|
||||
|
@ -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]),
|
||||
|
@ -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),
|
||||
|
@ -32,7 +32,7 @@ init(State) ->
|
||||
-spec do(rebar_state:t()) -> {ok, rebar_state:t()} | {error, string()}.
|
||||
do(State) ->
|
||||
DepsPaths = rebar_state:code_paths(State, all_deps),
|
||||
code:add_paths(DepsPaths),
|
||||
code:add_pathsa(DepsPaths),
|
||||
|
||||
ProjectApps = rebar_state:project_apps(State),
|
||||
Providers = rebar_state:providers(State),
|
||||
@ -83,7 +83,6 @@ build_app(State, Providers, AppInfo) ->
|
||||
end,
|
||||
|
||||
%% Legacy hook support
|
||||
|
||||
rebar_hooks:run_all_hooks(AppDir, pre, ?PROVIDER, Providers, S),
|
||||
AppInfo1 = compile(S, AppInfo),
|
||||
rebar_hooks:run_all_hooks(AppDir, post, ?PROVIDER, Providers, S),
|
||||
|
@ -64,7 +64,7 @@ short_desc() ->
|
||||
-spec do(rebar_state:t()) -> {ok, rebar_state:t()} | {error, string()}.
|
||||
do(State) ->
|
||||
?INFO("Dialyzer starting, this may take a while...", []),
|
||||
code:add_paths(rebar_state:code_paths(State, all_deps)),
|
||||
code:add_pathsa(rebar_state:code_paths(State, all_deps)),
|
||||
Plt = get_plt_location(State),
|
||||
Apps = rebar_state:project_apps(State),
|
||||
|
||||
|
@ -37,7 +37,7 @@ init(State) ->
|
||||
-spec do(rebar_state:t()) -> {ok, rebar_state:t()} | {error, string()}.
|
||||
do(State) ->
|
||||
?INFO("Performing EUnit tests...", []),
|
||||
code:add_paths(rebar_state:code_paths(State, all_deps)),
|
||||
code:add_pathsa(rebar_state:code_paths(State, all_deps)),
|
||||
%% Run eunit provider prehooks
|
||||
Providers = rebar_state:providers(State),
|
||||
Cwd = rebar_dir:get_cwd(),
|
||||
|
@ -93,7 +93,7 @@ shell(State) ->
|
||||
%% error_logger added by the tty handler
|
||||
ok = remove_error_handler(3),
|
||||
%% Add deps to path
|
||||
code:add_paths(rebar_state:code_paths(State, all_deps)),
|
||||
code:add_pathsa(rebar_state:code_paths(State, all_deps)),
|
||||
%% add project app test paths
|
||||
ok = add_test_paths(State),
|
||||
%% this call never returns (until user quits shell)
|
||||
|
@ -36,7 +36,7 @@ init(State) ->
|
||||
|
||||
-spec do(rebar_state:t()) -> {ok, rebar_state:t()} | {error, string()}.
|
||||
do(State) ->
|
||||
code:add_paths(rebar_state:code_paths(State, all_deps)),
|
||||
code:add_pathsa(rebar_state:code_paths(State, all_deps)),
|
||||
XrefChecks = prepare(State),
|
||||
|
||||
%% Run xref checks
|
||||
|
@ -164,8 +164,8 @@ test_basic_defines(Config) ->
|
||||
AppOpts = proplists:get_value(options, App:module_info(compile), []),
|
||||
SuiteOpts = proplists:get_value(options, Suite:module_info(compile), []),
|
||||
Expect = [{d, some_define}],
|
||||
lists:foreach(fun(Expect) -> true = lists:member(Expect, AppOpts) end, Expect),
|
||||
lists:foreach(fun(Expect) -> true = lists:member(Expect, SuiteOpts) end, Expect).
|
||||
lists:foreach(fun(E) -> true = lists:member(E, AppOpts) end, Expect),
|
||||
lists:foreach(fun(E) -> true = lists:member(E, SuiteOpts) end, Expect).
|
||||
|
||||
test_multi_defines(Config) ->
|
||||
AppDir = ?config(apps, Config),
|
||||
@ -198,10 +198,10 @@ test_multi_defines(Config) ->
|
||||
AppOpts2 = proplists:get_value(options, App2:module_info(compile), []),
|
||||
SuiteOpts2 = proplists:get_value(options, Suite2:module_info(compile), []),
|
||||
Expect = [{d, some_define}],
|
||||
lists:foreach(fun(Expect) -> true = lists:member(Expect, AppOpts1) end, Expect),
|
||||
lists:foreach(fun(Expect) -> true = lists:member(Expect, SuiteOpts1) end, Expect),
|
||||
lists:foreach(fun(Expect) -> true = lists:member(Expect, AppOpts2) end, Expect),
|
||||
lists:foreach(fun(Expect) -> true = lists:member(Expect, SuiteOpts2) end, Expect).
|
||||
lists:foreach(fun(E) -> true = lists:member(E, AppOpts1) end, Expect),
|
||||
lists:foreach(fun(E) -> true = lists:member(E, SuiteOpts1) end, Expect),
|
||||
lists:foreach(fun(E) -> true = lists:member(E, AppOpts2) end, Expect),
|
||||
lists:foreach(fun(E) -> true = lists:member(E, SuiteOpts2) end, Expect).
|
||||
|
||||
test_single_app_flag(Config) ->
|
||||
AppDir = ?config(apps, Config),
|
||||
|
@ -160,7 +160,7 @@ profiles_remain_applied_with_config_present(Config) ->
|
||||
|
||||
rebar_test_utils:create_config(AppDir, RebarConfig),
|
||||
|
||||
{ok, State} = rebar_test_utils:run_and_check(Config, RebarConfig,
|
||||
rebar_test_utils:run_and_check(Config, RebarConfig,
|
||||
["as", "not_ok", "compile"], {ok, [{app, Name}]}),
|
||||
|
||||
Path = filename:join([AppDir, "_build", "not_ok", "lib", Name, "ebin"]),
|
||||
|
Loading…
x
Reference in New Issue
Block a user