blob: 805289569bc1207d4243240bd7d9682a5592c2cb [file] [log] [blame]
Harald Weltee16d8142011-12-10 21:40:35 +01001% TCAP codec helper functions for test scripts and the like
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/>.
Harald Welteef30ca82012-04-16 13:14:53 +020019%
20% Additional Permission under GNU AGPL version 3 section 7:
21%
22% If you modify this Program, or any covered work, by linking or
23% combining it with runtime libraries of Erlang/OTP as released by
24% Ericsson on http://www.erlang.org (or a modified version of these
25% libraries), containing parts covered by the terms of the Erlang Public
26% License (http://www.erlang.org/EPLICENSE), the licensors of this
27% Program grant you additional permission to convey the resulting work
28% without the need to license the runtime libraries of Erlang/OTP under
29% the GNU Affero General Public License. Corresponding Source for a
30% non-source form of such a combination shall include the source code
31% for the parts of the runtime libraries of Erlang/OTP used as well as
32% that of the covered work.
Harald Weltee16d8142011-12-10 21:40:35 +010033
34-module(tcap_helper).
35-author('Harald Welte <laforge@gnumonks.org>').
36
37-include("tcap_asn.hrl").
38
39-export([build_inv_comp/3, build_inv_comp/4,
40 build_retres_comp/2, build_retreslast_comp/2, build_retreslast_comp/1,
41 enc_component/1,
42 build_begin/4, build_begin/3, build_end/3,
43 build_inv_begin/5, build_retresl_end/4
44 ]).
45
Harald Welte6deda592012-05-28 23:58:42 +020046-export([get_tcap_components/1, get_tcap_operation/1, get_tcap_operations/1,
47 check_for_tcap_op/3]).
48
Harald Weltee16d8142011-12-10 21:40:35 +010049format_id(undefined) ->
50 asn1_NOVALUE;
51format_id(Int) when is_integer(Int) ->
52 {present, Int}.
53
54process_uint32(Int) when is_integer(Int) ->
55 <<Int:32/big>>;
56process_uint32(Int) when is_list(Int); is_binary(Int) ->
57 Int.
58
59process_undefined(undefined) ->
60 asn1_NOVALUE;
61process_undefined(Other) ->
62 Other.
63
64
65% build a decoded Invoke component
66build_inv_comp(InvIdIn, Opcode, Argument, LinkedIdIn) ->
67 InvId = format_id(InvIdIn),
68 LinkedId = format_id(LinkedIdIn),
69 {invoke, #'Invoke'{invokeId = InvId, linkedId = LinkedId,
70 opcode = {local, Opcode},
71 argument = Argument}}.
72build_inv_comp(InvIdIn, Opcode, Argument) ->
73 build_inv_comp(InvIdIn, Opcode, Argument, undefined).
74
75% build a BER-encoded ReturnResult component
76build_retres_comp(InvIdIn, Data) ->
77 InvId = format_id(InvIdIn),
78 {resurnResult, #'ReturnResult'{invokeId = InvId, result = Data}}.
79
80% build a BER-encoded ReturnResultLast component
81build_retreslast_comp(InvIdIn, Data) ->
82 InvId = format_id(InvIdIn),
83 {returnResultLast, #'ReturnResult'{invokeId = InvId, result = Data}}.
84build_retreslast_comp(InvIdIn) ->
85 build_retreslast_comp(InvIdIn, asn1_NOVALUE).
86
87% helper function for BER encoding a Component
88enc_component(Comp) ->
89 {ok, Ret} = tcap_asn:encode('Component', Comp),
90 Ret.
91
92% helper function for BER-encoding the DialoguePDU and wrapping it in 'EXTERNAL' type
93enc_dialg_ext(Dpdu) ->
94 {ok, DpduEnc} = tcap_asn:encode('DialoguePDU', Dpdu),
95 ExtPdu = #'EXTERNAL'{'direct-reference' = {0,0,17,773,1,1,1},
96 'encoding' = {'single-ASN1-type', DpduEnc}},
97 ExtPdu.
98
99% Build a binary-encoded 'Begin' DialoguePortion message with specified components
100build_begin(OtidIn, ACname, ComponentsIn) ->
101 build_begin(OtidIn, ACname, asn1_NOVALUE, ComponentsIn).
102build_begin(OtidIn, ACname, UserDlgInfoIn, ComponentsIn) ->
103 Otid = process_uint32(OtidIn),
104 UserDlgInfo = process_undefined(UserDlgInfoIn),
105 Dpdu = {dialogueRequest, #'AARQ-apdu'{'protocol-version' = [version1],
106 'application-context-name' = ACname,
107 'user-information' = UserDlgInfo}},
108 ExtPdu = enc_dialg_ext(Dpdu),
109 {ok, EncComponents} = tcap_asn:encode('Components', ComponentsIn),
110 Msg={'begin', #'Begin'{otid = Otid, dialoguePortion = ExtPdu, components = EncComponents}},
111 enc_msg(Msg).
112
113% Build a binary-encoded 'End' DialoguePortion message with specified components
114build_end(DtidIn, ACname, ComponentsIn) ->
115 Dtid = process_uint32(DtidIn),
116 Dpdu = {dialogueResponse, #'AARE-apdu'{'protocol-version' = [version1],
117 'application-context-name' = ACname,
118 'result' = 0}},
119 ExtPdu = enc_dialg_ext(Dpdu),
120 {ok, EncComponents} = tcap_asn:encode('Components', ComponentsIn),
121 Msg = {'end', #'End'{dtid = Dtid, dialoguePortion = ExtPdu, components = EncComponents}},
122 enc_msg(Msg).
123
124
125enc_msg(Dlg) ->
126 {ok, Ret} = tcap_asn:encode('TCMessage', Dlg),
127 Ret.
128
129
130% build a BER-encoded Begin dialogue with Invoke component
131build_inv_begin(DlgId, InvId, ACname, Opcode, Argument) ->
132 C = build_inv_comp(InvId, Opcode, Argument),
133 build_begin(DlgId, ACname, [C]).
134
135% build a BER-encoded End dialogue with ReturnResultLast component
136build_retresl_end(Dtid, InvId, ACname, Argument) ->
137 C = build_retreslast_comp(InvId, Argument),
138 build_end(Dtid, ACname, [C]).
Harald Welte6deda592012-05-28 23:58:42 +0200139
140% get a list of components from the decoded TCAP+MAP nested record
141get_tcap_components({'begin', Beg}) ->
142 get_tcap_components(Beg);
143get_tcap_components({'end', Beg}) ->
144 get_tcap_components(Beg);
145get_tcap_components({'continue', Beg}) ->
146 get_tcap_components(Beg);
147% tcap_asn.erl
148get_tcap_components(#'Begin'{components=Comps}) ->
149 Comps;
150get_tcap_components(#'Continue'{components=Comps}) ->
151 Comps;
152get_tcap_components(#'End'{components=Comps}) ->
153 Comps;
154get_tcap_components(_) ->
155 [].
156
157% get the MAP operation of a specific component
158get_tcap_operation({basicROS, Rec}) ->
159 get_tcap_operation(Rec);
160get_tcap_operation({invoke, Rec}) ->
161 get_tcap_operation(Rec);
162get_tcap_operation({returnResult, Rec}) ->
163 get_tcap_operation(Rec);
164get_tcap_operation({returnResultNotLast, Rec}) ->
165 get_tcap_operation(Rec);
166get_tcap_operation(#'Invoke'{opcode=Op}) ->
167 {invoke, Op};
168get_tcap_operation(#'ReturnResult'{result=Res}) ->
169 {returnResult, Res#'ReturnResult_result'.opcode}.
170
171% get a list of the MAP operations inside the components of a MAP message
172get_tcap_operations(MapDec) ->
173 Comps = get_tcap_components(MapDec),
174 [get_tcap_operation(X) || X <- Comps].
175
176
177check_for_tcap_op(Comp, Op, MapDec) ->
178 MapOps = get_tcap_operations(MapDec),
179 % check for invoke of SRI-for-SM:
180 lists:member({Comp, Op}, MapOps).