~ubuntu-branches/debian/squeeze/erlang/squeeze

« back to all changes in this revision

Viewing changes to lib/asn1/test/h323test.erl

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2010-03-09 17:34:57 UTC
  • mfrom: (10.1.2 sid)
  • Revision ID: james.westby@ubuntu.com-20100309173457-4yd6hlcb2osfhx31
Tags: 1:13.b.4-dfsg-3
Manpages in section 1 are needed even if only arch-dependent packages are
built. So, re-enabled them.

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
%%
 
2
%% %CopyrightBegin%
 
3
%% 
 
4
%% Copyright Ericsson AB 1999-2009. All Rights Reserved.
 
5
%% 
 
6
%% The contents of this file are subject to the Erlang Public License,
 
7
%% Version 1.1, (the "License"); you may not use this file except in
 
8
%% compliance with the License. You should have received a copy of the
 
9
%% Erlang Public License along with this software. If not, it can be
 
10
%% retrieved online at http://www.erlang.org/.
 
11
%% 
 
12
%% Software distributed under the License is distributed on an "AS IS"
 
13
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
 
14
%% the License for the specific language governing rights and limitations
 
15
%% under the License.
 
16
%% 
 
17
%% %CopyrightEnd%
 
18
%%
 
19
%%
 
20
-module(h323test).
 
21
 
 
22
-compile(export_all).
 
23
-export([compile/3,run/1]).
 
24
-include("test_server.hrl").
 
25
 
 
26
compile(Config,Rules,Options) ->
 
27
    ?line DataDir = ?config(data_dir,Config),
 
28
    ?line OutDir = ?config(priv_dir,Config),
 
29
    ?line true = code:add_patha(?config(priv_dir,Config)),
 
30
    ?line ok = asn1ct:compile(DataDir ++ "H235-SECURITY-MESSAGES",[Rules,{outdir,OutDir}]++Options),
 
31
    ?line ok = asn1ct:compile(DataDir ++ "H323-MESSAGES",[Rules,{outdir,OutDir}]++Options),
 
32
    ?line ok = asn1ct:compile(DataDir ++ "MULTIMEDIA-SYSTEM-CONTROL",[Rules,{outdir,OutDir}]++Options).
 
33
    
 
34
run(per_bin) ->
 
35
    run();
 
36
run(per) ->
 
37
    run();
 
38
run(_Rules) -> 
 
39
    ok.
 
40
 
 
41
run() ->
 
42
    ?line alerting(),
 
43
    ?line connect(),
 
44
    ok.
 
45
 
 
46
arq() ->
 
47
    _AdmissionRequest = "27900007086000340036003300320038003700370101805337010180533600AC1F38C60693000D000445367AE75C5740120300AC1F38C6415004E0200100110000D7D22EA88D511C0200AC1F38C6C0580100".
 
48
 
 
49
 
 
50
t0() ->
 
51
    Setup = "00B8060008914A0001010180533622C000000000074572696373736F6E0356302E3100010180533700AC1F38C206B80045367AE75C5740120300AC1F38C6415000411C110000D7D22EA88D511C0200AC1F3806C0583802150000080E1403001E80800A04000100AC1F38C661A820400000060401004E1403001E80801114000100AC1F38C72EE000AC1F38C72EE00100010063AA34AB"
 
52
,
 
53
    ByteList = hexstr2bytes(Setup),
 
54
    asn1_wrapper:decode('H323-MESSAGES','H323-UU-PDU',ByteList).
 
55
 
 
56
t1() ->
 
57
    AdmissionRequest = "27900007086000340036003300320038003700370101805337010180533600AC1F38C60693000D000445367AE75C5740120300AC1F38C6415004E0200100110000D7D22EA88D511C0200AC1F38C6C0580100",
 
58
    ByteList = hexstr2bytes(AdmissionRequest),
 
59
    asn1_wrapper:decode('H323-MESSAGES','RasMessage',ByteList).
 
60
 
 
61
t2() ->
 
62
    Cs = "080200040504038090A56C059132303033700591323030347E00930500B8060008914A0001010180533622C000000000074572696373736F6E0356302E3100010180533700AC1F38C206B80045367AE75C5740120300AC1F38C6415000411C110000D7D22EA88D511C0200AC1F3806C0583802150000080E1403001E80800A04000100AC1F38C661A820400000060401004E1403001E80801114000100AC1F38C72EE000AC1F38C72EE00100010063AA34AB",
 
63
    ByteList = hexstr2bytes(Cs),
 
64
    asn1_wrapper:decode('H323-MESSAGES','H323-UU-PDU',ByteList).
 
65
 
 
66
t3() ->
 
67
    Cs = "10b8060008914a0002044003004d0067006f006e018085cc22c0b500534c164d6963726f736f6674ae204e65744d656574696e67ae0003332e3000000101808c990088e1293a06b8001689edc5bf23d3118c2d00c04f4b1cd0000c07000a00000204dc40b500534c3c0200000028000000000000001b0000008138427484ccd211b4e300a0c90d0660100000001289edc5bf23d3118c2d00c04f4b1cd00000000000000000a615d9ee",
 
68
    ByteList = hexstr2bytes(Cs),
 
69
    asn1_wrapper:decode('H323-MESSAGES','H323-UU-PDU',ByteList).
 
