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

« back to all changes in this revision

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