blob: 22b0272ece63beed59c0b9f5ec585e2eace6cab0 [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 Welteaa3b39e2012-02-02 23:52:00 +010027-export([parse_map_addr/1, encode_map_tbcd/1]).
Harald Welte268c5722011-02-09 14:38:15 +010028
Harald Welte74368cc2011-02-09 21:41:36 +010029-define(MAP_ADDR_NAT_UNKNOWN, 0).
30-define(MAP_ADDR_NAT_INTERNATIONAL, 1).
31-define(MAP_ADDR_NAT_NATIONAL, 2).
32-define(MAP_ADDR_NAT_NETWORK_SPEC, 3).
33-define(MAP_ADDR_NAT_SUBSCRIBER, 4).
34-define(MAP_ADDR_NAT_RES, 5).
35-define(MAP_ADDR_NAT_ABBREVIATED, 6).
36-define(MAP_ADDR_NAT_RES_FOR_EXT, 7).
37
38% convert from MAP -> ISUP 'nature of address'
39nature_map2isup(NatureMap) ->
40 case NatureMap of
41 ?MAP_ADDR_NAT_INTERNATIONAL -> ?ISUP_ADDR_NAT_INTERNATIONAL;
42 ?MAP_ADDR_NAT_NATIONAL -> ?ISUP_ADDR_NAT_NATIONAL;
43 ?MAP_ADDR_NAT_SUBSCRIBER -> ?ISUP_ADDR_NAT_SUBSCRIBER;
44 _ -> NatureMap
45 end.
46
47% convert from ISUP -> MAP 'nature of address'
48nature_isup2map(NatureIsup) ->
49 case NatureIsup of
50 ?ISUP_ADDR_NAT_INTERNATIONAL -> ?MAP_ADDR_NAT_INTERNATIONAL;
51 ?ISUP_ADDR_NAT_NATIONAL -> ?MAP_ADDR_NAT_NATIONAL;
52 ?ISUP_ADDR_NAT_SUBSCRIBER -> ?MAP_ADDR_NAT_SUBSCRIBER;
53 _ -> NatureIsup
54 end.
55
Harald Welte4ae92fb2011-02-10 17:53:15 +010056% Parse a TBCD-STRING
57parse_map_tbcd(<<>>, DigitList) ->
58 DigitList;
59parse_map_tbcd(BcdBin, DigitList) ->
60 <<Second:4, First:4, Remain/binary>> = BcdBin,
61 NewDigits = [First, Second],
62 parse_map_tbcd(Remain, DigitList ++ NewDigits).
63parse_map_tbcd(ListBcd) when is_list(ListBcd) ->
64 BinBcd = list_to_binary(ListBcd),
65 parse_map_tbcd(BinBcd);
66parse_map_tbcd(BinBcd) when is_binary(BinBcd) ->
67 parse_map_tbcd(BinBcd, []).
68
69% like parse_map_tbcd, but remove any trailing 0xF
70parse_map_addr(Bcd) ->
71 DigitList = parse_map_tbcd(Bcd),
72 LastDigit = lists:last(DigitList),
73 if
74 LastDigit == 15 ->
75 lists:sublist(DigitList, length(DigitList)-1);
76 true ->
77 DigitList
78 end.
79
80encode_map_tbcd(BcdInt) when is_integer(BcdInt) ->
81 BcdList = osmo_util:int2digit_list(BcdInt),
82 encode_map_tbcd(BcdList);
83encode_map_tbcd(BcdList) when is_list(BcdList) ->
84 encode_map_tbcd(BcdList, <<>>).
85encode_map_tbcd([], Bin) ->
86 Bin;
87encode_map_tbcd([First,Second|BcdList], Bin) ->
88 encode_map_tbcd(BcdList, <<Bin/binary, Second:4, First:4>>);
89encode_map_tbcd([Last], Bin) ->
90 encode_map_tbcd([], <<Bin/binary, 15:4, Last:4>>).
91
92encode_map_addr(Bcd) ->
93 encode_map_tbcd(Bcd).
94
95
Harald Welte74368cc2011-02-09 21:41:36 +010096
97parse_addr_string(AddrList) when is_list(AddrList) ->
98 parse_addr_string(list_to_binary(AddrList));
99parse_addr_string(AddrBin) when is_binary(AddrBin) ->
100 <<1:1, NatureMap:3, Numplan:4, Remain/binary>> = AddrBin,
Harald Welte4ae92fb2011-02-10 17:53:15 +0100101 PhoneNum = parse_map_addr(Remain),
Harald Welte74368cc2011-02-09 21:41:36 +0100102 NatureIsup = nature_map2isup(NatureMap),
103 #party_number{nature_of_addr_ind = NatureIsup,
104 numbering_plan = Numplan,
105 phone_number = PhoneNum}.
106
107encode_addr_string(#party_number{nature_of_addr_ind = NatureIsup,
108 numbering_plan = Numplan,
109 phone_number = PhoneNum}) ->
110 NatureMap = nature_isup2map(NatureIsup),
Harald Welte5b146412011-02-10 17:57:09 +0100111 PhoneBin = encode_map_addr(PhoneNum),
Harald Weltefc281c32011-02-09 22:39:08 +0100112 Bin = <<1:1, NatureMap:3, Numplan:4, PhoneBin/binary>>,
113 binary_to_list(Bin).
Harald Welte268c5722011-02-09 14:38:15 +0100114
115parse_tcap_msg(MsgBin) when is_binary(MsgBin) ->
Harald Welted08ea8d2011-02-09 23:13:48 +0100116 Msg = binary_to_list(MsgBin),
117 parse_tcap_msg(Msg);
118parse_tcap_msg(Msg) when is_list(Msg) ->
119 case asn1rt:decode('map', 'MapSpecificPDUs', Msg) of
Harald Welte268c5722011-02-09 14:38:15 +0100120 {ok, {Type, TcapMsgDec}} ->
Harald Welte21c6b942011-04-16 20:14:38 +0200121 fixup_dialogue({Type, TcapMsgDec});
Harald Welte268c5722011-02-09 14:38:15 +0100122 Error ->
123 Error
124 end.
125
Harald Welte21c6b942011-04-16 20:14:38 +0200126% Extract the dialoguePortion and feed it through external_1990ify/1
127fixup_dialogue({'begin', Beg = #'MapSpecificPDUs_begin'{dialoguePortion=Dia}}) ->
128 {'begin', Beg#'MapSpecificPDUs_begin'{dialoguePortion = external_1990ify(Dia)}};
129fixup_dialogue({'end', Beg = #'MapSpecificPDUs_end'{dialoguePortion=Dia}}) ->
130 {'end', Beg#'MapSpecificPDUs_end'{dialoguePortion = external_1990ify(Dia)}};
131fixup_dialogue({'continue', Beg = #'MapSpecificPDUs_continue'{dialoguePortion=Dia}}) ->
132 {'continue', Beg#'MapSpecificPDUs_continue'{dialoguePortion = external_1990ify(Dia)}};
133fixup_dialogue({'unidirectional', Beg = #'MapSpecificPDUs_unidirectional'{dialoguePortion=Dia}}) ->
134 {'unidirectional', Beg#'MapSpecificPDUs_unidirectional'{dialoguePortion = external_1990ify(Dia)}};
135fixup_dialogue(Default) ->
136 Default.
137
138% Take the EXTERNAL date type and convert from 1994-style to 1990 with 'single-ASN1-type'
139external_1990ify({'EXTERNAL', {syntax, DirRef}, IndirRef, Data}) when is_list(Data); is_binary(Data) ->
140 #'EXTERNAL'{'direct-reference' = DirRef,
141 'indirect-reference' = IndirRef,
142 encoding = {'single-ASN1-type', Data}};
143external_1990ify(Default) ->
144 Default.
145
Harald Welte0aa140b2011-02-09 23:15:22 +0100146encode_tcap_msg({Type, TcapMsgDec}) ->
147 case asn1rt:encode('map', 'MapSpecificPDUs', {Type, TcapMsgDec}) of
Harald Welted08ea8d2011-02-09 23:13:48 +0100148 {ok, List} ->
149 list_to_binary(List);
150 Error ->
151 Error
152 end.