Add some unfinished ISUP decoder routines

This commit is contained in:
Harald Welte 2011-01-15 21:39:20 +01:00
parent 1fbcd1c88b
commit 50a44c25e2
2 changed files with 171 additions and 0 deletions

53
src/isup.hrl Normal file
View File

@ -0,0 +1,53 @@
% Table 1 / Q.762 - ISDN user part message acronyms
-define(ISUP_MSGT_ACM). % Address complete
-define(ISUP_MSGT_ANM). % Answer
-define(ISUP_MSGT_APM). % Application transport
-define(ISUP_MSGT_BLA). % Blocking acknowledgement
-define(ISUP_MSGT_BLO). % Blocking
-define(ISUP_MSGT_CCR). % Continuity check request
-define(ISUP_MSGT_CFN). % Confusion
-define(ISUP_MSGT_CGB). % Circuit group blocking
-define(ISUP_MSGT_CGBA).% Circuit group blocking acknowledgement
-define(ISUP_MSGT_CGU). % Circuit group unblocking
-define(ISUP_MSGT_CGUA).% Circuit group unblocking acknowledgement
-define(ISUP_MSGT_CON). % Connect
-define(ISUP_MSGT_COT). % Continuity
-define(ISUP_MSGT_CPG). % Call progress
-define(ISUP_MSGT_CRG). % Charge information
-define(ISUP_MSGT_CQM). % Circuit group query
-define(ISUP_MSGT_CQR). % Circuit group query response
-define(ISUP_MSGT_DRS). % Delayed release (reserved used in 1988 version)
-define(ISUP_MSGT_FAA). % Facility accepted
-define(ISUP_MSGT_FAC). % Facility
-define(ISUP_MSGT_FAR). % Facility request
-define(ISUP_MSGT_FOT). % Forward transfer
-define(ISUP_MSGT_FRJ). % Facility reject
-define(ISUP_MSGT_GRA). % Circuit group reset acknowledgement
-define(ISUP_MSGT_GRS). % Circuit group reset
-define(ISUP_MSGT_IAM). % Initial address
-define(ISUP_MSGT_IDR). % Identification request
-define(ISUP_MSGT_IRS). % Identification response
-define(ISUP_MSGT_INF). % Information
-define(ISUP_MSGT_INR). % Information request
-define(ISUP_MSGT_LPA). % Loop back acknowledgement
-define(ISUP_MSGT_LOP). % Loop prevention
-define(ISUP_MSGT_NRM). % Network resource management
-define(ISUP_MSGT_OLM). % Overload
-define(ISUP_MSGT_PAM). % Pass-along
-define(ISUP_MSGT_PRI). % Pre-release information
-define(ISUP_MSGT_REL). % Release
-define(ISUP_MSGT_RES). % Resume
-define(ISUP_MSGT_RLC). % Release complete
-define(ISUP_MSGT_RSC). % Reset circuit
-define(ISUP_MSGT_SAM). % Subsequent address
-define(ISUP_MSGT_SDM). % Subsequent directory number
-define(ISUP_MSGT_SGM). % Segmentation
-define(ISUP_MSGT_SUS). % Suspend
-define(ISUP_MSGT_UBL). % Unblocking
-define(ISUP_MSGT_UBA). % Unblocking acknowledgement
-define(ISUP_MSGT_UCIC).% Unequipped circuit identification code
-define(ISUP_MSGT_UPA). % User part available
-define(ISUP_MSGT_UPT). % User part test
-define(ISUP_MSGT_USR). % User-to-user information

118
src/isup_codec.erl Normal file
View File

