Skip to content

Commit

Permalink
Merge pull request #31 from tsloughter/profiles
Browse files Browse the repository at this point in the history
Profiles
  • Loading branch information
tsloughter committed Dec 2, 2014
2 parents 8d655d3 + 3af351c commit 3b2d9ba
Show file tree
Hide file tree
Showing 39 changed files with 549 additions and 480 deletions.
2 changes: 1 addition & 1 deletion doc/plugins.md
Original file line number Diff line number Diff line change
Expand Up @@ -220,7 +220,7 @@ And then we can implement the switch to figure out what to search:
do(State) ->
Apps = case discovery_type(State) of
project -> rebar_state:project_apps(State);
deps -> rebar_state:project_apps(State) ++ rebar_state:src_deps(State)
deps -> rebar_state:project_apps(State) ++ rebar_state:all_deps(State)
end,
lists:foreach(fun check_todo_app/1, Apps),
{ok, State}.
Expand Down
2 changes: 1 addition & 1 deletion priv/templates/release.template
Original file line number Diff line number Diff line change
Expand Up @@ -6,7 +6,7 @@
{template, "app.erl.dtl", "{{name}}/{{apps_dir}}/{{name}}/src/{{name}}_app.erl"}.
{template, "sup.erl.dtl", "{{name}}/{{apps_dir}}/{{name}}/src/{{name}}_sup.erl"}.
{template, "otp_app.app.src.dtl", "{{name}}/{{apps_dir}}/{{name}}/src/{{name}}.app.src"}.
{template, "rebar.config.dtl", "{{name}}/rebar.config"}.
{template, "relx_rebar.config.dtl", "{{name}}/rebar.config"}.
{template, "relx.config.dtl", "{{name}}/relx.config"}.
{template, "sys.config.dtl", "{{name}}/config/sys.config"}.
{template, "vm.args.dtl", "{{name}}/config/vm.args"}.
Expand Down
12 changes: 0 additions & 12 deletions priv/templates/relx.config.dtl

This file was deleted.

20 changes: 20 additions & 0 deletions priv/templates/relx_rebar.config.dtl
Original file line number Diff line number Diff line change
@@ -0,0 +1,20 @@
{erl_opts, [debug_info]}.
{deps, []}.

{relx, [{release, {'{{name}}', "0.1.0"},
[{{name}},
sasl]},

{sys_config, "./config/sys.config"},
{vm_args, "./config/vm.args"},

{dev_mode, true},
{include_erts, false},

{extended_start_script, true}]
}.

{profiles, [{prod, [{relx, [{dev_mode, true},
{include_erts, false},]}]
}]
}.
11 changes: 1 addition & 10 deletions rebar.config
Original file line number Diff line number Diff line change
Expand Up @@ -17,22 +17,13 @@
debug_info,
warnings_as_errors]}.

%% Types dict:dict() and digraph:digraph() have been introduced in Erlang 17.
%% At the same time, their counterparts dict() and digraph() are to be
%% deprecated in Erlang 18. namespaced_types option is used to select proper
%% type name depending on the OTP version used.
{erl_opts,
[
{platform_define, "^[0-9]+", namespaced_types}
]}.

{deps, [
{erlware_commons, ".*",
{git, "https://github.com/erlware/erlware_commons.git",
{branch, "master"}}},
{providers, "",
{git, "https://github.com/tsloughter/providers.git",
{branch, "format_error1"}}},
{branch, "master"}}},
{erlydtl, ".*",
{git, "https://github.com/erlydtl/erlydtl.git",
{tag, "0.9.4"}}},
Expand Down
3 changes: 1 addition & 2 deletions src/rebar.app.src
Original file line number Diff line number Diff line change
Expand Up @@ -41,7 +41,6 @@
rebar_prv_release,
rebar_prv_version,
rebar_prv_common_test,
rebar_prv_help,
rebar_prv_test_deps]}
rebar_prv_help]}
]}
]}.
10 changes: 6 additions & 4 deletions src/rebar.hrl
Original file line number Diff line number Diff line change
Expand Up @@ -13,11 +13,13 @@

-define(FMT(Str, Args), lists:flatten(io_lib:format(Str, Args))).

