~ubuntu-branches/ubuntu/trusty/erlang/trusty

« back to all changes in this revision

Viewing changes to lib/erl_interface/test/ei_decode_SUITE.erl

  • Committer: Bazaar Package Importer
  • Author(s): Clint Byrum
  • Date: 2011-05-05 15:48:43 UTC
  • mfrom: (3.5.13 sid)
  • Revision ID: james.westby@ubuntu.com-20110505154843-0om6ekzg6m7ugj27
Tags: 1:14.b.2-dfsg-3ubuntu1
* Merge from debian unstable.  Remaining changes:
  - Drop libwxgtk2.8-dev build dependency. Wx isn't in main, and not
    supposed to.
  - Drop erlang-wx binary.
  - Drop erlang-wx dependency from -megaco, -common-test, and -reltool, they
    do not really need wx. Also drop it from -debugger; the GUI needs wx,
    but it apparently has CLI bits as well, and is also needed by -megaco,
    so let's keep the package for now.
  - debian/patches/series: Do what I meant, and enable build-options.patch
    instead.
* Additional changes:
  - Drop erlang-wx from -et
* Dropped Changes:
  - patches/pcre-crash.patch: CVE-2008-2371: outer level option with
    alternatives caused crash. (Applied Upstream)
  - fix for ssl certificate verification in newSSL: 
    ssl_cacertfile_fix.patch (Applied Upstream)
  - debian/patches/series: Enable native.patch again, to get stripped beam
    files and reduce the package size again. (build-options is what
    actually accomplished this)
  - Remove build-options.patch on advice from upstream and because it caused
    odd build failures.

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
%%
 
2
%% %CopyrightBegin%
 
3
%%
 
4
%% Copyright Ericsson AB 2004-2011. 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
%%
 
21
-module(ei_decode_SUITE).
 
22
 
 
23
-include_lib("test_server/include/test_server.hrl").
 
24
-include("ei_decode_SUITE_data/ei_decode_test_cases.hrl").
 
25
 
 
26
-export(
 
27
   [
 
28
    all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1, 
 
29
    init_per_group/2,end_per_group/2,
 
30
    test_ei_decode_long/1,
 
31
    test_ei_decode_ulong/1,
 
32
    test_ei_decode_longlong/1,
 
33
    test_ei_decode_ulonglong/1,
 
34
    test_ei_decode_char/1,
 
35
    test_ei_decode_nonoptimal/1,
 
36
    test_ei_decode_misc/1
 
37
   ]).
 
38
 
 
39
suite() -> [{ct_hooks,[ts_install_cth]}].
 
40
 
 
41
all() -> 
 
42
    [test_ei_decode_long, test_ei_decode_ulong,
 
43
     test_ei_decode_longlong, test_ei_decode_ulonglong,
 
44
     test_ei_decode_char, test_ei_decode_nonoptimal,
 
45
     test_ei_decode_misc].
 
46
 
 
47
groups() -> 
 
48
    [].
 
49
 
 
50
init_per_suite(Config) ->
 
51
    Config.
 
52
 
 
53
end_per_suite(_Config) ->
 
54
    ok.
 
55
 
 
56
init_per_group(_GroupName, Config) ->
 
57
    Config.
 
58
 
 
59
end_per_group(_GroupName, Config) ->
 
60
    Config.
 
61
 
 
62
 
 
63
%% ---------------------------------------------------------------------------
 
64
 
 
65
% NOTE: for historical reasons we don't pach as tight as we can,
 
66
%       we only fill 27 bits in 32 bit INTEGER_EXT 
 
67
 
 
68
 
 
69
%% ######################################################################## %%
 
70
 
 
71
test_ei_decode_long(suite) -> [];
 
72
test_ei_decode_long(Config) when is_list(Config) ->
 
73
    ?line P = runner:start(?test_ei_decode_long),
 
74
    send_integers(P),
 
75
    ?line runner:recv_eot(P),
 
76
    ok.
 
77
 
 
78
 
 
79
%% ######################################################################## %%
 
80
 
 
81
test_ei_decode_ulong(suite) -> [];
 
82
test_ei_decode_ulong(Config) when is_list(Config) ->
 
83
    ?line P = runner:start(?test_ei_decode_ulong),
 
