1%%
2%% %CopyrightBegin%
3%%
4%% Copyright Ericsson AB 2009-2018. All Rights Reserved.
5%%
6%% Licensed under the Apache License, Version 2.0 (the "License");
7%% you may not use this file except in compliance with the License.
8%% You may obtain a copy of the License at
9%%
10%%     http://www.apache.org/licenses/LICENSE-2.0
11%%
12%% Unless required by applicable law or agreed to in writing, software
13%% distributed under the License is distributed on an "AS IS" BASIS,
14%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
15%% See the License for the specific language governing permissions and
16%% limitations under the License.
17%%
18%% %CopyrightEnd%
19
20-module(reltool_server).
21
22%% Public
23-export([
24         start_link/0, start_link/1,
25         get_config/3, load_config/2, save_config/4,
26         get_rel/2, get_script/2,
27         reset_config/1, undo_config/1,
28         get_mod/2,
29         get_app/2, set_app/2,
30         get_apps/2, set_apps/2,
31         get_sys/1, set_sys/2,
32         get_status/1,
33         gen_rel_files/2, gen_target/2, gen_spec/1
34        ]).
35
36%% Internal
37-export([init/1, loop/1]).
38
39%% sys callback functions
40-export([
41         system_continue/3,
42         system_terminate/4,
43         system_code_change/4
44        ]).
45
46-include("reltool.hrl").
47
48-record(state,
49        {options,
50         parent_pid,
51         common,
52         sys,
53         old_sys,
54         status,
55         old_status,
56	 app_tab,
57	 old_app_tab,
58	 mod_tab,
59	 old_mod_tab,
60	 mod_used_by_tab}).
61
62%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
63%% Client
64
65start_link() ->
66    start_link([]).
67
68start_link(Options) ->
69    proc_lib:start_link(?MODULE,
70			init,
71			[[{parent, self()} | Options]],
72			infinity,
73			[]).
74
75get_config(Pid, InclDef, InclDeriv) ->
76    reltool_utils:call(Pid, {get_config, InclDef, InclDeriv}).
77
78load_config(Pid, FilenameOrConfig) ->
79    reltool_utils:call(Pid, {load_config, FilenameOrConfig}).
80
81save_config(Pid, Filename, InclDef, InclDeriv) ->
82    reltool_utils:call(Pid, {save_config, Filename, InclDef, InclDeriv}).
83
84reset_config(Pid) ->
85    reltool_utils:call(Pid, reset_config).
86
87undo_config(Pid) ->
88    reltool_utils:call(Pid, undo_config).
89
90get_rel(Pid, RelName) ->
91    reltool_utils:call(Pid, {get_rel, RelName}).
92
93get_script(Pid, RelName) ->
94    reltool_utils:call(Pid, {get_script, RelName}).
95
96get_mod(Pid, ModName) ->
97    reltool_utils:call(Pid, {get_mod, ModName}).
98
99get_app(Pid, AppName) ->
100    reltool_utils:call(Pid, {get_app, AppName}).
101
102set_app(Pid, App) ->
103    reltool_utils:call(Pid, {set_app, App}).
104
105get_apps(Pid, Kind) ->
106    reltool_utils:call(Pid, {get_apps, Kind}).
107
108set_apps(Pid, Apps) ->
109    reltool_utils:call(Pid, {set_apps, Apps}).
110
111get_sys(Pid) ->
112    reltool_utils:call(Pid, get_sys).
113
114set_sys(Pid, Sys) ->
115    reltool_utils:call(Pid, {set_sys, Sys}).
116
117get_status(Pid) ->
118    reltool_utils:call(Pid, get_status).
119
120gen_rel_files(Pid, Dir) ->
121    reltool_utils:call(Pid, {gen_rel_files, Dir}).
122
123gen_target(Pid, Dir) ->
124    reltool_utils:call(Pid, {gen_target, Dir}).
125
126gen_spec(Pid) ->
127    reltool_utils:call(Pid, gen_spec).
128
129%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
130%% Server
131
132init([{parent,Parent}|_] = Options) ->
133    try
134        do_init(Options)
135    catch
136	throw:{error,Reason} ->
137	    proc_lib:init_ack(Parent,{error,Reason});
138        error:Reason:Stacktrace ->
139            exit({Reason, Stacktrace})
140    end.
141
142do_init(Options) ->
143    AppTab = ets:new(reltool_apps1, [public, ordered_set, {keypos,#app.name}]),
144    OldAppTab = ets:new(reltool_apps2, [public, ordered_set, {keypos,#app.name}]),
145    ModTab = ets:new(reltool_mods1, [public, ordered_set, {keypos,#mod.name}]),
146    OldModTab = ets:new(reltool_mods2, [public, ordered_set, {keypos,#mod.name}]),
147    ModUsesTab = ets:new(reltool_mod_uses, [public, bag, {keypos, 1}]),
148    S = #state{options = Options,
149	       app_tab = AppTab,
150	       old_app_tab = OldAppTab,
151	       mod_tab = ModTab,
152	       old_mod_tab = OldModTab,
153	       mod_used_by_tab = ModUsesTab},
154
155    S2 = parse_options(S),
156    {S3, Apps, Status2} = refresh(S2),
157    Status3 =  analyse(S3, Apps, Status2),
158    %% Set old_xxx equal to xxx to allow undo=nop
159    FakeBackup = {ets:tab2list(S3#state.app_tab),ets:tab2list(S3#state.mod_tab)},
160    S4 = save_old(S3, S3, FakeBackup, Status3),
161    #state{parent_pid = Parent, sys=Sys, common=C} = S4,
162    proc_lib:init_ack(Parent, {ok, self(), C, Sys#sys{apps=undefined}}),
163    loop(S4).
164
165parse_options(S) ->
166    Sys = default_sys(),
167    C = #common{sys_debug = [],
168		wx_debug = 0,
169		trap_exit = true},
170    parse_options(S#state.options, S, C, Sys).
171
172default_sys() ->
173    #sys{root_dir          = reltool_utils:root_dir(),
174	 lib_dirs          = reltool_utils:erl_libs(),
175	 escripts          = [],
176	 incl_cond         = ?DEFAULT_INCL_COND,
177	 mod_cond          = ?DEFAULT_MOD_COND,
178	 apps              = ?DEFAULT_APPS,
179	 boot_rel          = ?DEFAULT_REL_NAME,
180	 rels              = reltool_utils:default_rels(),
181	 emu_name          = ?DEFAULT_EMU_NAME,
182	 profile           = ?DEFAULT_PROFILE,
183	 incl_sys_filters  = dec_re(incl_sys_filters,
184				    ?DEFAULT_INCL_SYS_FILTERS,
185				    []),
186	 excl_sys_filters  = dec_re(excl_sys_filters,
187				    ?DEFAULT_EXCL_SYS_FILTERS,
188				    []),
189	 incl_app_filters  = dec_re(incl_app_filters,
190				    ?DEFAULT_INCL_APP_FILTERS,
191				    []),
192	 excl_app_filters  = dec_re(excl_app_filters,
193				    ?DEFAULT_EXCL_APP_FILTERS,
194				    []),
195	 relocatable       = ?DEFAULT_RELOCATABLE,
196	 rel_app_type      = ?DEFAULT_REL_APP_TYPE,
197	 embedded_app_type = ?DEFAULT_EMBEDDED_APP_TYPE,
198	 app_file          = ?DEFAULT_APP_FILE,
199	 incl_archive_filters = dec_re(incl_archive_filters,
200				       ?DEFAULT_INCL_ARCHIVE_FILTERS,
201				       []),
202	 excl_archive_filters = dec_re(excl_archive_filters,
203				       ?DEFAULT_EXCL_ARCHIVE_FILTERS,
204				       []),
205	 archive_opts      = ?DEFAULT_ARCHIVE_OPTS,
206	 debug_info        = ?DEFAULT_DEBUG_INFO}.
207
208dec_re(Key, Regexps, Old) ->
209    reltool_utils:decode_regexps(Key, Regexps, Old).
210
211parse_options([{Key, Val} | KeyVals], S, C, Sys) ->
212    case Key of
213        parent ->
214            parse_options(KeyVals, S#state{parent_pid = Val}, C, Sys);
215        sys_debug ->
216            parse_options(KeyVals, S, C#common{sys_debug = Val}, Sys);
217        wx_debug ->
218            parse_options(KeyVals, S, C#common{wx_debug = Val}, Sys);
219        trap_exit ->
220            parse_options(KeyVals, S, C#common{trap_exit = Val}, Sys);
221        config ->
222            Sys2 = read_config(Sys, Val),
223            parse_options(KeyVals, S, C, Sys2);
224        sys ->
225            Sys2 = read_config(Sys, {sys, Val}),
226            parse_options(KeyVals, S, C, Sys2);
227        _ ->
228	    reltool_utils:throw_error("Illegal option: ~tp", [{Key, Val}])
229    end;
230parse_options([], S, C, Sys) ->
231    S#state{common = C, sys = Sys};
232parse_options(KeyVals, _S, _C, _Sys) ->
233    reltool_utils:throw_error("Illegal option: ~tp", [KeyVals]).
234
235loop(#state{sys = Sys} = S) ->
236    receive
237        {system, From, Msg} ->
238            sys:handle_system_msg(Msg,
239				  From,
240				  S#state.parent_pid,
241				  ?MODULE,
242				  (S#state.common)#common.sys_debug,
243				  S);
244        {call, ReplyTo, Ref, {get_config, InclDef, InclDeriv}} ->
245            Reply = do_get_config(S, InclDef, InclDeriv),
246            reltool_utils:reply(ReplyTo, Ref, Reply),
247            ?MODULE:loop(S);
248        {call, ReplyTo, Ref, {load_config, SysConfig}} ->
249	    Fun = fun() -> do_load_config(S, SysConfig) end,
250	    {S3, Status2} = config_and_refresh(S, Fun),
251            reltool_utils:reply(ReplyTo, Ref, Status2),
252            ?MODULE:loop(S3);
253        {call, ReplyTo, Ref, {save_config, Filename, InclDef, InclDeriv}} ->
254            Reply = do_save_config(S, Filename, InclDef, InclDeriv),
255            reltool_utils:reply(ReplyTo, Ref, Reply),
256            ?MODULE:loop(S);
257        {call, ReplyTo, Ref, reset_config} ->
258	    Fun = fun() -> parse_options(S) end,
259	    {S3, Status2} = config_and_refresh(S, Fun),
260            reltool_utils:reply(ReplyTo, Ref, Status2),
261            ?MODULE:loop(S3);
262        {call, ReplyTo, Ref, undo_config} ->
263            S2 = S#state{sys = S#state.old_sys,
264                         old_sys = Sys,
265			 status = S#state.old_status,
266			 old_status = S#state.status,
267			 app_tab = S#state.old_app_tab,
268			 old_app_tab = S#state.app_tab,
269			 mod_tab = S#state.old_mod_tab,
270			 old_mod_tab = S#state.mod_tab},
271            reltool_utils:reply(ReplyTo, Ref, ok),
272            ?MODULE:loop(S2);
273        {call, ReplyTo, Ref, {get_rel, RelName}} ->
274            Reply =
275                case lists:keysearch(RelName, #rel.name, Sys#sys.rels) of
276                    {value, Rel} ->
277                        reltool_target:gen_rel(Rel, sys_all_apps(S));
278                    false ->
279                        {error, "No such release: " ++ RelName}
280                end,
281            reltool_utils:reply(ReplyTo, Ref, Reply),
282            ?MODULE:loop(S);
283        {call, ReplyTo, Ref, {get_script, RelName}} ->
284            Reply =
285                case lists:keysearch(RelName, #rel.name, Sys#sys.rels) of
286                    {value, Rel} ->
287                        PathFlag = true,
288                        Vars = [],
289                        reltool_target:gen_script(Rel, sys_all_apps(S),
290						  PathFlag, Vars);
291                    false ->
292                        {error, "No such release: " ++ RelName}
293                end,
294            reltool_utils:reply(ReplyTo, Ref, Reply),
295            ?MODULE:loop(S);
296        {call, ReplyTo, Ref, {get_mod, ModName}} ->
297            Reply =
298                case ets:lookup(S#state.mod_tab, ModName) of
299                    [M] ->
300                        {ok, M};
301                    [] ->
302                        {ok, missing_mod(ModName, ?MISSING_APP_NAME)}
303                end,
304            reltool_utils:reply(ReplyTo, Ref, Reply),
305            ?MODULE:loop(S);
306        {call, ReplyTo, Ref, {get_app, AppName}} when is_atom(AppName) ->
307            Reply =
308                case ets:lookup(S#state.app_tab,AppName) of
309                    [App] ->
310                        {ok, App};
311                    [] ->
312                        {error, "No such application: " ++
313			 atom_to_list(AppName)}
314                end,
315            reltool_utils:reply(ReplyTo, Ref, Reply),
316            ?MODULE:loop(S);
317        {call, ReplyTo, Ref, {set_app, App}} ->
318	    Fun = fun() -> do_set_apps(S, [App]) end,
319	    {S3, Status2} = config_and_refresh(S, Fun),
320	    Reply =
321		case Status2 of
322		    {ok, Warnings} ->
323			[App2] = ets:lookup(S3#state.app_tab,App#app.name),
324			{ok, App2, Warnings};
325		    {error, _} ->
326			Status2
327		end,
328	    reltool_utils:reply(ReplyTo, Ref, Reply),
329	    ?MODULE:loop(S3);
330        {call, ReplyTo, Ref, {get_apps, Kind}} ->
331            AppNames =
332                case Kind of
333                    whitelist ->
334			%% Pre-included
335			ets:select(S#state.app_tab,
336				   [{#app{is_pre_included=true,_='_'},
337				     [],
338				     ['$_']}]);
339		    blacklist ->
340			%% Pre-excluded
341			ets:select(S#state.app_tab,
342				   [{#app{is_pre_included=false,_='_'},
343				     [],
344				     ['$_']}]);
345		    source ->
346			%% Not included and not pre-excluded
347			ets:select(S#state.app_tab,
348				   [{#app{is_included='$1',
349					  is_pre_included='$2',
350					  _='_'},
351				     [{'=/=','$1',true},
352				      {'=/=','$2',false}],
353				     ['$_']}]);
354                    derived ->
355			%% Included, but not pre-included
356			ets:select(S#state.app_tab,
357				   [{#app{is_included='$1',
358					  is_pre_included='$2',
359					  _='_'},
360				     [{'=:=','$1',true},
361				      {'=/=','$2',true}],
362				     ['$_']}])
363                end,
364            reltool_utils:reply(ReplyTo, Ref, {ok, AppNames}),
365            ?MODULE:loop(S);
366        {call, ReplyTo, Ref, {set_apps, Apps}} ->
367	    Fun = fun() -> do_set_apps(S, Apps) end,
368	    {S3, Status2} = config_and_refresh(S, Fun),
369            reltool_utils:reply(ReplyTo, Ref, Status2),
370	    ?MODULE:loop(S3);
371        {call, ReplyTo, Ref, get_sys} ->
372            reltool_utils:reply(ReplyTo, Ref, {ok, Sys#sys{apps = undefined}}),
373            ?MODULE:loop(S);
374        {call, ReplyTo, Ref, {set_sys, Sys2}} ->
375	    Fun = fun() -> S#state{sys =  Sys2#sys{apps = Sys#sys.apps}} end,
376	    {S3, Status} = config_and_refresh(S, Fun),
377            reltool_utils:reply(ReplyTo, Ref, Status),
378            ?MODULE:loop(S3);
379        {call, ReplyTo, Ref, get_status} ->
380            reltool_utils:reply(ReplyTo, Ref, S#state.status),
381            ?MODULE:loop(S);
382        {call, ReplyTo, Ref, {gen_rel_files, Dir}} ->
383            Status =
384                case reltool_target:gen_rel_files(sys_all_apps(S), Dir) of
385                    ok ->
386                        {ok, []};
387                    {error, Reason} ->
388                        {error, Reason}
389                end,
390            reltool_utils:reply(ReplyTo, Ref, Status),
391            ?MODULE:loop(S);
392        {call, ReplyTo, Ref, {gen_target, Dir}} ->
393            Reply = reltool_target:gen_target(sys_all_apps(S), Dir),
394            reltool_utils:reply(ReplyTo, Ref, Reply),
395            ?MODULE:loop(S);
396        {call, ReplyTo, Ref, gen_spec} ->
397            Reply = reltool_target:gen_spec(sys_all_apps(S)),
398            reltool_utils:reply(ReplyTo, Ref, Reply),
399            ?MODULE:loop(S);
400        {'EXIT', Pid, Reason} when Pid =:= S#state.parent_pid ->
401            exit(Reason);
402        {call, ReplyTo, Ref, Msg} when is_pid(ReplyTo), is_reference(Ref) ->
403            error_logger:format("~w~w got unexpected call:\n\t~tp\n",
404                                [?MODULE, self(), Msg]),
405            reltool_utils:reply(ReplyTo, Ref, {error, {invalid_call, Msg}}),
406            ?MODULE:loop(S);
407        Msg ->
408            error_logger:format("~w~w got unexpected message:\n\t~tp\n",
409                                [?MODULE, self(), Msg]),
410            ?MODULE:loop(S)
411    end.
412
413
414 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
415do_set_apps(#state{sys = Sys} = S, ChangedApps) ->
416    %% Create new list of configured applications
417    SysApps = app_update_config(ChangedApps, Sys#sys.apps),
418    S#state{sys = Sys#sys{apps = SysApps}}.
419
420%% Re-create the #sys.apps list by
421%% 1) taking configurable fields from the changed #app records and
422%%    create new default records
423%% 2) removing #app records if no configurable fields are set
424%% 3) keeping #app records that are not changed
425app_update_config([#app{name=Name,is_escript={inlined,Escript}}|_],_SysApps) ->
426    reltool_utils:throw_error("Application ~w is inlined in ~w. Can not change "
427			      "configuration for an inlined application.",
428			      [Name,Escript]);
429app_update_config([Config|Configs],SysApps) ->
430    NewSysApps =
431	case app_set_config_only(Config) of
432	    {delete,Name} ->
433		lists:keydelete(Name,#app.name,SysApps);
434	    New ->
435		lists:ukeymerge(#app.name,[New],SysApps)
436	end,
437    app_update_config(Configs,NewSysApps);
438app_update_config([],SysApps) ->
439    SysApps.
440
441app_set_config_only(#app{mods=ConfigMods} = Config) ->
442    app_set_config_only(mod_set_config_only(ConfigMods),Config).
443
444app_set_config_only([],#app{name                 = Name,
445			    incl_cond            = undefined,
446			    mod_cond             = undefined,
447			    use_selected_vsn     = undefined,
448			    debug_info           = undefined,
449			    app_file             = undefined,
450			    app_type             = undefined,
451			    incl_app_filters     = undefined,
452			    excl_app_filters     = undefined,
453			    incl_archive_filters = undefined,
454			    excl_archive_filters = undefined,
455			    archive_opts         = undefined,
456			    is_escript           = false})->
457    {delete,Name};
458app_set_config_only(Mods,#app{name                 = Name,
459			      incl_cond            = InclCond,
460			      mod_cond             = ModCond,
461			      use_selected_vsn     = UseSelectedVsn,
462			      debug_info           = DebugInfo,
463			      app_file             = AppFile,
464			      app_type             = AppType,
465			      incl_app_filters     = InclAppFilters,
466			      excl_app_filters     = ExclAppFilters,
467			      incl_archive_filters = InclArchiveFilters,
468			      excl_archive_filters = ExclArchiveFilters,
469			      archive_opts         = ArchiveOpts,
470			      vsn                  = Vsn,
471			      is_escript           = IsEscript,
472			      label                = Label,
473			      info                 = Info,
474			      active_dir           = ActiveDir,
475			      sorted_dirs          = SortedDirs}) ->
476    App = (default_app(Name))#app{incl_cond            = InclCond,
477				  mod_cond             = ModCond,
478				  use_selected_vsn     = UseSelectedVsn,
479				  debug_info           = DebugInfo,
480				  app_file             = AppFile,
481				  app_type             = AppType,
482				  incl_app_filters     = InclAppFilters,
483				  excl_app_filters     = ExclAppFilters,
484				  incl_archive_filters = InclArchiveFilters,
485				  excl_archive_filters = ExclArchiveFilters,
486				  archive_opts         = ArchiveOpts,
487				  vsn                  = Vsn,
488				  mods                 = Mods},
489
490    if IsEscript ->
491	    %% Some fields shall only be set if it is an escript, e.g. label
492	    %% must never be set for any other applications since that will
493	    %% prevent refreshing.
494	    App#app{is_escript  = IsEscript,
495		    active_dir  = ActiveDir,
496		    sorted_dirs = SortedDirs,
497		    label       = Label,
498		    info        = Info};
499       UseSelectedVsn =:= dir ->
500	    %% Must not loose active_dir if it is configured to be used
501	    App#app{active_dir = ActiveDir,
502		    sorted_dirs = [ActiveDir]};
503       true ->
504	    App
505    end.
506
507mod_set_config_only(ConfigMods) ->
508    [#mod{name       = Name,
509	  incl_cond  = InclCond,
510	  debug_info = DebugInfo} ||
511	#mod{name       = Name,
512	     incl_cond  = InclCond,
513	     debug_info = DebugInfo} <- ConfigMods,
514	(InclCond =/= undefined) orelse (DebugInfo =/= undefined)].
515
516
517 %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
518
519analyse(#state{sys=Sys} = S, Apps, Status) ->
520    %% Create a list of {RelName,AppName}, one element for each
521    %% AppName that needs to be included for the given release.
522    RelApps = apps_in_rels(Sys#sys.rels, Apps),
523
524    %% Initiate is_pre_included and is_included for all applications
525    %% based on #sys.incl_cond, #app.incl_cond and if the application
526    %% is included in a release (rel spec - see apps_in_rels above).
527    %% Then initiate the same for each module, and check that there
528    %% are no duplicated module names (in different applications)
529    %% where we cannot decide which one to use.
530    %% Write all #app to app_tab and all #mod to mod_tab.
531    Status2 = apps_init_is_included(S, Apps, RelApps, Status),
532
533    %% For each application that is not (directly or indirectly) part
534    %% of a release, but still has #app.is_included==true, propagate
535    %% is_included to the dependencies specified in the .app files.
536    app_propagate_is_included(S),
537
538    %% For each module that has #mod.is_included==true, propagate
539    %% is_included to the modules it uses.
540    mod_propagate_is_included(S),
541
542    %% Insert reverse dependencies - i.e. for each
543    %% #mod{name=Mod, uses_mods=[UsedMod]},
544    %% insert an entry {UsedMod,Mod} in mod_used_by_tab.
545    propagate_is_used_by(S),
546
547    %% Set the above reverse dependencies in #mod records
548    %% (used_by_mods) and accumulate in #app records.
549    %% Make sure #app.is_included is always true if some
550    %% #mod.is_included==true for at least one module in the app.
551    %% Set status=missing|ok for #app and #mod - indicates if module
552    %% (.beam file) is missing in file system.
553    app_recap_dependencies(S),
554
555    %% Check that the boot_rel exists.
556    %% Check that all applications that are listed in a 'rel' spec are
557    %% also really included in the target release.
558    %% Check that all mandatory applications are included in all rels.
559    verify_config(S, RelApps, Status2).
560
561apps_in_rels(Rels, Apps) ->
562    AllRelApps =
563	lists:foldl(fun(Rel, RelApps) ->
564			    MoreRelApps = apps_in_rel(Rel, Apps),
565			    MoreRelApps ++ RelApps
566		    end,
567		    [],
568		    Rels),
569    lists:reverse(AllRelApps).
570
571apps_in_rel(#rel{name = RelName, rel_apps = RelApps}, Apps) ->
572    Mandatory = [{RelName, kernel}, {RelName, stdlib}],
573    Explicit0 = [{RelName, AppName} || #rel_app{name=AppName} <- RelApps],
574    Explicit = Mandatory ++ Explicit0,
575    Deps =
576	[{RelName, AppName, Optional} ||
577	    RA <- RelApps,
578	    {AppName, Optional} <-
579		case lists:keyfind(RA#rel_app.name,
580				   #app.name,
581				   Apps) of
582		    #app{info = Info} ->
583			%% Included applications in rel shall overwrite included
584			%% applications in .app. I.e. included applications in
585			%% .app shall only be used if it is not defined in rel.
586			IA = case RA#rel_app.incl_apps of
587				 undefined ->
588				     Info#app_info.incl_apps;
589				 RelIA ->
590				     RelIA
591			     end,
592			build_more_apps(Info, IA);
593		    false ->
594			reltool_utils:throw_error(
595			  "Release ~tp uses non existing "
596			  "application ~w",
597			  [RelName,RA#rel_app.name])
598		end,
599	    not lists:keymember(AppName, 2, Explicit)],
600    more_apps_in_rels(Deps, Apps, Explicit).
601
602more_apps_in_rels([{RelName, AppName, Optional} | RelApps], Apps, Acc) ->
603    case lists:member({RelName, AppName}, Acc) of
604	true ->
605	    more_apps_in_rels(RelApps, Apps, Acc);
606	false ->
607	    case lists:keyfind(AppName, #app.name, Apps) of
608		#app{info = #app_info{incl_apps=IA} = Info} ->
609		    Extra = [{RelName, ChildName, ChildOptional} ||
610				{ChildName, ChildOptional} <- build_more_apps(Info, IA)],
611		    Acc2 = more_apps_in_rels(Extra, Apps, [{RelName, AppName} | Acc]),
612		    more_apps_in_rels(RelApps, Apps, Acc2);
613		false when Optional ->
614		    more_apps_in_rels(RelApps, Apps, Acc);
615		false ->
616		    reltool_utils:throw_error(
617		      "Release ~tp uses non existing application ~w",
618		      [RelName,AppName])
619	    end
620    end;
621more_apps_in_rels([], _Apps, Acc) ->
622    Acc.
623
624build_more_apps(#app_info{applications = AA, opt_apps = OA}, IA) ->
625    AAOpt = [{App, lists:member(App, OA)} || App <- AA],
626    IAOpt = [{App, false} || App <- IA],
627    AAOpt ++ IAOpt.
628
629apps_init_is_included(S, Apps, RelApps, Status) ->
630    lists:foldl(fun(App, AccStatus) ->
631			app_init_is_included(S, App, RelApps, AccStatus)
632		end,
633		Status,
634		Apps).
635
636app_init_is_included(#state{app_tab = AppTab, mod_tab = ModTab, sys=Sys},
637		     #app{name = AppName, mods = Mods} = A,
638		     RelApps,
639		     Status) ->
640    AppCond =
641        case A#app.incl_cond of
642            undefined -> Sys#sys.incl_cond;
643            _         -> A#app.incl_cond
644        end,
645    ModCond =
646        case A#app.mod_cond of
647            undefined -> Sys#sys.mod_cond;
648            _         -> A#app.mod_cond
649        end,
650    Rels = [RelName || {RelName, AN} <- RelApps, AN =:= AppName],
651    {Default, IsPreIncl, IsIncl, Status2} =
652        case {AppCond, Rels} of
653            {include, _} ->
654		{undefined, true, true, Status};
655            {exclude, []} ->
656		{undefined, false, false, Status};
657            {exclude, [RelName | _]} -> % App is included in at least one rel
658		reltool_utils:throw_error(
659		  "Application ~w is used in release ~tp and cannot be excluded",
660		  [AppName,RelName]);
661            {derived, []} ->
662		{undefined, undefined, undefined, Status};
663            {derived, [_ | _]} -> % App is included in at least one rel
664		{true, undefined, true, Status}
665        end,
666    {Mods2,Status3} = lists:mapfoldl(fun(Mod,Acc) ->
667					     mod_init_is_included(ModTab,
668								  Mod,
669								  ModCond,
670								  AppCond,
671								  Default,
672								  Acc)
673				     end,
674				     Status2,
675				     Mods),
676    A2 = A#app{mods = Mods2,
677	       is_pre_included = IsPreIncl,
678	       is_included = IsIncl,
679	       rels = Rels},
680    ets:insert(AppTab, A2),
681    Status3.
682
683mod_init_is_included(ModTab, M, ModCond, AppCond, Default, Status) ->
684    %% print(M#mod.name, hipe, "incl_cond -> ~w\n", [AppCond]),
685    IsIncl =
686        case AppCond of
687            include ->
688                case M#mod.incl_cond of
689                    include ->
690                        true;
691                    exclude ->
692                        false;
693		    derived ->
694			undefined;
695                    undefined ->
696                        %% print(M#mod.name, hipe, "mod_cond -> ~w\n",
697			%%       [ModCond]),
698                        case ModCond of
699                            all     -> true;
700                            app     -> false_to_undefined(M#mod.is_app_mod);
701                            ebin    -> false_to_undefined(M#mod.is_ebin_mod);
702                            derived -> Default;
703                            none    -> false
704                        end
705                end;
706            exclude ->
707                false;
708            derived ->
709                case M#mod.incl_cond of
710                    include ->
711                        true;
712                    exclude ->
713                        false;
714		    derived ->
715			undefined;
716                    undefined ->
717                        Default
718                end
719        end,
720
721    M2 = M#mod{is_pre_included = IsIncl, is_included = IsIncl},
722
723    Status2 =
724	case ets:lookup(ModTab,M#mod.name) of
725	    [Existing] ->
726		case {Existing#mod.is_included,IsIncl} of
727		    {false,_} ->
728			ets:insert(ModTab, M2),
729			reltool_utils:add_warning(
730			  "Module ~w exists in applications ~w and ~w. "
731			  "Using module from application ~w.",
732			  [M#mod.name, Existing#mod.app_name,
733			   M#mod.app_name, M#mod.app_name],
734			  Status);
735		    {_,false} ->
736			%% Don't insert in ModTab - using Existing
737			reltool_utils:add_warning(
738			  "Module ~w exists in applications ~w and ~w. "
739			  "Using module from application ~w.",
740			  [M#mod.name, Existing#mod.app_name,
741			   M#mod.app_name,Existing#mod.app_name],
742			  Status);
743		    {_,_} ->
744			reltool_utils:throw_error(
745			  "Module ~w potentially included by two different "
746			  "applications: ~w and ~w.",
747			  [M#mod.name,Existing#mod.app_name,M#mod.app_name])
748		end;
749	    [] ->
750		ets:insert(ModTab, M2),
751		Status
752	end,
753
754    %% print(M#mod.name, hipe, "~p -> ~w\n", [M2, IsIncl]),
755    {M2,Status2}.
756
757false_to_undefined(Bool) ->
758    case Bool of
759        false -> undefined;
760        _     -> Bool
761    end.
762
763get_no_rel_apps_and_dependencies(S) ->
764    ets:select(S#state.app_tab, [{#app{name='$1',
765				       is_included=true,
766				       info=#app_info{applications='$2',
767						      incl_apps='$3',
768						      _='_'},
769				       rels=[],
770				       _='_'},
771				  [],
772				  [{{'$1','$2','$3'}}]}]).
773
774app_propagate_is_included(S) ->
775    lists:foreach(
776      fun({AppName,DepNames1,DepNames2}) ->
777	      app_mark_is_included(S,AppName,DepNames1++DepNames2)
778      end,
779      get_no_rel_apps_and_dependencies(S)).
780
781app_mark_is_included(#state{app_tab=AppTab, mod_tab=ModTab, sys=Sys}=S,UsedByName,[AppName|AppNames]) ->
782    case ets:lookup(AppTab, AppName) of
783	[A] ->
784	    case A#app.is_included of
785		undefined ->
786		    %% Not yet marked => mark and propagate
787		    A2 =
788			case A#app.incl_cond of
789			    include ->
790				A#app{is_pre_included = true,
791				      is_included = true};
792			    exclude ->
793				A#app{is_pre_included = false,
794				      is_included = false};
795			    AppInclCond when AppInclCond==undefined;
796					     AppInclCond==derived  ->
797				A#app{is_included = true}
798			end,
799		    ets:insert(AppTab, A2),
800
801		    ModCond =
802			case A#app.mod_cond of
803			    undefined -> Sys#sys.mod_cond;
804			    _         -> A#app.mod_cond
805			end,
806		    Filter =
807			fun(M) ->
808				case ModCond of
809				    all     -> true;
810				    app     -> M#mod.is_app_mod;
811				    ebin    -> M#mod.is_ebin_mod;
812				    derived -> false;
813				    none    -> false
814				end
815			end,
816		    Mods = lists:filter(Filter, A#app.mods),
817		    %% Mark the modules of this app, but no need to go
818		    %% recursive on modules since this is done in
819		    %% mod_mark_is_included.
820		    [case M#mod.is_included of
821			 undefined ->
822			     M2 =
823				 case M#mod.incl_cond of
824				     include ->
825					 M#mod{is_pre_included = true,
826					       is_included = true};
827				     exclude ->
828					 M#mod{is_pre_included = false,
829					       is_included = false};
830				     ModInclCond when ModInclCond==undefined;
831						      ModInclCond==derived  ->
832					 M#mod{is_included = true}
833				 end,
834			     ets:insert(ModTab, M2);
835			 _ ->
836			     ok
837		     end || M <- Mods],
838
839		    %% Go recursive on dependencies
840		    #app{info=#app_info{applications=DepNames1,
841					incl_apps=DepNames2}} = A,
842		    app_mark_is_included(S,AppName,DepNames1++DepNames2);
843		_ ->
844		    %% Already marked
845		    ok
846	    end;
847	[] ->
848	    %% Missing app
849	    reltool_utils:throw_error(
850	      "Application ~tp uses non existing application ~w",
851	      [UsedByName,AppName])
852    end,
853    app_mark_is_included(S, UsedByName, AppNames);
854app_mark_is_included(_S, _UsedByName, []) ->
855    ok.
856
857%% Return the list for {ModName, UsesModNames} for all modules where
858%% #mod.is_included==true.
859get_all_mods_and_dependencies(S) ->
860    ets:select(S#state.mod_tab, [{#mod{name='$1',
861				       uses_mods='$2',
862				       is_included=true,
863				       _='_'},
864				  [],
865				  [{{'$1','$2'}}]}]).
866
867mod_propagate_is_included(S) ->
868    case lists:flatmap(
869	   fun({ModName,UsesModNames}) ->
870		   mod_mark_is_included(S,ModName,UsesModNames,[])
871	   end,
872	   get_all_mods_and_dependencies(S)) of
873	[] ->
874	    ok;
875	MissingMods ->
876	    MissingApp = default_app(?MISSING_APP_NAME, "missing"),
877	    MissingApp2 = MissingApp#app{label = ?MISSING_APP_TEXT,
878					 info = missing_app_info(""),
879					 mods = MissingMods,
880					 status = missing,
881					 uses_mods = []},
882	    ets:insert(S#state.app_tab, MissingApp2),
883	    ok
884    end.
885
886mod_mark_is_included(#state{app_tab=AppTab, mod_tab=ModTab, sys=Sys} = S,
887		     UsedByName, [ModName | ModNames], Acc) ->
888    Acc3 =
889        case ets:lookup(ModTab, ModName) of
890            [M] ->
891                case M#mod.is_included of
892                    undefined ->
893                        %% Not yet marked => mark and propagate
894                        M2 =
895                            case M#mod.incl_cond of
896                                include ->
897                                    M#mod{is_pre_included = true,
898					  is_included = true};
899                                exclude ->
900                                    M#mod{is_pre_included = false,
901					  is_included = false};
902				ModInclCond when ModInclCond==undefined;
903						 ModInclCond==derived  ->
904                                    M#mod{is_included = true}
905                            end,
906                        ets:insert(ModTab, M2),
907                        [A] = ets:lookup(AppTab, M2#mod.app_name),
908                        Acc2 =
909                            case A#app.is_included of
910                                undefined ->
911                                    ModCond =
912                                        case A#app.mod_cond of
913                                            undefined -> Sys#sys.mod_cond;
914                                            _         -> A#app.mod_cond
915                                        end,
916                                    Filter =
917                                        fun(M3) ->
918                                                case ModCond of
919                                                    all     -> true;
920                                                    app     -> M3#mod.is_app_mod;
921                                                    ebin    -> M3#mod.is_ebin_mod;
922                                                    derived -> false;
923                                                    none    -> false
924                                                end
925                                        end,
926                                    Mods = lists:filter(Filter, A#app.mods),
927                                    A2 = A#app{is_included = true},
928                                    ets:insert(AppTab, A2),
929                                    mod_mark_is_included(S,
930							 ModName,
931							 [M3#mod.name ||
932							     M3 <- Mods],
933							 Acc);
934				_ ->
935				    %% Already marked true or false
936                                    Acc
937                            end,
938                        mod_mark_is_included(S, ModName, M2#mod.uses_mods, Acc2);
939		    _ ->
940                        %% Already marked true or false
941                        Acc
942                end;
943            [] ->
944                M = missing_mod(ModName, ?MISSING_APP_NAME),
945                M2 = M#mod{is_included = true},
946                ets:insert(ModTab, M2),
947                [M2 | Acc]
948        end,
949    mod_mark_is_included(S, UsedByName, ModNames, Acc3);
950mod_mark_is_included(_S, _UsedByName, [], Acc) ->
951    Acc.
952
953propagate_is_used_by(S) ->
954    lists:foreach(
955      fun({Mod,UsesMods}) ->
956	      lists:foreach(
957		fun(UsedMod) ->
958			ets:insert(S#state.mod_used_by_tab,{UsedMod,Mod})
959		end,
960		UsesMods)
961      end,
962      get_all_mods_and_dependencies(S)).
963
964
965app_recap_dependencies(S) ->
966    ets:foldl(fun(App,_) -> app_recap_dependencies(S,App) end,
967	      ok, S#state.app_tab).
968
969app_recap_dependencies(S, #app{mods = Mods, is_included = IsIncl} = A) ->
970    {Mods2, IsIncl2} = mod_recap_dependencies(S, A, Mods, [], IsIncl),
971    AppStatus =
972        case lists:keymember(missing, #mod.status, Mods2) of
973            true  -> missing;
974            false -> ok
975        end,
976    UsesMods = [M#mod.uses_mods || M <- Mods2, M#mod.is_included =:= true],
977    UsesMods2 = lists:usort(lists:flatten(UsesMods)),
978    UsesApps = [M#mod.app_name || ModName <- UsesMods2,
979				  M <- ets:lookup(S#state.mod_tab, ModName)],
980    UsesApps2 = lists:usort(UsesApps),
981    UsedByMods = [M#mod.used_by_mods || M <- Mods2, M#mod.is_included =:= true],
982    UsedByMods2 = lists:usort(lists:flatten(UsedByMods)),
983    UsedByApps = [M#mod.app_name || ModName <- UsedByMods2,
984				    M <- ets:lookup(S#state.mod_tab, ModName)],
985    UsedByApps2 = lists:usort(UsedByApps),
986
987    A2 = A#app{mods = Mods2,
988               status = AppStatus,
989               uses_mods = UsesMods2,
990               used_by_mods = UsedByMods2,
991               uses_apps = UsesApps2,
992               used_by_apps = UsedByApps2,
993               is_included = IsIncl2},
994    ets:insert(S#state.app_tab,A2),
995    ok.
996
997mod_recap_dependencies(S, A, [#mod{name = ModName}=M1 | Mods], Acc, IsIncl) ->
998    case ets:lookup(S#state.mod_tab, ModName) of
999	[M2] when M2#mod.app_name=:=A#app.name ->
1000	    ModStatus = do_get_status(M2),
1001	    %% print(M2#mod.name, hipe, "status -> ~w\n", [ModStatus]),
1002	    {IsIncl2, M3} =
1003		case M2#mod.is_included of
1004		    true ->
1005			UsedByMods =
1006			    [N || {_, N} <- ets:lookup(S#state.mod_used_by_tab,
1007						       ModName)],
1008			{true, M2#mod{status = ModStatus, used_by_mods = UsedByMods}};
1009		    _    ->
1010			{IsIncl, M2#mod{status = ModStatus, used_by_mods = []}}
1011		end,
1012	    ets:insert(S#state.mod_tab, M3),
1013	    mod_recap_dependencies(S, A, Mods, [M3 | Acc], IsIncl2);
1014	[_] when A#app.is_included==false; M1#mod.incl_cond==exclude ->
1015	    %% App is explicitely excluded so it is ok that the module
1016	    %% record does not exist for this module in this
1017	    %% application.
1018	    mod_recap_dependencies(S, A, Mods, [M1 | Acc], IsIncl);
1019	[M2] ->
1020	    %% A module is potensially included by multiple
1021	    %% applications. This is not allowed!
1022	    reltool_utils:throw_error(
1023	      "Module ~w potentially included by two different applications: "
1024	      "~w and ~w.", [ModName,A#app.name, M2#mod.app_name])
1025    end;
1026mod_recap_dependencies(_S, _A, [], Acc, IsIncl) ->
1027    {lists:reverse(Acc), IsIncl}.
1028
1029do_get_status(M) ->
1030    if
1031        M#mod.exists =:= false, M#mod.is_included =/= false ->
1032            missing;
1033        true ->
1034            ok
1035    end.
1036
1037verify_config(#state{app_tab=AppTab, sys=#sys{boot_rel = BootRel, rels = Rels}},
1038	      RelApps, Status) ->
1039    case lists:keymember(BootRel, #rel.name, Rels) of
1040        true ->
1041	    Status2 = lists:foldl(fun(RA, Acc) ->
1042					  check_app(AppTab, RA, Acc) end,
1043				  Status,
1044				  RelApps),
1045	    lists:foldl(fun(#rel{name = RelName}, Acc)->
1046				check_rel(RelName, RelApps, Acc)
1047			end,
1048			Status2,
1049			Rels);
1050        false ->
1051	    reltool_utils:throw_error(
1052	      "Release ~tp is mandatory (used as boot_rel)",[BootRel])
1053    end.
1054
1055check_app(AppTab, {RelName, AppName}, Status) ->
1056    case ets:lookup(AppTab, AppName) of
1057	[#app{is_pre_included=IsPreIncl, is_included=IsIncl}]
1058	  when IsPreIncl; IsIncl ->
1059	    Status;
1060	_ ->
1061	    reltool_utils:throw_error(
1062	      "Release ~tp uses non included application ~w",[RelName,AppName])
1063    end.
1064
1065check_rel(RelName, RelApps, Status) ->
1066    EnsureApp =
1067        fun(AppName, Acc) ->
1068                case lists:member({RelName, AppName}, RelApps) of
1069                    true ->
1070                        Acc;
1071                    false ->
1072			reltool_utils:throw_error(
1073			  "Mandatory application ~w is not included in "
1074			  "release ~tp", [AppName,RelName])
1075                end
1076        end,
1077    Mandatory = [kernel, stdlib],
1078    lists:foldl(EnsureApp, Status, Mandatory).
1079
1080%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1081
1082refresh_app(#app{name = AppName,
1083                 is_escript = IsEscript,
1084                 active_dir = ActiveDir,
1085                 label = OptLabel,
1086                 mods = Mods,
1087                 status = AppStatus} = App,
1088            Force,
1089            Status) ->
1090    if
1091        Force; OptLabel =:= undefined ->
1092            {AppInfo, EbinMods, Status3} =
1093                case IsEscript of
1094                    false ->
1095
1096                        %% Add info from .app file
1097                        Base = get_base(AppName, ActiveDir),
1098                        DefaultVsn = get_vsn_from_dir(AppName,Base),
1099                        Ebin = filename:join([ActiveDir, "ebin"]),
1100                        AppFile =
1101			    filename:join([Ebin,
1102					   atom_to_list(AppName) ++ ".app"]),
1103                        {AI, Status2} =
1104			    read_app_info(AppFile,
1105					  AppFile,
1106					  AppName,
1107                                          ActiveDir,
1108                                          AppStatus,
1109					  DefaultVsn,
1110					  Status),
1111
1112			%% And read all modules from ebin and create
1113			%% #mod record with dependencies (uses_mods).
1114                        {AI, read_ebin_mods(Ebin, AppName), Status2};
1115                    _ ->
1116                        {App#app.info, Mods, Status}
1117                end,
1118
1119            %% Add non-existing modules - i.e. create default #mod
1120            %% records for all modules that are listed in .app file
1121            %% but do not exist in ebin.
1122	    AppInfoMods = lists:usort(AppInfo#app_info.modules),
1123	    Status4 =
1124		case AppInfo#app_info.modules -- AppInfoMods of
1125		    [] ->
1126			Status3;
1127		    DuplicatedMods  ->
1128			lists:foldl(
1129			  fun(M,S) ->
1130				  reltool_utils:add_warning(
1131				    "Module ~w duplicated in app file for "
1132				    "application ~w.", [M, AppName], S)
1133			  end,
1134			  Status3,
1135			  DuplicatedMods)
1136		end,
1137	    AppModNames =
1138		case AppInfo#app_info.mod of
1139		    {StartModName, _} ->
1140			case lists:member(StartModName, AppInfoMods) of
1141			    true  -> AppInfoMods;
1142			    false -> [StartModName | AppInfoMods]
1143			end;
1144		    undefined ->
1145			AppInfoMods
1146		end,
1147	    MissingMods = add_missing_mods(AppName, EbinMods, AppModNames),
1148
1149            %% Add optional user config for each module.
1150	    %% The #mod records that are already in the #app record at
1151	    %% this point do only contain user defined configuration
1152	    %% (set by parse_options/4). So here we merge with the
1153	    %% default records from above.
1154            Mods2 = add_mod_config(MissingMods ++ EbinMods, Mods),
1155
1156            %% Set app flag for each module in app file, i.e. the flag
1157            %% which indicates if the module is listed in the .app
1158            %% file or not. The start module also get the flag set to true.
1159            Mods3 = set_mod_flags(Mods2, AppModNames),
1160
1161	    %% Finally, set label and update the #app record
1162            AppVsn = AppInfo#app_info.vsn,
1163            AppLabel =
1164                case AppVsn of
1165                    "" -> atom_to_list(AppName);
1166                    _  -> atom_to_list(AppName) ++ "-" ++ AppVsn
1167                end,
1168            App2 = App#app{vsn = AppVsn,
1169                           label = AppLabel,
1170                           info = AppInfo,
1171                           mods = lists:keysort(#mod.name, Mods3)},
1172            {App2, Status4};
1173        true ->
1174            {App, Status}
1175    end.
1176
1177missing_app_info(Vsn) ->
1178    #app_info{vsn = Vsn}.
1179
1180read_app_info(_AppFileOrBin, _AppFile, erts, _ActiveDir, _AppStatus, DefaultVsn, Status) ->
1181    {missing_app_info(DefaultVsn), Status};
1182read_app_info(_AppFileOrBin, _AppFile, _AppName, undefined, missing, DefaultVsn, Status) ->
1183    {missing_app_info(DefaultVsn), Status};
1184read_app_info(AppFileOrBin, AppFile, AppName, _ActiveDir, _AppStatus, DefaultVsn, Status) ->
1185    EnoentText = file:format_error(enoent),
1186    case reltool_utils:prim_consult(AppFileOrBin) of
1187        {ok,  [{application, AppName, Info}]} ->
1188            AI = #app_info{vsn = DefaultVsn},
1189            parse_app_info(AppFile, Info, AI, Status);
1190        {ok, _BadApp} ->
1191            {missing_app_info(DefaultVsn),
1192	     reltool_utils:add_warning("~w: Illegal contents in app file ~tp, "
1193				       "application tuple with arity 3 expected.",
1194				       [AppName,AppFile],
1195				       Status)};
1196        {error, Text} when Text =:= EnoentText ->
1197	    {missing_app_info(DefaultVsn),
1198             reltool_utils:add_warning("~w: Missing app file ~tp.",
1199                                       [AppName,AppFile],
1200                                       Status)};
1201        {error, Text} ->
1202            {missing_app_info(DefaultVsn),
1203	     reltool_utils:add_warning("~w: Cannot parse app file ~tp (~tp).",
1204				       [AppName,AppFile,Text],
1205				       Status)}
1206    end.
1207
1208parse_app_info(File, [{Key, Val} | KeyVals], AI, Status) ->
1209    case Key of
1210        description ->
1211	    parse_app_info(File, KeyVals, AI#app_info{description = Val},
1212			   Status);
1213        id ->
1214	    parse_app_info(File, KeyVals, AI#app_info{id = Val}, Status);
1215        vsn ->
1216	    parse_app_info(File, KeyVals, AI#app_info{vsn = Val}, Status);
1217        modules ->
1218	    parse_app_info(File, KeyVals, AI#app_info{modules = Val}, Status);
1219        maxP ->
1220	    parse_app_info(File, KeyVals, AI#app_info{maxP = Val}, Status);
1221        maxT ->
1222	    parse_app_info(File, KeyVals, AI#app_info{maxT = Val}, Status);
1223        registered ->
1224	    parse_app_info(File, KeyVals, AI#app_info{registered = Val},
1225			   Status);
1226	optional_applications ->
1227	    parse_app_info(File, KeyVals, AI#app_info{opt_apps = Val}, Status);
1228        included_applications ->
1229	    parse_app_info(File, KeyVals, AI#app_info{incl_apps = Val}, Status);
1230        applications ->
1231	    parse_app_info(File, KeyVals, AI#app_info{applications = Val},
1232			   Status);
1233        env ->
1234	    parse_app_info(File, KeyVals, AI#app_info{env = Val}, Status);
1235        mod ->
1236	    parse_app_info(File, KeyVals, AI#app_info{mod = Val}, Status);
1237        start_phases ->
1238	    parse_app_info(File, KeyVals, AI#app_info{start_phases = Val},
1239			   Status);
1240	runtime_dependencies ->
1241	    parse_app_info(File, KeyVals, AI#app_info{runtime_dependencies = Val},
1242			   Status);
1243        _ ->
1244	    Status2 =
1245		reltool_utils:add_warning("Unexpected item ~tp in app file ~tp.",
1246					  [Key,File],
1247					  Status),
1248	    parse_app_info(File, KeyVals, AI, Status2)
1249    end;
1250parse_app_info(_, [], AI, Status) ->
1251    {AI, Status}.
1252
1253read_ebin_mods(Ebin, AppName) ->
1254    case erl_prim_loader:list_dir(Ebin) of
1255        {ok, Files} ->
1256            Ext = code:objfile_extension(),
1257            InitMod = fun(F) ->
1258                              File = filename:join([Ebin, F]),
1259                              init_mod(AppName, File, File, Ext)
1260                      end,
1261            Files2 = [F || F <- Files, filename:extension(F) =:= Ext],
1262            pmap(InitMod, Files2);
1263        error ->
1264            []
1265    end.
1266
1267pmap(Fun, List) ->
1268    lists:map(Fun, List).
1269    %% N = erlang:system_info(schedulers) * 2,
1270    %% pmap(Fun, List, 0, N, 0, [], []).
1271
1272%% -record(pmap_res, {count, ref, res}).
1273%% -record(pmap_wait, {count, ref, pid}).
1274%%
1275%% pmap(Fun, [H | T], N, Max, Count, WaitFor, Results) when N < Max ->
1276%%     Ref = make_ref(),
1277%%     Parent = self(),
1278%%     Count2 = Count + 1,
1279%%     Pid = spawn_link(fun() -> Parent ! #pmap_res{count = Count2, ref = Ref, res = Fun(H)}, unlink(Parent) end),
1280%%     PW = #pmap_wait{count = Count2, pid = Pid, ref = Ref},
1281%%     pmap(Fun, T, N + 1, Max, Count2, [PW | WaitFor], Results);
1282%% pmap(_Fun, [], _N, _Max, _Count, [], Results) ->
1283%%     %% Sort results and return them in the same orderas the original list
1284%%     [PR#pmap_res.res || PR <- lists:keysort(#pmap_res.count, Results)];
1285%% pmap(Fun, List, N, Max, Count, WaitFor, Results) ->
1286%%     receive
1287%%      #pmap_res{ref = Ref} = PR ->
1288%%          WaitFor2 = lists:keydelete(Ref, #pmap_wait.ref, WaitFor),
1289%%          pmap(Fun, List, N - 1, Max, Count, WaitFor2, [PR | Results]);
1290%%      {'EXIT', Reason} ->
1291%%          exit(Reason)
1292%%     end.
1293
1294init_mod(AppName, File, FileOrBin, Ext) ->
1295    UsesMods = xref_mod(FileOrBin),
1296    Base = filename:basename(File, Ext),
1297    ModName = list_to_atom(Base),
1298    #mod{name = ModName,
1299         app_name = AppName,
1300         incl_cond = undefined,
1301         is_ebin_mod = true,
1302         uses_mods = UsesMods,
1303         exists = true}.
1304
1305xref_mod({Base, Bin}) when is_binary(Bin) ->
1306    Dir = filename:absname("reltool_server.tmp"),
1307    ok = reltool_utils:recursive_delete(Dir),
1308    ok = file:make_dir(Dir),
1309    File = filename:join([Dir, Base]),
1310    ok = file:write_file(File, Bin),
1311    Res = xref_mod(File),
1312    ok = reltool_utils:recursive_delete(Dir),
1313    Res;
1314xref_mod(File) when is_list(File) ->
1315    {ok, Pid} = xref:start([{xref_mode, modules}]),
1316    link(Pid),
1317    ok = xref:set_default(Pid, [{verbose,false}, {warnings, false}]),
1318    ok = xref:set_library_path(Pid, []),
1319    {ok, _} = xref:add_module(Pid, File, []),
1320    {ok, UnknownMods} = xref:q(Pid, "UM", []),
1321    %% {ok, ExportedFuns} = xref:q(Pid, "X", []),
1322    %% io:format("Unres: ~p\n", [xref:variables(Pid, [predefined])]),
1323    %% io:format("Q: ~p\n", [xref:q(Pid, "XU", [])]),
1324    Ref = erlang:monitor(process, Pid),
1325    unlink(Pid),
1326    xref:stop(Pid),
1327    wait_for_processto_die(Ref, Pid, File),
1328    UnknownMods.
1329
1330wait_for_processto_die(Ref, Pid, File) ->
1331    receive
1332	{'DOWN', Ref, _Type, _Object, _Info} ->
1333	    ok
1334    after timer:seconds(30) ->
1335	    error_logger:error_msg("~w(~w): Waiting for process ~w to die ~tp\n",
1336				   [?MODULE, ?LINE, Pid, File]),
1337	    wait_for_processto_die(Ref, Pid, File)
1338    end.
1339
1340add_missing_mods(AppName, EbinMods, AppModNames) ->
1341    EbinModNames = [M#mod.name || M <- EbinMods],
1342    MissingModNames = AppModNames -- EbinModNames,
1343    [missing_mod(ModName, AppName) || ModName <- MissingModNames].
1344
1345missing_mod(ModName, AppName) ->
1346    %% io:format("Missing: ~w -> ~w\n", [AppName, ModName]),
1347    #mod{name = ModName,
1348         app_name = AppName,
1349         incl_cond = undefined,
1350         is_ebin_mod = false,
1351         exists = false,
1352         status = missing,
1353         uses_mods = []}.
1354
1355add_mod_config(Mods, ModConfigs) ->
1356    AddConfig =
1357        fun(Config, Acc) ->
1358                case lists:keyfind(Config#mod.name, #mod.name, Mods) of
1359                    #mod{} = M ->
1360                        M2 = M#mod{incl_cond = Config#mod.incl_cond},
1361                        lists:keystore(Config#mod.name, #mod.name, Acc, M2);
1362                    false ->
1363                        Config2 = Config#mod{uses_mods = [], exists = false},
1364                        [Config2 | Acc]
1365                end
1366        end,
1367    lists:foldl(AddConfig, Mods, ModConfigs).
1368
1369set_mod_flags(Mods, AppModNames) ->
1370    SetFlags =
1371        fun(#mod{name = N} = M) ->
1372                M#mod{is_app_mod = lists:member(N, AppModNames)}
1373        end,
1374    lists:map(SetFlags, Mods).
1375
1376%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1377
1378do_get_config(S, InclDef, InclDeriv) ->
1379    AppTab = S#state.app_tab,
1380    Sys =
1381        case InclDeriv of
1382            false ->
1383		%% Only the apps that exist in #sys.apps shall be
1384		%% included,and they shall be minimized
1385		Apps = [shrink_app(App) ||
1386			   #app{name=Name} <- (S#state.sys)#sys.apps,
1387			   App <- ets:lookup(AppTab,Name)],
1388		(S#state.sys)#sys{apps=Apps};
1389            true  ->
1390		sys_all_apps(S)
1391        end,
1392    reltool_target:gen_config(Sys, InclDef).
1393
1394shrink_app(A) ->
1395    Mods = [M#mod{is_app_mod = undefined,
1396                  is_ebin_mod = undefined,
1397                  uses_mods = undefined,
1398                  exists = false} ||
1399               M <- A#app.mods,
1400               M#mod.incl_cond =/= undefined],
1401    if
1402	A#app.is_escript ->
1403	    A#app{vsn = undefined,
1404		  label = undefined,
1405		  info = undefined,
1406		  mods = [],
1407		  uses_mods = undefined};
1408	true ->
1409            {Dir, Dirs, OptVsn} =
1410                case A#app.use_selected_vsn of
1411                    undefined ->
1412			{undefined, [], undefined};
1413                    vsn ->
1414			{undefined, [], A#app.vsn};
1415                    dir ->
1416			{A#app.active_dir, [A#app.active_dir], undefined}
1417                end,
1418            A#app{active_dir = Dir,
1419		  sorted_dirs = Dirs,
1420		  vsn = OptVsn,
1421		  label = undefined,
1422		  info = undefined,
1423		  mods = Mods,
1424		  uses_mods = undefined}
1425    end.
1426
1427
1428do_save_config(S, Filename, InclDef, InclDeriv) ->
1429    {ok, Config} = do_get_config(S, InclDef, InclDeriv),
1430    IoList = io_lib:format("%% ~s\n"
1431                           "%% config generated at ~w ~w\n"
1432                           "~tp.\n\n",
1433                           [epp:encoding_to_string(utf8),date(), time(), Config]),
1434    Bin = unicode:characters_to_binary(IoList),
1435    file:write_file(Filename, Bin).
1436
1437%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1438
1439do_load_config(S, SysConfig) ->
1440    S#state{sys = read_config(default_sys(), SysConfig)}.
1441
1442read_config(OldSys, Filename) when is_list(Filename) ->
1443    case file:consult(Filename) of
1444        {ok, [SysConfig | _]} ->
1445            read_config(OldSys, SysConfig);
1446        {ok, Content} ->
1447	    reltool_utils:throw_error("Illegal file content: ~p",[Content]);
1448        {error, Reason} ->
1449	    reltool_utils:throw_error("Illegal config file ~tp: ~ts",
1450				      [Filename,file:format_error(Reason)])
1451    end;
1452read_config(OldSys, {sys, KeyVals}) ->
1453    NewSys = decode(OldSys#sys{apps = [], rels = []}, KeyVals),
1454    Apps = [A#app{mods = lists:sort(A#app.mods)} || A <- NewSys#sys.apps],
1455    Rels =
1456	case NewSys#sys.rels of
1457	    []   -> reltool_utils:default_rels();
1458	    Rs -> Rs
1459	end,
1460    NewSys2 = NewSys#sys{apps = lists:sort(Apps),
1461			 rels = lists:sort(Rels)},
1462    case lists:keymember(NewSys2#sys.boot_rel, #rel.name, NewSys2#sys.rels) of
1463	true ->
1464	    NewSys2;
1465	false ->
1466	    reltool_utils:throw_error(
1467	      "Release ~tp is mandatory (used as boot_rel)",
1468	      [NewSys2#sys.boot_rel])
1469    end;
1470read_config(_OldSys, BadConfig) ->
1471    reltool_utils:throw_error("Illegal content: ~tp", [BadConfig]).
1472
1473decode(#sys{apps = Apps} = Sys, [{erts = Name, AppKeyVals} | SysKeyVals])
1474  when is_atom(Name), is_list(AppKeyVals) ->
1475    App = default_app(Name),
1476    App2= decode(App, AppKeyVals),
1477    decode(Sys#sys{apps = [App2 | Apps]}, SysKeyVals);
1478decode(#sys{apps = Apps} = Sys, [{app, Name, AppKeyVals} | SysKeyVals])
1479  when is_atom(Name), is_list(AppKeyVals) ->
1480    App = default_app(Name),
1481    App2 = decode(App, AppKeyVals),
1482    decode(Sys#sys{apps = [App2 | Apps]}, SysKeyVals);
1483decode(#sys{apps = Apps, escripts = Escripts} = Sys,
1484       [{escript, File0, AppKeyVals} | SysKeyVals])
1485  when is_list(File0), is_list(AppKeyVals) ->
1486    File = filename:absname(File0),
1487    App = default_escript_app(File),
1488    App2 = decode(App, AppKeyVals),
1489    decode(Sys#sys{apps = [App2 | Apps], escripts = [File | Escripts]},
1490	   SysKeyVals);
1491decode(#sys{rels = Rels} = Sys, [{rel, Name, Vsn, RelApps} | SysKeyVals])
1492  when is_list(Name), is_list(Vsn), is_list(RelApps) ->
1493    Rel = #rel{name = Name, vsn = Vsn, rel_apps = []},
1494    Rel2 = decode(Rel, RelApps),
1495    decode(Sys#sys{rels = [Rel2 | Rels]}, SysKeyVals);
1496decode(#sys{rels = Rels} = Sys, [{rel, Name, Vsn, RelApps, Opts} | SysKeyVals])
1497  when is_list(Name), is_list(Vsn), is_list(RelApps), is_list(Opts) ->
1498    Rel1 = lists:foldl(fun(Opt, Rel0) ->
1499        case Opt of
1500            {load_dot_erlang, Value} when is_boolean(Value) ->
1501                Rel0#rel{load_dot_erlang = Value};
1502            _ ->
1503                reltool_utils:throw_error("Illegal rel option: ~tp", [Opt])
1504        end
1505    end, #rel{name = Name, vsn = Vsn, rel_apps = []}, Opts),
1506    Rel2 = decode(Rel1, RelApps),
1507    decode(Sys#sys{rels = [Rel2 | Rels]}, SysKeyVals);
1508decode(#sys{} = Sys, [{Key, Val} | KeyVals]) ->
1509    Sys3 =
1510        case Key of
1511            root_dir when is_list(Val) ->
1512                Sys#sys{root_dir = Val};
1513            lib_dirs when is_list(Val) ->
1514                Sys#sys{lib_dirs = Val};
1515            mod_cond when Val =:= all;
1516			  Val =:= app;
1517                          Val =:= ebin;
1518			  Val =:= derived;
1519                          Val =:= none ->
1520                Sys#sys{mod_cond = Val};
1521            incl_cond when Val =:= include;
1522			   Val =:= exclude;
1523                           Val =:= derived ->
1524                Sys#sys{incl_cond = Val};
1525            boot_rel when is_list(Val) ->
1526                Sys#sys{boot_rel = Val};
1527            emu_name when is_list(Val) ->
1528                Sys#sys{emu_name = Val};
1529	    profile when Val =:= development;
1530			 Val =:= embedded;
1531			 Val =:= standalone ->
1532		InclSys = reltool_utils:choose_default(incl_sys_filters, Val, false),
1533		ExclSys = reltool_utils:choose_default(excl_sys_filters, Val, false),
1534		InclApp = reltool_utils:choose_default(incl_app_filters, Val, false),
1535		ExclApp = reltool_utils:choose_default(excl_app_filters, Val, false),
1536		AppType = reltool_utils:choose_default(embedded_app_type, Val, false),
1537		Sys#sys{profile = Val,
1538			incl_sys_filters = dec_re(incl_sys_filters,
1539						  InclSys,
1540						  Sys#sys.incl_sys_filters),
1541			excl_sys_filters = dec_re(excl_sys_filters,
1542						  ExclSys,
1543						  Sys#sys.excl_sys_filters),
1544			incl_app_filters = dec_re(incl_app_filters,
1545						  InclApp,
1546						  Sys#sys.incl_app_filters),
1547			excl_app_filters = dec_re(excl_app_filters,
1548						  ExclApp,
1549						  Sys#sys.excl_app_filters),
1550			embedded_app_type = AppType};
1551	    excl_lib when Val =:= otp_root ->
1552		Sys#sys{excl_lib=Val};
1553            incl_sys_filters ->
1554                Sys#sys{incl_sys_filters =
1555			    dec_re(Key, Val, Sys#sys.incl_sys_filters)};
1556            excl_sys_filters ->
1557                Sys#sys{excl_sys_filters =
1558			    dec_re(Key, Val, Sys#sys.excl_sys_filters)};
1559            incl_app_filters ->
1560                Sys#sys{incl_app_filters =
1561			    dec_re(Key, Val, Sys#sys.incl_app_filters)};
1562            excl_app_filters ->
1563                Sys#sys{excl_app_filters =
1564			    dec_re(Key, Val, Sys#sys.excl_app_filters)};
1565            incl_archive_filters ->
1566                Sys#sys{incl_archive_filters =
1567			    dec_re(Key, Val, Sys#sys.incl_archive_filters)};
1568            excl_archive_filters ->
1569                Sys#sys{excl_archive_filters =
1570			    dec_re(Key, Val, Sys#sys.excl_archive_filters)};
1571            archive_opts when is_list(Val) ->
1572                Sys#sys{archive_opts = Val};
1573            relocatable when Val =:= true; Val =:= false ->
1574                Sys#sys{relocatable = Val};
1575            rel_app_type when Val =:= permanent;
1576			      Val =:= transient;
1577			      Val =:= temporary;
1578			      Val =:= load;
1579			      Val =:= none ->
1580                Sys#sys{rel_app_type = Val};
1581	    embedded_app_type when Val =:= permanent;
1582				   Val =:= transient;
1583				   Val =:= temporary;
1584				   Val =:= load;
1585				   Val =:= none;
1586				   Val =:= undefined ->
1587                Sys#sys{embedded_app_type = Val};
1588            app_file when Val =:= keep; Val =:= strip; Val =:= all ->
1589                Sys#sys{app_file = Val};
1590            debug_info when Val =:= keep; Val =:= strip ->
1591                Sys#sys{debug_info = Val};
1592            _ ->
1593		reltool_utils:throw_error("Illegal option: ~tp", [{Key, Val}])
1594        end,
1595    decode(Sys3, KeyVals);
1596decode(#app{} = App, [{Key, Val} | KeyVals]) ->
1597    App2 =
1598        case Key of
1599            mod_cond when Val =:= all;
1600			  Val =:= app;
1601			  Val =:= ebin;
1602			  Val =:= derived;
1603			  Val =:= none ->
1604                App#app{mod_cond = Val};
1605            incl_cond when Val =:= include;
1606			   Val =:= exclude;
1607			   Val =:= derived ->
1608                App#app{incl_cond = Val};
1609
1610            debug_info when Val =:= keep;
1611			    Val =:= strip ->
1612                App#app{debug_info = Val};
1613            app_file when Val =:= keep;
1614			  Val =:= strip;
1615			  Val =:= all ->
1616                App#app{app_file = Val};
1617            app_type when Val =:= permanent;
1618			  Val =:= transient;
1619			  Val =:= temporary;
1620                          Val =:= load;
1621			  Val =:= none;
1622			  Val =:= undefined ->
1623                App#app{app_type = Val};
1624            incl_app_filters ->
1625                App#app{incl_app_filters =
1626			    dec_re(Key, Val, App#app.incl_app_filters)};
1627            excl_app_filters ->
1628                App#app{excl_app_filters =
1629			    dec_re(Key, Val, App#app.excl_app_filters)};
1630            incl_archive_filters ->
1631                App#app{incl_archive_filters =
1632			    dec_re(Key, Val, App#app.incl_archive_filters)};
1633            excl_archive_filters ->
1634                App#app{excl_archive_filters =
1635			    dec_re(Key, Val, App#app.excl_archive_filters)};
1636            archive_opts when is_list(Val) ->
1637                App#app{archive_opts = Val};
1638            vsn when is_list(Val), App#app.use_selected_vsn=:=undefined ->
1639		App#app{use_selected_vsn = vsn, vsn = Val};
1640	    lib_dir when is_list(Val), App#app.use_selected_vsn=:=undefined ->
1641		case filelib:is_dir(Val) of
1642		    true ->
1643			Dir = reltool_utils:normalize_dir(Val),
1644			App#app{use_selected_vsn = dir,
1645				active_dir = Dir,
1646				sorted_dirs = [Dir]};
1647		    false ->
1648			reltool_utils:throw_error("Illegal lib dir for ~w: ~tp",
1649						  [App#app.name, Val])
1650		end;
1651	    SelectVsn when SelectVsn=:=vsn; SelectVsn=:=lib_dir ->
1652		reltool_utils:throw_error("Mutual exclusive options "
1653					  "'vsn' and 'lib_dir'",[]);
1654            _ ->
1655		reltool_utils:throw_error("Illegal option: ~tp", [{Key, Val}])
1656        end,
1657    decode(App2, KeyVals);
1658decode(#app{mods = Mods} = App, [{mod, Name, ModKeyVals} | AppKeyVals]) ->
1659    Mod = decode(#mod{name = Name}, ModKeyVals),
1660    decode(App#app{mods = [Mod | Mods]}, AppKeyVals);
1661decode(#mod{} = Mod, [{Key, Val} | KeyVals]) ->
1662    Mod2 =
1663        case Key of
1664            incl_cond when Val =:= include; Val =:= exclude; Val =:= derived ->
1665                Mod#mod{incl_cond = Val};
1666            debug_info when Val =:= keep; Val =:= strip ->
1667                Mod#mod{debug_info = Val};
1668            _ ->
1669		reltool_utils:throw_error("Illegal option: ~tp", [{Key, Val}])
1670        end,
1671    decode(Mod2, KeyVals);
1672decode(#rel{rel_apps = RelApps} = Rel, [RelApp | KeyVals]) ->
1673    {ValidTypesAssigned, RA} =
1674        case RelApp of
1675            Name when is_atom(Name) ->
1676                {true, #rel_app{name = Name}};
1677            {Name, InclApps} when is_atom(Name), is_list(InclApps) ->
1678		VI = lists:all(fun erlang:is_atom/1, InclApps),
1679                {VI, #rel_app{name = Name, incl_apps = InclApps}};
1680            {Name, Type} when is_atom(Name) ->
1681                {is_type(Type), #rel_app{name = Name, app_type = Type}};
1682            {Name, Type, InclApps} when is_atom(Name), is_list(InclApps) ->
1683		VT = is_type(Type),
1684		VI = lists:all(fun erlang:is_atom/1, InclApps),
1685		{VT andalso VI,
1686                 #rel_app{name = Name, app_type = Type, incl_apps = InclApps}};
1687            _ ->
1688                {false, #rel_app{}}
1689        end,
1690    case ValidTypesAssigned of
1691	true ->
1692            decode(Rel#rel{rel_apps = RelApps ++ [RA]}, KeyVals);
1693        false ->
1694	    reltool_utils:throw_error("Illegal option: ~tp", [RelApp])
1695    end;
1696decode(Acc, []) ->
1697    Acc;
1698decode(_Acc, KeyVal) ->
1699    reltool_utils:throw_error("Illegal option: ~tp", [KeyVal]).
1700
1701is_type(Type) ->
1702    case Type of
1703        undefined -> true;
1704        permanent -> true;
1705        transient -> true;
1706        temporary -> true;
1707        load      -> true;
1708        none      -> true;
1709        _         -> false
1710    end.
1711
1712split_escript_name(File) when is_list(File) ->
1713    Label = filename:basename(File, ".escript"),
1714    {list_to_atom("*escript* " ++ Label), Label}.
1715
1716default_escript_app(File) ->
1717    {Name, Label} = split_escript_name(File),
1718    App = default_app(Name, File),
1719    App#app{is_escript = true,
1720	    label = Label,
1721	    info = missing_app_info("")}.
1722
1723%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1724
1725%% Apps is a list of #app records - sorted on #app.name - containing
1726%% only the apps that have specific configuration (e.g. in the config
1727%% file)
1728refresh(#state{sys=Sys} = S) ->
1729    RootDir = filename:absname(Sys#sys.root_dir),
1730    LibDirs = [filename:absname(D) || D <- Sys#sys.lib_dirs],
1731    Escripts = [filename:absname(E) || E <- Sys#sys.escripts],
1732
1733    %% Read all lib dirs and return sorted [{AppName,Dir}]
1734    SourceDirs = libs_to_dirs(RootDir, LibDirs),
1735
1736    %% Create #app records for all apps in SourceDirs, and merge with
1737    %% list of apps from config.
1738    MergedApps = merge_app_dirs(SourceDirs, Sys#sys.apps),
1739
1740    %% For each escript, find all related files and convert to #app
1741    %% and #mod records
1742    {AllApps, Status2} = escripts_to_apps(Escripts, MergedApps, {ok,[]}),
1743
1744    %% Make sure correct version of each application is used according
1745    %% to the user configuration.
1746    %% Then find all modules and their dependencies and set user
1747    %% configuration per module if it exists.
1748    {RefreshedApps, Status3} = refresh_apps(Sys#sys.apps, AllApps, [],
1749					    true, Status2),
1750
1751    %% Make sure erts exists in app list and has a version (or warn)
1752    {PatchedApps, Status4} = patch_erts_version(RootDir, RefreshedApps, Status3),
1753
1754    %% Update #sys and return
1755    Escripts2 = [A#app.active_dir || A <- PatchedApps, A#app.is_escript],
1756    Sys2 = Sys#sys{root_dir = RootDir,
1757		   lib_dirs = LibDirs,
1758		   escripts = Escripts2},
1759    {S#state{sys=Sys2}, PatchedApps, Status4}.
1760
1761patch_erts_version(RootDir, Apps, Status) ->
1762    AppName = erts,
1763    case lists:keyfind(AppName, #app.name, Apps) of
1764        #app{vsn = Vsn} = Erts ->
1765            LocalRoot = code:root_dir(),
1766            if
1767                LocalRoot =:= RootDir, Vsn =:= "" ->
1768                    Vsn2 = erlang:system_info(version),
1769                    Erts2 = Erts#app{vsn = Vsn2, label = "erts-" ++ Vsn2},
1770                    Apps2 = lists:keystore(AppName, #app.name, Apps, Erts2),
1771                    {Apps2, Status};
1772                Vsn =:= "" ->
1773                    {Apps, reltool_utils:add_warning("erts has no version",[],
1774						     Status)};
1775                true ->
1776                    {Apps, Status}
1777            end;
1778        false ->
1779	    reltool_utils:throw_error(
1780	      "erts cannot be found in the root directory ~tp", [RootDir])
1781    end.
1782
1783libs_to_dirs(RootDir, LibDirs) ->
1784    case file:list_dir(RootDir) of
1785        {ok, RootFiles} ->
1786            RootLibDir = filename:join([RootDir, "lib"]),
1787            AllLibDirs = [RootLibDir | LibDirs],
1788            case AllLibDirs -- lists:usort(AllLibDirs) of
1789                [] ->
1790                    Fun = fun(Base) ->
1791                                  AppDir = filename:join([RootLibDir, Base]),
1792                                  case filelib:is_dir(filename:join([AppDir,
1793								     "ebin"]),
1794						      erl_prim_loader) of
1795                                      true ->
1796                                          AppDir;
1797                                      false ->
1798                                          filename:join([RootDir,
1799							 Base,
1800							 "preloaded"])
1801                                  end
1802                          end,
1803                    ErtsFiles = [{erts, Fun(F)} || F <- RootFiles,
1804						   lists:prefix("erts", F)],
1805                    app_dirs2(AllLibDirs, [ErtsFiles]);
1806                [Duplicate | _] ->
1807		    reltool_utils:throw_error("Duplicate library: ~tp",[Duplicate])
1808            end;
1809        {error, Reason} ->
1810	    reltool_utils:throw_error("Missing root library ~tp: ~ts",
1811				      [RootDir,file:format_error(Reason)])
1812    end.
1813
1814app_dirs2([Lib | Libs], Acc) ->
1815    case file:list_dir(Lib) of
1816        {ok, Files} ->
1817            Filter =
1818                fun(Base) ->
1819                        AppDir = filename:join([Lib, Base]),
1820                        EbinDir = filename:join([AppDir, "ebin"]),
1821                        case filelib:is_dir(EbinDir, erl_prim_loader) of
1822                            true ->
1823				Name = find_app_name(Base,EbinDir),
1824                                case Name of
1825                                    erts -> false;
1826                                    _    -> {true, {Name, AppDir}}
1827                                end;
1828                            false ->
1829                                false
1830                        end
1831                end,
1832            Files2 = lists:zf(Filter, Files),
1833            app_dirs2(Libs, [Files2 | Acc]);
1834        {error, Reason} ->
1835	    reltool_utils:throw_error("Illegal library ~tp: ~ts",
1836				      [Lib, file:format_error(Reason)])
1837    end;
1838app_dirs2([], Acc) ->
1839    lists:sort(lists:append(Acc)).
1840
1841find_app_name(Base,EbinDir) ->
1842    {ok,EbinFiles} = erl_prim_loader:list_dir(EbinDir),
1843    AppFile =
1844	case [F || F <- EbinFiles, filename:extension(F)=:=".app"] of
1845	    [AF] ->
1846		AF;
1847	    _ ->
1848		undefined
1849	end,
1850    find_app_name1(Base,AppFile).
1851
1852find_app_name1(Base,undefined) ->
1853    {Name,_} = reltool_utils:split_app_name(Base),
1854    Name;
1855find_app_name1(_Base,AppFile) ->
1856    list_to_atom(filename:rootname(AppFile)).
1857
1858get_vsn_from_dir(AppName,Base) ->
1859    Prefix = atom_to_list(AppName) ++ "-",
1860    case lists:prefix(Prefix,Base) of
1861	true ->
1862	    lists:nthtail(length(Prefix),Base);
1863	false ->
1864	    ""
1865    end.
1866
1867
1868escripts_to_apps([Escript | Escripts], Apps, Status) ->
1869    {EscriptAppName, _Label} = split_escript_name(Escript),
1870    Ext = code:objfile_extension(),
1871
1872    %% First find all .app files and associate the app name to the app
1873    %% label - this is in order to now which application a module
1874    %% belongs to in the next round.
1875    AppFun = fun(FullName, _GetInfo, _GetBin, AppFiles) ->
1876		     Components = filename:split(FullName),
1877		     case Components of
1878			 [AppLabel, "ebin", File] ->
1879			     case filename:extension(File) of
1880				 ".app" ->
1881				     [{AppLabel,File}|AppFiles];
1882				 _ ->
1883				     AppFiles
1884			     end;
1885			 _ ->
1886			     AppFiles
1887		     end
1888	     end,
1889    AppFiles =
1890	case reltool_utils:escript_foldl(AppFun, [], Escript) of
1891	    {ok, AF} ->
1892		AF;
1893	    {error, Reason1} ->
1894		reltool_utils:throw_error("Illegal escript ~tp: ~tp",
1895					  [Escript,Reason1])
1896	end,
1897
1898    %% Next, traverse all files...
1899    Fun = fun(FullName, _GetInfo, GetBin, {FileAcc, StatusAcc}) ->
1900                  Components = filename:split(FullName),
1901                  case Components of
1902                      [AppLabel, "ebin", File] ->
1903                          case filename:extension(File) of
1904                              ".app" ->
1905				  AppName =
1906				      list_to_atom(filename:rootname(File)),
1907                                  DefaultVsn =
1908				      get_vsn_from_dir(AppName,AppLabel),
1909                                  AppFileName =
1910				      filename:join([Escript, FullName]),
1911                                  Dir = filename:join([Escript, AppName]),
1912                                  {Info, StatusAcc2} =
1913                                      read_app_info(GetBin(),
1914						    AppFileName,
1915						    AppName,
1916                                                    Dir,
1917                                                    ok,
1918						    DefaultVsn,
1919						    Status),
1920                                  {[{AppName, app, Dir, Info} | FileAcc],
1921				   StatusAcc2};
1922                              E when E =:= Ext ->
1923				  AppFile =
1924				      proplists:get_value(AppLabel,AppFiles),
1925				  AppName = find_app_name1(AppLabel,AppFile),
1926                                  Mod = init_mod(AppName,
1927						 File,
1928						 {File, GetBin()},
1929						 Ext),
1930                                  Dir = filename:join([Escript, AppName]),
1931                                  {[{AppName, mod, Dir, Mod} | FileAcc],
1932				   StatusAcc};
1933                              _ ->
1934                                  {FileAcc, StatusAcc}
1935                          end;
1936                      ["."] ->
1937                          Bin = GetBin(),
1938                          {ok, {ModName, _}} = beam_lib:version(Bin),
1939                          ModStr = atom_to_list(ModName) ++ Ext,
1940                          Mod = init_mod(EscriptAppName,
1941					 ModStr,
1942					 {ModStr, GetBin()},
1943					 Ext),
1944                          {[{EscriptAppName, mod, Escript, Mod} | FileAcc],
1945			   StatusAcc};
1946                      [File] ->
1947                          case filename:extension(File) of
1948                              E when E =:= Ext ->
1949                                  Mod = init_mod(EscriptAppName,
1950						 File,
1951						 {File, GetBin()},
1952						 Ext),
1953                                  {[{EscriptAppName, mod, File, Mod} | FileAcc],
1954				   StatusAcc};
1955                              _ ->
1956                                  {FileAcc, StatusAcc}
1957                          end;
1958                      _ ->
1959                          {FileAcc, StatusAcc}
1960                  end
1961          end,
1962
1963    case reltool_utils:escript_foldl(Fun, {[], Status}, Escript) of
1964	{ok, {Files, Status2}} ->
1965	    EscriptApp =
1966		case lists:keyfind(EscriptAppName,#app.name,Apps) of
1967		    false -> default_escript_app(Escript);
1968		    EA    -> EA
1969		end,
1970	    {Apps2, Status3} =
1971		escript_files_to_apps(EscriptAppName,
1972				      lists:sort(Files),
1973				      [EscriptApp],
1974				      Apps,
1975				      Status2),
1976	    escripts_to_apps(Escripts, Apps2, Status3);
1977	{error, Reason2} ->
1978	    reltool_utils:throw_error("Illegal escript ~tp: ~tp",
1979				      [Escript,Reason2])
1980    end;
1981escripts_to_apps([], Apps, Status) ->
1982    {Apps, Status}.
1983
1984%% Assume that all files for an app are in consecutive order
1985%% Assume the app info is before the mods
1986escript_files_to_apps(EscriptAppName,
1987		      [{AppName, Type, Dir, ModOrInfo} | Files],
1988		      Acc,
1989		      Apps,
1990		      Status) ->
1991    {NewAcc,Status3} =
1992	case Type of
1993	    mod ->
1994		case Acc of
1995		    [App | Acc2] when App#app.name =:= ModOrInfo#mod.app_name ->
1996			Mods = lists:ukeymerge(#mod.name,
1997					       [ModOrInfo],
1998					       App#app.mods),
1999			{[App#app{mods = Mods} | Acc2], Status};
2000		    Acc ->
2001			{NewApp, Status2} = init_escript_app(AppName,
2002							     EscriptAppName,
2003							     Dir,
2004							     missing_app_info(""),
2005							     [ModOrInfo],
2006							     Apps,
2007							     Status),
2008			{[NewApp | Acc], Status2}
2009		end;
2010           app ->
2011		{App, Status2} = init_escript_app(AppName,
2012						  EscriptAppName,
2013						  Dir,
2014						  ModOrInfo,
2015						  [],
2016						  Apps,
2017						  Status),
2018		{[App | Acc], Status2}
2019	end,
2020    escript_files_to_apps(EscriptAppName, Files, NewAcc, Apps, Status3);
2021escript_files_to_apps(_EscriptAppName, [], Acc, Apps, Status) ->
2022    {lists:ukeymerge(#app.name, lists:reverse(Acc), Apps), Status}.
2023
2024init_escript_app(AppName, EscriptAppName, Dir, Info, Mods, Apps, Status) ->
2025    App1 = default_app(AppName, Dir),
2026    IsEscript =
2027	if AppName=:=EscriptAppName -> true;
2028	   true -> {inlined, EscriptAppName}
2029	end,
2030    InclCond = (lists:keyfind(EscriptAppName,#app.name,Apps))#app.incl_cond,
2031    App2 = App1#app{is_escript = IsEscript,
2032		    label = filename:basename(Dir, ".escript"),
2033		    info = Info,
2034		    mods = Mods,
2035		    active_dir = Dir,
2036		    sorted_dirs = [Dir],
2037		    incl_cond = InclCond},% inlined apps inherit incl from escript
2038    case lists:keymember(AppName, #app.name, Apps) of
2039        true ->
2040	    reltool_utils:throw_error(
2041	      "~w: Application name clash. Escript ~tp contains application ~w.",
2042	      [AppName,Dir,AppName]);
2043        false ->
2044            {App2, Status}
2045    end.
2046
2047merge_app_dirs([{Name, Dir} | Rest], Apps) ->
2048    App =
2049        case lists:keyfind(Name, #app.name, Apps) of
2050            false ->
2051		default_app(Name, Dir);
2052            OldApp ->
2053		SortedDirs = lists:umerge(fun reltool_utils:app_dir_test/2,
2054					  [Dir], OldApp#app.sorted_dirs),
2055                OldApp#app{sorted_dirs = SortedDirs}
2056        end,
2057    Apps2 = lists:ukeymerge(#app.name, [App], Apps),
2058    merge_app_dirs(Rest, Apps2);
2059merge_app_dirs([], Apps) ->
2060    set_active_dirs(Apps).
2061
2062%% First dir, i.e. the one with highest version, is set to active dir,
2063%% unless a specific dir is given in config
2064set_active_dirs([#app{use_selected_vsn = dir} = App | Apps]) ->
2065    [App | set_active_dirs(Apps)];
2066set_active_dirs([#app{sorted_dirs = [ActiveDir|_]} = App | Apps]) ->
2067    [App#app{active_dir = ActiveDir} | set_active_dirs(Apps)];
2068set_active_dirs([#app{sorted_dirs = []} = App | Apps]) ->
2069    [App#app{active_dir = undefined} | set_active_dirs(Apps)];
2070set_active_dirs([]) ->
2071    [].
2072
2073
2074default_app(Name, Dir) ->
2075    App = default_app(Name),
2076    App#app{active_dir = Dir,
2077            sorted_dirs = [Dir]}.
2078
2079default_app(Name) ->
2080    #app{name = Name,
2081         is_escript = false,
2082         sorted_dirs = [],
2083         mods = [],
2084         status = missing}.
2085
2086
2087
2088refresh_apps(ConfigApps, [New | NewApps], Acc, Force, Status) ->
2089    {New2, Status3} =
2090	case lists:keymember(New#app.name,#app.name,ConfigApps) of
2091	    true ->
2092		%% There is user defined config for this application, make
2093		%% sure that the application exists and that correct
2094		%% version is used. Set active directory.
2095		{Info, ActiveDir, Status2} = ensure_app_info(New, Status),
2096		OptLabel =
2097		    case Info#app_info.vsn =:= New#app.vsn of
2098			true -> New#app.label;
2099			false -> undefined % Cause refresh
2100		    end,
2101		refresh_app(New#app{label = OptLabel,
2102				    active_dir = ActiveDir,
2103				    vsn = Info#app_info.vsn,
2104				    info = Info},
2105			    Force,
2106			    Status2);
2107	    false ->
2108		%% There is no user defined config for this
2109		%% application. This means that the app is found in the
2110		%% lib dirs, and that the highest version shall be
2111		%% used. I.e. the active_dir and vsn are already correct
2112		%% from merge_app_dirs.
2113		refresh_app(New, Force, Status)
2114	end,
2115    refresh_apps(ConfigApps, NewApps, [New2 | Acc], Force, Status3);
2116refresh_apps(_ConfigApps, [], Acc, _Force, Status) ->
2117    {lists:reverse(Acc), Status}.
2118
2119ensure_app_info(#app{is_escript = IsEscript, active_dir = Dir, info = Info},
2120		Status)
2121  when IsEscript=/=false ->
2122    %% Escript or application which is inlined in an escript
2123    {Info, Dir, Status};
2124ensure_app_info(#app{name = Name, sorted_dirs = []} = App, Status) ->
2125    Reason = "~w: Missing application directory.",
2126    case App of
2127        #app{incl_cond = exclude, status = missing, active_dir = Dir} ->
2128            Status2 = reltool_utils:add_warning(Reason, [Name], Status),
2129            {missing_app_info(""), Dir, Status2};
2130        _ ->
2131            reltool_utils:throw_error(Reason, [Name])
2132    end;
2133ensure_app_info(#app{name = Name,
2134		     vsn = Vsn,
2135		     use_selected_vsn = UseSelectedVsn,
2136		     active_dir = ActiveDir,
2137		     sorted_dirs = Dirs,
2138                     info = undefined,
2139                     status = AppStatus},
2140		Status) ->
2141    ReadInfo =
2142        fun(Dir, StatusAcc) ->
2143                Base = get_base(Name, Dir),
2144                Ebin = filename:join([Dir, "ebin"]),
2145                DefaultVsn = get_vsn_from_dir(Name,Base),
2146                AppFile = filename:join([Ebin, atom_to_list(Name) ++ ".app"]),
2147                read_app_info(AppFile, AppFile, Name, ActiveDir,
2148                              AppStatus, DefaultVsn, StatusAcc)
2149        end,
2150    {AllInfo, Status2} = lists:mapfoldl(ReadInfo, Status, Dirs),
2151    AllVsns = [I#app_info.vsn || I <- AllInfo],
2152    Status3 =
2153        case AllVsns -- lists:usort(AllVsns) of
2154            [] ->
2155                %% No redundant info
2156                Status2;
2157            [BadVsn | _] ->
2158		reltool_utils:throw_error(
2159		  "~w: Application version clash. "
2160		  "Multiple directories contain version ~tp.",
2161		  [Name,BadVsn])
2162        end,
2163    FirstInfo = hd(AllInfo),
2164    FirstDir = hd(Dirs),
2165    if
2166        UseSelectedVsn =:= dir ->
2167	    if ActiveDir =:= FirstDir ->
2168		    {FirstInfo, FirstDir, Status3};
2169	       true ->
2170		    Info = find_dir(ActiveDir, AllInfo, Dirs),
2171		    {Info, ActiveDir, Status3}
2172	    end;
2173        UseSelectedVsn =:= vsn ->
2174	    if Vsn =:= FirstInfo#app_info.vsn ->
2175		    {FirstInfo, FirstDir, Status3};
2176	       true ->
2177		    case find_vsn(Vsn, AllInfo, Dirs) of
2178			{Info, VsnDir} ->
2179			    {Info, VsnDir, Status3};
2180			false ->
2181			    reltool_utils:throw_error(
2182			      "~w: No application directory contains "
2183			      "selected version ~tp", [Name,Vsn])
2184		    end
2185	    end;
2186	true ->
2187            {FirstInfo, FirstDir, Status3}
2188    end;
2189ensure_app_info(#app{active_dir = Dir, info = Info}, Status) ->
2190    {Info, Dir, Status}.
2191
2192find_vsn(Vsn, [#app_info{vsn = Vsn} = Info | _], [Dir | _]) ->
2193    {Info, Dir};
2194find_vsn(Vsn, [_ | MoreInfo], [_ | MoreDirs]) ->
2195    find_vsn(Vsn, MoreInfo, MoreDirs);
2196find_vsn(_, [], []) ->
2197    false.
2198
2199find_dir(Dir, [Info | _], [Dir | _]) ->
2200    Info;
2201find_dir(Dir, [_ | MoreInfo], [_ | MoreDirs]) ->
2202    find_dir(Dir, MoreInfo, MoreDirs).
2203
2204get_base(Name, Dir) ->
2205    case Name of
2206        erts ->
2207            case filename:basename(Dir) of
2208                "preloaded" ->
2209                    filename:basename(filename:dirname(Dir));
2210                TmpBase ->
2211                    TmpBase
2212            end;
2213        _ ->
2214            filename:basename(Dir)
2215    end.
2216
2217sys_all_apps(#state{app_tab=AppTab, sys=Sys}) ->
2218    Sys#sys{apps = ets:match_object(AppTab,'_')}.
2219
2220config_and_refresh(OldS, Fun) ->
2221    try
2222	S = Fun(),
2223	{S2, Apps, Status2} = refresh(S),
2224	%% Analyse will write to app_tab and mod_tab, so we first
2225	%% backup these tables and clear them
2226	Backup = backup(OldS),
2227	try
2228	    Status3 = analyse(S2, Apps, Status2),
2229	    S3 = save_old(OldS, S2, Backup, Status3),
2230	    {S3, Status3}
2231	catch throw:{error,_} = Error1 ->
2232		restore(Backup,OldS),
2233		throw(Error1)
2234	end
2235    catch throw:{error,_} = Error2 ->
2236	    {OldS, Error2}
2237    end.
2238
2239
2240backup(S) ->
2241    Apps = ets:tab2list(S#state.app_tab),
2242    Mods = ets:tab2list(S#state.mod_tab),
2243    ets:delete_all_objects(S#state.app_tab),
2244    ets:delete_all_objects(S#state.mod_tab),
2245    ets:delete_all_objects(S#state.mod_used_by_tab), %tmp tab, no backup needed
2246    {Apps,Mods}.
2247
2248restore({Apps,Mods}, S) ->
2249    insert_all(S#state.app_tab,Apps),
2250    insert_all(S#state.mod_tab,Mods).
2251
2252save_old(#state{status=OldStatus,sys=OldSys},NewS,{OldApps,OldMods},NewStatus) ->
2253    ets:delete_all_objects(NewS#state.old_app_tab),
2254    ets:delete_all_objects(NewS#state.old_mod_tab),
2255    insert_all(NewS#state.old_app_tab,OldApps),
2256    insert_all(NewS#state.old_mod_tab,OldMods),
2257    NewS#state{old_sys=OldSys,
2258	       old_status=OldStatus,
2259	       status=NewStatus}.
2260
2261insert_all(Tab,Items) ->
2262    lists:foreach(fun(Item) -> ets:insert(Tab,Item) end, Items).
2263
2264
2265%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
2266%% sys callbacks
2267
2268system_continue(_Parent, _Debug, S) ->
2269    ?MODULE:loop(S).
2270
2271system_terminate(Reason, _Parent, _Debug, _S) ->
2272    exit(Reason).
2273
2274system_code_change(S,_Module,_OldVsn,_Extra) ->
2275    {ok, S}.
2276