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

« back to all changes in this revision

Viewing changes to lib/erl_interface/test/erl_eterm_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 1997-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(erl_eterm_SUITE).
 
22
 
 
23
-include_lib("test_server/include/test_server.hrl").
 
24
-include("erl_eterm_SUITE_data/eterm_test_cases.hrl").
 
25
 
 
26
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
27
%%% The tests are organised as follows:
 
28
%%%
 
29
%%% 1. Basic tests (encoding, decoding, memory allocation).
 
30
%%% 2. Constructing terms (the erl_mk_xxx() functions and erl_copy_term()).
 
31
%%% 3. Extracting & info functions (erl_hd(), erl_length() etc).
 
32
%%% 4. I/O list functions.
 
33
%%% 5. Miscellanous functions.
 
34
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
35
 
 
36
-export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1, 
 
37
         init_per_group/2,end_per_group/2, 
 
38
         build_terms/1, round_trip_conversion/1,
 
39
         decode_terms/1, decode_float/1,
 
40
         t_erl_mk_int/1, t_erl_mk_list/1,
 
41
         basic_copy/1,
 
42
         t_erl_cons/1,
 
43
         t_erl_mk_atom/1,
 
44
         t_erl_mk_binary/1,
 
45
         t_erl_mk_empty_list/1,
 
46
         t_erl_mk_float/1,
 
47
         t_erl_mk_pid/1,
 
48
         t_erl_mk_xpid/1,
 
49
         t_erl_mk_port/1,
 
50
         t_erl_mk_xport/1,
 
51
         t_erl_mk_ref/1,
 
52
         t_erl_mk_long_ref/1,
 
53
         t_erl_mk_string/1,
 
54
         t_erl_mk_estring/1,
 
55
         t_erl_mk_tuple/1,
 
56
         t_erl_mk_uint/1,
 
57
         t_erl_mk_var/1,
 
58
         t_erl_size/1,
 
59
         t_erl_var_content/1,
 
60
         t_erl_element/1,
 
61
         t_erl_length/1, t_erl_hd/1, t_erl_tl/1,
 
62
         type_checks/1, extractor_macros/1,
 
63
         t_erl_iolist_length/1, t_erl_iolist_to_binary/1,
 
64
         t_erl_iolist_to_string/1,
 
65
         erl_print_term/1, print_string/1,
 
66
         t_erl_free_compound/1,
 
67
         high_chaparal/1,
 
68
         broken_data/1,
 
69
         cnode_1/1]).
 
70
 
 
71
-export([start_cnode/1]).
 
72
 
 
73
-import(runner, [get_term/1]).
 
74
 
 
75
%% This test suite controls the running of the C language functions
 
76
%% in eterm_test.c and print_term.c.
 
77
 
 
78
suite() -> [{ct_hooks,[ts_install_cth]}].
 
79
 
 
80
all() -> 
 
81
    [build_terms, round_trip_conversion, decode_terms,
 
82
     decode_float, t_erl_mk_int, t_erl_mk_list, basic_copy,
 
83
     t_erl_mk_atom, t_erl_mk_binary, t_erl_mk_empty_list,
 
84
     t_erl_mk_float, t_erl_mk_pid, t_erl_mk_xpid,
 
85
     t_erl_mk_port, t_erl_mk_xport, t_erl_mk_ref,
 
86
     t_erl_mk_long_ref, t_erl_mk_string, t_erl_mk_estring,
 
87
     t_erl_mk_tuple, t_erl_mk_uint, t_erl_mk_var, t_erl_size,
 
88
     t_erl_var_content, t_erl_element, t_erl_cons,
 
89
     t_erl_length, t_erl_hd, t_erl_tl, type_checks,
 
90
     extractor_macros, t_erl_iolist_length,
 
91
     t_erl_iolist_to_binary, t_erl_iolist_to_string,
 
92
     erl_print_term, print_string, t_erl_free_compound,
 
93
     high_chaparal, broken_data, cnode_1].
 
94
 
 
95
groups() -> 
 
96
    [].
 
97
 
 
98
init_per_suite(Config) ->
 
99
    Config.
 
100
 
 
101
end_per_suite(_Config) ->
 
102
    ok.
 
103
 
 
104
init_per_group(_GroupName, Config) ->
 
105
    Config.
 
106
 
 
107
end_per_group(_GroupName, Config) ->
 
108
    Config.
 
109
 
 
110
 
 
111
 
 
112
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
113
%%%
 
114
%%%     1.   B a s i c    t e s t s
 
115
%%%
 
116
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
117
 
 
118
%% This test asks the C function to construct all data types in
 
119
%% a list and verifies that the result is as expected.
 
120
 
 
121
build_terms(suite) -> [];
 
122
build_terms(Config) when is_list(Config) ->
 
123
    ?line P = runner:start(?build_terms),
 
124
    ?line {term, Term} = get_term(P),
 
125
    ?line io:format("Received: ~p", [Term]),
 
126
    ?line [ARefLN, ARef, APortLN, APort, APidLN, APid,
 
127
           {element1, 42, 767}, "A string",
 
128
           1, -1, 0, 3.0, ABin, 'I am an atom'] = Term,
 
129
    ?line "A binary" = binary_to_list(ABin),
 
130
    ?line case ARef of
 
131
              R when is_reference(R), node(R) == kalle@localhost -> ok
 
132
          end,
 
133
    ?line case ARefLN of
 
134
              R1 when is_reference(R1), node(R1) == abcdefghijabcdefghij@localhost -> ok
 
135
          end,
 
136
    ?line case APort of
 
137
              Port when is_port(Port), node(Port) == kalle@localhost -> ok
 
138
          end,
 
139
    ?line case APortLN of
 
140
              Port1 when is_port(Port1), node(Port1) == abcdefghijabcdefghij@localhost -> ok
 
141
          end,
 
142
    ?line case APid of
 
143
              Pid when is_pid(Pid), node(Pid) == kalle@localhost -> ok
 
144
          end,
 
145
    ?line case APidLN of
 
146
              Pid1 when is_pid(Pid1), node(Pid1) == abcdefghijabcdefghij@localhost -> ok
 
147
          end,
 
148
 
 
149
    ?line runner:recv_eot(P),
 
150
    ok.
 
151
 
 
152
%% This test is run entirely in C code.
 
153
 
 
154
round_trip_conversion(suite) -> [];
 
155
round_trip_conversion(Config) when is_list(Config) ->
 
156
    ?line runner:test(?round_trip_conversion),
 
157
    ok.
 
158
 
 
159
%% This test sends a list of all data types to the C code function,
 
160
%% which decodes it and verifies it.
 
161
 
 
162
decode_terms(suite) -> [];
 
163
decode_terms(Config) when is_list(Config) ->
 