84
    send_integers(P),
 
85
    ?line runner:recv_eot(P),
 
86
    ok.
 
87
 
 
88
 
 
89
% (*) In practical terms, other values may fit into the ext format
 
90
% i32 is signed 32 bit on C side
 
91
% u32 is unsigned 32 bit on C side
 
92
 
 
93
%% ######################################################################## %%
 
94
 
 
95
test_ei_decode_longlong(suite) -> [];
 
96
test_ei_decode_longlong(Config) when is_list(Config) ->
 
97
    case os:type() of
 
98
        vxworks ->
 
99
            {skip,"Skipped on VxWorks"};
 
100
        _ ->
 
101
            ?line P = runner:start(?test_ei_decode_longlong),
 
102
            send_integers2(P),
 
103
            ?line runner:recv_eot(P),
 
104
            ok
 
105
    end.
 
106
 
 
107
 
 
108
%% ######################################################################## %%
 
109
 
 
110
test_ei_decode_ulonglong(suite) -> [];
 
111
test_ei_decode_ulonglong(Config) when is_list(Config) ->
 
112
    case os:type() of
 
113
        vxworks ->
 
114
            {skip,"Skipped on VxWorks"};
 
115
        _ ->
 
116
            ?line P = runner:start(?test_ei_decode_ulonglong),
 
117
            send_integers2(P),
 
118
            ?line runner:recv_eot(P),
 
119
            ok
 
120
    end.
 
121
 
 
122
 
 
123
%% ######################################################################## %%
 
124
%% A "character" for us is an 8 bit integer, alwasy positive, i.e.
 
125
%% it is unsigned.
 
126
%% FIXME maybe the API should change to use "unsigned char" to be clear?!
 
127
 
 
128
test_ei_decode_char(suite) -> [];
 
129
test_ei_decode_char(Config) when is_list(Config) ->
 
130
    ?line P = runner:start(?test_ei_decode_char),
 
131
 
 
132
    ?line send_term_as_binary(P,0),
 
