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

« back to all changes in this revision

Viewing changes to lib/ic/test/erl_client_c_server_SUITE_data/erl_client.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 2002-2010. 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(erl_client).
 
21
 
 
22
-export([void_test/2, long_test/2, longlong_test/2, ushort_test/2,
 
23
         ulong_test/2, ulonglong_test/2, double_test/2, char_test/2,
 
24
         wchar_test/2, octet_test/2, bool_test/2, struct_test/2,
 
25
         struct2_test/2, seq1_test/2, seq2_test/2, seq3_test/2,
 
26
         seq4_test/2, seq5_test/2, array1_test/2, array2_test/2,
 
27
         enum_test/2, string1_test/2, wstring1_test/2, string2_test/2,
 
28
         string3_test/2, string4_test/2, pid_test/2, port_test/2,
 
29
         ref_test/2, term_test/2, typedef_test/2,
 
30
         inline_sequence_test/2, term_sequence_test/2,
 
31
         term_struct_test/2
 
32
 
 
33
]).
 
34
 
 
35
-include("m.hrl").
 
36
-include("m_i.hrl").
 
37
-include("oe_erl_c_test.hrl").
 
38
 
 
39
%%b
 
40
void_test(Node, Timeout) ->
 
41
    Ret = m_i:void_test({olsson, Node}, Timeout),
 
42
    Ret == void.                                % XXX Not documented
 
43
%%e
 
44
 
 
45
%%b
 
46
long_test(Node, Timeout) ->
 
47
    In = max_long(),
 
48
    {Ret, Out} = m_i:long_test({olsson, Node}, Timeout, In),
 
49
    (Ret == In) and (Out == In).
 
50
%%e
 
51
 
 
52
%%b
 
53
longlong_test(Node, Timeout) ->
 
54
    In = 65537,
 
55
    {Ret, Out} = m_i:longlong_test({olsson, Node}, Timeout, In),
 
56
    (Ret == In) and (Out == In).
 
57
%%e
 
58
 
 
59
%%b
 
60
ushort_test(Node, Timeout) ->
 
61
    In = max_ushort(),
 
62
    {Ret, Out} = m_i:ushort_test({olsson, Node}, Timeout, In),
 
63
    (Ret == In) and (Out == In).
 
64
%%e
 
65
 
 
66
%%b
 
67
ulong_test(Node, Timeout) ->
 
68
    In = max_ulong(),
 
69
    {Ret, Out} = m_i:ulong_test({olsson, Node}, Timeout, In),
 
70
    (Ret == In) and (Out == In).
 
71
%%e
 
72
 
 
73
%%b
 
74
ulonglong_test(Node, Timeout) ->
 
75
    In = 65537,
 
76
    {Ret, Out} = m_i:ulonglong_test({olsson, Node}, Timeout, In),
 
77
    (Ret == In) and (Out == In).
 
78
%%e
 
79
 
 
80
%%b
 
81
double_test(Node, Timeout) ->
 
82
    In = 37768.93,
 
83
    {Ret, Out} = m_i:double_test({olsson, Node}, Timeout, In),
 
84
    (Ret == In) and (Out == In).
 
85
%%e
 
86
 
 
87
%%b
 
88
char_test(Node, Timeout) ->
 
89
    In = 80,
 
90
    {Ret, Out} = m_i:char_test({olsson, Node}, Timeout, In),
 
91
    (Ret == In) and (Out == In).
 
92
%%e
 
93
 
 
94
%%b
 
95
wchar_test(Node, Timeout) ->
 
96
    In = 4097,
 
97
    {Ret, Out} = m_i:wchar_test({olsson, Node}, Timeout, In),
 
98
    (Ret == In) and (Out == In).
 
99
%%e
 
100
 
 
101
%%b
 
102
octet_test(Node, Timeout) ->
 
103
    In = 255,
 
104
    {Ret, Out} = m_i:octet_test({olsson, Node}, Timeout, In),
 
105
    (Ret == In) and (Out == In).
 
106
%%e
 
107
 
 
108
%%b
 
109
bool_test(Node, Timeout) ->
 
110
    In = false,
 
111
    {Ret, Out} = m_i:bool_test({olsson, Node}, Timeout, In),
 
112
    (Ret == In) and (Out == In).
 
113
%%e
 
114
 
 
115
%%b
 
116
struct_test(Node, Timeout) ->
 
117
    In = #m_b{l = max_long(), c = $a},
 
118
    {Ret, Out} = m_i:struct_test({olsson, Node}, Timeout, In),
 
119
    (Ret == In) and (Out == In).
 
120
%%e
 
121
 
 
122
%%b
 