164
    ?line Dummy1 = list_to_atom(filename:join(?config(priv_dir, Config),
 
165
                                              dummy_file1)),
 
166
    ?line Dummy2 = list_to_atom(filename:join(?config(priv_dir, Config),
 
167
                                              dummy_file2)),
 
168
    ?line Port1 = open_port(Dummy1, [out]),
 
169
    ?line Port2 = open_port(Dummy2, [out]),
 
170
    ?line ABinary = list_to_binary("A binary"),
 
171
    ?line Terms = [make_ref(), make_ref(),
 
172
                   Port1, Port2,
 
173
                   self(), self(),
 
174
                   {element1, 42, 767}, "A string",
 
175
                   1, -1, 0, 3.0, ABinary, 'I am an atom'],
 
176
 
 
177
    ?line P = runner:start(?decode_terms),
 
178
    ?line runner:send_term(P, Terms),
 
179
    ?line runner:recv_eot(P),
 
180
 
 
181
    ok.
 
182
 
 
183
%% Decodes the floating point number 3.1415.
 
184
 
 
185
decode_float(suite) -> [];
 
186
decode_float(Config) when is_list(Config) ->
 
187
    ?line P = runner:start(?decode_float),
 
188
    ?line runner:send_term(P, 3.1415),
 
189
    ?line runner:recv_eot(P),
 
190
    ok.
 
191
 
 
192
%% Tests the erl_free_compound() function.
 
193
 
 
194
t_erl_free_compound(suite) -> [];
 
195
t_erl_free_compound(Config) when is_list(Config) ->
 
196
    ?line runner:test(?t_erl_free_compound),
 
197
    ok.
 
198
 
 
199
 
 
200
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
201
%%%
 
202
%%%     2.   C o n s t r u c t i n g   t e r m s
 
203
%%%
 
204
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
205
 
 
206
%% This tests the erl_mk_list() function.
 
207
 
 
208
t_erl_mk_list(suite) -> [];
 
209
t_erl_mk_list(Config) when is_list(Config) ->
 
210
    ?line P = runner:start(?t_erl_mk_list),
 
211
 
 
212
    ?line {term, []} = get_term(P),
 
213
    ?line {term, [abc]} = get_term(P),
 
214
    ?line {term, [abcdef, 42]} = get_term(P),
 
215
    ?line {term, [0.0, 23, [], 3.1415]} = get_term(P),
 
216
 
 
217
    ?line runner:recv_eot(P),
 
218
    ok.
 
219
 
 
220
 
 
221
%% This tests the erl_mk_int() function.
 
222
 
 
223
t_erl_mk_int(suite) -> [];
 
224
t_erl_mk_int(Config) when is_list(Config) ->
 
225
    ?line P = runner:start(?t_erl_mk_int),
 
226
    
 
227
    ?line {term, 0} = get_term(P),
 
228
    ?line {term, 127} = get_term(P),
 
229
    ?line {term, 128} = get_term(P),
 
230
    ?line {term, 255} = get_term(P),
 
231
    ?line {term, 256} = get_term(P),
 