70
    
 
71
dec_alerting() ->
 
72
    Cs = "0380060008914a0002020120110000000000000000000000000000000000",
 
73
    _Slask="E83AE983",
 
74
    ByteList = hexstr2bytes(Cs),
 
75
    asn1_wrapper:decode('H323-MESSAGES','H323-UserInformation',ByteList).
 
76
 
 
77
enc_alerting(V) ->
 
78
    asn1_wrapper:encode('H323-MESSAGES','H323-UserInformation',V).
 
79
 
 
80
alerting() ->
 
81
    ?line {ok,V} = dec_alerting(),
 
82
    ?line {ok,B} = enc_alerting(V),
 
83
    ?line ByteList = lists:flatten(B),
 
84
    ?line {ok,V} = asn1_wrapper:decode('H323-MESSAGES','H323-UserInformation',ByteList).
 
85
 
 
86
 
 
87
dec_connect() ->
 
88
    Cs = "02c0060008914a00020088e1293a04a322c0b500534c164d6963726f736f6674ae204e65744d656474696e67ae0003332e3000001689edc5bf23d3118c2d00c04f4b1cd00900110000000000000000000000000000000000",
 
89
    _Slask="2f530a3f",
 
90
    ByteList = hexstr2bytes(Cs),
 
91
    asn1_wrapper:decode('H323-MESSAGES','H323-UserInformation',ByteList).
 
92
    
 
93
enc_connect(V) ->
 
94
    asn1_wrapper:encode('H323-MESSAGES','H323-UserInformation',V).
 
95
 
 
96
connect() ->
 
97
    ?line {ok,V} = dec_connect(),
 
98
    ?line {ok,B} = enc_connect(V),
 
99
    ?line ByteList = lists:flatten(B),
 
100
    ?line {ok,V} = asn1_wrapper:decode('H323-MESSAGES','H323-UserInformation',ByteList).
 
101
 
 
102
dec_h245_TCS() ->
 
103
    Cs ="02700106000881750003" 
 
104
        "800d00003c000100000100000100000e"
 
105
        "807fff04b5428080010180000e483060"
 
106
        "0100800c96a88000002020b500534c48"
 
107
        "020000000000f4010000f40101000400"
 
108
        "0000000002000100401f000000100000"
 
109
        "000104002000f4010700000100000002"
 
110
        "00ff00000000c0004000f0000000cc01"
 
111
        "30ff880118ff00008000012040b38000"
 
112
        "0220c0b38000032020b500534c280200"
 
113
        "00000000a0000000a000040010000000"
 
114
        "000070000100401f0000580200000c00"
 
115
        "1000000000008000042020b500534c28"
 
116
        "020000000000a0000000a00004001000"
 
117
        "0000000071000100401f00003a070000"
 
118
        "25001000000000008000052020b50053"
 
119
        "4c280200000000008000000080000500"
 
120
        "14000000000072000100401f00000809"
 
121
        "000025001000000000008000062020b5"
 
122
        "00534c28020000000000800000008000"
 
123
        "050014000000000073000100401f0000"
 
124
        "7f0a00002b0010000000000080000722"
 
125
        "000b40000909a00120390c000a099001"
 
126
        "20390c000b09880120390c000c08a220"
 
127
        "3940000d089220390004800602070007"
 
128
        "00060004000500020001000000030000"
 
129
        "0a00000e800702070007000600040005"
 
130
        "000200010000000300000900000e8008"
 
131
        "02070007000600040005000200010000"
 
132
        "000300000c00000e8009020700070006"
 
133
        "00040005000200010000000300000b00"
 
134
        "000e800a020700070006000400050002"
 
135
        "00010000000300000d00000e0300000b"
 
136
        "01003280299d93369631bc",
 
137
    ByteList = hexstr2bytes(Cs),
 
138
    asn1_wrapper:decode('MULTIMEDIA-SYSTEM-CONTROL',
 
139
                  'MultimediaSystemControlMessage',ByteList).
 
140
 
 
141
        hexstr2bytes([D1,D2|T]) ->
 
142
    [dig2num(D1)*16+dig2num(D2)|hexstr2bytes(T)];
 
143
hexstr2bytes([]) ->
 
144
    [].
 
145
 
 
146
dig2num(D) when D >= $0, D =< $9 ->
 
147
    D - $0;
 
148
dig2num(D) when D >= $a, D =< $f ->
 
149
    10 + D - $a;
 
150
dig2num(D) when D >= $A, D =< $F ->
 
151
    10 + D - $A.
 
152
 
 
153
bytes2hexstr(Bytes) ->
 
154
    bytes2hexstr(Bytes,[]).
 
155
 
 
156
bytes2hexstr([B|Bytes],Acc) ->
 
157
    D1 = num2dig(B bsr 4),
 
158
    D2 = num2dig(B band 15),
 
159
    bytes2hexstr(Bytes,[D2,D1|Acc]);
 
160
bytes2hexstr([],Acc) ->
 
161
    lists:reverse(Acc).
 
162
 
 
163
num2dig(Num) when Num =< 9 ->
 
164
    $0 + Num;
 
165
num2dig(Num) ->
 
166
    $a + Num - 10.
 
167
                  
 
168
 
 
169
 
 
170
 
 
171
 
 
172