blob: 31c71ff4fce153e75f4ce994a0a363922c77f92d [file] [log] [blame]
Harald Welte790f3642011-02-03 17:44:50 +01001-module(mgw_nat_app).
2-behavior(application).
3-export([start/2, stop/1]).
4
Harald Welte15b3fc02011-02-06 17:57:24 +01005-export([reload_config/0]).
6
Harald Welte790f3642011-02-03 17:44:50 +01007start(_Type, _Args) ->
8 Sup = mgw_nat_sup:start_link(),
9 io:format("Sup ~p~n", [Sup]),
10 Sup.
11
12stop(_State) ->
13 ok.
Harald Welte15b3fc02011-02-06 17:57:24 +010014
15reload_config() ->
16 case init:get_argument(config) of
17 {ok, [ Files ]} ->
18 ConfFiles = [begin
19 S = filename:basename(F,".config"),
20 filename:join(filename:dirname(F),
21 S ++ ".config")
22 end || F <- Files],
23 % Move sys.config to the head of the list
24 Config = lists:sort(fun("sys.config", _) -> true;
25 (_, _) -> false end, ConfFiles),
26
27 OldEnv = application_controller:prep_config_change(),
28
29 Apps = [{application, A, make_appl(A)}
30 || {A,_,_} <- application:which_applications()],
31 application_controller:change_application_data(Apps, Config),
32 application_controller:config_change(OldEnv);
33 _ ->
34 {ok, []}
35 end.
36
37make_appl(App) when is_atom(App) ->
38 AppList = element(2,application:get_all_key(App)),
39 FullName = code:where_is_file(atom_to_list(App) ++ ".app"),
40 case file:consult(FullName) of
41 {ok, [{application, _, Opts}]} ->
42 Env = proplists:get_value(env, Opts, []),
43 lists:keyreplace(env, 1, AppList, {env, Env});
44 {error, _Reason} ->
45 lists:keyreplace(env, 1, AppList, {env, []})
46 end.