blob: d4fb5b074deeb8e29a4e6cdad9342bc98949f024 [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/>.
Harald Weltef8bf0322012-04-16 13:10:47 +020019%
20% Additional Permission under GNU AGPL version 3 section 7:
21%
22% If you modify this Program, or any covered work, by linking or
23% combining it with runtime libraries of Erlang/OTP as released by
24% Ericsson on http://www.erlang.org (or a modified version of these
25% libraries), containing parts covered by the terms of the Erlang Public
26% License (http://www.erlang.org/EPLICENSE), the licensors of this
27% Program grant you additional permission to convey the resulting work
28% without the need to license the runtime libraries of Erlang/OTP under
29% the GNU Affero General Public License. Corresponding Source for a
30% non-source form of such a combination shall include the source code
31% for the parts of the runtime libraries of Erlang/OTP used as well as
32% that of the covered work.
Harald Welte77804892011-02-06 18:12:47 +010033
34-module(osmo_util).
35-author('Harald Welte <laforge@gnumonks.org>').
36
37-export([digit_list2int/1, int2digit_list/1]).
38-export([reload_config/0]).
Harald Welte8a6823d2011-03-08 16:03:31 +010039-export([tuple_walk/3, tuple_walk_print_cb/3]).
Harald Welte0f2f5962011-04-04 15:59:49 +020040-export([make_prim/4, make_prim/3]).
Harald Welte8ff5df42011-04-04 21:52:52 +020041-export([pointcode2int/1, pointcode2int/2, pointcode_fmt/2]).
Harald Welte79e233f2012-01-31 22:30:22 +010042-export([asn_val/1]).
Harald Welte0f2f5962011-04-04 15:59:49 +020043
44-include("osmo_util.hrl").
45
46-compile({parse_transform, exprecs}).
47-export_records([primitive]).
Harald Welte77804892011-02-06 18:12:47 +010048
49% Convert a list of digits to an integer value
50digit_list2int(Int, []) ->
51 Int;
52digit_list2int(Int, [Digit|Tail]) ->
53 digit_list2int(Int*10 + Digit, Tail).
54digit_list2int(Digits) when is_list(Digits) ->
55 digit_list2int(0, Digits).
56
57% Convert an integer value into a list of decimal digits
58int2digit_list(0, Digits) when is_list(Digits) ->
59 Digits;
60int2digit_list(Int, Digits) when is_integer(Int), is_list(Digits) ->
61 Digit = Int rem 10,
62 int2digit_list(Int div 10, [Digit|Digits]).
63int2digit_list(Int) when is_integer(Int) ->
64 int2digit_list(Int, []).
65
66% reload configuration of an application
67reload_config() ->
68 case init:get_argument(config) of
69 {ok, [ Files ]} ->
70 ConfFiles = [begin
71 S = filename:basename(F,".config"),
72 filename:join(filename:dirname(F),
73 S ++ ".config")
74 end || F <- Files],
75 % Move sys.config to the head of the list
76 Config = lists:sort(fun("sys.config", _) -> true;
77 (_, _) -> false end, ConfFiles),
78
79 OldEnv = application_controller:prep_config_change(),
80
81 Apps = [{application, A, make_appl(A)}
82 || {A,_,_} <- application:which_applications()],
83 application_controller:change_application_data(Apps, Config),
84 application_controller:config_change(OldEnv);
85 _ ->
86 {ok, []}
87 end.
88
89make_appl(App) when is_atom(App) ->
90 AppList = element(2,application:get_all_key(App)),
91 FullName = code:where_is_file(atom_to_list(App) ++ ".app"),
92 case file:consult(FullName) of
93 {ok, [{application, _, Opts}]} ->
94 Env = proplists:get_value(env, Opts, []),
95 lists:keyreplace(env, 1, AppList, {env, Env});
96 {error, _Reason} ->
97 lists:keyreplace(env, 1, AppList, {env, []})
98 end.
Harald Weltecf436012011-03-07 12:54:15 +010099
100
101% Walk a named tuple and (recursively) all its fields, call user-supplied
102% callback for each of them
Harald Welte8a6823d2011-03-08 16:03:31 +0100103tuple_walk(Tpl, TupleCb, Args) when is_tuple(Tpl), is_function(TupleCb),
104 is_list(Args) ->
105 tuple_walk([], Tpl, TupleCb, Args).
Harald Weltecf436012011-03-07 12:54:15 +0100106
Harald Welte8a6823d2011-03-08 16:03:31 +0100107tuple_walk(Path, Tpl, TupleCb, Args) when is_list(Path), is_tuple(Tpl),
108 is_list(Args) ->
Harald Weltecf436012011-03-07 12:54:15 +0100109 % call Callback
Tobias Engeld49aa212013-06-13 11:16:57 +0200110 RetVal = TupleCb(Path, Tpl, Args),
111 if
112 is_tuple(RetVal) ->
113 [TplName|TplList] = tuple_to_list(RetVal),
114 NewTplList = tuple_fieldlist_walk(Path, TplName, TplList, TupleCb, Args),
115 list_to_tuple([TplName|NewTplList]);
116 true ->
117 RetVal
118 end;
Harald Welte8a6823d2011-03-08 16:03:31 +0100119tuple_walk(Path, TplL, TupleCb, Args) when is_list(Path), is_list(TplL),
120 is_list(Args) ->
121 tuple_walk_list(Path, TplL, TupleCb, Args, []).
Harald Welte4a0afae2011-03-07 23:54:04 +0100122
Harald Welte8a6823d2011-03-08 16:03:31 +0100123tuple_walk_list(_Path, [], _TupleCb, _Args, OutList) ->
Harald Welte4a0afae2011-03-07 23:54:04 +0100124 OutList;
Harald Welte8a6823d2011-03-08 16:03:31 +0100125tuple_walk_list(Path, [Head|Tail], TupleCb, Args, OutList) ->
Harald Welte4a0afae2011-03-07 23:54:04 +0100126 if
127 is_tuple(Head) ->
Harald Welte8a6823d2011-03-08 16:03:31 +0100128 NewHead = tuple_walk(Path, Head, TupleCb, Args);
Harald Welte4a0afae2011-03-07 23:54:04 +0100129 is_list(Head) ->
Harald Welte8a6823d2011-03-08 16:03:31 +0100130 NewHead = tuple_walk(Path, Head, TupleCb, Args);
Harald Welte4a0afae2011-03-07 23:54:04 +0100131 true ->
132 NewHead = Head
133 end,
Harald Welte8a6823d2011-03-08 16:03:31 +0100134 tuple_walk_list(Path, Tail, TupleCb, Args, OutList++[NewHead]).
Harald Welte4a0afae2011-03-07 23:54:04 +0100135
Harald Weltecf436012011-03-07 12:54:15 +0100136
Harald Welte8a6823d2011-03-08 16:03:31 +0100137tuple_fieldlist_walk(Path, TplName, FieldList, TupleCb, Args) ->
138 tuple_fieldlist_walk(Path, TplName, FieldList, TupleCb, Args, []).
Harald Weltecf436012011-03-07 12:54:15 +0100139
Harald Welte8a6823d2011-03-08 16:03:31 +0100140tuple_fieldlist_walk(_Path, _TplName, [], _TplCb, _Args, OutList) ->
Harald Weltecf436012011-03-07 12:54:15 +0100141 OutList;
Harald Welte8a6823d2011-03-08 16:03:31 +0100142tuple_fieldlist_walk(Path, TplName, [Head|List], TupleCb, Args, OutList) ->
Harald Weltecf436012011-03-07 12:54:15 +0100143 if
144 is_tuple(Head) ->
Harald Welte8a6823d2011-03-08 16:03:31 +0100145 NewHead = tuple_walk(Path++[TplName], Head, TupleCb, Args);
Harald Welte4a0afae2011-03-07 23:54:04 +0100146 is_list(Head) ->
Harald Welte8a6823d2011-03-08 16:03:31 +0100147 NewHead = tuple_walk(Path++[TplName], Head, TupleCb, Args);
Harald Weltecf436012011-03-07 12:54:15 +0100148 true ->
149 NewHead = Head
150 end,
Harald Welte8a6823d2011-03-08 16:03:31 +0100151 tuple_fieldlist_walk(Path, TplName, List, TupleCb, Args, OutList++[NewHead]).
Harald Weltecf436012011-03-07 12:54:15 +0100152
153
Harald Welte8a6823d2011-03-08 16:03:31 +0100154tuple_walk_print_cb(Path, Tpl, _Args) when is_list(Path), is_tuple(Tpl) ->
Harald Weltecf436012011-03-07 12:54:15 +0100155 io:format("~p:~p~n", [Path, Tpl]),
156 Tpl.
Harald Welte0f2f5962011-04-04 15:59:49 +0200157
158% helper function to create a #primitive record
159make_prim(Subsys, GenName, SpecName) ->
160 make_prim(Subsys, GenName, SpecName, []).
161make_prim(Subsys, GenName, SpecName, Param) ->
162 #primitive{subsystem = Subsys, gen_name = GenName,
163 spec_name = SpecName, parameters = Param}.
Harald Welte8ff5df42011-04-04 21:52:52 +0200164
165% parse a 3-tuple pointcode into a raw integer
Harald Welte7ad37a22011-12-08 11:50:00 +0100166pointcode2int(Int) when is_integer(Int) ->
167 Int;
Harald Welte0bd35282012-01-23 17:35:57 +0100168pointcode2int(undefined) ->
169 undefined;
Harald Welteba0ada72011-12-08 00:56:30 +0100170pointcode2int(#pointcode{repr=Type, value=Value}) ->
171 pointcode2int(Type, Value);
Harald Welte8ff5df42011-04-04 21:52:52 +0200172pointcode2int({Std, Param}) ->
173 pointcode2int(Std, Param).
174
175pointcode2int(itu, {A, B, C}) ->
176 <<PcInt:14/big>> = <<A:3, B:8, C:3>>,
177 PcInt;
178pointcode2int(ansi, {A, B, C}) ->
179 <<PcInt:24/big>> = <<A:8, B:8, C:8>>,
180 PcInt;
181pointcode2int(ttc, {A, B, C}) ->
182 <<PcInt:16/big>> = <<A:5, B:4, C:7>>,
183 PcInt.
184
185% format a point-code into a 3-tuple according to the standard used
186pointcode_fmt(Std, P) when is_binary(P) ->
187 <<PcInt/integer>> = P,
188 pointcode_fmt(Std, PcInt);
189pointcode_fmt(itu, PcInt) when is_integer(PcInt) ->
190 <<A:3, B:8, C:3>> = <<PcInt:14/big>>,
191 {pointcode, itu, {A, B, C}};
192pointcode_fmt(ansi, PcInt) ->
193 <<A:8, B:8, C:8>> = <<PcInt:24/big>>,
194 {pointcode, ansi, {A, B, C}};
195pointcode_fmt(ttc, PcInt) ->
196 <<A:5, B:4, C:7>> = <<PcInt:16/big>>,
197 {pointcode, ttc, {A, B, C}}.
Harald Welte79e233f2012-01-31 22:30:22 +0100198
199asn_val(undefined) ->
200 asn1_NOVALUE;
201asn_val([]) ->
202 asn1_NOVALUE;
203asn_val(Foo) ->
204 Foo.