blob: 21e2c41aee508ce66fd4ca0936f537658e556052 [file] [log] [blame]
Harald Welte268c5722011-02-09 14:38:15 +01001% GSM MAP codec wrapper 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(map_codec).
21-author('Harald Welte <laforge@gnumonks.org>').
Harald Welte21c6b942011-04-16 20:14:38 +020022-include("map.hrl").
Harald Welte74368cc2011-02-09 21:41:36 +010023-include_lib("osmo_ss7/include/isup.hrl").
Harald Welte268c5722011-02-09 14:38:15 +010024
Harald Welte0aa140b2011-02-09 23:15:22 +010025-export([parse_tcap_msg/1, encode_tcap_msg/1]).
Harald Welte74368cc2011-02-09 21:41:36 +010026-export([parse_addr_string/1, encode_addr_string/1]).
Harald Welte268c5722011-02-09 14:38:15 +010027
Harald Welte74368cc2011-02-09 21:41:36 +010028-define(MAP_ADDR_NAT_UNKNOWN, 0).
29-define(MAP_ADDR_NAT_INTERNATIONAL, 1).
30-define(MAP_ADDR_NAT_NATIONAL, 2).
31-define(MAP_ADDR_NAT_NETWORK_SPEC, 3).
32-define(MAP_ADDR_NAT_SUBSCRIBER, 4).
33-define(MAP_ADDR_NAT_RES, 5).
34-define(MAP_ADDR_NAT_ABBREVIATED, 6).
35-define(MAP_ADDR_NAT_RES_FOR_EXT, 7).
36
37% convert from MAP -> ISUP 'nature of address'
38nature_map2isup(NatureMap) ->
39 case NatureMap of
40 ?MAP_ADDR_NAT_INTERNATIONAL -> ?ISUP_ADDR_NAT_INTERNATIONAL;
41 ?MAP_ADDR_NAT_NATIONAL -> ?ISUP_ADDR_NAT_NATIONAL;
42 ?MAP_ADDR_NAT_SUBSCRIBER -> ?ISUP_ADDR_NAT_SUBSCRIBER;
43 _ -> NatureMap
44 end.
45
46% convert from ISUP -> MAP 'nature of address'
47nature_isup2map(NatureIsup) ->
48 case NatureIsup of
49 ?ISUP_ADDR_NAT_INTERNATIONAL -> ?MAP_ADDR_NAT_INTERNATIONAL;
50 ?ISUP_ADDR_NAT_NATIONAL -> ?MAP_ADDR_NAT_NATIONAL;
51 ?ISUP_ADDR_NAT_SUBSCRIBER -> ?MAP_ADDR_NAT_SUBSCRIBER;
52 _ -> NatureIsup
53 end.
54
Harald Welte4ae92fb2011-02-10 17:53:15 +010055% Parse a TBCD-STRING
56parse_map_tbcd(<<>>, DigitList) ->
57 DigitList;
58parse_map_tbcd(BcdBin, DigitList) ->
59 <<Second:4, First:4, Remain/binary>> = BcdBin,
60 NewDigits = [First, Second],
61 parse_map_tbcd(Remain, DigitList ++ NewDigits).
62parse_map_tbcd(ListBcd) when is_list(ListBcd) ->
63 BinBcd = list_to_binary(ListBcd),
64 parse_map_tbcd(BinBcd);
65parse_map_tbcd(BinBcd) when is_binary(BinBcd) ->
66 parse_map_tbcd(BinBcd, []).
67
68% like parse_map_tbcd, but remove any trailing 0xF
69parse_map_addr(Bcd) ->
70 DigitList = parse_map_tbcd(Bcd),
71 LastDigit = lists:last(DigitList),
72 if
73 LastDigit == 15 ->
74 lists:sublist(DigitList, length(DigitList)-1);
75 true ->
76 DigitList
77 end.
78
79encode_map_tbcd(BcdInt) when is_integer(BcdInt) ->
80 BcdList = osmo_util:int2digit_list(BcdInt),
81 encode_map_tbcd(BcdList);
82encode_map_tbcd(BcdList) when is_list(BcdList) ->
83 encode_map_tbcd(BcdList, <<>>).
84encode_map_tbcd([], Bin) ->
85 Bin;
86encode_map_tbcd([First,Second|BcdList], Bin) ->
87 encode_map_tbcd(BcdList, <<Bin/binary, Second:4, First:4>>);
88encode_map_tbcd([Last], Bin) ->
89 encode_map_tbcd([], <<Bin/binary, 15:4, Last:4>>).
90
91encode_map_addr(Bcd) ->
92 encode_map_tbcd(Bcd).
93
94
Harald Welte74368cc2011-02-09 21:41:36 +010095
96parse_addr_string(AddrList) when is_list(AddrList) ->
97 parse_addr_string(list_to_binary(AddrList));
98parse_addr_string(AddrBin) when is_binary(AddrBin) ->
99 <<1:1, NatureMap:3, Numplan:4, Remain/binary>> = AddrBin,
Harald Welte4ae92fb2011-02-10 17:53:15 +0100100 PhoneNum = parse_map_addr(Remain),
Harald Welte74368cc2011-02-09 21:41:36 +0100101 NatureIsup = nature_map2isup(NatureMap),
102 #party_number{nature_of_addr_ind = NatureIsup,
103 numbering_plan = Numplan,
104 phone_number = PhoneNum}.
105
106encode_addr_string(#party_number{nature_of_addr_ind = NatureIsup,
107 numbering_plan = Numplan,
108 phone_number = PhoneNum}) ->
109 NatureMap = nature_isup2map(NatureIsup),
Harald Welte5b146412011-02-10 17:57:09 +0100110 PhoneBin = encode_map_addr(PhoneNum),
Harald Weltefc281c32011-02-09 22:39:08 +0100111 Bin = <<1:1, NatureMap:3, Numplan:4, PhoneBin/binary>>,
112 binary_to_list(Bin).
Harald Welte268c5722011-02-09 14:38:15 +0100113
114parse_tcap_msg(MsgBin) when is_binary(MsgBin) ->
Harald Welted08ea8d2011-02-09 23:13:48 +0100115 Msg = binary_to_list(MsgBin),
116 parse_tcap_msg(Msg);
117parse_tcap_msg(Msg) when is_list(Msg) ->
118 case asn1rt:decode('map', 'MapSpecificPDUs', Msg) of
Harald Welte268c5722011-02-09 14:38:15 +0100119 {ok, {Type, TcapMsgDec}} ->
Harald Welte21c6b942011-04-16 20:14:38 +0200120 fixup_dialogue({Type, TcapMsgDec});
Harald Welte268c5722011-02-09 14:38:15 +0100121 Error ->
122 Error
123 end.
124
Harald Welte21c6b942011-04-16 20:14:38 +0200125% Extract the dialoguePortion and feed it through external_1990ify/1
126fixup_dialogue({'begin', Beg = #'MapSpecificPDUs_begin'{dialoguePortion=Dia}}) ->
127 {'begin', Beg#'MapSpecificPDUs_begin'{dialoguePortion = external_1990ify(Dia)}};
128fixup_dialogue({'end', Beg = #'MapSpecificPDUs_end'{dialoguePortion=Dia}}) ->
129 {'end', Beg#'MapSpecificPDUs_end'{dialoguePortion = external_1990ify(Dia)}};
130fixup_dialogue({'continue', Beg = #'MapSpecificPDUs_continue'{dialoguePortion=Dia}}) ->
131 {'continue', Beg#'MapSpecificPDUs_continue'{dialoguePortion = external_1990ify(Dia)}};
132fixup_dialogue({'unidirectional', Beg = #'MapSpecificPDUs_unidirectional'{dialoguePortion=Dia}}) ->
133 {'unidirectional', Beg#'MapSpecificPDUs_unidirectional'{dialoguePortion = external_1990ify(Dia)}};
134fixup_dialogue(Default) ->
135 Default.
136
137% Take the EXTERNAL date type and convert from 1994-style to 1990 with 'single-ASN1-type'
138external_1990ify({'EXTERNAL', {syntax, DirRef}, IndirRef, Data}) when is_list(Data); is_binary(Data) ->
139 #'EXTERNAL'{'direct-reference' = DirRef,
140 'indirect-reference' = IndirRef,
141 encoding = {'single-ASN1-type', Data}};
142external_1990ify(Default) ->
143 Default.
144
Harald Welte0aa140b2011-02-09 23:15:22 +0100145encode_tcap_msg({Type, TcapMsgDec}) ->
146 case asn1rt:encode('map', 'MapSpecificPDUs', {Type, TcapMsgDec}) of
Harald Welted08ea8d2011-02-09 23:13:48 +0100147 {ok, List} ->
148 list_to_binary(List);
149 Error ->
150 Error
151 end.