~statik/ubuntu/maverick/erlang/erlang-merge-testing

« back to all changes in this revision

Viewing changes to erts/emulator/test/nif_SUITE.erl

  • Committer: Elliot Murphy
  • Date: 2010-06-08 03:55:44 UTC
  • mfrom: (3.5.6 squeeze)
  • Revision ID: elliot@elliotmurphy.com-20100608035544-dd8zh2swk7jr5rz2
* Merge with Debian unstable; remaining Ubuntu changes:
  - Drop libwxgtk2.8-dev build dependency. Wx isn't in main, and not
    supposed to. (LP #438365)
  - 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.
* Added missing symlinks to /usr/include for a few new header files.
* Fixed generation of ${erlang-base:Depends} and ${erlang-x11:Depends}
  substitution variables.
* Added a fix for a re:compile/2 crash on a long regular expression.
* Changed urgency to medium as the change fixes a security bug.
* Manpages in section 1 are needed even if only arch-dependent packages are
  built. So, re-enabled them.
* Fixed HiPE architecture recognition for powerpc Debian architecture.
* Moved xsltproc and fop to build-depends-indep and do not build
  documentation if only architecture-specific packages are built.
* Refreshed all patches.
* Made Emacs look in man5 and man7 for Erlang manpages and added code
  skeleton files to erlang-mode package.
* New upstream release.
* Moved manpages from incorrect sections 4 and 6 to correct 5 and 7
  (closes: #498492).
* Made manpages regexp in Emacs mode match only 3erl pages in section 3.
* Removed docb_gen script which is no longer needed to build manpages.
* Added erlang-doc package which contains documentation in HTML and PDF
  formats. This package replaces erlang-doc-html package and it's easier
  to synchronize it with the main Erlang packages as it's built from
  a single source package (closes: #558451).
* Removed RPATH from ssl and crypto application binaries as required by
  Debian policy.
* Added libwxgtk2.4-dev and libwxgtk2.6-dev to build conflicts.
* Added a few dpendencies for erlang-dialyzer, erlang-et, erlang-observer
  and erlang-examples packages which now call functions from more modules
  than in 1:13.b.3.
* Added a workaround which disables vfork() for hppa architecture
  (closes: #562218).
* Strictened check for JDK 1.5 adding a call to String(int[], int, int)
  because GCJ 4.4 doesn't implement it and OpenJDK isn't available for all
  architectures.
* Fixed erlang-manpages package section.
* Made erlang-depends add only substvars which are requested in
  debian/control file. This minimizes number of warnings from dh_gencontrol.
  Also, improved descriptions of the functions in erlang-depends escript.
* Added erlang-erl-docgen package to erlang-nox dependencies.
* Made dummy packages erlang-nox and erlang-x11 architecture all.
* Cleaned up working with custom substitution variables in debian/rules.
* Reorganized debian/rules to ensure that manpages arent built twice, and
  aren't built at all if only architecture-dependent packages are requested.
* Fixed project links in README.Debian.
* Added a new package erlang-jinterface which provides tools for
  communication of Java programs with Erlang processes. This adds build
  depandency on default-jdk and as a result enables Java module for IDL
  compiler.
* Bumped standards version to 3.8.4.

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
1
%%
2
2
%% %CopyrightBegin%
3
 
%% 
4
 
%% Copyright Ericsson AB 2009. All Rights Reserved.
5
 
%% 
 
3
%%
 
4
%% Copyright Ericsson AB 2009-2010. All Rights Reserved.
 
5
%%
6
6
%% The contents of this file are subject to the Erlang Public License,
7
7
%% Version 1.1, (the "License"); you may not use this file except in
8
8
%% compliance with the License. You should have received a copy of the
9
9
%% Erlang Public License along with this software. If not, it can be
10
10
%% retrieved online at http://www.erlang.org/.
11
 
%% 
 
11
%%
12
12
%% Software distributed under the License is distributed on an "AS IS"
13
13
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
14
14
%% the License for the specific language governing rights and limitations
15
15
%% under the License.
16
 
%% 
 
16
%%
17
17
%% %CopyrightEnd%
18
18
%%
19
19
 
20
20
-module(nif_SUITE).
21
21
 
22
22
%%-define(line_trace,true).
 
23
%%-define(CHECK(Exp,Got), ?line check(Exp,Got,?LINE)).
 
24
-define(CHECK(Exp,Got), ?line Exp = Got).
23
25
 
24
26
-include("test_server.hrl").
25
27
 
26
28
-export([all/1, fin_per_testcase/2, basic/1, reload/1, upgrade/1, heap_frag/1,
27
 
         neg/1]).
 
29
         types/1, many_args/1, binaries/1, get_string/1, get_atom/1, api_macros/1,
 
30
         from_array/1, iolist_as_binary/1, resource/1, resource_takeover/1,
 
31
         threading/1, neg/1]).
28
32
 
 
33
-export([many_args_100/100]).
29
34
-define(nif_stub,nif_stub_error(?LINE)).
30
35
 
31
36
all(suite) ->
32
 
    [basic, reload, upgrade, heap_frag, neg].
 
37
    [basic, reload, upgrade, heap_frag, types, many_args, binaries, get_string,
 
38
     get_atom, api_macros, from_array, iolist_as_binary, resource,
 
39
     resource_takeover, threading, neg].
 
40
 
 
41
%%init_per_testcase(_Case, Config) ->
 
42
%%    ?line Dog = ?t:timetrap(?t:seconds(60*60*24)),
 
43
%%    [{watchdog, Dog}|Config].
33
44
 
34
45
fin_per_testcase(_Func, _Config) ->
 
46
    %%Dog = ?config(watchdog, Config),
 
47
    %%?t:timetrap_cancel(Dog),
35
48
    P1 = code:purge(nif_mod),
36
49
    Del = code:delete(nif_mod),
37
50
    P2 = code:purge(nif_mod),
50
63
reload(doc) -> ["Test reload callback in nif lib"];
51
64
reload(suite) -> [];  
52
65
reload(Config) when is_list(Config) ->    
 
66
    TmpMem = tmpmem(),
53
67
    ensure_lib_loaded(Config),
54
68
 
55
69
    ?line Data = ?config(data_dir, Config),
57
71
    ?line {ok,nif_mod,Bin} = compile:file(File, [binary,return_errors]),
58
72
    ?line {module,nif_mod} = erlang:load_module(nif_mod,Bin),
59
73
 
60
 
    ?line nif_mod:load_nif_lib(Config, 1),
 
74
    ?line ok = nif_mod:load_nif_lib(Config, 1),
61
75
 
62
76
    ?line hold_nif_mod_priv_data(nif_mod:get_priv_data_ptr()),
63
77
    ?line [{load,1,1,101},{get_priv_data_ptr,1,2,102}] = nif_mod_call_history(),    
64
78
        
65
 
    ?line nif_mod:load_nif_lib(Config, 2),
 
79
    ?line ok = nif_mod:load_nif_lib(Config, 2),
66
80
    ?line 2 = nif_mod:lib_version(),
67
81
    ?line [{reload,2,1,201},{lib_version,2,2,202}] = nif_mod_call_history(),    
68
82
 
69
 
    ?line nif_mod:load_nif_lib(Config, 1),
 
83
    ?line ok = nif_mod:load_nif_lib(Config, 1),
70
84
    ?line 1 = nif_mod:lib_version(),
71
85
    ?line [{reload,1,1,101},{lib_version,1,2,102}] = nif_mod_call_history(),    
72
86
 
78
92
    ?line [{unload,1,3,103}] = nif_mod_call_history(),    
79
93
 
80
94
    ?line [?MODULE, nif_mod] = erlang:system_info(taints),
 
95
    ?line verify_tmpmem(TmpMem),
81
96
    ok.
82
97
 
83
98
upgrade(doc) -> ["Test upgrade callback in nif lib"];
84
99
upgrade(suite) -> [];  
85
100
upgrade(Config) when is_list(Config) ->    
 
101
    TmpMem = tmpmem(),
86
102
    ensure_lib_loaded(Config),
87
103
 
88
104
    ?line Data = ?config(data_dir, Config),
90
106
    ?line {ok,nif_mod,Bin} = compile:file(File, [binary,return_errors]),
91
107
    ?line {module,nif_mod} = erlang:load_module(nif_mod,Bin),
92
108
 
93
 
    ?line nif_mod:load_nif_lib(Config, 1),
 
109
    ?line ok = nif_mod:load_nif_lib(Config, 1),
94
110
    ?line {Pid,MRef} = nif_mod:start(),
95
111
    ?line 1 = call(Pid,lib_version),
96
112
 
103
119
    ?line 1 = call(Pid,lib_version),
104
120
    ?line [{lib_version,1,4,104}] = nif_mod_call_history(),
105
121
 
106
 
    ?line nif_mod:load_nif_lib(Config, 1),
 
122
    ?line ok = nif_mod:load_nif_lib(Config, 1),
107
123
    ?line 1 = nif_mod:lib_version(),
108
124
    ?line [{upgrade,1,5,105},{lib_version,1,6,106}] = nif_mod_call_history(),
109
125
 
130
146
    ?line {Pid2,MRef2} = nif_mod:start(),
131
147
    ?line undefined = call(Pid2,lib_version),
132
148
 
133
 
    ?line nif_mod:load_nif_lib(Config, 1),
 
149
    ?line ok = nif_mod:load_nif_lib(Config, 1),
134
150
    ?line hold_nif_mod_priv_data(nif_mod:get_priv_data_ptr()),
135
151
    ?line 1 = call(Pid2,lib_version),
136
152
    ?line [{load,1,1,101},{get_priv_data_ptr,1,2,102},{lib_version,1,3,103}] = nif_mod_call_history(),
141
157
    ?line 1 = call(Pid2,lib_version),
142
158
    ?line [{lib_version,1,4,104}] = nif_mod_call_history(),
143
159
 
144
 
    ?line nif_mod:load_nif_lib(Config, 2),
 
160
    ?line ok = nif_mod:load_nif_lib(Config, 2),
145
161
    ?line 2 = nif_mod:lib_version(),
146
162
    ?line [{upgrade,2,1,201},{lib_version,2,2,202}] = nif_mod_call_history(),
147
163
 
166
182
    ?line [{unload,2,4,204}] = nif_mod_call_history(),    
167
183
 
168
184
    ?line [?MODULE, nif_mod] = erlang:system_info(taints),    
 
185
    ?line verify_tmpmem(TmpMem),
169
186
    ok.
170
187
 
171
188
heap_frag(doc) -> ["Test NIF building heap fragments"];
172
189
heap_frag(suite) -> [];  
173
190
heap_frag(Config) when is_list(Config) ->    
 
191
    TmpMem = tmpmem(),
174
192
    ensure_lib_loaded(Config),
175
193
    
176
194
    heap_frag_do(1,1000000),
 
195
    ?line verify_tmpmem(TmpMem),
177
196
    ok.
178
197
 
179
198
heap_frag_do(N, Max) when N > Max ->
184
203
    L = list_seq(N),
185
204
    heap_frag_do(((N*5) div 4) + 1, Max).
186
205
 
187
 
 
 
206
types(doc) -> ["Type tests"];
 
207
types(suite) -> [];
 
208
types(Config) when is_list(Config) ->
 
209
    TmpMem = tmpmem(),
 
210
    ensure_lib_loaded(Config),
 
211
    ?line ok = type_test(),
 
212
    lists:foreach(fun(Tpl) ->
 
213
                    Lst = erlang:tuple_to_list(Tpl),                 
 
214
                    Lst = tuple_2_list(Tpl)
 
215
                  end,
 
216
                  [{},{ok},{{}},{[],{}},{1,2,3,4,5}]),
 
217
    Stuff = [[],{},0,0.0,(1 bsl 100),(fun()-> ok end),make_ref(),self()],
 
218
    [eq_cmp(A,clone(B)) || A<-Stuff, B<-Stuff],                   
 
219
    ?line verify_tmpmem(TmpMem),
 
220
    ok.
 
221
 
 
222
clone(X) ->
 
223
    binary_to_term(term_to_binary(X)).
 
224
 
 
225
eq_cmp(A,B) ->
 
226
    eq_cmp_do(A,B),
 
227
    eq_cmp_do([A,B],[A,B]),
 
228
    eq_cmp_do({A,B},{A,B}).
 
229
 
 
230
eq_cmp_do(A,B) ->
 
231
    %%?t:format("compare ~p and ~p\n",[A,B]),
 
232
    Eq = (A =:= B),
 
233
    ?line Eq = is_identical(A,B),
 
234
    ?line Cmp = if
 
235
            A < B -> -1;
 
236
            A == B -> 0;
 
237
            A > B -> 1
 
238
        end,
 
239
    ?line Cmp = case compare(A,B) of
 
240
                    C when is_integer(C), C < 0 -> -1;
 
241
                    0 -> 0;
 
242
                    C when is_integer(C) -> 1
 
243
                end,       
 
244
    ok. 
 
245
 
 
246
 
 
247
many_args(doc) -> ["Test NIF with many arguments"];
 
248
many_args(suite) -> [];
 
249
many_args(Config) when is_list(Config) ->
 
250
    TmpMem = tmpmem(),
 
251
    ?line ensure_lib_loaded(Config ,1),
 
252
    ?line ok = apply(?MODULE,many_args_100,lists:seq(1,100)),
 
253
    ?line ok = many_args_100(1,2,3,4,5,6,7,8,9,10,11,12,13,14,15,16,17,18,19,20,21,22,23,24,25,26,27,28,29,30,31,32,33,34,35,36,37,38,39,40,41,42,43,44,45,46,47,48,49,50,51,52,53,54,55,56,57,58,59,60,61,62,63,64,65,66,67,68,69,70,71,72,73,74,75,76,77,78,79,80,81,82,83,84,85,86,87,88,89,90,91,92,93,94,95,96,97,98,99,100),
 
254
    ?line verify_tmpmem(TmpMem),
 
255
    ok.
 
256
 
 
257
binaries(doc) -> ["Test NIF binary handling."];
 
258
binaries(suite) -> [];
 
259
binaries(Config) when is_list(Config) ->
 
260
    TmpMem = tmpmem(),
 
261
    ?line ensure_lib_loaded(Config, 1),
 
262
    ?line RefcBin = list_to_binary(lists:seq(1,255)),
 
263
    ?line RefcBin = clone_bin(RefcBin),
 
264
    ?line HeapBin = list_to_binary(lists:seq(1,20)),
 
265
    ?line HeapBin = clone_bin(HeapBin),
 
266
    ?line <<_:8,Sub1:6/binary,_/binary>> = RefcBin, 
 
267
    ?line <<_:8,Sub2:6/binary,_/binary>> = HeapBin,
 
268
    ?line Sub1 = Sub2,
 
269
    ?line Sub1 = clone_bin(Sub1),
 
270
    ?line Sub2 = clone_bin(Sub2),
 
271
    ?line <<_:9,Sub3:6/binary,_/bitstring>> = RefcBin, 
 
272
    ?line <<_:9,Sub4:6/binary,_/bitstring>> = HeapBin,
 
273
    ?line Sub3 = Sub4,
 
274
    ?line Sub3 = clone_bin(Sub3),
 
275
    ?line Sub4 = clone_bin(Sub4),
 
276
    %% When NIFs get bitstring support
 
277
    %%?line <<_:8,Sub5:27/bitstring,_/bitstring>> = RefcBin, 
 
278
    %%?line <<_:8,Sub6:27/bitstring,_/bitstring>> = HeapBin,
 
279
    %%?line Sub5 = Sub6,
 
280
    %%?line Sub5 = clone_bin(Sub5),
 
281
    %%?line Sub6 = clone_bin(Sub6),
 
282
    %%?line <<_:9,Sub7:27/bitstring,_/bitstring>> = RefcBin, 
 
283
    %%?line <<_:9,Sub8:27/bitstring,_/bitstring>> = HeapBin,
 
284
    %%?line Sub7 = Sub8,
 
285
    %%?line Sub7 = clone_bin(Sub7),
 
286
    %%?line Sub8 = clone_bin(Sub8),
 
287
    %%?line <<>> = clone_bin(<<>>),
 
288
 
 
289
    <<_:8,SubBinA:200/binary,_/binary>> = RefcBin,
 
290
    <<_:9,SubBinB:200/binary,_/bitstring>> = RefcBin,
 
291
    <<_:8,SubBinC:17/binary,_/binary>> = HeapBin,
 
292
    <<_:9,SubBinD:17/binary,_/bitstring>> = HeapBin,
 
293
    test_make_sub_bin(RefcBin),
 
294
    test_make_sub_bin(HeapBin),
 
295
    test_make_sub_bin(SubBinA),
 
296
    test_make_sub_bin(SubBinB),
 
297
    test_make_sub_bin(SubBinC),
 
298
    test_make_sub_bin(SubBinD),
 
299
    
 
300
    ?line verify_tmpmem(TmpMem),
 
301
    ok.
 
302
 
 
303
test_make_sub_bin(Bin) ->
 
304
    Size = byte_size(Bin),
 
305
    Rest10 = Size - 10,
 
306
    Rest1 = Size - 1,
 
307
    ?line Bin = make_sub_bin(Bin, 0, Size),
 
308
    <<_:10/binary,Sub0:Rest10/binary>> = Bin,
 
309
    ?line Sub0 = make_sub_bin(Bin, 10, Rest10),
 
310
    <<Sub1:10/binary,_/binary>> = Bin,
 
311
    ?line Sub1 = make_sub_bin(Bin, 0, 10),
 
312
    <<_:7/binary,Sub2:10/binary,_/binary>> = Bin,
 
313
    ?line Sub2 = make_sub_bin(Bin, 7, 10),
 
314
    ?line <<>> = make_sub_bin(Bin, 0, 0),
 
315
    ?line <<>> = make_sub_bin(Bin, 10, 0),
 
316
    ?line <<>> = make_sub_bin(Bin, Rest1, 0),
 
317
    ?line <<>> = make_sub_bin(Bin, Size, 0),
 
318
    ok.
 
319
    
 
320
get_string(doc) -> ["Test enif_get_string"];
 
321
get_string(suite) -> [];
 
322
get_string(Config) when is_list(Config) ->
 
323
    ?line ensure_lib_loaded(Config, 1),
 
324
    ?line {7, <<"hejsan",0,_:3/binary>>} = string_to_bin("hejsan",10),
 
325
    ?line {7, <<"hejsan",0,_>>} = string_to_bin("hejsan",8),
 
326
    ?line {7, <<"hejsan",0>>} = string_to_bin("hejsan",7),
 
327
    ?line {-6, <<"hejsa",0>>} = string_to_bin("hejsan",6),
 
328
    ?line {-5, <<"hejs",0>>} = string_to_bin("hejsan",5),
 
329
    ?line {-1, <<0>>} = string_to_bin("hejsan",1),
 
330
    ?line {0, <<>>} = string_to_bin("hejsan",0),
 
331
    ?line {1, <<0>>} = string_to_bin("",1),
 
332
    ?line {0, <<>>} = string_to_bin("",0),
 
333
    ok.
 
334
 
 
335
get_atom(doc) -> ["Test enif_get_atom"];
 
336
get_atom(suite) -> [];
 
337
get_atom(Config) when is_list(Config) ->
 
338
    ?line ensure_lib_loaded(Config, 1),
 
339
    ?line {7, <<"hejsan",0,_:3/binary>>} = atom_to_bin(hejsan,10),
 
340
    ?line {7, <<"hejsan",0,_>>} = atom_to_bin(hejsan,8),
 
341
    ?line {7, <<"hejsan",0>>} = atom_to_bin(hejsan,7),
 
342
    ?line {0, <<_:6/binary>>} = atom_to_bin(hejsan,6),
 
343
    ?line {0, <<>>} = atom_to_bin(hejsan,0),
 
344
    ?line {1, <<0>>} = atom_to_bin('',1),
 
345
    ?line {0, <<>>} = atom_to_bin('',0),
 
346
    ok.
 
347
 
 
348
api_macros(doc) -> ["Test macros enif_make_list<N> and enif_make_tuple<N>"];
 
349
api_macros(suite) -> [];
 
350
api_macros(Config) when is_list(Config) ->
 
351
    ?line ensure_lib_loaded(Config, 1),
 
352
    Expected = {[lists:seq(1,N) || N <- lists:seq(1,9)],
 
353
                [list_to_tuple(lists:seq(1,N)) || N <- lists:seq(1,9)]
 
354
               },
 
355
    ?line Expected = macros(list_to_tuple(lists:seq(1,9))),
 
356
    ok.
 
357
 
 
358
from_array(doc) -> ["enif_make_[tuple|list]_from_array"];
 
359
from_array(suite) -> [];
 
360
from_array(Config) when is_list(Config) ->
 
361
    ?line ensure_lib_loaded(Config, 1),
 
362
    lists:foreach(fun(Tpl) ->
 
363
                          Lst = tuple_to_list(Tpl),
 
364
                          ?line {Lst,Tpl} = tuple_2_list_and_tuple(Tpl)
 
365
                  end,
 
366
                  [{}, {1,2,3}, {[4,5],[],{},{6,7}}, {{}}, {[]}]),
 
367
    ok.
 
368
 
 
369
iolist_as_binary(doc) -> ["enif_inspect_iolist_as_binary"];
 
370
iolist_as_binary(suite) -> [];
 
371
iolist_as_binary(Config) when is_list(Config) ->
 
372
    ?line ensure_lib_loaded(Config, 1),
 
373
    TmpMem = tmpmem(),
 
374
    List = [<<"hejsan">>, <<>>, [], [17], [<<>>],
 
375
            [127,128,255,0],
 
376
            [1, 2, 3, <<"abc">>, [<<"def">>,4], 5, <<"ghi">>],
 
377
            [1, 2, 3, <<"abc">>, [<<"def">>,4], 5 | <<"ghi">>]],
 
378
            
 
379
    lists:foreach(fun(IoL) ->
 
380
                          B1 = erlang:iolist_to_binary(IoL),
 
381
                          ?line B2 = iolist_2_bin(IoL),
 
382
                          ?line B1 = B2
 
383
                  end,
 
384
                  List),
 
385
    ?line verify_tmpmem(TmpMem),
 
386
    ok.
 
387
 
 
388
resource(doc) -> ["Test memory managed objects, aka 'resources'"];
 
389
resource(suite) -> [];
 
390
resource(Config) when is_list(Config) ->
 
391
    ?line ensure_lib_loaded(Config, 1),
 
392
    ?line Type = get_resource_type(0),
 
393
    resource_hugo(Type),
 
394
    resource_otto(Type),
 
395
    resource_new(Type),
 
396
    resource_neg(Type),
 
397
    ok.
 
398
 
 
399
resource_hugo(Type) ->
 
400
    DtorCall = resource_hugo_do(Type),
 
401
    erlang:garbage_collect(),
 
402
    ?line DtorCall = last_resource_dtor_call(),
 
403
    ok.
 
404
 
 
405
resource_hugo_do(Type) ->
 
406
    HugoBin = <<"Hugo Hacker">>,
 
407
    ?line HugoPtr = alloc_resource(Type, HugoBin),
 
408
    ?line Hugo = make_resource(HugoPtr),
 
409
    ?line <<>> = Hugo,
 
410
    release_resource(HugoPtr),
 
411
    erlang:garbage_collect(),
 
412
    ?line {HugoPtr,HugoBin} = get_resource(Type,Hugo),
 
413
    Pid = spawn_link(fun() ->                        
 
414
                             receive {Pid, Type, Resource, Ptr, Bin} ->
 
415
                                     Pid ! {self(), got_it},
 
416
                                     receive {Pid, check_it} ->
 
417
                                             ?line {Ptr,Bin} = get_resource(Type,Resource),
 
418
                                             Pid ! {self(), ok}
 
419
                                     end
 
420
                             end
 
421
                     end),
 
422
    Pid ! {self(), Type, Hugo, HugoPtr, HugoBin},
 
423
    ?line {Pid, got_it} = receive_any(),
 
424
    erlang:garbage_collect(),   % just to make our ProcBin move in memory
 
425
    Pid ! {self(), check_it},
 
426
    ?line {Pid, ok} = receive_any(),
 
427
    ?line [] = last_resource_dtor_call(),
 
428
    ?line {HugoPtr,HugoBin} = get_resource(Type,Hugo),
 
429
    {HugoPtr, HugoBin, 1}.
 
430
 
 
431
resource_otto(Type) ->
 
432
    {OttoPtr, OttoBin} = resource_otto_do(Type),
 
433
    erlang:garbage_collect(),
 
434
    ?line [] = last_resource_dtor_call(),
 
435
    release_resource(OttoPtr),
 
436
    ?line {OttoPtr,OttoBin,1} = last_resource_dtor_call(),
 
437
    ok.
 
438
    
 
439
resource_otto_do(Type) ->
 
440
    OttoBin = <<"Otto Ordonnans">>,
 
441
    ?line OttoPtr = alloc_resource(Type, OttoBin),
 
442
    ?line Otto = make_resource(OttoPtr),
 
443
    ?line <<>> = Otto,
 
444
    %% forget resource term but keep referenced by NIF
 
445
    {OttoPtr, OttoBin}.    
 
446
 
 
447
resource_new(Type) ->
 
448
    ?line {PtrB,BinB} = resource_new_do1(Type),
 
449
    erlang:garbage_collect(),
 
450
    ?line {PtrB,BinB,1} = last_resource_dtor_call(),
 
451
    ok.
 
452
    
 
453
resource_new_do1(Type) ->
 
454
    ?line {{PtrA,BinA}, {ResB,PtrB,BinB}} = resource_new_do2(Type),
 
455
    erlang:garbage_collect(),
 
456
    ?line {PtrA,BinA,1} = last_resource_dtor_call(),
 
457
    ?line {PtrB,BinB} = get_resource(Type, ResB),
 
458
    %% forget ResB and make it garbage
 
459
    {PtrB,BinB}.
 
460
    
 
461
resource_new_do2(Type) ->
 
462
    BinA = <<"NewA">>,
 
463
    BinB = <<"NewB">>,
 
464
    ?line ResA = make_new_resource(Type, BinA),
 
465
    ?line ResB = make_new_resource(Type, BinB),
 
466
    ?line <<>> = ResA,
 
467
    ?line <<>> = ResB,
 
468
    ?line {PtrA,BinA} = get_resource(Type, ResA),
 
469
    ?line {PtrB,BinB} = get_resource(Type, ResB),
 
470
    ?line true = (PtrA =/= PtrB),
 
471
    ?line [] = last_resource_dtor_call(),
 
472
    %% forget ResA and make it garbage
 
473
    {{PtrA,BinA}, {ResB,PtrB,BinB}}.
 
474
 
 
475
resource_neg(TypeA) ->
 
476
    TypeB = get_resource_type(1),
 
477
    Aptr = alloc_resource(TypeA, <<"Arnold">>),
 
478
    Bptr = alloc_resource(TypeB, <<"Bobo">>),
 
479
    ?line {'EXIT',{badarg,_}} = (catch get_resource(TypeA, Bptr)),
 
480
    ?line {'EXIT',{badarg,_}} = (catch get_resource(TypeB, Aptr)),
 
481
    ok.
 
482
    
 
483
-define(RT_CREATE,1).
 
484
-define(RT_TAKEOVER,2).
 
485
 
 
486
resource_takeover(doc) -> ["Test resource takeover by module reload and upgrade"];
 
487
resource_takeover(suite) -> [];  
 
488
resource_takeover(Config) when is_list(Config) ->    
 
489
    TmpMem = tmpmem(),
 
490
    ensure_lib_loaded(Config),
 
491
 
 
492
    ?line Data = ?config(data_dir, Config),
 
493
    ?line File = filename:join(Data, "nif_mod"),
 
494
    ?line {ok,nif_mod,ModBin} = compile:file(File, [binary,return_errors]),
 
495
    ?line {module,nif_mod} = erlang:load_module(nif_mod,ModBin),
 
496
 
 
497
    ?line ok = nif_mod:load_nif_lib(Config, 1, 
 
498
                                    [{resource_type, 0, ?RT_CREATE, "resource_type_A",resource_dtor_A,
 
499
                                      ?RT_CREATE},
 
500
                                     {resource_type, 1, ?RT_CREATE, "resource_type_null_A",null,
 
501
                                      ?RT_CREATE},
 
502
                                     {resource_type, 2, ?RT_CREATE bor ?RT_TAKEOVER, "resource_type_A_null",resource_dtor_A,
 
503
                                      ?RT_CREATE},
 
504
                                     {resource_type, 3, ?RT_CREATE, "resource_type_B_goneX",resource_dtor_B,
 
505
                                      ?RT_CREATE},
 
506
                                     {resource_type, 4, ?RT_CREATE, "resource_type_null_goneX",null,
 
507
                                      ?RT_CREATE},
 
508
                                     {resource_type, null, ?RT_TAKEOVER, "Pink unicorn", resource_dtor_A,
 
509
                                      ?RT_TAKEOVER}
 
510
                                    ]),
 
511
 
 
512
    ?line hold_nif_mod_priv_data(nif_mod:get_priv_data_ptr()),
 
513
    ?line [{load,1,1,101},{get_priv_data_ptr,1,2,102}] = nif_mod_call_history(),
 
514
 
 
515
    ?line {Holder, _MRef} = spawn_opt(fun resource_holder/0, [link, monitor]),
 
516
 
 
517
    {A1,BinA1} = make_resource(0,Holder,"A1"),
 
518
    {A2,BinA2} = make_resource(0,Holder,"A2"),
 
519
    {A3,BinA3} = make_resource(0,Holder,"A3"),
 
520
 
 
521
    {NA1,_BinNA1} = make_resource(1,Holder,"NA1"),
 
522
    {NA2,BinNA2} = make_resource(1,Holder,"NA2"),
 
523
    {NA3,_BinNA3} = make_resource(1,Holder,"NA3"),
 
524
 
 
525
    {AN1,BinAN1} = make_resource(2,Holder,"AN1"),
 
526
    {AN2,_BinAN2} = make_resource(2,Holder,"AN2"),
 
527
    {AN3,BinAN3} = make_resource(2,Holder,"AN3"),
 
528
 
 
529
    {BGX1,BinBGX1} = make_resource(3,Holder,"BGX1"),
 
530
    {BGX2,BinBGX2} = make_resource(3,Holder,"BGX2"),
 
531
 
 
532
    {NGX1,_BinNGX1} = make_resource(4,Holder,"NGX1"),
 
533
    {NGX2,_BinNGX2} = make_resource(4,Holder,"NGX2"),
 
534
 
 
535
    ?line [] = nif_mod_call_history(),
 
536
 
 
537
    ?line ok = forget_resource(A1),
 
538
    ?line [{{resource_dtor_A_v1,BinA1},1,3,103}] = nif_mod_call_history(),    
 
539
 
 
540
    ?line ok = forget_resource(NA1),
 
541
    ?line [] = nif_mod_call_history(), % no dtor
 
542
 
 
543
    ?line ok = forget_resource(AN1),
 
544
    ?CHECK([{{resource_dtor_A_v1,BinAN1},1,4,104}] , nif_mod_call_history()),
 
545
 
 
546
    ?line ok = forget_resource(BGX1),
 
547
    ?CHECK([{{resource_dtor_B_v1,BinBGX1},1,5,105}], nif_mod_call_history()),
 
548
 
 
549
    ?line ok = forget_resource(NGX1),
 
550
    ?CHECK([], nif_mod_call_history()), % no dtor
 
551
 
 
552
    ?line ok = nif_mod:load_nif_lib(Config, 2,
 
553
                                    [{resource_type, 0, ?RT_TAKEOVER, "resource_type_A",resource_dtor_A,
 
554
                                      ?RT_TAKEOVER},
 
555
                                     {resource_type, 1, ?RT_TAKEOVER bor ?RT_CREATE, "resource_type_null_A",resource_dtor_A,
 
556
                                      ?RT_TAKEOVER},
 
557
                                     {resource_type, 2, ?RT_TAKEOVER, "resource_type_A_null",null,
 
558
                                      ?RT_TAKEOVER},
 
559
                                     {resource_type, null, ?RT_TAKEOVER, "Pink unicorn", resource_dtor_A,
 
560
                                      ?RT_TAKEOVER},
 
561
                                     {resource_type, null, ?RT_CREATE, "resource_type_B_goneX",resource_dtor_B,
 
562
                                      ?RT_CREATE},
 
563
                                     {resource_type, null, ?RT_CREATE, "resource_type_null_goneX",null,
 
564
                                      ?RT_CREATE},
 
565
                                     {resource_type, 3, ?RT_CREATE, "resource_type_B_goneY",resource_dtor_B,
 
566
                                      ?RT_CREATE},
 
567
                                     {resource_type, 4, ?RT_CREATE, "resource_type_null_goneY",null,
 
568
                                      ?RT_CREATE}
 
569
                                    ]),
 
570
    ?CHECK([{reload,2,1,201}], nif_mod_call_history()),
 
571
 
 
572
    ?line BinA2 = read_resource(0,A2),
 
573
    ?line ok = forget_resource(A2),
 
574
    ?CHECK([{{resource_dtor_A_v2,BinA2},2,2,202}], nif_mod_call_history()),    
 
575
 
 
576
    ?line ok = forget_resource(NA2),
 
577
    ?CHECK([{{resource_dtor_A_v2,BinNA2},2,3,203}], nif_mod_call_history()),    
 
578
 
 
579
    ?line ok = forget_resource(AN2),
 
580
    ?CHECK([], nif_mod_call_history()),    % no dtor
 
581
 
 
582
    ?line ok = forget_resource(BGX2),  % calling dtor in orphan library v1 still loaded
 
583
    ?CHECK([{{resource_dtor_B_v1,BinBGX2},1,6,106}], nif_mod_call_history()),
 
584
    % How to test that lib v1 is closed here?
 
585
 
 
586
    ?line ok = forget_resource(NGX2),
 
587
    ?CHECK([], nif_mod_call_history()),  % no dtor
 
588
 
 
589
    {BGY1,BinBGY1} = make_resource(3,Holder,"BGY1"),
 
590
    {NGY1,_BinNGY1} = make_resource(4,Holder,"NGY1"),
 
591
 
 
592
    %% Module upgrade with same lib-version
 
593
    ?line {module,nif_mod} = erlang:load_module(nif_mod,ModBin),
 
594
    ?line undefined = nif_mod:lib_version(),
 
595
    ?line ok = nif_mod:load_nif_lib(Config, 2,
 
596
                                    [{resource_type, 2, ?RT_TAKEOVER, "resource_type_A",resource_dtor_B,
 
597
                                      ?RT_TAKEOVER},
 
598
                                     {resource_type, 0, ?RT_TAKEOVER bor ?RT_CREATE, "resource_type_null_A",null,
 
599
                                      ?RT_TAKEOVER},
 
600
                                     {resource_type, 1, ?RT_TAKEOVER, "resource_type_A_null",resource_dtor_A,
 
601
                                      ?RT_TAKEOVER},
 
602
                                     {resource_type, null, ?RT_TAKEOVER, "Pink elephant", resource_dtor_A,
 
603
                                      ?RT_TAKEOVER},
 
604
                                     {resource_type, 3, ?RT_CREATE, "resource_type_B_goneZ",resource_dtor_B,
 
605
                                      ?RT_CREATE},
 
606
                                     {resource_type, 4, ?RT_CREATE, "resource_type_null_goneZ",null,
 
607
                                      ?RT_CREATE}
 
608
                                    ]),
 
609
 
 
610
    ?line 2 = nif_mod:lib_version(),
 
611
    ?CHECK([{upgrade,2,4,204},{lib_version,2,5,205}], nif_mod_call_history()),
 
612
 
 
613
    ?line ok = forget_resource(A3),
 
614
    ?CHECK([{{resource_dtor_B_v2,BinA3},2,6,206}], nif_mod_call_history()),    
 
615
 
 
616
    ?line ok = forget_resource(NA3),
 
617
    ?CHECK([], nif_mod_call_history()),    
 
618
 
 
619
    ?line ok = forget_resource(AN3),
 
620
    ?CHECK([{{resource_dtor_A_v2,BinAN3},2,7,207}], nif_mod_call_history()),
 
621
 
 
622
    {A4,BinA4} = make_resource(2,Holder, "A4"),
 
623
    {NA4,BinNA4} = make_resource(0,Holder, "NA4"),
 
624
    {AN4,_BinAN4} = make_resource(1,Holder, "AN4"),
 
625
 
 
626
    {BGZ1,BinBGZ1} = make_resource(3,Holder,"BGZ1"),
 
627
    {NGZ1,_BinNGZ1} = make_resource(4,Holder,"NGZ1"),
 
628
 
 
629
    ?line false = code:purge(nif_mod),
 
630
    ?line [] = nif_mod_call_history(),
 
631
 
 
632
    ?line ok = forget_resource(NGY1),
 
633
    ?line [] = nif_mod_call_history(),
 
634
 
 
635
    ?line ok = forget_resource(BGY1),  % calling dtor in orphan library v2 still loaded
 
636
    ?line [{{resource_dtor_B_v2,BinBGY1},2,8,208},{unload,2,9,209}] = nif_mod_call_history(),
 
637
 
 
638
    %% Module upgrade with other lib-version
 
639
    ?line {module,nif_mod} = erlang:load_module(nif_mod,ModBin),
 
640
    ?line undefined = nif_mod:lib_version(),
 
641
    ?line ok = nif_mod:load_nif_lib(Config, 1,
 
642
                                    [{resource_type, 2, ?RT_TAKEOVER, "resource_type_A",resource_dtor_A,
 
643
                                      ?RT_TAKEOVER},
 
644
                                     {resource_type, 0, ?RT_TAKEOVER bor ?RT_CREATE, "resource_type_null_A",resource_dtor_A,
 
645
                                      ?RT_TAKEOVER},
 
646
                                     {resource_type, 1, ?RT_TAKEOVER, "resource_type_A_null",null,
 
647
                                      ?RT_TAKEOVER},
 
648
                                     {resource_type, null, ?RT_TAKEOVER, "Mr Pink", resource_dtor_A,
 
649
                                      ?RT_TAKEOVER}
 
650
                                    ]),
 
651
 
 
652
    ?line 1 = nif_mod:lib_version(),
 
653
    ?line [{upgrade,1,1,101},{lib_version,1,2,102}] = nif_mod_call_history(),
 
654
 
 
655
    %%?line false= check_process_code(Pid, nif_mod),
 
656
    ?line false = code:purge(nif_mod),
 
657
    %% no unload here as we still have instances with destructors
 
658
    ?line [] = nif_mod_call_history(),
 
659
 
 
660
    ?line ok = forget_resource(BGZ1),  % calling dtor in orphan library v2 still loaded
 
661
    ?line [{{resource_dtor_B_v2,BinBGZ1},2,10,210},{unload,2,11,211}] = nif_mod_call_history(),
 
662
 
 
663
    ?line ok = forget_resource(NGZ1),
 
664
    ?line [] = nif_mod_call_history(),
 
665
 
 
666
    ?line ok = forget_resource(A4),
 
667
    ?line [{{resource_dtor_A_v1,BinA4},1,3,103}] = nif_mod_call_history(),
 
668
 
 
669
    ?line ok = forget_resource(NA4),
 
670
    ?line [{{resource_dtor_A_v1,BinNA4},1,4,104}] = nif_mod_call_history(),
 
671
 
 
672
    ?line ok = forget_resource(AN4),
 
673
    ?line [] = nif_mod_call_history(),
 
674
 
 
675
    ?line [?MODULE, nif_mod] = erlang:system_info(taints),
 
676
    ?line verify_tmpmem(TmpMem),    
 
677
    ok.
 
678
 
 
679
make_resource(Type,Holder,Str) when is_list(Str) ->
 
680
    Bin = list_to_binary(Str),
 
681
    A1 = make_resource_do(Type,Holder,Bin),
 
682
    ?line Bin = read_resource(Type,A1),
 
683
    {A1,Bin}.
 
684
 
 
685
make_resource_do(Type, Holder, Bin) ->
 
686
    Holder ! {self(), make, Type, Bin},
 
687
    {Holder, make_ok, Id} = receive_any(),
 
688
    {Holder,Id}.
 
689
 
 
690
read_resource(Type, {Holder,Id}) ->
 
691
    Holder ! {self(), get, Type, Id},
 
692
    {Holder, get_ok, Bin} = receive_any(),
 
693
    Bin.
 
694
 
 
695
forget_resource({Holder,Id}) ->
 
696
    Holder ! {self(), forget, Id},
 
697
    {Holder, forget_ok, Id} = receive_any(),
 
698
    ok.
 
699
 
 
700
 
 
701
resource_holder() ->
 
702
    resource_holder([]).
 
703
resource_holder(List) ->
 
704
    %%io:format("resource_holder waiting for msg\n", []),
 
705
    Msg = receive_any(),
 
706
    %%io:format("resource_holder got ~p with list = ~p\n", [Msg,List]),
 
707
    case Msg of
 
708
        {Pid, make, Type, Bin} ->           
 
709
            ?line Resource = nif_mod:make_new_resource(Type, Bin),
 
710
            Id = {make_ref(),Bin},
 
711
            Pid ! {self(), make_ok, Id},
 
712
            resource_holder([{Id,Resource} | List]);
 
713
        {Pid, get, Type, Id} ->
 
714
            {Id,Resource} = lists:keyfind(Id, 1, List),
 
715
            Pid ! {self(), get_ok, nif_mod:get_resource(Type, Resource)},
 
716
            resource_holder(List);
 
717
        
 
718
        {Pid, forget, Id} ->
 
719
            NewList = lists:keydelete(Id, 1, List),
 
720
            %%io:format("resource_holder forget: NewList = ~p\n", [NewList]),
 
721
            resource_holder(Pid, {self(),forget_ok,Id}, NewList)
 
722
    end.
 
723
 
 
724
resource_holder(Pid,Reply,List) ->
 
725
    erlang:garbage_collect(),
 
726
    %%io:format("resource_holder GC'ed, now send ~p to ~p\n", [Reply,Pid]),
 
727
    Pid ! Reply,
 
728
    resource_holder(List).
 
729
 
 
730
 
 
731
threading(doc) -> ["Test the threading API functions (reuse tests from driver API)"];
 
732
threading(Config) when is_list(Config) ->    
 
733
    ?line Data = ?config(data_dir, Config),
 
734
    ?line File = filename:join(Data, "tester"),
 
735
    ?line {ok,tester,ModBin} = compile:file(File, [binary,return_errors]),
 
736
    ?line {module,tester} = erlang:load_module(tester,ModBin),
 
737
 
 
738
    ?line ok = tester:load_nif_lib(Config, "basic"),   
 
739
    ?line ok = tester:run(),
 
740
 
 
741
    ?line ok = tester:load_nif_lib(Config, "rwlock"),
 
742
    ?line ok = tester:run(),
 
743
 
 
744
    ?line ok = tester:load_nif_lib(Config, "tsd"),
 
745
    ?line ok = tester:run().
 
746
    
188
747
neg(doc) -> ["Negative testing of load_nif"];
189
 
neg(suite) -> [];
190
748
neg(Config) when is_list(Config) ->
 
749
    TmpMem = tmpmem(),
191
750
    ?line {'EXIT',{badarg,_}} = (catch erlang:load_nif(badarg, 0)),
192
 
    ?line {error,load_failed,_} = erlang:load_nif("pink_unicorn", 0),
 
751
    ?line {error,{load_failed,_}} = erlang:load_nif("pink_unicorn", 0),
193
752
    
194
753
    ?line Data = ?config(data_dir, Config),
195
754
    ?line File = filename:join(Data, "nif_mod"),
196
755
    ?line {ok,nif_mod,Bin} = compile:file(File, [binary,return_errors]),
197
756
    ?line {module,nif_mod} = erlang:load_module(nif_mod,Bin),
198
757
 
199
 
    ?line {error,bad_lib,_} = nif_mod:load_nif_lib(Config, no_init),    
 
758
    ?line {error,{bad_lib,_}} = nif_mod:load_nif_lib(Config, no_init),    
 
759
    ?line verify_tmpmem(TmpMem),
200
760
    ?line ok.
201
761
 
202
762
 
203
763
 
204
764
ensure_lib_loaded(Config) ->
205
765
    ensure_lib_loaded(Config, 1).
206
 
 
207
766
ensure_lib_loaded(Config, Ver) ->
208
767
    ?line case lib_version() of
209
768
              undefined ->
210
769
                  ?line Path = ?config(data_dir, Config),    
211
770
                  ?line Lib = "nif_SUITE." ++ integer_to_list(Ver),
212
 
                  ?line ok = erlang:load_nif(filename:join(Path,Lib), 0);
 
771
                  ?line ok = erlang:load_nif(filename:join(Path,Lib), []);
213
772
              Ver when is_integer(Ver) ->
214
773
                  ok
215
774
          end.
216
775
 
 
776
tmpmem() ->
 
777
    case erlang:system_info({allocator,temp_alloc}) of
 
778
        false -> undefined;
 
779
        MemInfo ->
 
780
            MSBCS = lists:foldl(
 
781
                      fun ({instance, _, L}, Acc) ->
 
782
                              {value,{_,MBCS}} = lists:keysearch(mbcs, 1, L),
 
783
                              {value,{_,SBCS}} = lists:keysearch(sbcs, 1, L),
 
784
                              [MBCS,SBCS | Acc]
 
785
                      end,
 
786
                      [],
 
787
                      MemInfo),
 
788
            lists:foldl(
 
789
              fun(L, {Bl0,BlSz0}) ->
 
790
                      {value,{_,Bl,_,_}} = lists:keysearch(blocks, 1, L),
 
791
                      {value,{_,BlSz,_,_}} = lists:keysearch(blocks_size, 1, L),
 
792
                      {Bl0+Bl,BlSz0+BlSz}
 
793
              end, {0,0}, MSBCS)
 
794
    end.
 
795
 
 
796
verify_tmpmem(MemInfo) ->
 
797
    %%wait_for_test_procs(),
 
798
    case tmpmem() of
 
799
        MemInfo ->
 
800
            io:format("Tmp mem info: ~p", [MemInfo]),
 
801
            case MemInfo of
 
802
                {notsup,undefined} ->
 
803
                    %% Use 'erl +Mea max' to do more complete memory leak testing.
 
804
                    {comment,"Incomplete or no mem leak testing"};
 
805
                _ ->
 
806
                    ok
 
807
            end;
 
808
        Other ->
 
809
            io:format("Expected: ~p", [MemInfo]),
 
810
            io:format("Actual:   ~p", [Other]),
 
811
            ?t:fail()
 
812
    end.
 
813
 
217
814
call(Pid,Cmd) ->
218
815
    %%io:format("~p calling ~p with ~p\n",[self(), Pid, Cmd]),
219
816
    Pid ! {self(), Cmd},
224
821
receive_any() ->
225
822
    receive M -> M end.      
226
823
 
 
824
%% check(Exp,Got,Line) ->
 
825
%%     case Got of
 
826
%%      Exp -> Exp;         
 
827
%%      _ ->
 
828
%%          io:format("CHECK at ~p: Expected ~p but got ~p\n",[Line,Exp,Got]),
 
829
%%          Got
 
830
%%     end.
 
831
            
 
832
 
227
833
%% The NIFs:
228
834
lib_version() -> undefined.
229
835
call_history() -> ?nif_stub.
230
836
hold_nif_mod_priv_data(_Ptr) -> ?nif_stub.
231
837
nif_mod_call_history() -> ?nif_stub.
232
838
list_seq(_To) -> ?nif_stub.
233
 
    
 
839
type_test() -> ?nif_stub.
 
840
tuple_2_list(_) -> ?nif_stub.    
 
841
is_identical(_,_) -> ?nif_stub.
 
842
compare(_,_) -> ?nif_stub.
 
843
many_args_100(_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_,_) -> ?nif_stub.
 
844
clone_bin(_) -> ?nif_stub.
 
845
make_sub_bin(_,_,_) -> ?nif_stub.
 
846
string_to_bin(_,_) -> ?nif_stub.
 
847
atom_to_bin(_,_) -> ?nif_stub.    
 
848
macros(_) -> ?nif_stub.
 
849
tuple_2_list_and_tuple(_) -> ?nif_stub.
 
850
iolist_2_bin(_) -> ?nif_stub.
 
851
get_resource_type(_) -> ?nif_stub.
 
852
alloc_resource(_,_) -> ?nif_stub.
 
853
make_resource(_) -> ?nif_stub.
 
854
get_resource(_,_) -> ?nif_stub.
 
855
release_resource(_) -> ?nif_stub.
 
856
last_resource_dtor_call() -> ?nif_stub.
 
857
make_new_resource(_,_) -> ?nif_stub.
 
858
 
234
859
nif_stub_error(Line) ->
235
860
    exit({nif_not_loaded,module,?MODULE,line,Line}).