123
struct2_test(Node, Timeout) ->
 
124
    In = #m_es{ f = banana, l = max_long()},
 
125
    {Ret, Out} = m_i:struct2_test({olsson, Node}, Timeout, In),
 
126
    (Ret == In) and (Out == In).
 
127
%%e
 
128
 
 
129
%%b
 
130
seq1_test(Node, Timeout) ->
 
131
    B1 = #m_b{l = max_long(), c = $a},
 
132
    B2 = #m_b{l = min_long(), c = $b},
 
133
    In = [B1, B2],
 
134
    {Ret, Out} = m_i:seq1_test({olsson, Node}, Timeout, In),
 
135
    (Ret == In) and (Out == In).
 
136
%%e
 
137
 
 
138
%%b
 
139
seq2_test(Node, Timeout) ->
 
140
    B = #m_b{l = max_long(), c = $a},
 
141
    A = #m_a{l = min_long(), y = [B, B], d = 4711.31},
 
142
    In = [A, A, A],
 
143
    {Ret, Out} = m_i:seq2_test({olsson, Node}, Timeout, In),
 
144
    (Ret == In) and (Out == In).
 
145
%%e
 
146
 
 
147
%%b
 
148
seq3_test(Node, Timeout) ->
 
149
    In = [max_long(), min_long(), max_long()],
 
150
    {Ret, Out} = m_i:seq3_test({olsson, Node}, Timeout, In),
 
151
    (Ret == In) and (Out == In).
 
152
%%e
 
153
 
 
154
%%b
 
155
seq4_test(Node, Timeout) ->
 
156
    In = [["hello", "all"], ["Erlang", "users", "!"]],
 
157
    {Ret, Out} = m_i:seq4_test({olsson, Node}, Timeout, In),
 
158
    (Ret == In) and (Out == In).
 
159
%%e
 
160
 
 
161
%%b
 
162
seq5_test(Node, Timeout) ->
 
163
    Arr3 = mk_array(3, max_long()),
 
164
    In = [[Arr3, Arr3], [Arr3, Arr3, Arr3]],
 
165
    {Ret, Out} = m_i:seq5_test({olsson, Node}, Timeout, In),
 
166
    (Ret == In) and (Out == In).
 
167
%%e
 
168
 
 
169
%%b
 
170
array1_test(Node, Timeout) ->
 
171
    In = mk_array(500, min_long()),
 
172
    {Ret, Out} = m_i:array1_test({olsson, Node}, Timeout, In),
 
173
    (Ret == In) and (Out == In).
 
174
%%e
 
175
 
 
176
%%b
 
177
array2_test(Node, Timeout) ->
 
178
    In = mk_array(2, mk_array(3, min_long())),
 
179
    {Ret, Out} = m_i:array2_test({olsson, Node}, Timeout, In),
 
180
    (Ret == In) and (Out == In).
 
181
%%e
 
182
 
 
183
%%b
 
184
enum_test(Node, Timeout) ->
 
185
    In = banana,
 
186
    {Ret, Out} = m_i:enum_test({olsson, Node}, Timeout, In),
 
187
    (Ret == In) and (Out == In).
 
188
%%e
 
189
 
 
190
%%b
 
191
string1_test(Node, Timeout) ->
 
192
    In = "Developing Erlang applications is fun!", 
 
193
    {Ret, Out} = m_i:string1_test({olsson, Node}, Timeout, In),
 
194
    (Ret == In) and (Out == In).
 
195
%%e
 
196
 
 
197
%%b
 
198
wstring1_test(Node, Timeout) ->
 
199
    In = [1047| "eveloping Erlang applications is fun!"], 
 
200
    {Ret, Out} = m_i:wstring1_test({olsson, Node}, Timeout, In),
 
201
    (Ret == In) and (Out == In).
 
202
%%e
 
203
 
 
204
%%b
 
205
string2_test(Node, Timeout) ->
 
206
    In = ["Developing Erlang applications ", "is fun!"],
 
207
    {Ret, Out} = m_i:string2_test({olsson, Node}, Timeout, In),
 
208
    (Ret == In) and (Out == In).
 
209
%%e
 
210
 
 
211
%%b
 
212
string3_test(Node, Timeout) ->
 
213
    In = "Developing Erlang applications is fun!", 
 
214
    {Ret, Out} = m_i:string3_test({olsson, Node}, Timeout, In),
 
215
    (Ret == In) and (Out == In).
 
216
%%e
 
217
 
 
218
%%b
 
219
string4_test(Node, Timeout) ->
 
220
    
 
221
    In = #m_strRec{
 
222
      bb = true, 
 
