Skip to content

Commit

Permalink
only eval config scripts and apply overrides once per app (#1879)
Browse files Browse the repository at this point in the history
* only eval config scripts and apply overrides once per app

* move new resource behaviour to rebar_resource_v2 and keep v1

* cleanup use of rebar_resource module and unused functions
  • Loading branch information
tsloughter authored Sep 11, 2018
1 parent 24af536 commit 5c08535
Show file tree
Hide file tree
Showing 34 changed files with 646 additions and 482 deletions.
2 changes: 1 addition & 1 deletion bootstrap
Original file line number Diff line number Diff line change
Expand Up @@ -174,7 +174,7 @@ bootstrap_rebar3() ->
Res = symlink_or_copy(filename:absname("src"),
filename:absname("_build/default/lib/rebar/src")),
true = Res == ok orelse Res == exists,
Sources = ["src/rebar_resource.erl" | filelib:wildcard("src/*.erl")],
Sources = ["src/rebar_resource_v2.erl", "src/rebar_resource.erl" | filelib:wildcard("src/*.erl")],
[compile_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
9 changes: 9 additions & 0 deletions src/rebar.hrl
Original file line number Diff line number Diff line change
Expand Up @@ -33,6 +33,10 @@
-define(HEX_AUTH_FILE, "hex.config").
-define(PUBLIC_HEX_REPO, <<"hexpm">>).

%% ignore this function in all modules
%% not every module that exports it and relies on it being called implements provider
-ignore_xref([{format_error, 1}]).

%% the package record is used in a select match spec which upsets dialyzer
%% this is the suggested workaround from Tobias
%% http://erlang.org/pipermail/erlang-questions/2009-February/041445.html
Expand All @@ -46,6 +50,11 @@
dependencies :: [#{package => unicode:unicode_binary(),
requirement => unicode:unicode_binary()}] | ms_field()}).

-record(resource, {type :: atom(),
module :: module(),
state :: term(),
implementation :: rebar_resource | rebar_resource_v2}).

-ifdef(namespaced_types).
-type rebar_dict() :: dict:dict().
-else.
Expand Down
2 changes: 1 addition & 1 deletion src/rebar3.erl
Original file line number Diff line number Diff line change
Expand Up @@ -194,7 +194,7 @@ init_config() ->
?DEBUG("Load global config file ~ts", [GlobalConfigFile]),
try state_from_global_config(Config1, GlobalConfigFile)
catch
_:_->
_:_ ->
?WARN("Global config ~ts exists but can not be read. Ignoring global config values.", [GlobalConfigFile]),
rebar_state:new(Config1)
end;
Expand Down
37 changes: 21 additions & 16 deletions src/rebar_app_discover.erl
Original file line number Diff line number Diff line change
Expand Up @@ -9,8 +9,7 @@
find_apps/2,
find_apps/3,
find_app/2,
find_app/3,
find_app/4]).
find_app/3]).

-include("rebar.hrl").
-include_lib("providers/include/providers.hrl").
Expand Down Expand Up @@ -95,7 +94,7 @@ format_error({missing_module, Module}) ->
merge_deps(AppInfo, State) ->
%% These steps make sure that hooks and artifacts are run in the context of
%% the application they are defined at. If an umbrella structure is used and
%% they are deifned at the top level they will instead run in the context of
%% they are defined at the top level they will instead run in the context of
%% the State and at the top level, not as part of an application.
CurrentProfiles = rebar_state:current_profiles(State),
Default = reset_hooks(rebar_state:default(State), CurrentProfiles),
Expand Down Expand Up @@ -205,7 +204,7 @@ reset_hooks(Opts, CurrentProfiles) ->
-spec all_app_dirs([file:name()]) -> [{file:name(), [file:name()]}].
all_app_dirs(LibDirs) ->
lists:flatmap(fun(LibDir) ->
SrcDirs = find_config_src(LibDir, ["src"]),
{_, SrcDirs} = find_config_src(LibDir, ["src"]),
app_dirs(LibDir, SrcDirs)
end, LibDirs).