-define(DEFAULT_BASE_DIR, "").
-define(DEFAULT_BASE_DIR, "_build").
-define(DEFAULT_PROFILE_DIR, "default").
-define(DEFAULT_LIB_DIRS, ["_checkouts", "apps", "lib", "."]).
-define(DEFAULT_DEPS_DIR, "_deps").
-define(DEFAULT_PLUGINS_DIR, "_plugins").
-define(DEFAULT_TEST_DEPS_DIR, "_tdeps").
-define(DEFAULT_DEPS_DIR, "lib").
-define(DEFAULT_PLUGINS_DIR, "plugins").
-define(DEFAULT_TEST_DEPS_DIR, "test/lib").
-define(DEFAULT_RELEASE_DIR, "rel").
-define(DEFAULT_CONFIG_FILE, "rebar.config").
-define(LOCK_FILE, "rebar.lock").
-define(CONFIG_DIR, ".rebar3").
Expand Down
45 changes: 26 additions & 19 deletions src/rebar3.erl
Original file line number Diff line number Diff line change
Expand Up @@ -74,15 +74,15 @@ main(Args) ->
run(BaseState, Command) ->
_ = application:load(rebar),
BaseState1 = rebar_state:set(BaseState, task, Command),
run_aux(BaseState1, [Command]).
run_aux(BaseState1, [], [Command]).

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

run(RawArgs) ->
_ = application:load(rebar),
BaseConfig = init_config(),
{GlobalPluginProviders, BaseConfig} = init_config(),

case erlang:system_info(version) of
"6.1" ->
Expand All @@ -93,9 +93,9 @@ run(RawArgs) ->
end,

{BaseConfig1, _Args1} = set_options(BaseConfig, {[], []}),
run_aux(BaseConfig1, RawArgs).
run_aux(BaseConfig1, GlobalPluginProviders, RawArgs).

run_aux(State, RawArgs) ->
run_aux(State, GlobalPluginProviders, RawArgs) ->
%% Make sure crypto is running
case crypto:start() of
ok -> ok;
Expand All @@ -106,23 +106,28 @@ run_aux(State, RawArgs) ->
application:start(ssl),
inets:start(),

%% Process each command, resetting any state between each one
State2 = case rebar_state:get(State, base_dir, undefined) of
undefined ->
rebar_state:set(State, base_dir, filename:absname(rebar_state:dir(State)));
Dir ->
rebar_state:set(State, base_dir, filename:absname(Dir))
State2 = case os:getenv("REBAR_DEFAULT_PROFILE") of
false ->
rebar_state:current_profile(State, default);
Profile ->
State1 = rebar_state:current_profile(State, list_to_atom(Profile)),
rebar_state:default(State1, rebar_state:opts(State1))
end,

{ok, Providers} = application:get_env(rebar, providers),
%% Process each command, resetting any state between each one
BaseDir = rebar_dir:base_dir(State2),
State3 = rebar_state:set(State2, base_dir,
filename:join(filename:absname(rebar_state:dir(State2)), BaseDir)),

{ok, PluginProviders, State3} = rebar_plugins:install(State2),
rebar_core:update_code_path(State3),
{ok, Providers} = application:get_env(rebar, providers),
{ok, PluginProviders, State4} = rebar_plugins:install(State3),
rebar_core:update_code_path(State4),

State4 = rebar_state:create_logic_providers(Providers++PluginProviders, State3),
AllProviders = Providers++PluginProviders++GlobalPluginProviders,
State5 = rebar_state:create_logic_providers(AllProviders, State4),
{Task, Args} = parse_args(RawArgs),

rebar_core:process_command(rebar_state:command_args(State4, Args), list_to_atom(Task)).
rebar_core:process_command(rebar_state:command_args(State5, Args), list_to_atom(Task)).

init_config() ->
%% Initialize logging system
Expand All @@ -144,15 +149,17 @@ init_config() ->
end,