@ -0,0 +1,118 @@
% ITU-T Q.76x ISUPcoding / decoding
% (C) 2011 by Harald Welte <laforge@gnumonks.org>
%
% All Rights Reserved
%
% This program is free software; you can redistribute it and/or modify
% it under the terms of the GNU Affero General Public License as
% published by the Free Software Foundation; either version 3 of the
% License, or (at your option) any later version.
%
% This program is distributed in the hope that it will be useful,
% but WITHOUT ANY WARRANTY; without even the implied warranty of
% MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
% GNU General Public License for more details.
%
% You should have received a copy of the GNU Affero General Public License
% along with this program. If not, see <http://www.gnu.org/licenses/>.
-module(isup_codec).
-author('Harald Welte <laforge@gnumonks.org>').
-include("isup.hrl").
-export([parse_isup_msg/1, encode_isup_msg/1]).
% References to 'Tabe C-xxx' are to Annex C of Q.767
% Default case: no fixed and no variable parts, only options
% ANM, RLC, FOT
parse_isup_msgt(M, Bin) when
M == ?ISUP_MSGT_ANM;
M == ?ISUP_MSGT_RLC;
M == ?ISUP_MSGT_FOT;
parse_isup_opts(Bin);
% Table C-5 Address complete
parse_isup_msgt(?ISUP_MSGT_ACM, Bin) ->
<<BackCallInd:16, Remain/binary>> = Bin,
BciOpt = {backward_call_ind, BackCallInd},
Opts = parse_isup_opts(Remain)
[BciOpt|Opts];
% Table C-7 Call progress
parse_isup_msgt(?ISUP_MSGT_CPG, Bin) ->
<<EventInf:8, Remain/binary>> = Bin,
BciOpt = {event_info, EventInf},
Opts = parse_isup_opts(Remain)
[BciOpt|Opts];
% Table C-9 Circuit group reset acknowledgement
parse_isup_msgt(?ISUP_MSGT_GRA, Bin) ->
% V: Range and status
% Table C-11 Connect
parse_isup_msgt(?ISUP_MSGT_CON, Bin) ->
<<BackCallInd:16, Remain/binary>> = Bin,
BciOpt = {backward_call_ind, BackCallInd},
Opts = parse_isup_opts(Remain)
[BciOpt|Opts];
% Table C-12 Continuity
parse_isup_msgt(?ISUP_MSGT_COT, Bin) ->
<<ContInd:8>> = Bin,
[{continuity_ind, ContInd}];
% Table C-16 Initial address
parse_isup_msgt(?ISUP_MSGT_IAM, Bin) ->
<<CINat:8, FwCallInd:16/big, CallingCat:8, TransmReq:8, VarAndOpt/binary>> = Bin,
FixedOpts = [{conn_ind_nature, CINat}, {fw_call_ind, FwCallInd}, {calling_cat, CallingCat},
{transm_medium_req, TransmReq}],
% V: Called Party Number
VarOpts = FIXME;
Opts = parse_isup_opts(Remain),
[FixedOpts,VarOpts,Opts];
% Table C-17 Release
parse_isup_msgt(?ISUP_MSGT_REL, Bin) ->
% V: Cause indicators
VarOpts = FIXME;
Opts = parse_isup_opts(Remain),
[VarOpts,Opts];
% Table C-19 Subsequent address
parse_isup_msgt(?ISUP_MSGT_SAM, Bin) ->
% V: Subsequent number
VarOpts = FIXME;
Opts = parse_isup_opts(Remain),
[VarOpts,Opts];
% Table C-21 Suspend, Resume
parse_isup_msgt(Msgt, Bin) when Msgt == ?ISUP_MSGT_RES or Msgt == ?ISUP_MSGT_SUS ->
<<SuspResInd:8, Remain/binary>> = Bin,
FixedOpts = [{susp_res_ind, SuspResInd}],
Opts = parse_isup_opts(Remain),
[FixedOpts|Opts];
% Table C-23
parse_isup_msgt(M, <<>>) when
M == ?ISUP_MSGT_BLO;
M == ?ISUP_MSGT_BLA;
M == ?ISUP_MSGT_CCR;
M == ?ISUP_MSGT_RSC;
M == ?ISUP_MSGT_UBL;
M == ?ISUP_MSGT_UBA ->
[].
% Table C-25
parse_isup_msgt(M, Bin) when
M == ?ISUP_MSGT_CGB;
M == ?ISUP_MSGT_CGBA;
M == ISUP_MSGT_CGU;
M == ISUP_MSGT_CGUA ->
<<CGMsgt:8, VarBin/binary>> = Bin,
FixedOpts = [{cg_supv_msgt, CGMsgt}],
% V: Range and status
VarOpts = FIXME,
[FixedOpts|VarOpts];
% Table C-26 Circuit group reset
parse_isup_msgt(?ISUP_MSGT_GRS, Bin) ->
% V: Range without status
VarOpts = FIXME,
VarOpts.
parse_isup_msg(Databin) when is_binary(DataBin) ->
<<0:4, Cic:12/big, MsgType:8, Remain/binary>> = DataBin,
Opts = parse_isup_msgt(MsgType, Remain),
#isup_msg{cic = Cic, msg_type = MsgType, parameters = Opts}.