blob: 9aa555f13d9893ce4b163301d244d385e0e7a5aa [file] [log] [blame]
Harald Welte9fe07292012-02-13 20:54:17 +01001% Maintain a list of IMSIs in a gb_tree and match against it
2
Harald Welte7bd1d4a2013-02-06 09:02:46 +01003% (C) 2012-2013 by Harald Welte <laforge@gnumonks.org>
4% (C) 2012-2013 by On-Waves
Harald Welte9fe07292012-02-13 20:54:17 +01005%
6% All Rights Reserved
7%
8% This program is free software; you can redistribute it and/or modify
Harald Weltefb222d92012-04-16 13:19:15 +02009% it under the terms of the GNU Affero General Public License as
10% published by the Free Software Foundation; either version 3 of the
11% License, or (at your option) any later version.
Harald Welte9fe07292012-02-13 20:54:17 +010012%
13% This program is distributed in the hope that it will be useful,
14% but WITHOUT ANY WARRANTY; without even the implied warranty of
15% MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
16% GNU General Public License for more details.
17%
Harald Weltefb222d92012-04-16 13:19:15 +020018% You should have received a copy of the GNU Affero General Public License
19% along with this program. If not, see <http://www.gnu.org/licenses/>.
20%
21% Additional Permission under GNU AGPL version 3 section 7:
22%
23% If you modify this Program, or any covered work, by linking or
24% combining it with runtime libraries of Erlang/OTP as released by
25% Ericsson on http://www.erlang.org (or a modified version of these
26% libraries), containing parts covered by the terms of the Erlang Public
27% License (http://www.erlang.org/EPLICENSE), the licensors of this
28% Program grant you additional permission to convey the resulting work
29% without the need to license the runtime libraries of Erlang/OTP under
30% the GNU Affero General Public License. Corresponding Source for a
31% non-source form of such a combination shall include the source code
32% for the parts of the runtime libraries of Erlang/OTP used as well as
33% that of the covered work.
Harald Welte9fe07292012-02-13 20:54:17 +010034
35-module(imsi_list).
36-author('Harald Welte <laforge@gnumonks.org>').
37
Harald Welte6675c742013-02-06 09:14:37 +010038-export([read_file/1, read_list/1, match_imsi/2, match_imsi/3,
39 num_entries/1]).
Harald Welte7bd1d4a2013-02-06 09:02:46 +010040
41-record(state, {forward, reverse}).
Harald Welte9fe07292012-02-13 20:54:17 +010042
43lines2tree(Iodev) ->
Harald Welte7bd1d4a2013-02-06 09:02:46 +010044 S = #state{forward = gb_trees:empty(),
45 reverse = gb_trees:empty()},
46 lines2tree(Iodev, S).
Harald Welte9fe07292012-02-13 20:54:17 +010047
48chomp(Line) when is_list(Line) ->
49 case lists:last(Line) of
50 10 ->
51 lists:sublist(Line, 1, length(Line)-1);
52 _ ->
53 Line
54 end.
55
Harald Weltefce6cf12012-02-20 07:56:16 +010056% convert from "12345" to [1,2,3,4,5]
57string_num_to_int_list(Line2) ->
Harald Welte7bd1d4a2013-02-06 09:02:46 +010058 [case string:to_integer([X]) of
59 {Int,[]} -> Int;
60 {error, F} ->
61 error_logger:error_report([{imsi_list_syntax_error,
62 Line2, {error, F}}]),
63 undefined
64 end || X <- Line2].
Harald Weltefce6cf12012-02-20 07:56:16 +010065
Harald Welte7bd1d4a2013-02-06 09:02:46 +010066lines2tree(Iodev, State) ->
Harald Welte9fe07292012-02-13 20:54:17 +010067 case file:read_line(Iodev) of
68 eof ->
Harald Welte7bd1d4a2013-02-06 09:02:46 +010069 {ok, State};
Harald Welte9fe07292012-02-13 20:54:17 +010070 {error, Reason} ->
71 {error, Reason};
72 ebadf ->
73 {error, ebadf};
74 {ok, Line} ->
75 % FIXME: convert to digit list
76 Line2 = chomp(Line),
Harald Weltefce6cf12012-02-20 07:56:16 +010077 case string:tokens(Line2, ",;") of
78 [ImsiOldStr, ImsiNewStr] ->
79 ImsiOld = string_num_to_int_list(ImsiOldStr),
80 ImsiNew = string_num_to_int_list(ImsiNewStr),
Harald Welte7bd1d4a2013-02-06 09:02:46 +010081 FwNew = gb_trees:insert(ImsiOld, ImsiNew,
82 State#state.forward),
83 RevNew = gb_trees:insert(ImsiNew, ImsiOld,
84 State#state.reverse),
85 lines2tree(Iodev, #state{forward = FwNew,
86 reverse = RevNew});
87 % FIXME: handle empty lines or skip bad lines
Harald Weltefce6cf12012-02-20 07:56:16 +010088 _ ->
89 {error, file_format}
90 end
Harald Welte9fe07292012-02-13 20:54:17 +010091 end.
92
93
94read_file(FileName) ->
95 % read a text file with one IMSI per line into a gb_tree
96 case file:open(FileName, [read]) of
97 {ok, IoDev} ->
98 lines2tree(IoDev);
99 {error, Reason} ->
100 {error, Reason}
101 end.
102
103read_list(List) when is_list(List) ->
Harald Welte7bd1d4a2013-02-06 09:02:46 +0100104 S = #state{forward = gb_trees:empty(),
105 reverse = gb_trees:empty()},
106 read_list(List, S).
Harald Welte9fe07292012-02-13 20:54:17 +0100107
108read_list([], Tree) ->
109 Tree;
Harald Welte7bd1d4a2013-02-06 09:02:46 +0100110read_list([{Old, New}|Tail], State) ->
111 FwNew = gb_trees:insert(Old, New, State#state.forward),
112 RevNew = gb_trees:insert(New, Old, State#state.reverse),
113 read_list(Tail, #state{forward = FwNew, reverse = RevNew}).
Harald Welte9fe07292012-02-13 20:54:17 +0100114
Harald Welte7bd1d4a2013-02-06 09:02:46 +0100115match_imsi(State, Imsi) when is_list(Imsi) ->
116 match_imsi(forward, State, Imsi).
117
118match_imsi(forward, State, Imsi) when is_list(Imsi) ->
119 case gb_trees:lookup(Imsi, State#state.forward) of
120 {value, ImsiNew} ->
121 {ok, ImsiNew};
122 none ->
123 {error, no_entry}
124 end;
125match_imsi(reverse, State, Imsi) when is_list(Imsi) ->
126 case gb_trees:lookup(Imsi, State#state.reverse) of
Harald Weltefce6cf12012-02-20 07:56:16 +0100127 {value, ImsiNew} ->
128 {ok, ImsiNew};
Harald Welte9fe07292012-02-13 20:54:17 +0100129 none ->
Harald Weltefce6cf12012-02-20 07:56:16 +0100130 {error, no_entry}
Harald Welte9fe07292012-02-13 20:54:17 +0100131 end.
Harald Welte6675c742013-02-06 09:14:37 +0100132
133num_entries(State) when is_record(State, state) ->
134 gb_trees:size(State#state.forward).