Expand Down Expand Up @@ -278,8 +277,9 @@ find_apps(LibDirs, SrcDirs, Validate) ->
%% app info record.
-spec find_app(file:filename_all(), valid | invalid | all) -> {true, rebar_app_info:t()} | false.
find_app(AppDir, Validate) ->
SrcDirs = find_config_src(AppDir, ["src"]),
find_app(rebar_app_info:new(), AppDir, SrcDirs, Validate).
{Config, SrcDirs} = find_config_src(AppDir, ["src"]),
AppInfo = rebar_app_info:update_opts(rebar_app_info:new(), dict:new(), Config),
find_app_(AppInfo, AppDir, SrcDirs, Validate).

%% @doc check that a given app in a directory is there, and whether it's
%% valid or not based on the second argument. Returns the related
Expand All @@ -291,7 +291,7 @@ find_app(AppInfo, AppDir, Validate) ->
%% of src/
AppOpts = rebar_app_info:opts(AppInfo),
SrcDirs = rebar_dir:src_dirs(AppOpts, ["src"]),
find_app(AppInfo, AppDir, SrcDirs, Validate).
find_app_(AppInfo, AppDir, SrcDirs, Validate).

%% @doc check that a given app in a directory is there, and whether it's
%% valid or not based on the second argument. The third argument includes
Expand All @@ -301,6 +301,14 @@ find_app(AppInfo, AppDir, Validate) ->
[file:filename_all()], valid | invalid | all) ->
{true, rebar_app_info:t()} | false.
find_app(AppInfo, AppDir, SrcDirs, Validate) ->
Config = rebar_config:consult(AppDir),
AppInfo1 = rebar_app_info:update_opts(AppInfo, rebar_app_info:opts(AppInfo), Config),
find_app_(AppInfo1, AppDir, SrcDirs, Validate).

-spec find_app_(rebar_app_info:t(), file:filename_all(),
[file:filename_all()], valid | invalid | all) ->
{true, rebar_app_info:t()} | false.
find_app_(AppInfo, AppDir, SrcDirs, Validate) ->
AppFile = filelib:wildcard(filename:join([AppDir, "ebin", "*.app"])),
AppSrcFile = lists:append(
[filelib:wildcard(filename:join([AppDir, SrcDir, "*.app.src"]))
Expand Down Expand Up @@ -331,17 +339,14 @@ create_app_info(AppInfo, AppDir, AppFile) ->
AppInfo2 = rebar_app_info:applications(
rebar_app_info:app_details(AppInfo1, AppDetails),
IncludedApplications++Applications),
C = rebar_config:consult(AppDir),
AppInfo3 = rebar_app_info:update_opts(AppInfo2,
rebar_app_info:opts(AppInfo2), C),
Valid = case rebar_app_utils:validate_application_info(AppInfo3) =:= true
andalso rebar_app_info:has_all_artifacts(AppInfo3) =:= true of
Valid = case rebar_app_utils:validate_application_info(AppInfo2) =:= true
andalso rebar_app_info:has_all_artifacts(AppInfo2) =:= true of
true ->
true;
_ ->
false
end,
rebar_app_info:dir(rebar_app_info:valid(AppInfo3, Valid), AppDir).
rebar_app_info:dir(rebar_app_info:valid(AppInfo2, Valid), AppDir).

%% @doc Read in and parse the .app file if it is availabe. Do the same for
%% the .app.src file if it exists.
Expand Down Expand Up @@ -408,7 +413,7 @@ try_handle_app_src_file(_AppInfo, _, _AppDir, [], _Validate) ->
try_handle_app_src_file(_AppInfo, _, _AppDir, _AppSrcFile, valid) ->
false;
try_handle_app_src_file(AppInfo, _, AppDir, [File], Validate) when Validate =:= invalid
; Validate =:= all ->
; Validate =:= all ->
AppInfo1 = rebar_app_info:app_file(AppInfo, undefined),
AppInfo2 = create_app_info(AppInfo1, AppDir, File),
case filename:extension(File) of
Expand Down Expand Up @@ -437,8 +442,8 @@ to_atom(Bin) ->
find_config_src(AppDir, Default) ->
case rebar_config:consult(AppDir) of
[] ->
Default;
{[], Default};
Terms ->
%% TODO: handle profiles I guess, but we don't have that info
proplists:get_value(src_dirs, Terms, Default)
{Terms, proplists:get_value(src_dirs, Terms, Default)}
end.
37 changes: 32 additions & 5 deletions src/rebar_app_info.erl
Original file line number Diff line number Diff line change
Expand Up @@ -7,6 +7,7 @@
new/4,
new/5,
update_opts/3,
update_opts_deps/2,
discover/1,
name/1,
name/2,
Expand Down Expand Up @@ -53,6 +54,8 @@
is_checkout/2,
valid/1,
valid/2,
is_available/1,
is_available/2,

verify_otp_vsn/1,
has_all_artifacts/1,
Expand Down Expand Up @@ -87,7 +90,8 @@
source :: string() | tuple() | checkout | undefined,
is_lock=false :: boolean(),
is_checkout=false :: boolean(),
valid :: boolean() | undefined}).
valid :: boolean() | undefined,
is_available=false :: boolean()}).

