blob: a1c70fe56eaa85177435aedc1c1bcc42a5265571 [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 Welte0f2f5962011-04-04 15:59:49 +020026-export([make_prim/4, make_prim/3]).
Harald Welte8ff5df42011-04-04 21:52:52 +020027-export([pointcode2int/1, pointcode2int/2, pointcode_fmt/2]).
Harald Welte79e233f2012-01-31 22:30:22 +010028-export([asn_val/1]).
Harald Welte0f2f5962011-04-04 15:59:49 +020029
30-include("osmo_util.hrl").
31
32-compile({parse_transform, exprecs}).
33-export_records([primitive]).
Harald Welte77804892011-02-06 18:12:47 +010034
35% Convert a list of digits to an integer value
36digit_list2int(Int, []) ->
37 Int;
38digit_list2int(Int, [Digit|Tail]) ->
39 digit_list2int(Int*10 + Digit, Tail).
40digit_list2int(Digits) when is_list(Digits) ->
41 digit_list2int(0, Digits).
42
43% Convert an integer value into a list of decimal digits
44int2digit_list(0, Digits) when is_list(Digits) ->
45 Digits;
46int2digit_list(Int, Digits) when is_integer(Int), is_list(Digits) ->
47 Digit = Int rem 10,
48 int2digit_list(Int div 10, [Digit|Digits]).
49int2digit_list(Int) when is_integer(Int) ->
50 int2digit_list(Int, []).
51
52% reload configuration of an application
53reload_config() ->
54 case init:get_argument(config) of
55 {ok, [ Files ]} ->
56 ConfFiles = [begin
57 S = filename:basename(F,".config"),
58 filename:join(filename:dirname(F),
59 S ++ ".config")
60 end || F <- Files],
61 % Move sys.config to the head of the list
62 Config = lists:sort(fun("sys.config", _) -> true;
63 (_, _) -> false end, ConfFiles),
64
65 OldEnv = application_controller:prep_config_change(),
66
67 Apps = [{application, A, make_appl(A)}
68 || {A,_,_} <- application:which_applications()],
69 application_controller:change_application_data(Apps, Config),
70 application_controller:config_change(OldEnv);
71 _ ->
72 {ok, []}
73 end.
74
75make_appl(App) when is_atom(App) ->
76 AppList = element(2,application:get_all_key(App)),
77 FullName = code:where_is_file(atom_to_list(App) ++ ".app"),
78 case file:consult(FullName) of
79 {ok, [{application, _, Opts}]} ->
80 Env = proplists:get_value(env, Opts, []),
81 lists:keyreplace(env, 1, AppList, {env, Env});
82 {error, _Reason} ->
83 lists:keyreplace(env, 1, AppList, {env, []})
84 end.
Harald Weltecf436012011-03-07 12:54:15 +010085
86
87% Walk a named tuple and (recursively) all its fields, call user-supplied
88% callback for each of them
Harald Welte8a6823d2011-03-08 16:03:31 +010089tuple_walk(Tpl, TupleCb, Args) when is_tuple(Tpl), is_function(TupleCb),
90 is_list(Args) ->
91 tuple_walk([], Tpl, TupleCb, Args).
Harald Weltecf436012011-03-07 12:54:15 +010092
Harald Welte8a6823d2011-03-08 16:03:31 +010093tuple_walk(Path, Tpl, TupleCb, Args) when is_list(Path), is_tuple(Tpl),
94 is_list(Args) ->
Harald Weltecf436012011-03-07 12:54:15 +010095 % call Callback
Harald Welte8a6823d2011-03-08 16:03:31 +010096 NewTpl = TupleCb(Path, Tpl, Args),
Harald Weltecf436012011-03-07 12:54:15 +010097 [TplName|TplList] = tuple_to_list(NewTpl),
Harald Welte8a6823d2011-03-08 16:03:31 +010098 NewTplList = tuple_fieldlist_walk(Path, TplName, TplList, TupleCb, Args),
Harald Welte4a0afae2011-03-07 23:54:04 +010099 list_to_tuple([TplName|NewTplList]);
Harald Welte8a6823d2011-03-08 16:03:31 +0100100tuple_walk(Path, TplL, TupleCb, Args) when is_list(Path), is_list(TplL),
101 is_list(Args) ->
102 tuple_walk_list(Path, TplL, TupleCb, Args, []).
Harald Welte4a0afae2011-03-07 23:54:04 +0100103
Harald Welte8a6823d2011-03-08 16:03:31 +0100104tuple_walk_list(_Path, [], _TupleCb, _Args, OutList) ->
Harald Welte4a0afae2011-03-07 23:54:04 +0100105 OutList;
Harald Welte8a6823d2011-03-08 16:03:31 +0100106tuple_walk_list(Path, [Head|Tail], TupleCb, Args, OutList) ->
Harald Welte4a0afae2011-03-07 23:54:04 +0100107 if
108 is_tuple(Head) ->
Harald Welte8a6823d2011-03-08 16:03:31 +0100109 NewHead = tuple_walk(Path, Head, TupleCb, Args);
Harald Welte4a0afae2011-03-07 23:54:04 +0100110 is_list(Head) ->
Harald Welte8a6823d2011-03-08 16:03:31 +0100111 NewHead = tuple_walk(Path, Head, TupleCb, Args);
Harald Welte4a0afae2011-03-07 23:54:04 +0100112 true ->
113 NewHead = Head
114 end,
Harald Welte8a6823d2011-03-08 16:03:31 +0100115 tuple_walk_list(Path, Tail, TupleCb, Args, OutList++[NewHead]).
Harald Welte4a0afae2011-03-07 23:54:04 +0100116
Harald Weltecf436012011-03-07 12:54:15 +0100117
Harald Welte8a6823d2011-03-08 16:03:31 +0100118tuple_fieldlist_walk(Path, TplName, FieldList, TupleCb, Args) ->
119 tuple_fieldlist_walk(Path, TplName, FieldList, TupleCb, Args, []).
Harald Weltecf436012011-03-07 12:54:15 +0100120
Harald Welte8a6823d2011-03-08 16:03:31 +0100121tuple_fieldlist_walk(_Path, _TplName, [], _TplCb, _Args, OutList) ->
Harald Weltecf436012011-03-07 12:54:15 +0100122 OutList;
Harald Welte8a6823d2011-03-08 16:03:31 +0100123tuple_fieldlist_walk(Path, TplName, [Head|List], TupleCb, Args, OutList) ->
Harald Weltecf436012011-03-07 12:54:15 +0100124 if
125 is_tuple(Head) ->
Harald Welte8a6823d2011-03-08 16:03:31 +0100126 NewHead = tuple_walk(Path++[TplName], Head, TupleCb, Args);
Harald Welte4a0afae2011-03-07 23:54:04 +0100127 is_list(Head) ->
Harald Welte8a6823d2011-03-08 16:03:31 +0100128 NewHead = tuple_walk(Path++[TplName], Head, TupleCb, Args);
Harald Weltecf436012011-03-07 12:54:15 +0100129 true ->
130 NewHead = Head
131 end,
Harald Welte8a6823d2011-03-08 16:03:31 +0100132 tuple_fieldlist_walk(Path, TplName, List, TupleCb, Args, OutList++[NewHead]).
Harald Weltecf436012011-03-07 12:54:15 +0100133
134
Harald Welte8a6823d2011-03-08 16:03:31 +0100135tuple_walk_print_cb(Path, Tpl, _Args) when is_list(Path), is_tuple(Tpl) ->
Harald Weltecf436012011-03-07 12:54:15 +0100136 io:format("~p:~p~n", [Path, Tpl]),
137 Tpl.
Harald Welte0f2f5962011-04-04 15:59:49 +0200138
139% helper function to create a #primitive record
140make_prim(Subsys, GenName, SpecName) ->
141 make_prim(Subsys, GenName, SpecName, []).
142make_prim(Subsys, GenName, SpecName, Param) ->
143 #primitive{subsystem = Subsys, gen_name = GenName,
144 spec_name = SpecName, parameters = Param}.
Harald Welte8ff5df42011-04-04 21:52:52 +0200145
146% parse a 3-tuple pointcode into a raw integer
Harald Welte7ad37a22011-12-08 11:50:00 +0100147pointcode2int(Int) when is_integer(Int) ->
148 Int;
Harald Welte0bd35282012-01-23 17:35:57 +0100149pointcode2int(undefined) ->
150 undefined;
Harald Welteba0ada72011-12-08 00:56:30 +0100151pointcode2int(#pointcode{repr=Type, value=Value}) ->
152 pointcode2int(Type, Value);
Harald Welte8ff5df42011-04-04 21:52:52 +0200153pointcode2int({Std, Param}) ->
154 pointcode2int(Std, Param).
155
156pointcode2int(itu, {A, B, C}) ->
157 <<PcInt:14/big>> = <<A:3, B:8, C:3>>,
158 PcInt;
159pointcode2int(ansi, {A, B, C}) ->
160 <<PcInt:24/big>> = <<A:8, B:8, C:8>>,
161 PcInt;
162pointcode2int(ttc, {A, B, C}) ->
163 <<PcInt:16/big>> = <<A:5, B:4, C:7>>,
164 PcInt.
165
166% format a point-code into a 3-tuple according to the standard used
167pointcode_fmt(Std, P) when is_binary(P) ->
168 <<PcInt/integer>> = P,
169 pointcode_fmt(Std, PcInt);
170pointcode_fmt(itu, PcInt) when is_integer(PcInt) ->
171 <<A:3, B:8, C:3>> = <<PcInt:14/big>>,
172 {pointcode, itu, {A, B, C}};
173pointcode_fmt(ansi, PcInt) ->
174 <<A:8, B:8, C:8>> = <<PcInt:24/big>>,
175 {pointcode, ansi, {A, B, C}};
176pointcode_fmt(ttc, PcInt) ->
177 <<A:5, B:4, C:7>> = <<PcInt:16/big>>,
178 {pointcode, ttc, {A, B, C}}.
Harald Welte79e233f2012-01-31 22:30:22 +0100179
180asn_val(undefined) ->
181 asn1_NOVALUE;
182asn_val([]) ->
183 asn1_NOVALUE;
184asn_val(Foo) ->
185 Foo.