blob: 28bd0307d50a6635adfcf2bd08bb1425365b2e63 [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]).
Harald Welte8a6823d2011-03-08 16:03:31 +010025-export([tuple_walk/3, tuple_walk_print_cb/3]).
Harald Welte77804892011-02-06 18:12:47 +010026
27% Convert a list of digits to an integer value
28digit_list2int(Int, []) ->
29 Int;
30digit_list2int(Int, [Digit|Tail]) ->
31 digit_list2int(Int*10 + Digit, Tail).
32digit_list2int(Digits) when is_list(Digits) ->
33 digit_list2int(0, Digits).
34
35% Convert an integer value into a list of decimal digits
36int2digit_list(0, Digits) when is_list(Digits) ->
37 Digits;
38int2digit_list(Int, Digits) when is_integer(Int), is_list(Digits) ->
39 Digit = Int rem 10,
40 int2digit_list(Int div 10, [Digit|Digits]).
41int2digit_list(Int) when is_integer(Int) ->
42 int2digit_list(Int, []).
43
44% reload configuration of an application
45reload_config() ->
46 case init:get_argument(config) of
47 {ok, [ Files ]} ->
48 ConfFiles = [begin
49 S = filename:basename(F,".config"),
50 filename:join(filename:dirname(F),
51 S ++ ".config")
52 end || F <- Files],
53 % Move sys.config to the head of the list
54 Config = lists:sort(fun("sys.config", _) -> true;
55 (_, _) -> false end, ConfFiles),
56
57 OldEnv = application_controller:prep_config_change(),
58
59 Apps = [{application, A, make_appl(A)}
60 || {A,_,_} <- application:which_applications()],
61 application_controller:change_application_data(Apps, Config),
62 application_controller:config_change(OldEnv);
63 _ ->
64 {ok, []}
65 end.
66
67make_appl(App) when is_atom(App) ->
68 AppList = element(2,application:get_all_key(App)),
69 FullName = code:where_is_file(atom_to_list(App) ++ ".app"),
70 case file:consult(FullName) of
71 {ok, [{application, _, Opts}]} ->
72 Env = proplists:get_value(env, Opts, []),
73 lists:keyreplace(env, 1, AppList, {env, Env});
74 {error, _Reason} ->
75 lists:keyreplace(env, 1, AppList, {env, []})
76 end.
Harald Weltecf436012011-03-07 12:54:15 +010077
78
79% Walk a named tuple and (recursively) all its fields, call user-supplied
80% callback for each of them
Harald Welte8a6823d2011-03-08 16:03:31 +010081tuple_walk(Tpl, TupleCb, Args) when is_tuple(Tpl), is_function(TupleCb),
82 is_list(Args) ->
83 tuple_walk([], Tpl, TupleCb, Args).
Harald Weltecf436012011-03-07 12:54:15 +010084
Harald Welte8a6823d2011-03-08 16:03:31 +010085tuple_walk(Path, Tpl, TupleCb, Args) when is_list(Path), is_tuple(Tpl),
86 is_list(Args) ->
Harald Weltecf436012011-03-07 12:54:15 +010087 % call Callback
Harald Welte8a6823d2011-03-08 16:03:31 +010088 NewTpl = TupleCb(Path, Tpl, Args),
Harald Weltecf436012011-03-07 12:54:15 +010089 [TplName|TplList] = tuple_to_list(NewTpl),
Harald Welte8a6823d2011-03-08 16:03:31 +010090 NewTplList = tuple_fieldlist_walk(Path, TplName, TplList, TupleCb, Args),
Harald Welte4a0afae2011-03-07 23:54:04 +010091 list_to_tuple([TplName|NewTplList]);
Harald Welte8a6823d2011-03-08 16:03:31 +010092tuple_walk(Path, TplL, TupleCb, Args) when is_list(Path), is_list(TplL),
93 is_list(Args) ->
94 tuple_walk_list(Path, TplL, TupleCb, Args, []).
Harald Welte4a0afae2011-03-07 23:54:04 +010095
Harald Welte8a6823d2011-03-08 16:03:31 +010096tuple_walk_list(_Path, [], _TupleCb, _Args, OutList) ->
Harald Welte4a0afae2011-03-07 23:54:04 +010097 OutList;
Harald Welte8a6823d2011-03-08 16:03:31 +010098tuple_walk_list(Path, [Head|Tail], TupleCb, Args, OutList) ->
Harald Welte4a0afae2011-03-07 23:54:04 +010099 if
100 is_tuple(Head) ->
Harald Welte8a6823d2011-03-08 16:03:31 +0100101 NewHead = tuple_walk(Path, Head, TupleCb, Args);
Harald Welte4a0afae2011-03-07 23:54:04 +0100102 is_list(Head) ->
Harald Welte8a6823d2011-03-08 16:03:31 +0100103 NewHead = tuple_walk(Path, Head, TupleCb, Args);
Harald Welte4a0afae2011-03-07 23:54:04 +0100104 true ->
105 NewHead = Head
106 end,
Harald Welte8a6823d2011-03-08 16:03:31 +0100107 tuple_walk_list(Path, Tail, TupleCb, Args, OutList++[NewHead]).
Harald Welte4a0afae2011-03-07 23:54:04 +0100108
Harald Weltecf436012011-03-07 12:54:15 +0100109
Harald Welte8a6823d2011-03-08 16:03:31 +0100110tuple_fieldlist_walk(Path, TplName, FieldList, TupleCb, Args) ->
111 tuple_fieldlist_walk(Path, TplName, FieldList, TupleCb, Args, []).
Harald Weltecf436012011-03-07 12:54:15 +0100112
Harald Welte8a6823d2011-03-08 16:03:31 +0100113tuple_fieldlist_walk(_Path, _TplName, [], _TplCb, _Args, OutList) ->
Harald Weltecf436012011-03-07 12:54:15 +0100114 OutList;
Harald Welte8a6823d2011-03-08 16:03:31 +0100115tuple_fieldlist_walk(Path, TplName, [Head|List], TupleCb, Args, OutList) ->
Harald Weltecf436012011-03-07 12:54:15 +0100116 if
117 is_tuple(Head) ->
Harald Welte8a6823d2011-03-08 16:03:31 +0100118 NewHead = tuple_walk(Path++[TplName], Head, TupleCb, Args);
Harald Welte4a0afae2011-03-07 23:54:04 +0100119 is_list(Head) ->
Harald Welte8a6823d2011-03-08 16:03:31 +0100120 NewHead = tuple_walk(Path++[TplName], Head, TupleCb, Args);
Harald Weltecf436012011-03-07 12:54:15 +0100121 true ->
122 NewHead = Head
123 end,
Harald Welte8a6823d2011-03-08 16:03:31 +0100124 tuple_fieldlist_walk(Path, TplName, List, TupleCb, Args, OutList++[NewHead]).
Harald Weltecf436012011-03-07 12:54:15 +0100125
126
Harald Welte8a6823d2011-03-08 16:03:31 +0100127tuple_walk_print_cb(Path, Tpl, _Args) when is_list(Path), is_tuple(Tpl) ->
Harald Weltecf436012011-03-07 12:54:15 +0100128 io:format("~p:~p~n", [Path, Tpl]),
129 Tpl.