133
    ?line send_term_as_binary(P,16#7f),
 
134
    ?line send_term_as_binary(P,16#ff),
 
135
 
 
136
    ?line send_term_as_binary(P, []), % illegal type
 
137
 
 
138
    ?line runner:recv_eot(P),
 
139
    ok.
 
140
 
 
141
 
 
142
%% ######################################################################## %%
 
143
 
 
144
test_ei_decode_nonoptimal(suite) -> [];
 
145
test_ei_decode_nonoptimal(Config) when is_list(Config) ->
 
146
    ?line P = runner:start(?test_ei_decode_nonoptimal),
 
147
 
 
148
    send_non_optimal_pos(P),                    % decode_char
 
149
    send_non_optimal(P),                        % decode_long
 
150
    send_non_optimal_pos(P),                    % decode_ulong
 
151
    case os:type() of
 
152
        vxworks ->
 
153
            ok;
 
154
        _ ->
 
155
            send_non_optimal(P),                        % decode_longlong
 
156
            send_non_optimal_pos(P)                     % decode_ulonglong
 
157
    end,
 
158
 
 
159
    ?line runner:recv_eot(P),
 
160
    ok.
 
161
 
 
162
 
 
163
send_non_optimal(P) ->
 
164
    send_non_optimal_pos(P),
 
165
    send_non_optimal_neg(P).
 
166
 
 
167
send_non_optimal_pos(P) ->
 
168
    ?line send_raw(P, <<131,97,42>>),
 
169
    ?line send_raw(P, <<131,98,42:32>>),
 
170
    ?line send_raw(P, <<131,110,1,0,42>>),
 
171
    ?line send_raw(P, <<131,110,2,0,42,0>>),
 
172
    ?line send_raw(P, <<131,110,4,0,42,0,0,0>>),
 
173
    ?line send_raw(P, <<131,111,0,0,0,1,0,42>>),
 
174
    ?line send_raw(P, <<131,111,0,0,0,2,0,42,0>>),
 
175
    ?line send_raw(P, <<131,111,0,0,0,3,0,42,0,0>>),
 
176
    ?line send_raw(P, <<131,111,0,0,0,6,0,42,0,0,0,0,0>>),
 
177
    ok.
 
178
 
 
179
send_non_optimal_neg(P) ->
 
180
%   ?line send_raw(P, <<131,97,-42>>),
 
181
    ?line send_raw(P, <<131,98,-42:32>>),
 
182
    ?line send_raw(P, <<131,110,1,1,42>>),
 
183
    ?line send_raw(P, <<131,110,2,1,42,0>>),
 
184
    ?line send_raw(P, <<131,110,4,1,42,0,0,0>>),
 
185
    ?line send_raw(P, <<131,111,0,0,0,1,1,42>>),
 
186
    ?line send_raw(P, <<131,111,0,0,0,2,1,42,0>>),
 
187
    ?line send_raw(P, <<131,111,0,0,0,3,1,42,0,0>>),
 
188
    ?line send_raw(P, <<131,111,0,0,0,6,1,42,0,0,0,0,0>>),
 
189
    ok.
 
190
 
 
191
 
 
192
%% ######################################################################## %%
 
193
 
 
194
test_ei_decode_misc(suite) -> [];
 
195
test_ei_decode_misc(Config) when is_list(Config) ->
 
196
    ?line P = runner:start(?test_ei_decode_misc),
 
197
 
 
198
    ?line send_term_as_binary(P,0.0),
 
199
    ?line send_term_as_binary(P,-1.0),
 
200
    ?line send_term_as_binary(P,1.0),
 
201
 
 
202
    ?line send_term_as_binary(P,false),
 
203
    ?line send_term_as_binary(P,true),
 
204
 
 
205
    ?line send_term_as_binary(P,foo),
 
206
    ?line send_term_as_binary(P,''),
 
207
    ?line send_term_as_binary(P,'������'),
 
208
 
 
209
    ?line send_term_as_binary(P,"foo"),
 
210
    ?line send_term_as_binary(P,""),
 
211
    ?line send_term_as_binary(P,"������"),
 
212
 
 
213
    ?line send_term_as_binary(P,<<"foo">>),
 
214
    ?line send_term_as_binary(P,<<>>),
 
215
    ?line send_term_as_binary(P,<<"������">>),
 
216
 
 
217
%    ?line send_term_as_binary(P,{}),
 
218
%    ?line send_term_as_binary(P,[]),
 
219
 
 
220
    ?line runner:recv_eot(P),
 
221
    ok.
 
222
 
 
223
 
 
224
%% ######################################################################## %%
 
225
 
 
226
send_term_as_binary(Port, Term) when is_port(Port) ->
 
227
    Port ! {self(), {command, term_to_binary(Term)}}.
 
228
 
 
229
send_raw(Port, Bin) when is_port(Port) ->
 
230
    Port ! {self(), {command, Bin}}.
 
231
 
 
232
 
 
233
send_integers(P) ->
 
234
    ?line send_term_as_binary(P,0),             % SMALL_INTEGER_EXT smallest
 
235
    ?line send_term_as_binary(P,255),           % SMALL_INTEGER_EXT largest
 
236
    ?line send_term_as_binary(P,256),           % INTEGER_EXT smallest pos (*)
 
237
    ?line send_term_as_binary(P,-1),            % INTEGER_EXT largest  neg 
 
238
 
 
239
    ?line send_term_as_binary(P, 16#07ffffff),  % INTEGER_EXT old largest (28 bits)
 
240
    ?line send_term_as_binary(P,-16#08000000),  % INTEGER_EXT old smallest
 
241
    ?line send_term_as_binary(P, 16#08000000),  % SMALL_BIG_EXT old smallest pos(*)
 
242
    ?line send_term_as_binary(P,-16#08000001),  % SMALL_BIG_EXT old largest neg (*)
 
243
 
 
244
    ?line send_term_as_binary(P, 16#7fffffff),  % INTEGER_EXT new largest (32 bits)
 
245
    ?line send_term_as_binary(P,-16#80000000),  % INTEGER_EXT new smallest (32 bis)
 
246
    ?line send_term_as_binary(P, 16#80000000),  % SMALL_BIG_EXT new smallest pos(*)
 
247
    ?line send_term_as_binary(P,-16#80000001),  % SMALL_BIG_EXT new largest neg (*)
 
248
 
 
249
    case erlang:system_info({wordsize,external}) of
 
250
        4 ->     
 
251
          ?line send_term_as_binary(P, 16#80000000),% SMALL_BIG_EXT u32
 
252
          ?line send_term_as_binary(P, 16#ffffffff),% SMALL_BIG_EXT largest u32
 
253
 
 
254
          ?line send_term_as_binary(P, 16#7fffffffffff), % largest  i48
 
255
          ?line send_term_as_binary(P,-16#800000000000), % smallest i48
 
256
          ?line send_term_as_binary(P, 16#ffffffffffff), % largest  u48
 
257
          ?line send_term_as_binary(P, 16#7fffffffffffffff), % largest  i64
 
258
          ?line send_term_as_binary(P,-16#8000000000000000), % smallest i64
 
259
          ?line send_term_as_binary(P, 16#ffffffffffffffff); % largest  u64
 
260
        8 ->
 
261
          ?line send_term_as_binary(P, 16#8000000000000000),% SMALL_BIG_EXT u64
 
262
          % SMALL_BIG_EXT largest u64
 
263
          ?line send_term_as_binary(P, 16#ffffffffffffffff),
 
264
          % largest  i96
 
265
          ?line send_term_as_binary(P, 16#7fffffffffffffffffffffff), 
 
266
          % smallest i96
 
267
          ?line send_term_as_binary(P,-16#800000000000000000000000), 
 
268
          % largest  u96
 
269
          ?line send_term_as_binary(P, 16#ffffffffffffffffffffffff), 
 
270
          % largest  i128
 
271
          ?line send_term_as_binary(P, 16#7fffffffffffffffffffffffffffffff), 
 
272
          % smallest i128
 
273
          ?line send_term_as_binary(P,-16#80000000000000000000000000000000),
 
274
          % largest  u128 
 
275
          ?line send_term_as_binary(P, 16#ffffffffffffffffffffffffffffffff) 
 
276
    end,
 
277
    ?line send_term_as_binary(P, []), % illegal type
 
278
    ok.
 
279
 
 
280
send_integers2(P) ->
 
281
    ?line send_term_as_binary(P,0),             % SMALL_INTEGER_EXT smallest
 
282
    ?line send_term_as_binary(P,255),           % SMALL_INTEGER_EXT largest
 
283
    ?line send_term_as_binary(P,256),           % INTEGER_EXT smallest pos (*)
 
284
    ?line send_term_as_binary(P,-1),            % INTEGER_EXT largest  neg 
 
285
    
 
286
    ?line send_term_as_binary(P, 16#07ffffff),  % INTEGER_EXT old largest (28 bits)
 
287
    ?line send_term_as_binary(P,-16#08000000),  % INTEGER_EXT old smallest 
 
288
    ?line send_term_as_binary(P, 16#08000000),  % SMALL_BIG_EXT old smallest pos(*)
 
289
    ?line send_term_as_binary(P,-16#08000001),  % SMALL_BIG_EXT old largest neg (*)
 
290
 
 
291
    ?line send_term_as_binary(P, 16#7fffffff),  % INTEGER_EXT new largest (32 bits)
 
292
    ?line send_term_as_binary(P,-16#80000000),  % INTEGER_EXT new smallest
 
293
    ?line send_term_as_binary(P, 16#80000000),  % SMALL_BIG_EXT new smallest pos(*)
 
294
    ?line send_term_as_binary(P,-16#80000001),  % SMALL_BIG_EXT new largest neg (*)
 
295
 
 
296
    ?line send_term_as_binary(P, 16#ffffffff),% SMALL_BIG_EXT largest u32
 
297
 
 
298
    ?line send_term_as_binary(P, 16#7fffffffffff), % largest  i48
 
299
    ?line send_term_as_binary(P,-16#800000000000), % smallest i48
 
300
    ?line send_term_as_binary(P, 16#ffffffffffff), % largest  u48
 
301
    ?line send_term_as_binary(P, 16#7fffffffffffffff), % largest  i64
 
302
    ?line send_term_as_binary(P,-16#8000000000000000), % smallest i64
 
303
    ?line send_term_as_binary(P, 16#ffffffffffffffff), % largest  u64
 
304
    ?line send_term_as_binary(P, []), % illegal type
 
305
    ok.