%%============================================================================
%% types
Expand Down Expand Up @@ -152,8 +156,10 @@ new(Parent, AppName, Vsn, Dir, Deps) ->
update_opts(AppInfo, Opts, Config) ->
LockDeps = case resource_type(AppInfo) of
pkg ->
Deps = deps(AppInfo),
[{{locks, default}, Deps}, {{deps, default}, Deps}];
%% Deps are set separate for packages
%% instead of making it seem we have no deps
%% don't set anything here.
[];
_ ->
deps_from_config(dir(AppInfo), Config)
end,
Expand All @@ -165,8 +171,18 @@ update_opts(AppInfo, Opts, Config) ->

NewOpts = rebar_opts:merge_opts(LocalOpts, Opts),

AppInfo#app_info_t{opts=NewOpts
,default=NewOpts}.
AppInfo#app_info_t{opts=NewOpts,
default=NewOpts}.

%% @doc update the opts based on new deps, usually from an app's hex registry metadata
-spec update_opts_deps(t(), [any()]) -> t().
update_opts_deps(AppInfo=#app_info_t{opts=Opts}, Deps) ->
LocalOpts = dict:from_list([{{locks, default}, Deps}, {{deps, default}, Deps}]),
NewOpts = rebar_opts:merge_opts(LocalOpts, Opts),
AppInfo#app_info_t{opts=NewOpts,
default=NewOpts,
deps=Deps}.


