File 3231-Add-optional_applications-to-.app-resource-files.patch of Package erlang
From 791467116fdfabacb80d33cb458f22982e4f32ae Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?Jos=C3=A9=20Valim?= <jose.valim@dashbit.co>
Date: Mon, 29 Jun 2020 11:43:19 +0200
Subject: [PATCH] Add optional_applications to .app resource files
Both Mix and Rebar allow some applications to be absent
at runtime - sometimes also known as optional dependencies.
However, given optional applications are not stored in .app
resource files, releases do not consider optional applications
in its boot order, leaving it up to chance if an optional app
will be started before its parent.
Users can try to explicitly list optional applications on their
release definition files, but given the order is not enforced,
this manual specification may be reordered when new apps are
added, leaving developers with broken releases.
This PR introduces the "optional_applications" field to .app
resource files. If an application is listed on both "applications"
and "optional_applications", it will be attempted to be started
before its parent but the parent won't fail to start in case it
is missing:
If application "b" is an optional application for application "a",
and application "b" is missing, "application:start(a)" will still
succeed.
If application "b" is an optional application for application "a",
and application "b" is available, "application:ensure_all_started(a)"
will automatically start application "b" before "a".
systools and reltool have also been modified to consider
optional_applications.
---
lib/kernel/doc/src/app.xml | 21 ++++--
lib/kernel/doc/src/application.xml | 38 +++++-----
lib/kernel/src/application.erl | 59 +++++++++++----
lib/kernel/src/application_controller.erl | 46 ++++++------
lib/kernel/test/application_SUITE.erl | 73 +++++++++++++++++--
lib/reltool/src/reltool.hrl | 1 +
lib/reltool/src/reltool_server.erl | 30 +++++---
lib/reltool/src/reltool_target.erl | 20 +++--
lib/reltool/test/reltool_server_SUITE.erl | 6 +-
.../sort_apps/z-1.0/ebin/z.app | 3 +-
lib/sasl/src/systools.hrl | 2 +
lib/sasl/src/systools_make.erl | 28 +++++--
lib/sasl/test/systools_SUITE.erl | 51 ++++++++++++-
.../d_opt_apps/lib/app1-1.0/ebin/app1.app | 8 ++
.../d_opt_apps/lib/app1-1.0/src/myapp1.erl | 1 +
.../d_opt_apps/lib/app2-1.0/ebin/app2.app | 7 ++
.../d_opt_apps/lib/app2-1.0/src/myapp2.erl | 1 +
17 files changed, 297 insertions(+), 98 deletions(-)
create mode 100644 lib/sasl/test/systools_SUITE_data/d_opt_apps/lib/app1-1.0/ebin/app1.app
create mode 100644 lib/sasl/test/systools_SUITE_data/d_opt_apps/lib/app1-1.0/src/myapp1.erl
create mode 100644 lib/sasl/test/systools_SUITE_data/d_opt_apps/lib/app2-1.0/ebin/app2.app
create mode 100644 lib/sasl/test/systools_SUITE_data/d_opt_apps/lib/app2-1.0/src/myapp2.erl
diff --git a/lib/kernel/doc/src/app.xml b/lib/kernel/doc/src/app.xml
index 8b8ac4c010..bdbd5a6e42 100644
--- a/lib/kernel/doc/src/app.xml
+++ b/lib/kernel/doc/src/app.xml
@@ -59,6 +59,7 @@
{maxT, MaxT},
{registered, Names},
{included_applications, Apps},
+ {optional_applications, Apps},
{applications, Apps},
{env, Env},
{mod, Start},
@@ -148,10 +149,21 @@ ApplicationVersion = string()</code>
<tag><c>applications</c></tag>
<item>
<p>All applications that must be started before this
- application is allowed to be started. <c>systools</c> uses
- this list to generate correct start scripts. Defaults to
- the empty list, but notice that all applications have
- dependencies to (at least) Kernel and STDLIB.</p>
+ application. If an application is also listed in
+ <c>optional_applications</c>, then the application
+ is not required to exist (but if it exists, it is
+ also guaranteed to be started before this one).</p>
+ <p><c>systools</c> uses this list to generate correct start
+ scripts. Defaults to the empty list, but notice that all
+ applications have dependencies to (at least) Kernel and STDLIB.</p>
+ </item>
+ <tag><c>optional_applications</c></tag>
+ <item>
+ <p>A list of <c>applications</c> that are optional.
+ Note if you want an optional dependency to be
+ automatically started before the current application
+ whenever it is available, it must be listed on both
+ <c>applications</c> and <c>optional_applications</c>.</p>
</item>
<tag><c>env</c></tag>
<item>
@@ -239,4 +251,3 @@ ApplicationVersion = string()</code>
<seeerl marker="sasl:systools"><c>systools(3)</c></seeerl></p>
</section>
</fileref>
-
diff --git a/lib/kernel/doc/src/application.xml b/lib/kernel/doc/src/application.xml
index 81d97c41bc..30778cd6ae 100644
--- a/lib/kernel/doc/src/application.xml
+++ b/lib/kernel/doc/src/application.xml
@@ -73,18 +73,16 @@
<desc>
<p>Equivalent to calling
<seemfa marker="#start/1"><c>start/1,2</c></seemfa>
- repeatedly on all dependencies that are not yet started for an
- application that is not yet started.</p>
- <p>Returns <c>{ok, AppNames}</c>, where <c>AppNames</c> is a list of the application names
- that was actually started by this call.
- The list might be empty, or not contain all dependencies if the application
- or some of its dependencies are already started.</p>
+ repeatedly on all dependencies that are not yet started for an application.
+ Optional dependencies will also be loaded and started if they are available.</p>
+ <p>Returns <c>{ok, AppNames}</c> for a successful start or for an already started
+ application (which is, however, omitted from the <c>AppNames</c> list).</p>
<p>The function reports <c>{error, {AppName,Reason}}</c> for errors, where
<c>Reason</c> is any possible reason returned by
<seemfa marker="#start/1"><c>start/1,2</c></seemfa>
when starting a specific dependency.</p>
- <p>If an error occurs, the applications started by the function are stopped
- to bring the set of running applications back to its initial state.</p>
+ <p>If an error occurs, the applications started by the function are stopped
+ to bring the set of running applications back to its initial state.</p>
</desc>
</func>
<func>
@@ -352,16 +350,22 @@ Nodes = [cp1@cave, {cp2@cave, cp3@cave}]</code>
<p>The application controller checks the value of
the application specification key <c>applications</c>, to
ensure that all applications needed to be started before
- this application are running. Otherwise,
+ this application are running. If an application is missing
+ and the application is not marked as optional,
<c>{error,{not_started,App}}</c> is returned, where <c>App</c>
- is the name of the missing application.</p>
- <p>The application controller then creates an <em>application master</em>
- for the application. The application master becomes the
- group leader of all the processes in the application. I/O is
- forwarded to the previous group leader, though, this is just
- a way to identify processes that belong to the application.
- Used for example to find itself from any process, or,
- reciprocally, to kill them all when it terminates.</p>
+ is the name of the missing application. Note this function
+ makes no attempt to start any of the applications listed in
+ <c>applications</c>, not even optional ones. See
+ <seemfa marker="#ensure_all_started/1"><c>ensure_all_started/1,2</c></seemfa>
+ for recursively starting the current application and its
+ dependencies.</p>
+ <p>Once validated, the application controller then creates an
+ <em>application master</em> for the application. The application
+ master becomes the group leader of all the processes in the
+ application. I/O is forwarded to the previous group leader,
+ though, this is just a way to identify processes that belong
+ to the application. Used for example to find itself from any
+ process, or, reciprocally, to kill them all when it terminates.</p>
<p>
The application master starts the application by calling
the application callback function <c>Module:start/2</c> as
diff --git a/lib/kernel/src/application.erl b/lib/kernel/src/application.erl
index a349662c45..c13263ee86 100644
--- a/lib/kernel/src/application.erl
+++ b/lib/kernel/src/application.erl
@@ -130,7 +130,7 @@ ensure_all_started(Application) ->
Started :: [atom()],
Reason :: term().
ensure_all_started(Application, Type) ->
- case ensure_all_started(Application, Type, []) of
+ case ensure_all_started([Application], [], Type, []) of
{ok, Started} ->
{ok, lists:reverse(Started)};
{error, Reason, Started} ->
@@ -138,23 +138,45 @@ ensure_all_started(Application, Type) ->
{error, Reason}
end.
-ensure_all_started(Application, Type, Started) ->
- case start(Application, Type) of
- ok ->
- {ok, [Application | Started]};
- {error, {already_started, Application}} ->
- {ok, Started};
- {error, {not_started, Dependency}} ->
- case ensure_all_started(Dependency, Type, Started) of
+ensure_all_started([App | Apps], OptionalApps, Type, Started) ->
+ case ensure_loaded(App) of
+ {ok, Name} ->
+ case ensure_started(Name, App, Type, Started) of
{ok, NewStarted} ->
- ensure_all_started(Application, Type, NewStarted);
+ ensure_all_started(Apps, OptionalApps, Type, NewStarted);
Error ->
Error
end;
+ {error, {"no such file or directory", _} = Reason} ->
+ case lists:member(App, OptionalApps) of
+ true ->
+ ensure_all_started(Apps, OptionalApps, Type, Started);
+ false ->
+ {error, {App, Reason}, Started}
+ end;
{error, Reason} ->
- {error, {Application, Reason}, Started}
- end.
+ {error, {App, Reason}, Started}
+ end;
+ensure_all_started([], _OptionalApps, _Type, Started) ->
+ {ok, Started}.
+ensure_started(Name, App, Type, Started) ->
+ {ok, ChildApps} = get_key(Name, applications),
+ {ok, OptionalApps} = get_key(Name, optional_applications),
+
+ case ensure_all_started(ChildApps, OptionalApps, Type, Started) of
+ {ok, NewStarted} ->
+ case application_controller:start_application(Name, Type) of
+ ok ->
+ {ok, [App | NewStarted]};
+ {error, {already_started, App}} ->
+ {ok, NewStarted};
+ {error, Reason} ->
+ {error, {App, Reason}, NewStarted}
+ end;
+ Error ->
+ Error
+ end.
-spec start(Application) -> 'ok' | {'error', Reason} when
Application :: atom(),
@@ -169,12 +191,19 @@ start(Application) ->
Reason :: term().
start(Application, RestartType) ->
+ case ensure_loaded(Application) of
+ {ok, Name} ->
+ application_controller:start_application(Name, RestartType);
+ Error ->
+ Error
+ end.
+
+ensure_loaded(Application) ->
case load(Application) of
ok ->
- Name = get_appl_name(Application),
- application_controller:start_application(Name, RestartType);
+ {ok, get_appl_name(Application)};
{error, {already_loaded, Name}} ->
- application_controller:start_application(Name, RestartType);
+ {ok, Name};
Error ->
Error
end.
diff --git a/lib/kernel/src/application_controller.erl b/lib/kernel/src/application_controller.erl
index 2516fbae74..525a983285 100644
--- a/lib/kernel/src/application_controller.erl
+++ b/lib/kernel/src/application_controller.erl
@@ -158,7 +158,7 @@
%% Env = [{Key, Value}]
%%-----------------------------------------------------------------
--record(appl, {name, appl_data, descr, id, vsn, restart_type, inc_apps, apps}).
+-record(appl, {name, appl_data, descr, id, vsn, restart_type, inc_apps, opt_apps, apps}).
%%-----------------------------------------------------------------
%% Func: start/1
@@ -373,6 +373,8 @@ get_key(AppName, Key) ->
{ok, (Appl#appl.appl_data)#appl_data.regs};
included_applications ->
{ok, Appl#appl.inc_apps};
+ optional_applications ->
+ {ok, Appl#appl.opt_apps};
applications ->
{ok, Appl#appl.apps};
env ->
@@ -404,6 +406,7 @@ get_all_key(AppName) ->
{maxT, (Appl#appl.appl_data)#appl_data.maxT},
{registered, (Appl#appl.appl_data)#appl_data.regs},
{included_applications, Appl#appl.inc_apps},
+ {optional_applications, Appl#appl.opt_apps},
{applications, Appl#appl.apps},
{env, get_all_env(AppName)},
{mod, (Appl#appl.appl_data)#appl_data.mod},
@@ -1277,15 +1280,15 @@ do_load_application(Application, S) ->
%% Recursively load the application and its included apps.
%load(S, {ApplData, ApplEnv, IncApps, Descr, Vsn, Apps}) ->
-load(S, {ApplData, ApplEnv, IncApps, Descr, Id, Vsn, Apps}) ->
+load(S, {ApplData, ApplEnv, IncApps, OptApps, Descr, Id, Vsn, Apps}) ->
Name = ApplData#appl_data.name,
ConfEnv = get_env_i(Name, S),
NewEnv = merge_app_env(ApplEnv, ConfEnv),
CmdLineEnv = get_cmd_env(Name),
NewEnv2 = merge_app_env(NewEnv, CmdLineEnv),
add_env(Name, NewEnv2),
- Appl = #appl{name = Name, descr = Descr, id = Id, vsn = Vsn,
- appl_data = ApplData, inc_apps = IncApps, apps = Apps},
+ Appl = #appl{name = Name, descr = Descr, id = Id, vsn = Vsn, apps = Apps,
+ appl_data = ApplData, inc_apps = IncApps, opt_apps = OptApps},
ets:insert(ac_tab, {{loaded, Name}, Appl}),
NewS =
foldl(fun(App, S1) ->
@@ -1322,13 +1325,13 @@ check_start_cond(AppName, RestartType, Started, Running) ->
{error, {already_started, AppName}};
false ->
foreach(
- fun(AppName2) ->
- case lists:keymember(AppName2, 1, Started) of
- true -> ok;
- false ->
- throw({error, {not_started, AppName2}})
- end
- end, Appl#appl.apps),
+ fun(AppName2) ->
+ case lists:keymember(AppName2, 1, Started) orelse
+ lists:member(AppName2, Appl#appl.opt_apps) of
+ true -> ok;
+ false -> throw({error, {not_started, AppName2}})
+ end
+ end, Appl#appl.apps),
{ok, Appl}
end;
false ->
@@ -1385,14 +1388,13 @@ start_appl(Appl, S, Type) ->
%% Name = ApplData#appl_data.name,
Running = S#state.running,
foreach(
- fun(AppName) ->
- case lists:keymember(AppName, 1, Running) of
- true ->
- ok;
- false ->
- throw({info, {not_running, AppName}})
- end
- end, Appl#appl.apps),
+ fun(AppName) ->
+ case lists:keymember(AppName, 1, Running) orelse
+ lists:member(AppName, Appl#appl.opt_apps) of
+ true -> ok;
+ false -> throw({info, {not_running, AppName}})
+ end
+ end, Appl#appl.apps),
case application_master:start_link(ApplData, Type) of
{ok, _Pid} = Ok ->
Ok;
@@ -1526,9 +1528,10 @@ make_appl_i({application, Name, Opts}) when is_atom(Name), is_list(Opts) ->
MaxP = get_opt(maxP, Opts, infinity),
MaxT = get_opt(maxT, Opts, infinity),
IncApps = get_opt(included_applications, Opts, []),
+ OptApps = get_opt(optional_applications, Opts, []),
{#appl_data{name = Name, regs = Regs, mod = Mod, phases = Phases,
mods = Mods, maxP = MaxP, maxT = MaxT},
- Env, IncApps, Descr, Id, Vsn, Apps};
+ Env, IncApps, OptApps, Descr, Id, Vsn, Apps};
make_appl_i({application, Name, Opts}) when is_list(Opts) ->
throw({error,{invalid_name,Name}});
make_appl_i({application, _Name, Opts}) ->
@@ -1580,7 +1583,7 @@ is_loaded_app(AppName, [{application, AppName, App} | _]) ->
is_loaded_app(AppName, [_ | T]) -> is_loaded_app(AppName, T);
is_loaded_app(_AppName, []) -> false.
-do_change_appl({ok, {ApplData, Env, IncApps, Descr, Id, Vsn, Apps}},
+do_change_appl({ok, {ApplData, Env, IncApps, OptApps, Descr, Id, Vsn, Apps}},
OldAppl, Config) ->
AppName = OldAppl#appl.name,
@@ -1601,6 +1604,7 @@ do_change_appl({ok, {ApplData, Env, IncApps, Descr, Id, Vsn, Apps}},
id=Id,
vsn=Vsn,
inc_apps=IncApps,
+ opt_apps=OptApps,
apps=Apps};
do_change_appl({error, _R} = Error, _Appl, _ConfData) ->
throw(Error).
diff --git a/lib/kernel/test/application_SUITE.erl b/lib/kernel/test/application_SUITE.erl
index 4af0c942b5..3584b90378 100644
--- a/lib/kernel/test/application_SUITE.erl
+++ b/lib/kernel/test/application_SUITE.erl
@@ -31,7 +31,7 @@
otp_3002/1, otp_3184/1, otp_4066/1, otp_4227/1, otp_5363/1,
otp_5606/1,
start_phases/1, get_key/1, get_env/1,
- set_env/1, set_env_persistent/1, set_env_errors/1,
+ set_env/1, set_env_persistent/1, set_env_errors/1, optional_applications/1,
permit_false_start_local/1, permit_false_start_dist/1, script_start/1,
nodedown_start/1, init2973/0, loop2973/0, loop5606/1, otp_16504/1]).
@@ -60,7 +60,7 @@ all() ->
permit_false_start_dist, get_key, get_env, ensure_all_started,
set_env, set_env_persistent, set_env_errors,
{group, distr_changed}, config_change, shutdown_func, shutdown_timeout,
- shutdown_deadlock, config_relative_paths,
+ shutdown_deadlock, config_relative_paths, optional_applications,
persistent_env, handle_many_config_files, format_log_1, format_log_2,
invalid_app_file].
@@ -970,7 +970,7 @@ ensure_all_started(_Conf) ->
w_app9(Fd9),
file:close(Fd9),
{ok, Fd10} = file:open("app10.app", [write]),
- w_app10_dep9(Fd10),
+ w_app10(Fd10, [app9], []),
file:close(Fd10),
{ok, FdErr} = file:open("app_chain_error.app", [write]),
w_app(FdErr, app_chain_error()),
@@ -1039,6 +1039,60 @@ ensure_all_started(_Conf) ->
ok = application:unload(app_chain_error),
ok.
+optional_applications(_Conf) ->
+ {ok, Fd10} = file:open("app10.app", [write]),
+ w_app10(Fd10, [app9], []),
+ file:close(Fd10),
+
+ {error,{not_started,app9}} = application:start(app10),
+ {ok, []} = application:get_key(app10, optional_applications),
+ ok = application:unload(app10),
+
+ %% List app9 as an optional application and app10 starts
+ {ok, Fd10Opt} = file:open("app10.app", [write]),
+ w_app10(Fd10Opt, [app9], [app9]),
+ file:close(Fd10Opt),
+
+ ok = application:start(app10),
+ {ok, [app9]} = application:get_key(app10, optional_applications),
+ false = lists:keymember(app9,1,application:which_applications()),
+
+ ok = application:stop(app10),
+ ok = application:unload(app10),
+
+ %% If app9 is defined, we can still start app10 without app9
+ {ok, Fd9} = file:open("app9.app", [write]),
+ w_app9(Fd9),
+ file:close(Fd9),
+
+ ok = application:start(app10),
+ false = lists:keymember(app9,1,application:which_applications()),
+
+ ok = application:stop(app10),
+ ok = application:unload(app10),
+
+ %% But if we use ensure all started, then app9 is started too
+ {ok, [app9, app10]} = application:ensure_all_started(app10, temporary),
+ true = lists:keymember(app9,1,application:which_applications()),
+
+ ok = application:stop(app9),
+ ok = application:unload(app9),
+ ok = application:stop(app10),
+ ok = application:unload(app10),
+
+ %% Finally, let's have an optional dependency with a start error
+ {ok, Fd10Error} = file:open("app10.app", [write]),
+ w_app10(Fd10Error, [app_start_error], [app_start_error]),
+ file:close(Fd10Error),
+
+ {ok, FdAppError} = file:open("app_start_error.app", [write]),
+ w_app_start_error(FdAppError),
+ file:close(FdAppError),
+
+ {error,{app_start_error,_}} = application:ensure_all_started(app10, temporary),
+ ok = application:unload(app10),
+ ok.
+
%%%-----------------------------------------------------------------
%%% Testing of reported bugs and other tickets.
%%%-----------------------------------------------------------------
@@ -1430,7 +1484,7 @@ otp_4227(Conf) when is_list(Conf) ->
rpc:multicall(Cps, application, load, [app9()]),
?UNTIL(is_loaded(app9, Cps)),
{[ok,ok],[]} =
- rpc:multicall(Cps, application, load, [app10_dep9()]),
+ rpc:multicall(Cps, application, load, [app10([app9], [])]),
{error, {not_started, app9}} =
rpc:call(Cp1, application, start, [app10]),
@@ -1642,6 +1696,7 @@ get_key(Conf) when is_list(Conf) ->
{maxT, infinity},
{registered, []},
{included_applications, [appinc1, appinc2]},
+ {optional_applications, []},
{applications, [kernel]},
{env, Env},
{mod, {application_starter, [ch_sup, {appinc, 41, 43}] }},
@@ -1686,6 +1741,7 @@ get_key(Conf) when is_list(Conf) ->
{maxT, infinity},
{registered, []},
{included_applications, [appinc1, appinc2]},
+ {optional_applications, []},
{applications, [kernel]},
{env, Env},
{mod, {application_starter, [ch_sup, {appinc, 41, 43}] }},
@@ -2623,13 +2679,14 @@ app9() ->
{applications, [kernel]},
{mod, {ch_sup, {app9, 19, 19}}}]}.
-app10_dep9() ->
+app10(Apps, OptionalApps) ->
{application, app10,
[{description, "ERTS CXC 138 10"},
{vsn, "2.0"},
{modules, []},
{registered, []},
- {applications, [kernel, app9]},
+ {applications, [kernel] ++ Apps},
+ {optional_applications, OptionalApps},
{mod, {ch_sup, {app10, 20, 20}}}]}.
appinc() ->
@@ -2953,8 +3010,8 @@ w_app8(Fd) ->
w_app9(Fd) ->
io:format(Fd, "~p.\n", [app9()]).
-w_app10_dep9(Fd) ->
- io:format(Fd, "~p.\n", [app10_dep9()]).
+w_app10(Fd, Deps, Optional) ->
+ io:format(Fd, "~p.\n", [app10(Deps, Optional)]).
w_app_start_error(Fd) ->
io:format(Fd, "~p.\n", [app_start_error()]).
diff --git a/lib/reltool/src/reltool.hrl b/lib/reltool/src/reltool.hrl
index 892aaf8649..354f374ace 100644
--- a/lib/reltool/src/reltool.hrl
+++ b/lib/reltool/src/reltool.hrl
@@ -164,6 +164,7 @@
maxP = infinity :: '_' | integer() | infinity,
maxT = infinity :: '_' | integer() | infinity,
registered = [] :: '_' | [atom()],
+ opt_apps = [] :: '_' | [app_name()],
incl_apps = [] :: '_' | '$3' | [app_name()],
applications = [] :: '_' | '$2' | [app_name()],
env = [] :: '_' | [{atom(), term()}],
diff --git a/lib/reltool/src/reltool_server.erl b/lib/reltool/src/reltool_server.erl
index 2de8000fd8..b62288dfd4 100644
--- a/lib/reltool/src/reltool_server.erl
+++ b/lib/reltool/src/reltool_server.erl
@@ -573,23 +573,23 @@ apps_in_rel(#rel{name = RelName, rel_apps = RelApps}, Apps) ->
Explicit0 = [{RelName, AppName} || #rel_app{name=AppName} <- RelApps],
Explicit = Mandatory ++ Explicit0,
Deps =
- [{RelName, AppName} ||
+ [{RelName, AppName, Optional} ||
RA <- RelApps,
- AppName <-
+ {AppName, Optional} <-
case lists:keyfind(RA#rel_app.name,
#app.name,
Apps) of
- App=#app{info = #app_info{applications = AA}} ->
+ #app{info = Info} ->
%% Included applications in rel shall overwrite included
%% applications in .app. I.e. included applications in
%% .app shall only be used if it is not defined in rel.
IA = case RA#rel_app.incl_apps of
undefined ->
- (App#app.info)#app_info.incl_apps;
+ Info#app_info.incl_apps;
RelIA ->
RelIA
end,
- AA ++ IA;
+ build_more_apps(Info, IA);
false ->
reltool_utils:throw_error(
"Release ~tp uses non existing "
@@ -599,16 +599,19 @@ apps_in_rel(#rel{name = RelName, rel_apps = RelApps}, Apps) ->
not lists:keymember(AppName, 2, Explicit)],
more_apps_in_rels(Deps, Apps, Explicit).
-more_apps_in_rels([{RelName, AppName} = RA | RelApps], Apps, Acc) ->
- case lists:member(RA, Acc) of
+more_apps_in_rels([{RelName, AppName, Optional} | RelApps], Apps, Acc) ->
+ case lists:member({RelName, AppName}, Acc) of
true ->
more_apps_in_rels(RelApps, Apps, Acc);
false ->
case lists:keyfind(AppName, #app.name, Apps) of
- #app{info = #app_info{applications = AA, incl_apps=IA}} ->
- Extra = [{RelName, N} || N <- AA++IA],
- Acc2 = more_apps_in_rels(Extra, Apps, [RA | Acc]),
+ #app{info = #app_info{incl_apps=IA} = Info} ->
+ Extra = [{RelName, ChildName, ChildOptional} ||
+ {ChildName, ChildOptional} <- build_more_apps(Info, IA)],
+ Acc2 = more_apps_in_rels(Extra, Apps, [{RelName, AppName} | Acc]),
more_apps_in_rels(RelApps, Apps, Acc2);
+ false when Optional ->
+ more_apps_in_rels(RelApps, Apps, Acc);
false ->
reltool_utils:throw_error(
"Release ~tp uses non existing application ~w",
@@ -618,6 +621,11 @@ more_apps_in_rels([{RelName, AppName} = RA | RelApps], Apps, Acc) ->
more_apps_in_rels([], _Apps, Acc) ->
Acc.
+build_more_apps(#app_info{applications = AA, opt_apps = OA}, IA) ->
+ AAOpt = [{App, lists:member(App, OA)} || App <- AA],
+ IAOpt = [{App, false} || App <- IA],
+ AAOpt ++ IAOpt.
+
apps_init_is_included(S, Apps, RelApps, Status) ->
lists:foldl(fun(App, AccStatus) ->
app_init_is_included(S, App, RelApps, AccStatus)
@@ -1215,6 +1223,8 @@ parse_app_info(File, [{Key, Val} | KeyVals], AI, Status) ->
registered ->
parse_app_info(File, KeyVals, AI#app_info{registered = Val},
Status);
+ optional_applications ->
+ parse_app_info(File, KeyVals, AI#app_info{opt_apps = Val}, Status);
included_applications ->
parse_app_info(File, KeyVals, AI#app_info{incl_apps = Val}, Status);
applications ->
diff --git a/lib/reltool/src/reltool_target.erl b/lib/reltool/src/reltool_target.erl
index dfa62479a0..ba1562bf15 100644
--- a/lib/reltool/src/reltool_target.erl
+++ b/lib/reltool/src/reltool_target.erl
@@ -250,6 +250,7 @@ gen_app(#app{name = Name,
maxP = MaxP,
maxT = MaxT,
registered = Regs,
+ opt_apps = OptApps,
incl_apps = InclApps,
applications = ReqApps,
env = Env,
@@ -272,6 +273,7 @@ gen_app(#app{name = Name,
{modules, Mods},
{registered, Regs},
{applications, ReqApps},
+ {optional_applications, OptApps},
{included_applications, InclApps},
{env, Env},
{maxT, MaxT},
@@ -349,12 +351,13 @@ do_merge_apps(RelName, [#rel_app{name = Name} = RA | RelApps], Apps, RelAppType,
do_merge_apps(RelName, RelApps, Apps, RelAppType, Acc);
false ->
{value, App} = lists:keysearch(Name, #app.name, Apps),
- MergedApp = merge_app(RelName, RA, RelAppType, App),
- ReqNames = (MergedApp#app.info)#app_info.applications,
- IncNames = (MergedApp#app.info)#app_info.incl_apps,
- Acc2 = [MergedApp | Acc],
+ #app{info = Info} = MergedApp = merge_app(RelName, RA, RelAppType, App),
+ #app_info{applications = Children, incl_apps = IncNames, opt_apps = OptNames} = Info,
+ ReqNames = [ChildName || ChildName <- Children,
+ not lists:member(ChildName, OptNames),
+ lists:keymember(ChildName, #app.name, Apps)],
do_merge_apps(RelName, ReqNames ++ IncNames ++ RelApps,
- Apps, RelAppType, Acc2)
+ Apps, RelAppType, [MergedApp | Acc])
end;
do_merge_apps(RelName, [Name | RelApps], Apps, RelAppType, Acc) ->
case is_already_merged(Name, RelApps, Acc) of
@@ -543,8 +546,9 @@ find_pos([], _OrderedApps) ->
find_pos(N, Name, [#app{name=Name}|_OrderedApps]) ->
{N, Name};
find_pos(N, Name, [_OtherAppl|OrderedApps]) ->
- find_pos(N+1, Name, OrderedApps).
-
+ find_pos(N+1, Name, OrderedApps);
+find_pos(_N, Name, []) ->
+ {optional, Name}.
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
@@ -578,7 +582,7 @@ sort_apps([#app{name = Name, info = Info} = App | Apps],
Visited,
[],
[]),
- Missing1 = NotFnd1 ++ NotFnd2 ++ Missing,
+ Missing1 = (NotFnd1 -- Info#app_info.opt_apps) ++ NotFnd2 ++ Missing,
case Uses ++ Incs of
[] ->
%% No more app that must be started before this one is
diff --git a/lib/reltool/test/reltool_server_SUITE.erl b/lib/reltool/test/reltool_server_SUITE.erl
index 500b298424..063bbc0d1d 100644
--- a/lib/reltool/test/reltool_server_SUITE.erl
+++ b/lib/reltool/test/reltool_server_SUITE.erl
@@ -401,7 +401,8 @@ create_release_sort(Config) ->
RelVsn = "1.0",
%% Application z (.app file):
%% includes [tools, mnesia]
- %% uses [kernel, stdlib, sasl, inets]
+ %% uses [kernel, stdlib, sasl, inets, unknown]
+ %% where unknown is optional dependency
Sys =
{sys,
[
@@ -623,7 +624,8 @@ create_script_sort(Config) ->
LibDir = filename:join(DataDir,"sort_apps"),
%% Application z (.app file):
%% includes [tools, mnesia]
- %% uses [kernel, stdlib, sasl, inets]
+ %% uses [kernel, stdlib, sasl, inets, unknown]
+ %% where unknown is optional dependency
Sys =
{sys,
[
diff --git a/lib/reltool/test/reltool_server_SUITE_data/sort_apps/z-1.0/ebin/z.app b/lib/reltool/test/reltool_server_SUITE_data/sort_apps/z-1.0/ebin/z.app
index 8608bc554b..4a9f884e24 100644
--- a/lib/reltool/test/reltool_server_SUITE_data/sort_apps/z-1.0/ebin/z.app
+++ b/lib/reltool/test/reltool_server_SUITE_data/sort_apps/z-1.0/ebin/z.app
@@ -4,5 +4,6 @@
{vsn, "1.0"},
{modules,[]},
{registered, []},
- {applications, [kernel, stdlib, sasl, inets]},
+ {applications, [kernel, stdlib, sasl, inets, unknown]},
+ {optional_applications, [unknown]},
{included_applications, [tools, mnesia]}]}.
diff --git a/lib/sasl/src/systools.hrl b/lib/sasl/src/systools.hrl
index 6b2a597427..01118e320c 100644
--- a/lib/sasl/src/systools.hrl
+++ b/lib/sasl/src/systools.hrl
@@ -48,6 +48,8 @@
%% Module = atom(), Vsn = string().
uses = [], %% [Application] list of applications required
%% by the application, Application = atom().
+ optional = [], %% [Application] list of applications in uses
+ %% that are optional, Application = atom().
includes = [], %% [Application] list of applications included
%% by the application, Application = atom().
regs = [], %% [RegNames] a list of registered process
diff --git a/lib/sasl/src/systools_make.erl b/lib/sasl/src/systools_make.erl
index c7a14df28e..7b86bf58d0 100644
--- a/lib/sasl/src/systools_make.erl
+++ b/lib/sasl/src/systools_make.erl
@@ -642,10 +642,10 @@ read_application(_Name, _, [], _, _, FirstError) ->
parse_application({application, Name, Dict}, File, Vsn, Incls)
when is_atom(Name),
is_list(Dict) ->
- Items = [vsn,id,description,modules,registered,
- applications,included_applications,mod,start_phases,env,maxT,maxP],
+ Items = [vsn,id,description,modules,registered,applications,
+ optional_applications,included_applications,mod,start_phases,env,maxT,maxP],
case catch get_items(Items, Dict) of
- [Vsn,Id,Desc,Mods,Regs,Apps,Incs0,Mod,Phases,Env,MaxT,MaxP] ->
+ [Vsn,Id,Desc,Mods,Regs,Apps,Opts,Incs0,Mod,Phases,Env,MaxT,MaxP] ->
case override_include(Name, Incs0, Incls) of
{ok, Incs} ->
{ok, #application{name=Name,
@@ -654,6 +654,7 @@ parse_application({application, Name, Dict}, File, Vsn, Incls)
description=Desc,
modules=Mods,
uses=Apps,
+ optional=Opts,
includes=Incs,
regs=Regs,
mod=Mod,
@@ -665,7 +666,7 @@ parse_application({application, Name, Dict}, File, Vsn, Incls)
{error, IncApps} ->
{error, {override_include, IncApps}}
end;
- [OtherVsn,_,_,_,_,_,_,_,_,_,_,_] ->
+ [OtherVsn,_,_,_,_,_,_,_,_,_,_,_,_] ->
{error, {no_valid_version, {Vsn, OtherVsn}}};
Err ->
{error, {Err, {application, Name, Dict}}}
@@ -729,6 +730,11 @@ check_item({_,{applications,Apps}},I) ->
true -> Apps;
_ -> throw({bad_param, I})
end;
+check_item({_,{optional_applications,Apps}},I) ->
+ case a_list_p(Apps) of
+ true -> Apps;
+ _ -> throw({bad_param, I})
+ end;
check_item({_,{included_applications,Apps}},I) ->
case a_list_p(Apps) of
true -> Apps;
@@ -768,6 +774,8 @@ check_item({_,{maxP,MaxP}},I) ->
infinity -> infinity;
_ -> throw({bad_param, I})
end;
+check_item(false, optional_applications) -> % optional !
+ [];
check_item(false, included_applications) -> % optional !
[];
check_item(false, mod) -> % mod is optional !
@@ -905,7 +913,8 @@ find_top_app(App, InclApps) ->
undefined_applications(Appls) ->
Uses = append(map(fun({_,A}) ->
- A#application.uses ++ A#application.includes
+ (A#application.uses -- A#application.optional) ++
+ A#application.includes
end, Appls)),
Defined = map(fun({{X,_},_}) -> X end, Appls),
filter(fun(X) -> not member(X, Defined) end, Uses).
@@ -958,7 +967,9 @@ find_pos([], _OrderedAppls) ->
find_pos(N, Name, [{Name,_Vsn,_Type}|_OrderedAppls]) ->
{N, Name};
find_pos(N, Name, [_OtherAppl|OrderedAppls]) ->
- find_pos(N+1, Name, OrderedAppls).
+ find_pos(N+1, Name, OrderedAppls);
+find_pos(_N, Name, []) ->
+ {optional, Name}.
%%______________________________________________________________________
%% check_modules(Appls, Path, TestP) ->
@@ -1299,7 +1310,7 @@ sort_appls([{N, A}|T], Missing, Circular, Visited) ->
T, Visited, [], []),
{Incs, T2, NotFnd2} = find_all(Name, lists:reverse(A#application.includes),
T1, Visited, [], []),
- Missing1 = NotFnd1 ++ NotFnd2 ++ Missing,
+ Missing1 = (NotFnd1 -- A#application.optional) ++ NotFnd2 ++ Missing,
case Uses ++ Incs of
[] ->
%% No more app that must be started before this one is
@@ -1470,7 +1481,7 @@ load_commands(Mods, Path) ->
%% Pack an application to an application term.
pack_app(#application{name=Name,vsn=V,id=Id,description=D,modules=M,
- uses=App,includes=Incs,regs=Regs,mod=Mod,start_phases=SF,
+ uses=App,optional=Opts,includes=Incs,regs=Regs,mod=Mod,start_phases=SF,
env=Env,maxT=MaxT,maxP=MaxP}) ->
{application, Name,
[{description,D},
@@ -1479,6 +1490,7 @@ pack_app(#application{name=Name,vsn=V,id=Id,description=D,modules=M,
{modules, M},
{registered, Regs},
{applications, App},
+ {optional_applications, Opts},
{included_applications, Incs},
{env, Env},
{maxT, MaxT},
diff --git a/lib/sasl/test/systools_SUITE.erl b/lib/sasl/test/systools_SUITE.erl
index 53ce272b17..b9d8ff2e02 100644
--- a/lib/sasl/test/systools_SUITE.erl
+++ b/lib/sasl/test/systools_SUITE.erl
@@ -60,7 +60,7 @@ groups() ->
[script_options, normal_script, start_script, unicode_script, no_mod_vsn_script,
wildcard_script, variable_script, abnormal_script,
no_sasl_script, no_dot_erlang_script,
- src_tests_script, crazy_script,
+ src_tests_script, crazy_script, optional_apps_script,
included_script, included_override_script,
included_fail_script, included_bug_script, exref_script,
duplicate_modules_script,
@@ -320,6 +320,46 @@ unicode_script(cleanup,Config) ->
file:delete(fname(?privdir, "unicode_app.tgz")),
ok.
+%% make_script: Check that script handles optional apps.
+optional_apps_script(Config) when is_list(Config) ->
+ {ok, OldDir} = file:get_cwd(),
+ PSAVE = code:get_path(), % Save path
+
+ DataDir = filename:absname(?copydir),
+ LibDir = fname([DataDir, d_opt_apps, lib]),
+ P1 = fname([LibDir, 'app1-1.0', ebin]),
+ P2 = fname([LibDir, 'app2-1.0', ebin]),
+ true = code:add_patha(P1),
+ true = code:add_patha(P2),
+
+ %% First assemble a release without the optional app
+ {OptDir, OptName} = create_script(optional_apps_missing,Config),
+ ok = file:set_cwd(OptDir),
+ ok = systools:make_script(filename:basename(OptName), [{script_name, "start"}]),
+ {ok, [{script,_,OptCommands}]} = read_script_file("start"),
+
+ %% Check optional_applications is part of the generated script
+ [[app2]] =
+ [proplists:get_value(optional_applications, Properties) ||
+ {apply,{application,load,[{application,app1,Properties}]}} <- OptCommands],
+
+ %% And there is no app2
+ [] =
+ [ok || {apply,{application,load,[{application,app2,_}]}} <- OptCommands],
+
+ %% Now let's include the optional app
+ {AllDir, AllName} = create_script(optional_apps_all,Config),
+ ok = file:set_cwd(AllDir),
+ ok = systools:make_script(filename:basename(AllName), [{script_name, "start"}]),
+ {ok, [{script,_,AllCommands}]} = read_script_file("start"),
+
+ %% Check boot order is still correct
+ BootOrder = [App || {apply,{application,start_boot,[App,permanent]}} <- AllCommands],
+ [kernel, stdlib, sasl, app2, app1] = BootOrder,
+
+ ok = file:set_cwd(OldDir),
+ code:set_path(PSAVE), % Restore path
+ ok.
%% make_script:
%% Modules specified without version in .app file (db-3.1).
@@ -2544,8 +2584,13 @@ create_script(replace_app0,Config) ->
do_create_script(repace_app0,Config,current,Apps);
create_script(replace_app1,Config) ->
Apps = core_apps(current) ++ [{db,"1.0"},{fe,"2.1"}],
- do_create_script(repace_app1,Config,current,Apps).
-
+ do_create_script(repace_app1,Config,current,Apps);
+create_script(optional_apps_missing,Config) ->
+ Apps = core_apps(current) ++ [{app1,"1.0"}],
+ do_create_script(optional_apps_missing,Config,current,Apps);
+create_script(optional_apps_all,Config) ->
+ Apps = core_apps(current) ++ [{app1,"1.0"},{app2,"1.0"}],
+ do_create_script(optional_apps_all,Config,current,Apps).
do_create_script(Id,Config,ErtsVsn,AppVsns) ->
do_create_script(Id,string:to_upper(atom_to_list(Id)),Config,ErtsVsn,AppVsns).
diff --git a/lib/sasl/test/systools_SUITE_data/d_opt_apps/lib/app1-1.0/ebin/app1.app b/lib/sasl/test/systools_SUITE_data/d_opt_apps/lib/app1-1.0/ebin/app1.app
new file mode 100644
index 0000000000..be01854653
--- /dev/null
+++ b/lib/sasl/test/systools_SUITE_data/d_opt_apps/lib/app1-1.0/ebin/app1.app
@@ -0,0 +1,8 @@
+{application, app1,
+ [{description, "Application 1"},
+ {vsn, "1.0"},
+ {modules, [myapp1]},
+ {registered, []},
+ {applications, [app2]},
+ {optional_applications, [app2]},
+ {env, []}]}.
diff --git a/lib/sasl/test/systools_SUITE_data/d_opt_apps/lib/app1-1.0/src/myapp1.erl b/lib/sasl/test/systools_SUITE_data/d_opt_apps/lib/app1-1.0/src/myapp1.erl
new file mode 100644
index 0000000000..03e3583c3d
--- /dev/null
+++ b/lib/sasl/test/systools_SUITE_data/d_opt_apps/lib/app1-1.0/src/myapp1.erl
@@ -0,0 +1 @@
+-module(myapp1).
diff --git a/lib/sasl/test/systools_SUITE_data/d_opt_apps/lib/app2-1.0/ebin/app2.app b/lib/sasl/test/systools_SUITE_data/d_opt_apps/lib/app2-1.0/ebin/app2.app
new file mode 100644
index 0000000000..c432fa5136
--- /dev/null
+++ b/lib/sasl/test/systools_SUITE_data/d_opt_apps/lib/app2-1.0/ebin/app2.app
@@ -0,0 +1,7 @@
+{application, app2,
+ [{description, "Application 2"},
+ {vsn, "1.0"},
+ {modules, [myapp2]},
+ {registered, []},
+ {applications, []},
+ {env, []}]}.
diff --git a/lib/sasl/test/systools_SUITE_data/d_opt_apps/lib/app2-1.0/src/myapp2.erl b/lib/sasl/test/systools_SUITE_data/d_opt_apps/lib/app2-1.0/src/myapp2.erl
new file mode 100644
index 0000000000..f8a4c1e139
--- /dev/null
+++ b/lib/sasl/test/systools_SUITE_data/d_opt_apps/lib/app2-1.0/src/myapp2.erl
@@ -0,0 +1 @@
+-module(myapp2).
--
2.26.2