blob: eb4051931d962afd7db387e43594c26bf5408079 [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/>.
19
20-module(tcap_helper).
21-author('Harald Welte <laforge@gnumonks.org>').
22
23-include("tcap_asn.hrl").
24
25-export([build_inv_comp/3, build_inv_comp/4,
26 build_retres_comp/2, build_retreslast_comp/2, build_retreslast_comp/1,
27 enc_component/1,
28 build_begin/4, build_begin/3, build_end/3,
29 build_inv_begin/5, build_retresl_end/4
30 ]).
31
32format_id(undefined) ->
33 asn1_NOVALUE;
34format_id(Int) when is_integer(Int) ->
35 {present, Int}.
36
37process_uint32(Int) when is_integer(Int) ->
38 <<Int:32/big>>;
39process_uint32(Int) when is_list(Int); is_binary(Int) ->
40 Int.
41
42process_undefined(undefined) ->
43 asn1_NOVALUE;
44process_undefined(Other) ->
45 Other.
46
47
48% build a decoded Invoke component
49build_inv_comp(InvIdIn, Opcode, Argument, LinkedIdIn) ->
50 InvId = format_id(InvIdIn),
51 LinkedId = format_id(LinkedIdIn),
52 {invoke, #'Invoke'{invokeId = InvId, linkedId = LinkedId,
53 opcode = {local, Opcode},
54 argument = Argument}}.
55build_inv_comp(InvIdIn, Opcode, Argument) ->
56 build_inv_comp(InvIdIn, Opcode, Argument, undefined).
57
58% build a BER-encoded ReturnResult component
59build_retres_comp(InvIdIn, Data) ->
60 InvId = format_id(InvIdIn),
61 {resurnResult, #'ReturnResult'{invokeId = InvId, result = Data}}.
62
63% build a BER-encoded ReturnResultLast component
64build_retreslast_comp(InvIdIn, Data) ->
65 InvId = format_id(InvIdIn),
66 {returnResultLast, #'ReturnResult'{invokeId = InvId, result = Data}}.
67build_retreslast_comp(InvIdIn) ->
68 build_retreslast_comp(InvIdIn, asn1_NOVALUE).
69
70% helper function for BER encoding a Component
71enc_component(Comp) ->
72 {ok, Ret} = tcap_asn:encode('Component', Comp),
73 Ret.
74
75% helper function for BER-encoding the DialoguePDU and wrapping it in 'EXTERNAL' type
76enc_dialg_ext(Dpdu) ->
77 {ok, DpduEnc} = tcap_asn:encode('DialoguePDU', Dpdu),
78 ExtPdu = #'EXTERNAL'{'direct-reference' = {0,0,17,773,1,1,1},
79 'encoding' = {'single-ASN1-type', DpduEnc}},
80 ExtPdu.
81
82% Build a binary-encoded 'Begin' DialoguePortion message with specified components
83build_begin(OtidIn, ACname, ComponentsIn) ->
84 build_begin(OtidIn, ACname, asn1_NOVALUE, ComponentsIn).
85build_begin(OtidIn, ACname, UserDlgInfoIn, ComponentsIn) ->
86 Otid = process_uint32(OtidIn),
87 UserDlgInfo = process_undefined(UserDlgInfoIn),
88 Dpdu = {dialogueRequest, #'AARQ-apdu'{'protocol-version' = [version1],
89 'application-context-name' = ACname,
90 'user-information' = UserDlgInfo}},
91 ExtPdu = enc_dialg_ext(Dpdu),
92 {ok, EncComponents} = tcap_asn:encode('Components', ComponentsIn),
93 Msg={'begin', #'Begin'{otid = Otid, dialoguePortion = ExtPdu, components = EncComponents}},
94 enc_msg(Msg).
95
96% Build a binary-encoded 'End' DialoguePortion message with specified components
97build_end(DtidIn, ACname, ComponentsIn) ->
98 Dtid = process_uint32(DtidIn),
99 Dpdu = {dialogueResponse, #'AARE-apdu'{'protocol-version' = [version1],
100 'application-context-name' = ACname,
101 'result' = 0}},
102 ExtPdu = enc_dialg_ext(Dpdu),
103 {ok, EncComponents} = tcap_asn:encode('Components', ComponentsIn),
104 Msg = {'end', #'End'{dtid = Dtid, dialoguePortion = ExtPdu, components = EncComponents}},
105 enc_msg(Msg).
106
107
108enc_msg(Dlg) ->
109 {ok, Ret} = tcap_asn:encode('TCMessage', Dlg),
110 Ret.
111
112
113% build a BER-encoded Begin dialogue with Invoke component
114build_inv_begin(DlgId, InvId, ACname, Opcode, Argument) ->
115 C = build_inv_comp(InvId, Opcode, Argument),
116 build_begin(DlgId, ACname, [C]).
117
118% build a BER-encoded End dialogue with ReturnResultLast component
119build_retresl_end(Dtid, InvId, ACname, Argument) ->
120 C = build_retreslast_comp(InvId, Argument),
121 build_end(Dtid, ACname, [C]).