%% @private extract the deps for an app in `Dir' based on its config file data
-spec deps_from_config(file:filename(), [any()]) -> [{tuple(), any()}, ...].
Expand Down Expand Up @@ -478,6 +494,17 @@ is_checkout(#app_info_t{is_checkout=IsCheckout}) ->
is_checkout(AppInfo=#app_info_t{}, IsCheckout) ->
AppInfo#app_info_t{is_checkout=IsCheckout}.

%% @doc returns whether the app source exists in the deps dir
-spec is_available(t()) -> boolean().
is_available(#app_info_t{is_available=IsAvailable}) ->
IsAvailable.

%% @doc sets whether the app's source is available
%% only set if the app's source is found in the expected dep directory
-spec is_available(t(), boolean()) -> t().
is_available(AppInfo=#app_info_t{}, IsAvailable) ->
AppInfo#app_info_t{is_available=IsAvailable}.

%% @doc returns whether the app is valid (built) or not
-spec valid(t()) -> boolean().
valid(AppInfo=#app_info_t{valid=undefined}) ->
Expand Down
47 changes: 24 additions & 23 deletions src/rebar_app_utils.erl
Original file line number Diff line number Diff line change
Expand Up @@ -217,26 +217,23 @@ parse_dep(_, Dep, _, _, _) ->
dep_to_app(Parent, DepsDir, Name, Vsn, Source, IsLock, State) ->
CheckoutsDir = rebar_utils:to_list(rebar_dir:checkouts_dir(State, Name)),
AppInfo = case rebar_app_info:discover(CheckoutsDir) of
{ok, App} ->
rebar_app_info:source(rebar_app_info:is_checkout(App, true), checkout);
not_found ->
Dir = rebar_utils:to_list(filename:join(DepsDir, Name)),
{ok, AppInfo0} =
case rebar_app_info:discover(Dir) of
{ok, App} ->
{ok, rebar_app_info:parent(App, Parent)};
not_found ->
rebar_app_info:new(Parent, Name, Vsn, Dir, [])
end,
rebar_app_info:source(AppInfo0, Source)
end,
C = rebar_config:consult(rebar_app_info:dir(AppInfo)),
AppInfo1 = rebar_app_info:update_opts(AppInfo, rebar_app_info:opts(AppInfo), C),
Overrides = rebar_state:get(State, overrides, []),
AppInfo2 = rebar_app_info:set(AppInfo1, overrides, rebar_app_info:get(AppInfo, overrides, [])++Overrides),
AppInfo3 = rebar_app_info:apply_overrides(rebar_app_info:get(AppInfo2, overrides, []), AppInfo2),
AppInfo4 = rebar_app_info:apply_profiles(AppInfo3, [default, prod]),
AppInfo5 = rebar_app_info:profiles(AppInfo4, [default]),
{ok, App} ->
rebar_app_info:source(rebar_app_info:is_checkout(App, true), checkout);
not_found ->
Dir = rebar_utils:to_list(filename:join(DepsDir, Name)),
{ok, AppInfo0} =
case rebar_app_info:discover(Dir) of
{ok, App} ->
{ok, rebar_app_info:is_available(rebar_app_info:parent(App, Parent),
true)};
not_found ->
rebar_app_info:new(Parent, Name, Vsn, Dir, [])
end,
rebar_app_info:source(AppInfo0, Source)
end,
Overrides = rebar_app_info:get(AppInfo, overrides, []) ++ rebar_state:get(State, overrides, []),
AppInfo2 = rebar_app_info:set(AppInfo, overrides, Overrides),
AppInfo5 = rebar_app_info:profiles(AppInfo2, [default]),
rebar_app_info:is_lock(AppInfo5, IsLock).

%% @doc Takes a given application app_info record along with the project.
Expand All @@ -250,7 +247,7 @@ expand_deps_sources(Dep, State) ->
%% around version if required.
-spec update_source(rebar_app_info:t(), Source, rebar_state:t()) ->
rebar_app_info:t() when
Source :: rebar_resource:source().
Source :: rebar_resource_v2:source().
update_source(AppInfo, {pkg, PkgName, PkgVsn, Hash}, State) ->
case rebar_packages:resolve_version(PkgName, PkgVsn, Hash,
?PACKAGE_TABLE, State) of
Expand All @@ -259,8 +256,12 @@ update_source(AppInfo, {pkg, PkgName, PkgVsn, Hash}, State) ->
checksum = Hash1,
dependencies = Deps} = Package,
AppInfo1 = rebar_app_info:source(AppInfo, {pkg, PkgName, PkgVsn1, Hash1, RepoConfig}),
AppInfo2 = rebar_app_info:resource_type(rebar_app_info:deps(AppInfo1, Deps), pkg),
rebar_app_info:original_vsn(AppInfo2, PkgVsn1);

%% TODO: Remove?
AppInfo2 = rebar_app_info:resource_type(AppInfo1, pkg),

AppInfo3 = rebar_app_info:update_opts_deps(AppInfo2, Deps),
rebar_app_info:original_vsn(AppInfo3, PkgVsn1);
not_found ->
throw(?PRV_ERROR({missing_package, PkgName, PkgVsn}));
{error, {invalid_vsn, InvalidVsn}} ->
Expand Down
Loading

0 comments on commit 5c08535

Please sign in to comment.