blob: 7de068b723c18581a7cf17cc6d3b00fac8764648 [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
46format_id(undefined) ->
47 asn1_NOVALUE;
48format_id(Int) when is_integer(Int) ->
49 {present, Int}.
50
51process_uint32(Int) when is_integer(Int) ->
52 <<Int:32/big>>;
53process_uint32(Int) when is_list(Int); is_binary(Int) ->
54 Int.
55
56process_undefined(undefined) ->
57 asn1_NOVALUE;
58process_undefined(Other) ->
59 Other.
60
61
62% build a decoded Invoke component
63build_inv_comp(InvIdIn, Opcode, Argument, LinkedIdIn) ->
64 InvId = format_id(InvIdIn),
65 LinkedId = format_id(LinkedIdIn),
66 {invoke, #'Invoke'{invokeId = InvId, linkedId = LinkedId,
67 opcode = {local, Opcode},
68 argument = Argument}}.
69build_inv_comp(InvIdIn, Opcode, Argument) ->
70 build_inv_comp(InvIdIn, Opcode, Argument, undefined).
71
72% build a BER-encoded ReturnResult component
73build_retres_comp(InvIdIn, Data) ->
74 InvId = format_id(InvIdIn),
75 {resurnResult, #'ReturnResult'{invokeId = InvId, result = Data}}.
76
77% build a BER-encoded ReturnResultLast component
78build_retreslast_comp(InvIdIn, Data) ->
79 InvId = format_id(InvIdIn),
80 {returnResultLast, #'ReturnResult'{invokeId = InvId, result = Data}}.
81build_retreslast_comp(InvIdIn) ->
82 build_retreslast_comp(InvIdIn, asn1_NOVALUE).
83
84% helper function for BER encoding a Component
85enc_component(Comp) ->
86 {ok, Ret} = tcap_asn:encode('Component', Comp),
87 Ret.
88
89% helper function for BER-encoding the DialoguePDU and wrapping it in 'EXTERNAL' type
90enc_dialg_ext(Dpdu) ->
91 {ok, DpduEnc} = tcap_asn:encode('DialoguePDU', Dpdu),
92 ExtPdu = #'EXTERNAL'{'direct-reference' = {0,0,17,773,1,1,1},
93 'encoding' = {'single-ASN1-type', DpduEnc}},
94 ExtPdu.
95
96% Build a binary-encoded 'Begin' DialoguePortion message with specified components
97build_begin(OtidIn, ACname, ComponentsIn) ->
98 build_begin(OtidIn, ACname, asn1_NOVALUE, ComponentsIn).
99build_begin(OtidIn, ACname, UserDlgInfoIn, ComponentsIn) ->
100 Otid = process_uint32(OtidIn),
101 UserDlgInfo = process_undefined(UserDlgInfoIn),
102 Dpdu = {dialogueRequest, #'AARQ-apdu'{'protocol-version' = [version1],
103 'application-context-name' = ACname,
104 'user-information' = UserDlgInfo}},
105 ExtPdu = enc_dialg_ext(Dpdu),
106 {ok, EncComponents} = tcap_asn:encode('Components', ComponentsIn),
107 Msg={'begin', #'Begin'{otid = Otid, dialoguePortion = ExtPdu, components = EncComponents}},
108 enc_msg(Msg).
109
110% Build a binary-encoded 'End' DialoguePortion message with specified components
111build_end(DtidIn, ACname, ComponentsIn) ->
112 Dtid = process_uint32(DtidIn),
113 Dpdu = {dialogueResponse, #'AARE-apdu'{'protocol-version' = [version1],
114 'application-context-name' = ACname,
115 'result' = 0}},
116 ExtPdu = enc_dialg_ext(Dpdu),
117 {ok, EncComponents} = tcap_asn:encode('Components', ComponentsIn),
118 Msg = {'end', #'End'{dtid = Dtid, dialoguePortion = ExtPdu, components = EncComponents}},
119 enc_msg(Msg).
120
121
122enc_msg(Dlg) ->
123 {ok, Ret} = tcap_asn:encode('TCMessage', Dlg),
124 Ret.
125
126
127% build a BER-encoded Begin dialogue with Invoke component
128build_inv_begin(DlgId, InvId, ACname, Opcode, Argument) ->
129 C = build_inv_comp(InvId, Opcode, Argument),
130 build_begin(DlgId, ACname, [C]).
131
132% build a BER-encoded End dialogue with ReturnResultLast component
133build_retresl_end(Dtid, InvId, ACname, Argument) ->
134 C = build_retreslast_comp(InvId, Argument),
135 build_end(Dtid, ACname, [C]).