blob: 025808f9f3a43262a8f6851d0808a6166112f00f [file] [log] [blame]
Harald Welte50a44c22011-01-15 21:39:20 +01001% ITU-T Q.76x ISUPcoding / decoding
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(isup_codec).
21-author('Harald Welte <laforge@gnumonks.org>').
22-include("isup.hrl").
23
24-export([parse_isup_msg/1, encode_isup_msg/1]).
25
26% References to 'Tabe C-xxx' are to Annex C of Q.767
27
28% Default case: no fixed and no variable parts, only options
29% ANM, RLC, FOT
30parse_isup_msgt(M, Bin) when
31 M == ?ISUP_MSGT_ANM;
32 M == ?ISUP_MSGT_RLC;
33 M == ?ISUP_MSGT_FOT;
34 parse_isup_opts(Bin);
35% Table C-5 Address complete
36parse_isup_msgt(?ISUP_MSGT_ACM, Bin) ->
37 <<BackCallInd:16, Remain/binary>> = Bin,
38 BciOpt = {backward_call_ind, BackCallInd},
39 Opts = parse_isup_opts(Remain)
40 [BciOpt|Opts];
41% Table C-7 Call progress
42parse_isup_msgt(?ISUP_MSGT_CPG, Bin) ->
43 <<EventInf:8, Remain/binary>> = Bin,
44 BciOpt = {event_info, EventInf},
45 Opts = parse_isup_opts(Remain)
46 [BciOpt|Opts];
47% Table C-9 Circuit group reset acknowledgement
48parse_isup_msgt(?ISUP_MSGT_GRA, Bin) ->
49 % V: Range and status
50
51% Table C-11 Connect
52parse_isup_msgt(?ISUP_MSGT_CON, Bin) ->
53 <<BackCallInd:16, Remain/binary>> = Bin,
54 BciOpt = {backward_call_ind, BackCallInd},
55 Opts = parse_isup_opts(Remain)
56 [BciOpt|Opts];
57% Table C-12 Continuity
58parse_isup_msgt(?ISUP_MSGT_COT, Bin) ->
59 <<ContInd:8>> = Bin,
60 [{continuity_ind, ContInd}];
61% Table C-16 Initial address
62parse_isup_msgt(?ISUP_MSGT_IAM, Bin) ->
63 <<CINat:8, FwCallInd:16/big, CallingCat:8, TransmReq:8, VarAndOpt/binary>> = Bin,
64 FixedOpts = [{conn_ind_nature, CINat}, {fw_call_ind, FwCallInd}, {calling_cat, CallingCat},
65 {transm_medium_req, TransmReq}],
66 % V: Called Party Number
67 VarOpts = FIXME;
68 Opts = parse_isup_opts(Remain),
69 [FixedOpts,VarOpts,Opts];
70% Table C-17 Release
71parse_isup_msgt(?ISUP_MSGT_REL, Bin) ->
72 % V: Cause indicators
73 VarOpts = FIXME;
74 Opts = parse_isup_opts(Remain),
75 [VarOpts,Opts];
76% Table C-19 Subsequent address
77parse_isup_msgt(?ISUP_MSGT_SAM, Bin) ->
78 % V: Subsequent number
79 VarOpts = FIXME;
80 Opts = parse_isup_opts(Remain),
81 [VarOpts,Opts];
82% Table C-21 Suspend, Resume
83parse_isup_msgt(Msgt, Bin) when Msgt == ?ISUP_MSGT_RES or Msgt == ?ISUP_MSGT_SUS ->
84 <<SuspResInd:8, Remain/binary>> = Bin,
85 FixedOpts = [{susp_res_ind, SuspResInd}],
86 Opts = parse_isup_opts(Remain),
87 [FixedOpts|Opts];
88% Table C-23
89parse_isup_msgt(M, <<>>) when
90 M == ?ISUP_MSGT_BLO;
91 M == ?ISUP_MSGT_BLA;
92 M == ?ISUP_MSGT_CCR;
93 M == ?ISUP_MSGT_RSC;
94 M == ?ISUP_MSGT_UBL;
95 M == ?ISUP_MSGT_UBA ->
96 [].
97% Table C-25
98parse_isup_msgt(M, Bin) when
99 M == ?ISUP_MSGT_CGB;
100 M == ?ISUP_MSGT_CGBA;
101 M == ISUP_MSGT_CGU;
102 M == ISUP_MSGT_CGUA ->
103 <<CGMsgt:8, VarBin/binary>> = Bin,
104 FixedOpts = [{cg_supv_msgt, CGMsgt}],
105 % V: Range and status
106 VarOpts = FIXME,
107 [FixedOpts|VarOpts];
108% Table C-26 Circuit group reset
109parse_isup_msgt(?ISUP_MSGT_GRS, Bin) ->
110 % V: Range without status
111 VarOpts = FIXME,
112 VarOpts.
113
114
115parse_isup_msg(Databin) when is_binary(DataBin) ->
116 <<0:4, Cic:12/big, MsgType:8, Remain/binary>> = DataBin,
117 Opts = parse_isup_msgt(MsgType, Remain),
118 #isup_msg{cic = Cic, msg_type = MsgType, parameters = Opts}.