232
 
 
233
    ?line {term, 16#FFFF} = get_term(P),
 
234
    ?line {term, 16#10000} = get_term(P),
 
235
 
 
236
    ?line {term, 16#07FFFFFF} = get_term(P),
 
237
    ?line {term, 16#0FFFFFFF} = get_term(P),
 
238
    ?line {term, 16#1FFFFFFF} = get_term(P),
 
239
    ?line {term, 16#3FFFFFFF} = get_term(P),
 
240
    ?line {term, 16#7FFFFFFF} = get_term(P),
 
241
 
 
242
    ?line {term, 16#08000000} = get_term(P),
 
243
    ?line {term, 16#10000000} = get_term(P),
 
244
    ?line {term, 16#20000000} = get_term(P),
 
245
    ?line {term, 16#40000000} = get_term(P),
 
246
 
 
247
 
 
248
    ?line {term, -16#07FFFFFF} = get_term(P),
 
249
    ?line {term, -16#0FFFFFFF} = get_term(P),
 
250
    ?line {term, -16#1FFFFFFF} = get_term(P),
 
251
    ?line {term, -16#3FFFFFFF} = get_term(P),
 
252
    ?line {term, -16#7FFFFFFF} = get_term(P),
 
253
 
 
254
    ?line {term, -16#08000000} = get_term(P),
 
255
    ?line {term, -16#10000000} = get_term(P),
 
256
    ?line {term, -16#20000000} = get_term(P),
 
257
    ?line {term, -16#40000000} = get_term(P),
 
258
 
 
259
    ?line {term, -16#08000001} = get_term(P),
 
260
    ?line {term, -16#10000001} = get_term(P),
 
261
    ?line {term, -16#20000001} = get_term(P),
 
262
    ?line {term, -16#40000001} = get_term(P),
 
263
 
 
264
    ?line {term, -16#08000002} = get_term(P),
 
265
    ?line {term, -16#10000002} = get_term(P),
 
266
    ?line {term, -16#20000002} = get_term(P),
 
267
    ?line {term, -16#40000002} = get_term(P),
 
268
 
 
269
    ?line {term, -1999999999} = get_term(P),
 
270
    ?line {term, -2000000000} = get_term(P),
 
271
    ?line {term, -2000000001} = get_term(P),
 
272
 
 
273
    ?line runner:recv_eot(P),
 
274
    ok.
 
275
 
 
276
 
 
277
%% Basic test of erl_copy_term().
 
278
 
 
279
basic_copy(suite) -> [];
 
280
basic_copy(Config) when is_list(Config) ->
 
281
    ?line runner:test(?basic_copy),
 
282
    ok.
 
283
 
 
284
 
 
285
%% This tests the erl_mk_tuple() function.
 
286
 
 
287
t_erl_mk_tuple(suite) -> [];
 
288
t_erl_mk_tuple(Config) when is_list(Config) ->
 
289
    ?line P = runner:start(?t_erl_mk_tuple),
 
290
 
 
291
    ?line {term, {madonna, 21, 'mad donna', 12}} = get_term(P),
 
292
    ?line {term, {'Madonna',21,{children,{"Isabella",2}},
 
293
                  {'home page',"http://www.madonna.com/"}}} = get_term(P),
 
294
 
 
295
    ?line runner:recv_eot(P),
 
296
    ok.
 
297
 
 
298
 
 
299
%% This tests the erl_mk_atom() function.
 
300
 
 
301
t_erl_mk_atom(suite) -> [];
 
302
t_erl_mk_atom(Config) when is_list(Config) ->
 
303
    ?line P = runner:start(?t_erl_mk_atom),
 
304
 
 
305
    ?line {term, madonna} = (get_term(P)),
 
306
    ?line {term, 'Madonna'} = (get_term(P)),
 
307
    ?line {term, 'mad donna'} = (get_term(P)),
 
308
    ?line {term, '_madonna_'} = (get_term(P)),
 
309
    ?line {term, '/home/madonna/tour_plan'} = (get_term(P)),
 
310
    ?line {term, 'http://www.madonna.com/tour_plan'} = (get_term(P)),
 
311
    ?line {term, '\'madonna\''} = (get_term(P)),
 
312
    ?line {term, '\"madonna\"'} = (get_term(P)),
 
313
    ?line {term, '\\madonna\\'} = (get_term(P)),
 
314
    ?line {term, '{madonna,21,\'mad donna\',12}'} = (get_term(P)),
 
315
 
 
316
    ?line runner:recv_eot(P),
 
317
    ok.
 
318
 
 
319
 
 
320
%% This tests the erl_mk_binary() function.
 
321
 
 
322
t_erl_mk_binary(suite) -> [];
 
323
t_erl_mk_binary(Config) when is_list(Config) ->
 
324
    ?line P = runner:start(?t_erl_mk_binary),
 
325
 
 
326
    ?line {term, Bin} = (get_term(P)),
 
327
    ?line "{madonna,21,'mad donna',1234.567.890, !#$%&/()=?+-@, \" \\}" = 
 
328
        binary_to_list(Bin),
 
329
 
 
330
    ?line runner:recv_eot(P),
 
331
    ok.
 
332
 
 
333
 
 
334
%% This tests the erl_mk_empty_list() function.
 
335
 
 
336
t_erl_mk_empty_list(suite) -> [];
 
337
t_erl_mk_empty_list(Config) when is_list(Config) ->
 
338
    ?line P = runner:start(?t_erl_mk_empty_list),
 
339
 
 
340
    ?line {term, []} = get_term(P),
 
341
 
 
342
    ?line runner:recv_eot(P),
 
343
    ok.
 
344
 
 
345
 
 
346
%% This tests the erl_mk_float() function.
 
347
 
 
348
t_erl_mk_float(suite) -> [];
 
349
t_erl_mk_float(Config) when is_list(Config) ->
 
350
    case os:type() of 
 
351
        vxworks ->
 
352
            {skipped, "Floating point numbers never compare equal on PPC"};
 
353
        _ ->
 
354
            ?line P = runner:start(?t_erl_mk_float),
 
355
            ?line {term, {3.1415, 1.999999, 2.000000, 2.000001, 
 
356
                          2.000002, 12345.67890}} = 
 
357
                get_term(P),
 
358
            ?line runner:recv_eot(P),
 
359
            ok
 
360
    end.
 
361
 
 
362
 
 
363
%% This tests the erl_mk_pid() function.
 
364
 
 
365
t_erl_mk_pid(suite) -> [];
 
366
t_erl_mk_pid(Config) when is_list(Config) ->
 
367
    ?line P = runner:start(?t_erl_mk_pid),
 
368
 
 
369
    ?line {term, A_pid} = (get_term(P)),
 
370
    ?line {pid, kalle@localhost, 3, 2} = nc2vinfo(A_pid),
 
371
 
 
372
    ?line runner:recv_eot(P),
 
373
    ok.
 
374
 
 
375
t_erl_mk_xpid(suite) -> [];
 
376
t_erl_mk_xpid(Config) when is_list(Config) ->
 
377
    ?line P = runner:start(?t_erl_mk_xpid),
 
378
 
 
379
    ?line {term, A_pid} = (get_term(P)),
 
380
    ?line {pid, kalle@localhost, 32767, 8191} = nc2vinfo(A_pid),
 
381
 
 
382
    ?line runner:recv_eot(P),
 
383
    ok.
 
384
 
 
385
 
 
386
%% This tests the erl_mk_port() function.
 
387
 
 
388
t_erl_mk_port(suite) -> [];
 
389
t_erl_mk_port(Config) when is_list(Config) ->
 
390
    ?line P = runner:start(?t_erl_mk_port),
 
391
 
 
392
    ?line {term, A_port} = (get_term(P)),
 
393
    ?line {port, kalle@localhost, 4} = nc2vinfo(A_port),
 
394
 
 
395
    ?line runner:recv_eot(P),
 
396
    ok.
 
397
 
 
398
t_erl_mk_xport(suite) -> [];
 
399
t_erl_mk_xport(Config) when is_list(Config) ->
 
400
    ?line P = runner:start(?t_erl_mk_xport),
 
401
 
 
402
    ?line {term, A_port} = (get_term(P)),
 
403
    ?line {port, kalle@localhost, 268435455} = nc2vinfo(A_port),
 
404
 
 
405
    ?line runner:recv_eot(P),
 
406
    ok.
 
407
 
 
408
 
 
409
%% This tests the erl_mk_ref() function.
 
410
 
 
411
t_erl_mk_ref(suite) -> [];
 
412
t_erl_mk_ref(Config) when is_list(Config) ->
 
413
    ?line P = runner:start(?t_erl_mk_ref),
 
414
 
 
415
    ?line {term, A_ref} = (get_term(P)),
 
416
    ?line {ref, kalle@localhost, _Length, [6]} = nc2vinfo(A_ref),
 
417
 
 
418
    ?line runner:recv_eot(P),
 
419
    ok.
 
420
 
 
421
t_erl_mk_long_ref(suite) -> [];
 
422
t_erl_mk_long_ref(Config) when is_list(Config) ->
 
423
    ?line P = runner:start(?t_erl_mk_long_ref),
 
424
 
 
425
    ?line {term, A_ref} = (get_term(P)),
 
426
    ?line {ref, kalle@localhost, _Length, [4294967295,4294967295,262143]}
 
427
        = nc2vinfo(A_ref),
 
428
 
 
429
    ?line runner:recv_eot(P),
 
430
    ok.
 
431
 
 
432
 
 
433
%% This tests the erl_mk_string() function.
 
434
 
 
435
t_erl_mk_string(suite) -> [];
 
436
t_erl_mk_string(Config) when is_list(Config) ->
 
437
    ?line P = runner:start(?t_erl_mk_string),
 
438
 
 
439
    ?line {term, "madonna"} = (get_term(P)),
 
440
    ?line {term, "Madonna"} = (get_term(P)),
 
441
    ?line {term, "mad donna"} = (get_term(P)),
 
442
    ?line {term, "_madonna_"} = (get_term(P)),
 
443
    ?line {term, "/home/madonna/tour_plan"} = (get_term(P)),
 
444
    ?line {term, "http://www.madonna.com/tour_plan"} = (get_term(P)),
 
445
    ?line {term, "\'madonna\'"} = (get_term(P)),
 
446
    ?line {term, "\"madonna\""} = (get_term(P)),
 
447
    ?line {term, "\\madonna\\"} = (get_term(P)),
 
448
    ?line {term, "{madonna,21,'mad donna',12}"} = (get_term(P)),
 
449
 
 
450
    ?line runner:recv_eot(P),
 
451
    ok.
 
452
 
 
453
 
 
454
%% This tests the erl_mk_estring() function.
 
455
 
 
456
t_erl_mk_estring(suite) -> [];
 
457
t_erl_mk_estring(Config) when is_list(Config) ->
 
458
    ?line P = runner:start(?t_erl_mk_estring),
 
459
 
 
460
    ?line {term, "madonna"} = (get_term(P)),
 
461
    ?line {term, "Madonna"} = (get_term(P)),
 
462
    ?line {term, "mad donna"} = (get_term(P)),
 
463
    ?line {term, "_madonna_"} = (get_term(P)),
 
464
    ?line {term, "/home/madonna/tour_plan"} = (get_term(P)),
 
465
    ?line {term, "http://www.madonna.com/tour_plan"} = (get_term(P)),
 
466
    ?line {term, "\'madonna\'"} = (get_term(P)),
 
467
    ?line {term, "\"madonna\""} = (get_term(P)),
 
468
    ?line {term, "\\madonna\\"} = (get_term(P)),
 
469
    ?line {term, "{madonna,21,'mad donna',12}"} = (get_term(P)),
 
470
 
 
471
    ?line runner:recv_eot(P),
 
472
    ok.
 
473
 
 
474
 
 
475
%% This tests the erl_mk_uint() function.
 
476
 
 
477
t_erl_mk_uint(suite) -> [];
 
478
t_erl_mk_uint(Config) when is_list(Config) ->
 
479
    ?line P = runner:start(?t_erl_mk_uint),
 
480
 
 
481
    ?line {term, 54321} = (get_term(P)),
 
482
    ?line {term, 2147483647} = (get_term(P)),
 
483
    ?line {term, 2147483648} = (get_term(P)),
 
484
    ?line {term, 2147483649} = (get_term(P)),
 
485
    ?line {term, 2147483650} = (get_term(P)),
 
486
    ?line {term, 4294967295} = (get_term(P)),
 
487
 
 
488
    ?line runner:recv_eot(P),
 
489
    ok.
 
490
 
 
491
 
 
492
%% This tests the erl_mk_var() function.
 
493
 
 
494
t_erl_mk_var(suite) -> [];
 
495
t_erl_mk_var(Config) when is_list(Config) ->
 
496
    ?line P = runner:start(?t_erl_mk_var),
 
497
 
 
498
    ?line {term, 1} = (get_term(P)),
 
499
    ?line {term, 0} = (get_term(P)),
 
500
    ?line {term, 1} = (get_term(P)),
 
501
    ?line {term, 0} = (get_term(P)),
 
502
    ?line {term, 1} = (get_term(P)),
 
503
    ?line {term, 0} = (get_term(P)),
 
504
    ?line {term, 1} = (get_term(P)),
 
505
 
 
506
    ?line runner:recv_eot(P),
 
507
    ok.
 
508
 
 
509
 
 
510
%% This tests the erl_cons() function.
 
511
 
 
512
t_erl_cons(suite) -> [];
 
513
t_erl_cons(Config) when is_list(Config) ->
 
514
    ?line P = runner:start(?t_erl_cons),
 
515
 
 
516
    ?line {term, [madonna, 21]} = get_term(P),
 
517
 
 
518
    ?line runner:recv_eot(P),
 
519
    ok.
 
520
 
 
521
 
 
522
 
 
523
 
 
524
 
 
525
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
526
%%%
 
527
%%%     3.   E x t r a c t i n g  &   i n f o    f u n c t i o n s
 
528
%%%
 
529
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
530
 
 
531
%% Tests the erl_length() function.
 
532
 
 
533
t_erl_length(suite) -> [];
 
534
t_erl_length(Config) when is_list(Config) ->
 
535
    ?line P = runner:start(?t_erl_length),
 
536
 
 
537
    ?line 0 = erl_length(P, []),
 
538
    ?line 1 = erl_length(P, [a]),
 
539
    ?line 2 = erl_length(P, [a, b]),
 
540
    ?line 3 = erl_length(P, [a, b, c]),
 
541
 
 
542
    ?line 4 = erl_length(P, [a, [x, y], c, []]),
 
543
 
 
544
    ?line -1 = erl_length(P, [a|b]),
 
545
    ?line -1 = erl_length(P, a),
 
546
 
 
547
    ?line runner:finish(P),
 
548
    ok.
 
549
 
 
550
%% Invokes the erl_length() function.
 
551
 
 
552
erl_length(Port, List) ->
 
553
    call_erl_function(Port, List).
 
554
 
 
555
%% Tests the erl_hd() function.
 
556
 
 
557
t_erl_hd(suite) -> [];
 
558
t_erl_hd(Config) when is_list(Config) ->
 
559
    ?line P = runner:start(?t_erl_hd),
 
560
    
 
561
    ?line 'NULL' = erl_hd(P, 42),
 
562
    ?line 'NULL' = erl_hd(P, abc),
 
563
    ?line 'NULL' = erl_hd(P, []),
 
564
 
 
565
    ?line [] = erl_hd(P, [[], a]),
 
566
    ?line a = erl_hd(P, [a]),
 
567
    ?line a = erl_hd(P, [a, b]),
 
568
    ?line a = erl_hd(P, [a, b, c]),
 
569
    ?line a = erl_hd(P, [a|b]),
 
570
 
 
571
    ?line runner:send_eot(P),
 
572
    ?line runner:recv_eot(P),
 
573
    ok.
 
574
 
 
575
%% Invokes the erl_hd() function.
 
576
 
 
577
erl_hd(Port, List) ->
 
578
    call_erl_function(Port, List).
 
579
 
 
580
%% Tests the erl_tail() function.
 
581
 
 
582
t_erl_tl(suite) -> [];
 
583
t_erl_tl(Config) when is_list(Config) ->
 
584
    ?line P = runner:start(?t_erl_tl),
 
585
 
 
586
    ?line 'NULL' = erl_tl(P, 42),
 
587
    ?line 'NULL' = erl_tl(P, abc),
 
588
    ?line 'NULL' = erl_tl(P, []),
 
589
 
 
590
    ?line [] = erl_tl(P, [a]),
 
591
    ?line [b] = erl_tl(P, [a, b]),
 
592
    ?line [b, c] = erl_tl(P, [a, b, c]),
 
593
 
 
594
    ?line b = erl_tl(P, [a|b]),
 
595
 
 
596
    ?line runner:send_eot(P),
 
597
    ?line runner:recv_eot(P),
 
598
    ok.
 
599
 
 
600
%% Invokes the erl_tail() function in erl_interface.
 
601
 
 
602
erl_tl(Port, List) ->
 
603
    call_erl_function(Port, List).
 
604
 
 
605
%% Tests the type checking macros (done in the C program).
 
606
 
 
607
type_checks(suite) -> [];
 
608
type_checks(Config) when is_list(Config) ->
 
609
    ?line runner:test(?type_checks),
 
610
    ok.
 
611
 
 
612
%% Tests the extractor macros (done in the C program).
 
613
 
 
614
extractor_macros(suite) -> [];
 
615
extractor_macros(Config) when is_list(Config) ->
 
616
    ?line runner:test(?extractor_macros),
 
617
    ok.
 
618
 
 
619
 
 
620
%% This tests the erl_size() function.
 
621
 
 
622
t_erl_size(suite) -> [];
 
623
t_erl_size(Config) when is_list(Config) ->
 
624
    ?line P = runner:start(?t_erl_size),
 
625
 
 
626
    ?line {term, 0} = (get_term(P)),
 
627
    ?line {term, 4} = (get_term(P)),
 
628
 
 
629
    ?line {term, 0} = (get_term(P)),
 
630
    ?line {term, 27} = (get_term(P)),
 
631
 
 
632
    ?line runner:recv_eot(P),
 
633
    ok.
 
634
 
 
635
 
 
636
%% This tests the erl_var_content() function.
 
637
 
 
638
t_erl_var_content(suite) -> [];
 
639
t_erl_var_content(Config) when is_list(Config) ->
 
640
    ?line P = runner:start(?t_erl_var_content),
 
641
 
 
642
    ?line {term, 17} = (get_term(P)),
 
643
    ?line {term, "http://www.madonna.com"} = (get_term(P)),
 
644
    ?line {term, 2} = (get_term(P)),
 
645
    ?line {term, "http://www.madonna.com"} = (get_term(P)),
 
646
    ?line {term, 2} = (get_term(P)),
 
647
 
 
648
    ?line runner:recv_eot(P),
 
649
    ok.
 
650
 
 
651
 
 
652
%% This tests the erl_element() function.
 
653
 
 
654
t_erl_element(suite) -> [];
 
655
t_erl_element(Config) when is_list(Config) ->
 
656
    ?line P = runner:start(?t_erl_element),
 
657
 
 
658
    ?line {term, madonna} = get_term(P),
 
659
    ?line {term, 21} = get_term(P),
 
660
    ?line {term, 'mad donna'} = get_term(P),
 
661
    ?line {term, 12} = get_term(P),
 
662
 
 
663
    ?line {term, 'Madonna'} = get_term(P),
 
664
    ?line {term, 21} = get_term(P),
 
665
    ?line {term, {children,{"Isabella",2}}} = get_term(P),
 
666
    ?line {term, {'home page',"http://www.madonna.com/"}} = get_term(P),
 
667
 
 
668
    ?line runner:recv_eot(P),
 
669
    ok.
 
670
 
 
671
 
 
672
 
 
673
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
674
%%%
 
675
%%%     4.   I / O   l i s t   f u n c t i o n s
 
676
%%%
 
677
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
678
 
 
679
%% Tests the erl_iolist_length() function.
 
680
 
 
681
t_erl_iolist_length(suite) -> [];
 
682
t_erl_iolist_length(Config) when is_list(Config) ->
 
683
    ?line P = runner:start(?t_erl_iolist_length),
 
684
 
 
685
    %% Flat lists.
 
686
 
 
687
    ?line 0 = erl_iolist_length(P, []),
 
688
    ?line 1 = erl_iolist_length(P, [10]),
 
689
    ?line 2 = erl_iolist_length(P, [10, 20]),
 
690
    ?line 3 = erl_iolist_length(P, [10, 20, 30]),
 
691
    ?line 256 = erl_iolist_length(P, lists:seq(0, 255)),
 
692
 
 
693
    %% Deep lists.
 
694
 
 
695
    ?line 0 = erl_iolist_length(P, [[]]),
 
696
    ?line 1 = erl_iolist_length(P, [[], 42]),
 
697
    ?line 1 = erl_iolist_length(P, [42, []]),
 
698
    ?line 2 = erl_iolist_length(P, [42, [], 45]),
 
699
 
 
700
    ?line 3 = erl_iolist_length(P, [42, [90], 45]),
 
701
    ?line 3 = erl_iolist_length(P, [[42, [90]], 45]),
 
702
    ?line 3 = erl_iolist_length(P, [[42, [90]], 45]),
 
703
 
 
704
    %% List with binaries.
 
705
 
 
706
    ?line 0 = erl_iolist_length(P, [list_to_binary([])]),
 
707
    ?line 0 = erl_iolist_length(P, [[], list_to_binary([])]),
 
708
    ?line 1 = erl_iolist_length(P, [[1], list_to_binary([])]),
 
709
    ?line 1 = erl_iolist_length(P, [[], list_to_binary([2])]),
 
710
    ?line 2 = erl_iolist_length(P, [[42], list_to_binary([2])]),
 
711
    ?line 4 = erl_iolist_length(P, [[42], list_to_binary([2, 3, 4])]),
 
712
 
 
713
    %% Binaries as tail.
 
714
 
 
715
    ?line 0 = erl_iolist_length(P, [[]| list_to_binary([])]),
 
716
    ?line 1 = erl_iolist_length(P, [[1]| list_to_binary([])]),
 
717
    ?line 1 = erl_iolist_length(P, [[]| list_to_binary([2])]),
 
718
    ?line 2 = erl_iolist_length(P, [[42]| list_to_binary([2])]),
 
719
 
 
720
    %% Binaries only.
 
721
 
 
722
    ?line 0 = erl_iolist_length(P, list_to_binary("")),
 
723
    ?line 1 = erl_iolist_length(P, list_to_binary([1])),
 
724
    ?line 2 = erl_iolist_length(P, list_to_binary([1, 2])),
 
725
 
 
726
    %% Illegal cases.
 
727
 
 
728
    ?line -1 = erl_iolist_length(P, [42|43]),
 
729
    ?line -1 = erl_iolist_length(P, a),
 
730
 
 
731
    ?line -1 = erl_iolist_length(P, [a]),
 
732
    ?line -1 = erl_iolist_length(P, [256]),
 
733
    ?line -1 = erl_iolist_length(P, [257]),
 
734
    ?line -1 = erl_iolist_length(P, [-1]),
 
735
    ?line -1 = erl_iolist_length(P, [-2]),
 
736
    ?line -1 = erl_iolist_length(P, [-127]),
 
737
    ?line -1 = erl_iolist_length(P, [-128]),
 
738
 
 
739
    ?line runner:finish(P),
 
740
    ok.
 
741
 
 
742
%% Invokes the erl_iolist_length() function.
 
743
 
 
744
erl_iolist_length(Port, List) ->
 
745
    call_erl_function(Port, List).
 
746
 
 
747
%% Tests the erl_iolist_to_binary() function.
 
748
 
 
749
t_erl_iolist_to_binary(suite) -> [];
 
750
t_erl_iolist_to_binary(Config) when is_list(Config) ->
 
751
    ?line P = runner:start(?t_erl_iolist_to_binary),
 
752
 
 
753
    %% Flat lists.
 
754
 
 
755
    ?line [] = iolist_to_list(P, []),
 
756
    ?line [10] = iolist_to_list(P, [10]),
 
757
    ?line [10, 20] = iolist_to_list(P, [10, 20]),
 
758
    ?line [10, 20, 30] = iolist_to_list(P, [10, 20, 30]),
 
759
    ?line AllBytes = lists:seq(0, 255),
 
760
    ?line AllBytes = iolist_to_list(P, AllBytes),
 
761
 
 
762
    %% Deep lists.
 
763
 
 
764
    ?line [] = iolist_to_list(P, [[]]),
 
765
    ?line [42] = iolist_to_list(P, [[], 42]),
 
766
    ?line [42] = iolist_to_list(P, [42, []]),
 
767
    ?line [42, 45] = iolist_to_list(P, [42, [], 45]),
 
768
 
 
769
    ?line [42, 90, 45] = iolist_to_list(P, [42, [90], 45]),
 
770
    ?line [42, 90, 45] = iolist_to_list(P, [[42, [90]], 45]),
 
771
    ?line [42, 90, 45] = iolist_to_list(P, [[42, [90]], 45]),
 
772
 
 
773
    %% List with binaries.
 
774
 
 
775
    ?line [] = iolist_to_list(P, [list_to_binary([])]),
 
776
    ?line [] = iolist_to_list(P, [[], list_to_binary([])]),
 
777
    ?line [1] = iolist_to_list(P, [[1], list_to_binary([])]),
 
778
    ?line [2] = iolist_to_list(P, [[], list_to_binary([2])]),
 
779
    ?line [42, 2] = iolist_to_list(P, [[42], list_to_binary([2])]),
 
780
    ?line [42, 2, 3, 4] = iolist_to_list(P, [[42], list_to_binary([2, 3, 4])]),
 
781
 
 
782
    %% Binaries as tail.
 
783
 
 
784
    ?line [] = iolist_to_list(P, [[]| list_to_binary([])]),
 
785
    ?line [1] = iolist_to_list(P, [[1]| list_to_binary([])]),
 
786
    ?line [2] = iolist_to_list(P, [[]| list_to_binary([2])]),
 
787
    ?line [42, 2] = iolist_to_list(P, [[42]| list_to_binary([2])]),
 
788
 
 
789
    %% Binaries only.
 
790
 
 
791
    ?line [] = iolist_to_list(P, list_to_binary("")),
 
792
    ?line [1] = iolist_to_list(P, list_to_binary([1])),
 
793
    ?line [1, 2] = iolist_to_list(P, list_to_binary([1, 2])),
 
794
 
 
795
    %% Illegal cases.
 
796
 
 
797
    ?line 'NULL' = iolist_to_list(P, [42|43]),
 
798
    ?line 'NULL' = iolist_to_list(P, a),
 
799
 
 
800
    ?line 'NULL' = iolist_to_list(P, [a]),
 
801
    ?line 'NULL' = iolist_to_list(P, [256]),
 
802
    ?line 'NULL' = iolist_to_list(P, [257]),
 
803
    ?line 'NULL' = iolist_to_list(P, [-1]),
 
804
    ?line 'NULL' = iolist_to_list(P, [-2]),
 
805
    ?line 'NULL' = iolist_to_list(P, [-127]),
 
806
    ?line 'NULL' = iolist_to_list(P, [-128]),
 
807
 
 
808
    ?line runner:finish(P),
 
809
    ok.
 
810
 
 
811
iolist_to_list(Port, Term) ->
 
812
    case call_erl_function(Port, Term) of
 
813
        'NULL' ->
 
814
            'NULL';
 
815
        Bin when is_binary(Bin) ->
 
816
            binary_to_list(Bin)
 
817
    end.
 
818
 
 
819
%% Tests the erl_iolist_to_string() function.
 
820
 
 
821
t_erl_iolist_to_string(suite) -> [];
 
822
t_erl_iolist_to_string(Config) when is_list(Config) ->
 
823
    ?line P = runner:start(?t_erl_iolist_to_string),
 
824
 
 
825
    %% Flat lists.
 
826
 
 
827
    ?line [0] = iolist_to_string(P, []),
 
828
    ?line [10, 0] = iolist_to_string(P, [10]),
 
829
    ?line [10, 20, 0] = iolist_to_string(P, [10, 20]),
 
830
    ?line [10, 20, 30, 0] = iolist_to_string(P, [10, 20, 30]),
 
831
    ?line AllBytes = lists:seq(1, 255)++[0],
 
832
    ?line AllBytes = iolist_to_string(P, lists:seq(1, 255)),
 
833
 
 
834
    %% Deep lists.
 
835
 
 
836
    ?line [0] = iolist_to_string(P, [[]]),
 
837
    ?line [42, 0] = iolist_to_string(P, [[], 42]),
 
838
    ?line [42, 0] = iolist_to_string(P, [42, []]),
 
839
    ?line [42, 45, 0] = iolist_to_string(P, [42, [], 45]),
 
840
 
 
841
    ?line [42, 90, 45, 0] = iolist_to_string(P, [42, [90], 45]),
 
842
    ?line [42, 90, 45, 0] = iolist_to_string(P, [[42, [90]], 45]),
 
843
    ?line [42, 90, 45, 0] = iolist_to_string(P, [[42, [90]], 45]),
 
844
 
 
845
    %% List with binaries.
 
846
 
 
847
    ?line [0] = iolist_to_string(P, [list_to_binary([])]),
 
848
    ?line [0] = iolist_to_string(P, [[], list_to_binary([])]),
 
849
    ?line [1, 0] = iolist_to_string(P, [[1], list_to_binary([])]),
 
850
    ?line [2, 0] = iolist_to_string(P, [[], list_to_binary([2])]),
 
851
    ?line [42, 2, 0] = iolist_to_string(P, [[42], list_to_binary([2])]),
 
852
    ?line [42, 2, 3, 4, 0] = iolist_to_string(P, [[42],
 
853
                                                  list_to_binary([2, 3, 4])]),
 
854
 
 
855
    %% Binaries as tail.
 
856
 
 
857
    ?line [0] = iolist_to_string(P, [[]| list_to_binary([])]),
 
858
    ?line [1, 0] = iolist_to_string(P, [[1]| list_to_binary([])]),
 
859
    ?line [2, 0] = iolist_to_string(P, [[]| list_to_binary([2])]),
 
860
    ?line [42, 2, 0] = iolist_to_string(P, [[42]| list_to_binary([2])]),
 
861
 
 
862
    %% Binaries only.
 
863
 
 
864
    ?line [0] = iolist_to_string(P, list_to_binary("")),
 
865
    ?line [1, 0] = iolist_to_string(P, list_to_binary([1])),
 
866
    ?line [1, 2, 0] = iolist_to_string(P, list_to_binary([1, 2])),
 
867
 
 
868
    %% Illegal cases.
 
869
 
 
870
    ?line 'NULL' = iolist_to_string(P, [0]),
 
871
    ?line 'NULL' = iolist_to_string(P, [65, 0, 66]),
 
872
    ?line 'NULL' = iolist_to_string(P, [65, 66, 67, 0]),
 
873
 
 
874
    ?line 'NULL' = iolist_to_string(P, [42|43]),
 
875
    ?line 'NULL' = iolist_to_string(P, a),
 
876
 
 
877
    ?line 'NULL' = iolist_to_string(P, [a]),
 
878
    ?line 'NULL' = iolist_to_string(P, [256]),
 
879
    ?line 'NULL' = iolist_to_string(P, [257]),
 
880
    ?line 'NULL' = iolist_to_string(P, [-1]),
 
881
    ?line 'NULL' = iolist_to_string(P, [-2]),
 
882
    ?line 'NULL' = iolist_to_string(P, [-127]),
 
883
    ?line 'NULL' = iolist_to_string(P, [-128]),
 
884
 
 
885
    ?line runner:finish(P),
 
886
    ok.
 
887
 
 
888
%% Invokes the erl_iolist_to_string() function.
 
889
 
 
890
iolist_to_string(Port, Term) ->
 
891
    runner:send_term(Port, Term),
 
892
    case get_term(Port) of
 
893
        {bytes, Result} -> Result;
 
894
        'NULL'       -> 'NULL'
 
895
    end.
 
896
 
 
897
 
 
898
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
899
%%%
 
900
%%%     5.   M i s c e l l a n o u s   T e s t s
 
901
%%%
 
902
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
903
 
 
904
erl_print_term(suite) -> [];
 
905
erl_print_term(doc) -> "Tests the erl_print_term() function";
 
906
erl_print_term(Config) when is_list(Config) ->
 
907
    ?line PrintTerm = print_term(Config),
 
908
    ?line P = open_port({spawn, PrintTerm}, [stream]),
 
909
 
 
910
    %% Lists.
 
911
 
 
912
    ?line print(P, "[]", []),
 
913
    ?line print(P, "[a]", [a]),
 
914
    ?line print(P, "[[a]]", [[a]]),
 
915
    ?line print(P, "[[]]", [[]]),
 
916
    ?line print(P, "[a,b,c]", [a,b,c]),
 
917
    ?line print(P, "[a,b|c]", [a,b|c]),
 
918
    ?line print(P, "[a,[],c]", [a,[],c]),
 
919
    ?line print(P, "[a,[1000,1],c]", [a,[1000,1],c]),
 
920
 
 
921
    %% Tuples.
 
922
 
 
923
    ?line print(P, "{}", {}),
 
924
    ?line print(P, "{ok}", {ok}),
 
925
    ?line print(P, "{1,2,3}", {1, 2, 3}),
 
926
 
 
927
    %% Pids.
 
928
 
 
929
    ?line {_X, Y, Z} = split_pid(self()),
 
930
    ?line PidString = lists:flatten(io_lib:format("<~s.~w.~w>",
 
931
                                                  [node(), Y, Z])),
 
932
    ?line print(P, PidString, self()),
 
933
 
 
934
    ?line unlink(P),
 
935
    ?line exit(P, die),
 
936
    ok.
 
937
 
 
938
split_pid(Pid) when is_pid(Pid) ->
 
939
    split_pid(pid_to_list(Pid), 0, []).
 
940
 
 
941
split_pid([$<|Rest], Cur, Result) ->
 
942
    split_pid(Rest, Cur, Result);
 
943
split_pid([Digit|Rest], Cur, Result) when $0 =< Digit, Digit =< $9 ->
 
944
    split_pid(Rest, 10*Cur+Digit-$0, Result);
 
945
split_pid([$.|Rest], Cur, Result) ->
 
946
    split_pid(Rest, 0, Result++[Cur]);
 
947
split_pid([$>], Cur, Result) ->
 
948
    list_to_tuple(Result++[Cur]).
 
949
 
 
950
print_string(suite) -> [];
 
951
print_string(doc) -> "Test printing a string with erl_print_term()";
 
952
print_string(Config) when is_list(Config) ->
 
953
    ?line PrintTerm = print_term(Config),
 
954
    ?line P = open_port({spawn, PrintTerm}, [stream]),
 
955
 
 
956
    %% Strings.
 
957
 
 
958
    ?line print(P, "\"ABC\"", "ABC"),
 
959
    ?line {11, "\"\\tABC\\r\\n\""} = print(P, "\tABC\r\n"),
 
960
 
 
961
    %% Not strings.
 
962
 
 
963
    ?line print(P, "[65,66,67,0]", "ABC\000"),
 
964
 
 
965
    ?line unlink(P),
 
966
    ?line exit(P, die),
 
967
    ok.
 
968
 
 
969
print(Port, TermString, Term) ->
 
970
    Length = length(TermString),
 
971
    {Length, TermString} = print(Port, Term).
 
972
 
 
973
%% This function uses the erl_print_term() function in erl_interface
 
974
%% to print a term.
 
975
%% Returns: {NumChars, Chars}
 
976
 
 
977
print(Port, Term) ->
 
978
    Bin = term_to_binary(Term),
 
979
    Size = size(Bin),
 
980
    Port ! {self(), {command, [Size div 256, Size rem 256, Bin]}},
 
981
    collect_line(Port, []).
 
982
 
 
983
collect_line(Port, Result) ->
 
984
    receive
 
985
        {Port, {data, Data}} ->
 
986
            case lists:reverse(Data) of
 
987
                [$\n|Rest] ->
 
988
                    collect_line1(Rest++Result, []);
 
989
                Chars ->
 
990
                    collect_line(Port, Chars++Result)
 
991
            end
 
992
    after test_server:seconds(5) ->
 
993
            test_server:fail("No response from C program")
 
994
    end.
 
995
 
 
996
collect_line1([$\r|Rest], Result) ->
 
997
    {list_to_integer(Result), lists:reverse(Rest)};
 
998
collect_line1([C|Rest], Result) ->
 
999
    collect_line1(Rest, [C|Result]).
 
1000
 
 
1001
%% Test case submitted by Per Lundgren, ERV.
 
1002
 
 
1003
high_chaparal(suite) -> [];
 
1004
high_chaparal(Config) when is_list(Config) ->
 
1005
    ?line P = runner:start(?high_chaparal),
 
1006
    ?line {term, [hello, world]} = get_term(P),
 
1007
    ?line runner:recv_eot(P),
 
1008
    ok.
 
1009
 
 
1010
%% OTP-7448
 
1011
broken_data(suite) -> [];
 
1012
broken_data(Config) when is_list(Config) ->
 
1013
    ?line P = runner:start(?broken_data),
 
1014
    ?line runner:recv_eot(P),
 
1015
    ok.
 
1016
 
 
1017
%% This calls a C function with one parameter and returns the result.
 
1018
 
 
1019
call_erl_function(Port, Term) ->
 
1020
    runner:send_term(Port, Term),
 
1021
    case get_term(Port) of
 
1022
        {term, Result} -> Result;
 
1023
        'NULL'       -> 'NULL'
 
1024
    end.
 
1025
 
 
1026
print_term(Config) when is_list(Config) ->
 
1027
    filename:join(?config(data_dir, Config), "print_term").
 
1028
 
 
1029
 
 
1030
 
 
1031
%%% We receive a ref from the cnode, and expect it to be a long ref.
 
1032
%%% We also send a ref we created ourselves, and expect to get it
 
1033
%%% back, without having been mutated into short form. We must take
 
1034
%%% care then to check the actual returned ref, and not the original
 
1035
%%% one, which is equal to it.
 
1036
cnode_1(suite) -> [];
 
1037
cnode_1(doc) -> "Tests involving cnode: sends a long ref from a cnode to us";
 
1038
cnode_1(Config) when is_list(Config) ->
 
1039
    ?line Cnode = filename:join(?config(data_dir, Config), "cnode"),
 
1040
    ?line register(mip, self()),
 
1041
    ?line spawn_link(?MODULE, start_cnode, [Cnode]),
 
1042
    ?line Ref1 = get_ref(),
 
1043
    io:format("Ref1 ~p~n", [Ref1]),
 
1044
    ?line check_ref(Ref1),
 
1045
    ?line Ref2 = make_ref(),
 
1046
    ?line receive
 
1047
              Pid -> Pid
 
1048
          end,
 
1049
    ?line Fun1 = fun(X) -> {Pid, X} end,        % sneak in a fun test here
 
1050
    %?line Fun1 = {wait_with_funs, new_dist_format},
 
1051
    ?line Term = {Ref2, Fun1, {1,2,3,4,5,6,7,8,9,10}},
 
1052
    %% A term which will overflow the original buffer used in 'cnode'.
 
1053
    ?line Pid ! Term,
 
1054
    ?line receive
 
1055
              Term2 ->
 
1056
                  io:format("received ~p~n", [Term2]),
 
1057
                  case Term2 of
 
1058
                      Term ->
 
1059
                          {Ref22,_,_} = Term2,
 
1060
                          ?line check_ref(Ref22);
 
1061
                      X ->
 
1062
                      test_server:fail({receive1,X})
 
1063
                  end
 
1064
          after 5000 ->
 
1065
                  test_server:fail(receive1)
 
1066
          end,
 
1067
    ?line receive
 
1068
              Pid ->
 
1069
                  ok;
 
1070
              Y ->
 
1071
                  test_server:fail({receive1,Y})
 
1072
          after 5000 ->
 
1073
                  test_server:fail(receive2)
 
1074
          end,
 
1075
    ?line io:format("ref = ~p~n", [Ref1]),
 
1076
    ?line check_ref(Ref1),
 
1077
    ok.
 
1078
 
 
1079
check_ref(Ref) ->
 
1080
    case bin_ext_type(Ref) of
 
1081
        101 ->
 
1082
            test_server:fail(oldref);
 
1083
        114 ->
 
1084
            ok;
 
1085
        Type ->
 
1086
            test_server:fail({type, Type})
 
1087
    end.
 
1088
 
 
1089
bin_ext_type(T) ->
 
1090
    [131, Type | _] = binary_to_list(term_to_binary(T)),
 
1091
    Type.
 
1092
 
 
1093
get_ref() ->
 
1094
    receive
 
1095
        X when is_reference(X) ->
 
1096
            X
 
1097
    after 5000 ->
 
1098
            test_server:fail({cnode, timeout})
 
1099
    end.
 
1100
 
 
1101
start_cnode(Cnode) ->
 
1102
    open_port({spawn, Cnode ++ " " ++ atom_to_list(erlang:get_cookie())}, []),
 
1103
    rec_cnode().
 
1104
 
 
1105
rec_cnode() ->
 
1106
    receive
 
1107
        X ->
 
1108
            io:format("from cnode: ~p~n", [X]),
 
1109
            rec_cnode()
 
1110
    end.
 
1111
 
 
1112
nc2vinfo(Pid) when is_pid(Pid) ->
 
1113
    ?line [_NodeStr, NumberStr, SerialStr]
 
1114
        = string:tokens(pid_to_list(Pid), "<.>"),
 
1115
    ?line Number = list_to_integer(NumberStr),
 
1116
    ?line Serial = list_to_integer(SerialStr),
 
1117
    ?line {pid, node(Pid), Number, Serial};
 
1118
nc2vinfo(Port) when is_port(Port) ->
 
1119
    ?line ["#Port", _NodeStr, NumberStr]
 
1120
        = string:tokens(erlang:port_to_list(Port), "<.>"),
 
1121
    ?line Number = list_to_integer(NumberStr),
 
1122
    ?line {port, node(Port), Number};    
 
1123
nc2vinfo(Ref) when is_reference(Ref) ->
 
1124
    ?line ["#Ref", _NodeStr | NumStrList]
 
1125
        = string:tokens(erlang:ref_to_list(Ref), "<.>"),
 
1126
    ?line {Len, RevNumList} = lists:foldl(fun ("0", {N, []}) ->
 
1127
                                                  {N+1, []};
 
1128
                                              (IStr, {N, Is}) ->
 
1129
                                                  {N+1,
 
1130
                                                   [list_to_integer(IStr)|Is]}
 
1131
                                          end,
 
1132
                                          {0, []},
 
1133
                                          NumStrList),
 
1134
    ?line {ref, node(Ref), Len, lists:reverse(RevNumList)};
 
1135
nc2vinfo(Other) ->
 
1136
    ?line {badarg, Other}.
 
1137
 
 
1138