blob: 7ddb527680797374e8c946f0db5628492ace4660 [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 Weltecf436012011-03-07 12:54:15 +010025-export([tuple_walk/2, tuple_walk_print_cb/2]).
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
81tuple_walk(Tpl, TupleCb) when is_tuple(Tpl), is_function(TupleCb) ->
82 tuple_walk([], Tpl, TupleCb).
83
84tuple_walk(Path, Tpl, TupleCb) when is_list(Path), is_tuple(Tpl) ->
85 % call Callback
86 NewTpl = TupleCb(Path, Tpl),
87 [TplName|TplList] = tuple_to_list(NewTpl),
88 NewTplList = tuple_fieldlist_walk(Path, TplName, TplList, TupleCb),
Harald Welte4a0afae2011-03-07 23:54:04 +010089 list_to_tuple([TplName|NewTplList]);
90tuple_walk(Path, TplL, TupleCb) when is_list(Path), is_list(TplL) ->
91 tuple_walk_list(Path, TplL, TupleCb, []).
92
93tuple_walk_list(_Path, [], _TupleCb, OutList) ->
94 OutList;
95tuple_walk_list(Path, [Head|Tail], TupleCb, OutList) ->
96 if
97 is_tuple(Head) ->
98 NewHead = tuple_walk(Path, Head, TupleCb);
99 is_list(Head) ->
100 NewHead = tuple_walk(Path, Head, TupleCb);
101 true ->
102 NewHead = Head
103 end,
104 tuple_walk_list(Path, Tail, TupleCb, OutList++[NewHead]).
105
Harald Weltecf436012011-03-07 12:54:15 +0100106
107tuple_fieldlist_walk(Path, TplName, FieldList, TupleCb) ->
108 tuple_fieldlist_walk(Path, TplName, FieldList, TupleCb, []).
109
110tuple_fieldlist_walk(_Path, _TplName, [], _TplCb, OutList) ->
111 OutList;
112tuple_fieldlist_walk(Path, TplName, [Head|List], TupleCb, OutList) ->
113 if
114 is_tuple(Head) ->
115 NewHead = tuple_walk(Path++[TplName], Head, TupleCb);
Harald Welte4a0afae2011-03-07 23:54:04 +0100116 is_list(Head) ->
117 NewHead = tuple_walk(Path++[TplName], Head, TupleCb);
Harald Weltecf436012011-03-07 12:54:15 +0100118 true ->
119 NewHead = Head
120 end,
121 tuple_fieldlist_walk(Path, TplName, List, TupleCb, OutList++[NewHead]).
122
123
124tuple_walk_print_cb(Path, Tpl) when is_list(Path), is_tuple(Tpl) ->
125 io:format("~p:~p~n", [Path, Tpl]),
126 Tpl.