%% If $HOME/.rebar3/config exists load and use as global config
Home = rebar_utils:home_dir(),
Home = rebar_dir:home_dir(),
GlobalConfigFile = filename:join([Home, ?CONFIG_DIR, "config"]),
State = case filelib:is_regular(GlobalConfigFile) of
true ->
?DEBUG("Load global config file ~p",
[GlobalConfigFile]),
GlobalConfig = rebar_state:new(rebar_config:consult_file(GlobalConfigFile)),
rebar_state:new(GlobalConfig, Config1);
GlobalConfig = rebar_state:new(global, rebar_config:consult_file(GlobalConfigFile)),
{ok, PluginProviders, GlobalConfig1} = rebar_plugins:install(GlobalConfig),
rebar_state:new(GlobalConfig1, Config1);
false ->
PluginProviders = [],
rebar_state:new(Config1)
end,

Expand All @@ -168,7 +175,7 @@ init_config() ->

%% TODO: Do we need this still? I think it may still be used.
%% Initialize vsn cache
rebar_state:set(State1, vsn_cache, dict:new()).
{PluginProviders, rebar_state:set(State1, vsn_cache, dict:new())}.

%%
%% Parse command line arguments using getopt and also filtering out any
Expand Down
2 changes: 1 addition & 1 deletion src/rebar_app_discover.erl
Original file line number Diff line number Diff line change
Expand Up @@ -124,7 +124,7 @@ create_app_info(AppDir, AppFile) ->
C = rebar_config:consult(AppDir),
S = rebar_state:new(rebar_state:new(), C, AppDir),
AppDeps = rebar_state:deps_names(S),
AbsCwd = filename:absname(rebar_utils:get_cwd()),
AbsCwd = filename:absname(rebar_dir:get_cwd()),
{ok, AppInfo} = rebar_app_info:new(AppName, AppVsn, AppDir, AppDeps),
RebarConfig = filename:join(AppDir, "rebar.config"),
AppState = case filelib:is_file(RebarConfig) of
Expand Down
2 changes: 1 addition & 1 deletion src/rebar_app_utils.erl
Original file line number Diff line number Diff line change
Expand Up @@ -56,7 +56,7 @@ find(Name, Vsn, Apps) ->

-spec is_app_dir() -> {true, file:name()} | false.
is_app_dir() ->
is_app_dir(rebar_utils:get_cwd()).
is_app_dir(rebar_dir:get_cwd()).

-spec is_app_dir(file:name()) -> {true, file:name()} | false.
is_app_dir(Dir) ->
Expand Down
9 changes: 2 additions & 7 deletions src/rebar_base_compiler.erl
Original file line number Diff line number Diff line change
Expand Up @@ -258,10 +258,5 @@ format_error(AbsSource, Extra, {Mod, Desc}) ->
ErrorDesc = Mod:format_error(Desc),
?FMT("~s: ~s~s~n", [AbsSource, Extra, ErrorDesc]).

maybe_absname(Config, Filename) ->
case rebar_utils:processing_base_dir(Config) of
true ->
Filename;
false ->
filename:absname(Filename)
end.
maybe_absname(_Config, Filename) ->
Filename.
32 changes: 17 additions & 15 deletions src/rebar_core.erl
Original file line number Diff line number Diff line change
Expand Up @@ -40,40 +40,42 @@ process_command(State, Command) ->
not_found ->
{error, io_lib:format("Command ~p not found", [Command])};
CommandProvider ->
Profile = providers:profile(CommandProvider),
State1 = rebar_state:current_profile(State, Profile),
Opts = providers:opts(CommandProvider)++rebar3:global_option_spec_list(),
case Command of
do ->
do(TargetProviders, State);
do(TargetProviders, State1);
_ ->
case getopt:parse(Opts, rebar_state:command_args(State)) of
case getopt:parse(Opts, rebar_state:command_args(State1)) of
{ok, Args} ->
State2 = rebar_state:command_parsed_args(State, Args),
do(TargetProviders, State2);
State3 = rebar_state:command_parsed_args(State1, Args),
do(TargetProviders, State3);
{error, {invalid_option, Option}} ->
{error, io_lib:format("Invalid option ~s on task ~p", [Option, Command])}
end
end
end.

