blob: bc6a88582cf6c9cf7a4c7502cf01738df40bfe81 [file] [log] [blame]
Harald Welte77804892011-02-06 18:12:47 +01001% Osmocom Erlang utility functions
2
3% (C) 2011 by Harald Welte <laforge@gnumonks.org>
4%
5% All Rights Reserved
6%
7% This program is free software; you can redistribute it and/or modify
8% it under the terms of the GNU Affero General Public License as
9% published by the Free Software Foundation; either version 3 of the
10% License, or (at your option) any later version.
11%
12% This program is distributed in the hope that it will be useful,
13% but WITHOUT ANY WARRANTY; without even the implied warranty of
14% MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
15% GNU General Public License for more details.
16%
17% You should have received a copy of the GNU Affero General Public License
18% along with this program. If not, see <http://www.gnu.org/licenses/>.
19
20-module(osmo_util).
21-author('Harald Welte <laforge@gnumonks.org>').
22
23-export([digit_list2int/1, int2digit_list/1]).
24-export([reload_config/0]).
25
26% Convert a list of digits to an integer value
27digit_list2int(Int, []) ->
28 Int;
29digit_list2int(Int, [Digit|Tail]) ->
30 digit_list2int(Int*10 + Digit, Tail).
31digit_list2int(Digits) when is_list(Digits) ->
32 digit_list2int(0, Digits).
33
34% Convert an integer value into a list of decimal digits
35int2digit_list(0, Digits) when is_list(Digits) ->
36 Digits;
37int2digit_list(Int, Digits) when is_integer(Int), is_list(Digits) ->
38 Digit = Int rem 10,
39 int2digit_list(Int div 10, [Digit|Digits]).
40int2digit_list(Int) when is_integer(Int) ->
41 int2digit_list(Int, []).
42
43% reload configuration of an application
44reload_config() ->
45 case init:get_argument(config) of
46 {ok, [ Files ]} ->
47 ConfFiles = [begin
48 S = filename:basename(F,".config"),
49 filename:join(filename:dirname(F),
50 S ++ ".config")
51 end || F <- Files],
52 % Move sys.config to the head of the list
53 Config = lists:sort(fun("sys.config", _) -> true;
54 (_, _) -> false end, ConfFiles),
55
56 OldEnv = application_controller:prep_config_change(),
57
58 Apps = [{application, A, make_appl(A)}
59 || {A,_,_} <- application:which_applications()],
60 application_controller:change_application_data(Apps, Config),
61 application_controller:config_change(OldEnv);
62 _ ->
63 {ok, []}
64 end.
65
66make_appl(App) when is_atom(App) ->
67 AppList = element(2,application:get_all_key(App)),
68 FullName = code:where_is_file(atom_to_list(App) ++ ".app"),
69 case file:consult(FullName) of
70 {ok, [{application, _, Opts}]} ->
71 Env = proplists:get_value(env, Opts, []),
72 lists:keyreplace(env, 1, AppList, {env, Env});
73 {error, _Reason} ->
74 lists:keyreplace(env, 1, AppList, {env, []})
75 end.