223
      str4 = "Developing Erlang applications "
 
224
      "is fun!",
 
225
      str7 = mk_array(3, mk_array(2, max_long())),
 
226
      str5 = [$a, $b, $c, $d, $e, $f],
 
227
      str6 = "123456789012",
 
228
      str8 = {$x, $y, $x},
 
229
      str9 = "123456789012",
 
230
      str10 = [$a, $b, $c, $d, $e, $f]
 
231
      },
 
232
    {Ret, Out} = m_i:string4_test({olsson, Node}, Timeout, In),
 
233
    (Ret == In) and (Out == In).
 
234
%%e
 
235
 
 
236
%%b
 
237
pid_test(Node, Timeout) ->
 
238
    In = self(),
 
239
    {Ret, Out} = m_i:pid_test({olsson, Node}, Timeout, In),
 
240
    (Ret == In) and (Out == In).
 
241
%%e
 
242
 
 
243
%%b
 
244
port_test(Node, Timeout) ->
 
245
    In = get(port_test_port),
 
246
    {Ret, Out} = m_i:port_test({olsson, Node}, Timeout, In),
 
247
    (Ret == In) and (Out == In).
 
248
%%e
 
249
 
 
250
%%b
 
251
ref_test(Node, Timeout) ->
 
252
    In = make_ref(),
 
253
    {Ret, Out} = m_i:ref_test({olsson, Node}, Timeout, In),
 
254
    (Ret == In) and (Out == In).
 
255
%%e
 
256
 
 
257
%%b
 
258
term_test(Node, Timeout) ->
 
259
    In = {[a, b], 17, kalle},
 
260
    {Ret, Out} = m_i:term_test({olsson, Node}, Timeout, In),
 
261
    (Ret == In) and (Out == In).
 
262
%%e
 
263
 
 
264
%%b
 
265
typedef_test(Node, Timeout) ->
 
266
    In1 = {nisse, [1, 2], olsson},
 
267
    In2 = get(port_test_port),
 
268
    {Ret, Out1, Out2} = m_i:typedef_test({olsson, Node}, Timeout, In1, In2),
 
269
    %% XXX Should check that Ret is an integer.
 
270
    (Out1 == In1) and (Out2 == In2).
 
271
%%e
 
272
 
 
273
%%b
 
274
inline_sequence_test(Node, Timeout) ->
 
275
    In = #m_s{l = min_long(), sl = [max_long(), min_long()]}, 
 
276
    {Ret, Out} = m_i:inline_sequence_test({olsson, Node}, Timeout, In),
 
277
    (Ret == In) and (Out == In).
 
278
%%e
 
279
 
 
280
%%b
 
281
term_sequence_test(Node, Timeout) ->
 
282
    In = lists:duplicate(17, {nisse, [1, 2], {kalle, olsson}}),
 
283
    {Ret, Out} = m_i:term_sequence_test({olsson, Node}, Timeout, In),
 
284
    (Ret == In) and (Out == In).
 
285
%%e
 
286
 
 
287
%%b
 
288
term_struct_test(Node, Timeout) ->
 
289
    In = #m_et{e = {nisse, ["abcde"], {kalle, olsson}}, l = 4711},
 
290
    {Ret, Out} = m_i:term_struct_test({olsson, Node}, Timeout, In),
 
291
    (Ret == In) and (Out == In).
 
292
%%e
 
293
 
 
294
 
 
295
%% Locals
 
296
 
 
297
mk_array(Es) ->
 
298
    list_to_tuple(Es).
 
299
 
 
300
mk_array(N, E) ->
 
301
    mk_array(lists:duplicate(N, E)). 
 
302
 
 
303
%% max_short() ->
 
304
%%     power_of_two(15) - 1.
 
305
max_long() ->
 
306
    power_of_two(31) - 1.
 
307
max_longlong() ->
 
308
    power_of_two(63) - 1.
 
309
max_ushort() ->
 
310
    power_of_two(16) - 1.
 
311
max_ulong() ->
 
312
    power_of_two(32) - 1.
 
313
max_ulonglong() ->
 
314
    power_of_two(64) - 1.
 
315
 
 
316
%% min_short() ->
 
317
%%     -power_of_two(15).
 
318
min_long() ->
 
319
    -power_of_two(31).
 
320
%% min_longlong() ->
 
321
%%     -power_of_two(63).
 
322
%% min_ushort() ->
 
323
%%     0.
 
324
%% min_ulong() ->
 
325
%%     0.
 
326
%% min_ulonglong() ->
 
327
%%     0.
 
328
 
 
329
power_of_two(N) -> 
 
330
    round(math:pow(2, N)).
 
331