-spec do([atom()], rebar_state:t()) -> {ok, rebar_state:t()} | {error, string()}.
-spec do([{atom(), atom()}], rebar_state:t()) -> {ok, rebar_state:t()} | {error, string()}.
do([], State) ->
{ok, State};
do([ProviderName | Rest], State) ->
do([{ProviderName, Profile} | Rest], State) ->
State1 = rebar_state:current_profile(State, Profile),
Provider = providers:get_provider(ProviderName
,rebar_state:providers(State)),
case providers:do(Provider, State) of
{ok, State1} ->
do(Rest, State1);
,rebar_state:providers(State1)),
case providers:do(Provider, State1) of
{ok, State2} ->
do(Rest, State2);
{error, Error} ->
{error, Error}
end.

update_code_path(State) ->
true = rebar_utils:expand_code_path(),
BaseDir = rebar_state:get(State, base_dir, ?DEFAULT_BASE_DIR),
LibDirs = rebar_state:get(State, lib_dirs, ?DEFAULT_LIB_DIRS),
DepsDir = filename:join(BaseDir, rebar_state:get(State, deps_dir, ?DEFAULT_DEPS_DIR)),
PluginsDir = filename:join(BaseDir, rebar_state:get(State, plugins_dir, ?DEFAULT_PLUGINS_DIR)),
LibDirs = rebar_dir:lib_dirs(State),
DepsDir = rebar_dir:deps_dir(State),
PluginsDir = rebar_dir:plugins_dir(State),
_UpdatedCodePaths = update_code_path_([DepsDir, PluginsDir | LibDirs]).


Expand All @@ -82,7 +84,7 @@ update_code_path(State) ->
%% ===================================================================

update_code_path_(Paths) ->
LibPaths = expand_lib_dirs(Paths, rebar_utils:get_cwd(), []),
LibPaths = expand_lib_dirs(Paths, rebar_dir:get_cwd(), []),
ok = code:add_pathsa(LibPaths),
%% track just the paths we added, so we can remove them without
%% removing other paths added by this dep
Expand Down
4 changes: 2 additions & 2 deletions src/rebar_cover_utils.erl
Original file line number Diff line number Diff line change
Expand Up @@ -78,7 +78,7 @@ init(true, BeamFiles, TargetDir) ->

group_leader(F, CoverPid),

?INFO("Cover compiling ~s\n", [rebar_utils:get_cwd()]),
?INFO("Cover compiling ~s\n", [rebar_dir:get_cwd()]),

Compiled = [{Beam, cover:compile_beam(Beam)} || Beam <- BeamFiles],
case [Module || {_, {ok, Module}} <- Compiled] of
Expand Down Expand Up @@ -121,7 +121,7 @@ analyze(Config, FilteredModules, SrcModules, TargetDir) ->
[html])
end, Coverage),

Index = filename:join([rebar_utils:get_cwd(), TargetDir, "index.html"]),
Index = filename:join([rebar_dir:get_cwd(), TargetDir, "index.html"]),
?CONSOLE("Cover analysis: ~s\n", [Index]),

%% Export coverage data, if configured
Expand Down
12 changes: 9 additions & 3 deletions src/rebar_digraph.erl
Original file line number Diff line number Diff line change
Expand Up @@ -32,9 +32,15 @@ add(Graph, {PkgName, Deps}) ->
end,

lists:foreach(fun(DepName) ->
V3 = case digraph:vertex(Graph, DepName) of
case DepName of
{Name, _Vsn} ->
Name;
Name ->
Name
end,
V3 = case digraph:vertex(Graph, Name) of
false ->
digraph:add_vertex(Graph, DepName);
digraph:add_vertex(Graph, Name);
{V2, []} ->
V2
end,
Expand Down Expand Up @@ -94,5 +100,5 @@ names_to_apps(Names, Apps) ->
-spec find_app_by_name(atom(), [rebar_app_info:t()]) -> {ok, rebar_app_info:t()} | error.
find_app_by_name(Name, Apps) ->
ec_lists:find(fun(App) ->
ec_cnv:to_atom(rebar_app_info:name(App)) =:= ec_cnv:to_atom(Name)
binary_to_atom(rebar_app_info:name(App), utf8) =:= binary_to_atom(Name, utf8)
end, Apps).

0 comments on commit 3b2d9ba

Please sign in to comment.