~statik/ubuntu/lucid/erlang/merge-erlang13b3

« back to all changes in this revision

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

  • Committer: Elliot Murphy
  • Date: 2009-12-22 02:56:21 UTC
  • mfrom: (3.3.5 sid)
  • Revision ID: elliot@elliotmurphy.com-20091222025621-qv3rja8gbpiabkbe
* Merge with Debian testing; 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.
* Fixed dialyzer(1) manpage which was placed into section 3 and conflicted
  with dialyzer(3erl).
* New upstream release (it adds a new binary package erlang-erl-docgen).
* Refreshed patches, removed most of emacs.patch which is applied upstream.
* Linked run_test binary from erlang-common-test package to /usr/bin.
* Fixed VCS headers in debian/control.
* Moved from prebuilt manpages to generated from sources. This adds
  erlang-manpages binary package and xsltproc build dependency.

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
%%
 
2
%% %CopyrightBegin%
 
3
%% 
 
4
%% Copyright Ericsson AB 1999-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
-module(code_SUITE).
 
21
-export([all/1,
 
22
         new_binary_types/1,t_check_process_code/1,t_check_process_code_ets/1,
 
23
         external_fun/1,get_chunk/1,module_md5/1,make_stub/1,
 
24
         make_stub_many_funs/1,constant_pools/1,
 
25
         false_dependency/1,coverage/1]).
 
26
 
 
27
-include("test_server.hrl").
 
28
 
 
29
all(suite) ->
 
30
    [new_binary_types,t_check_process_code,t_check_process_code_ets,
 
31
     external_fun,get_chunk,module_md5,make_stub,make_stub_many_funs,
 
32
     constant_pools,false_dependency,coverage].
 
33
 
 
34
new_binary_types(Config) when is_list(Config) ->
 
35
    ?line Data = ?config(data_dir, Config),
 
36
    ?line File = filename:join(Data, "my_code_test"),
 
37
    ?line {ok,my_code_test,Bin} = compile:file(File, [binary]),
 
38
    ?line {module,my_code_test} = erlang:load_module(my_code_test,
 
39
                                                     make_sub_binary(Bin)),
 
40
    ?line true = erlang:delete_module(my_code_test),
 
41
    ?line true = erlang:purge_module(my_code_test),
 
42
 
 
43
    ?line {module,my_code_test} = erlang:load_module(my_code_test,
 
44
                                                     make_unaligned_sub_binary(Bin)),
 
45
    ?line true = erlang:delete_module(my_code_test),
 
46
    ?line true = erlang:purge_module(my_code_test),
 
47
 
 
48
    %% Try heap binaries and bad binaries.
 
49
    ?line {error,badfile} = erlang:load_module(my_code_test, <<1,2>>),
 
50
    ?line {error,badfile} = erlang:load_module(my_code_test,
 
51
                                                make_sub_binary(<<1,2>>)),
 
52
    ?line {error,badfile} = erlang:load_module(my_code_test,
 
53
                                                make_unaligned_sub_binary(<<1,2>>)),
 
54
    ?line {'EXIT',{badarg,_}} = (catch erlang:load_module(my_code_test,
 
55
                                                      bit_sized_binary(Bin))),
 
56
    ok.
 
57
 
 
58
t_check_process_code(doc) -> "Test check_process_code/2.";
 
59
t_check_process_code(Config) when is_list(Config) ->
 
60
    case erlang:system_info(heap_type) of
 
61
        private -> t_check_process_code_1(Config);
 
62
        hybrid -> {skip,"Hybrid heap"}
 
63
    end.
 
64
 
 
65
t_check_process_code_1(Config) ->
 
66
    ?line Priv = ?config(priv_dir, Config),
 
67
    ?line Data = ?config(data_dir, Config),
 
68
    ?line File = filename:join(Data, "my_code_test"),
 
69
    ?line Code = filename:join(Priv, "my_code_test"),
 
70
 
 
71
    ?line {ok,my_code_test} = c:c(File, [{outdir,Priv}]),
 
72
 
 
73
    ?line MyFun = fun(X, Y) -> X + Y end,       %Confuse things.
 
74
    ?line F = my_code_test:make_fun(42),
 
75
    ?line 2 = fun_refc(F),
 
76
    ?line MyFun2 = fun(X, Y) -> X * Y end,      %Confuse things.
 
77
    ?line 44 = F(2),
 
78
 
 
79
    %% Delete the module and call the fun again.
 
80
    ?line true = erlang:delete_module(my_code_test),
 
81
    ?line 2 = fun_refc(F),
 
82
    ?line 45 = F(3),
 
83
    ?line {'EXIT',{undef,_}} = (catch my_code_test:make_fun(33)),
 
84
 
 
85
    %% The fun should still be there, preventing purge.
 
86
    ?line true = erlang:check_process_code(self(), my_code_test),
 
87
    gc(),
 
88
    gc(),                                       %Place funs on the old heap.
 
89
    ?line true = erlang:check_process_code(self(), my_code_test),
 
90
 
 
91
    %% Using the funs here guarantees that they will not be prematurely garbed.
 
92
    ?line 48 = F(6),
 
93
    ?line 3 = MyFun(1, 2),
 
94
    ?line 12 = MyFun2(3, 4),
 
95
 
 
96
    %% Kill all funs.
 
97
    t_check_process_code1(Code, []).
 
98
 
 
99
%% The real fun was killed, but we have some fakes which look similar.
 
100
 
 
101
t_check_process_code1(Code, Fakes) ->
 
102
    ?line MyFun = fun(X, Y) -> X + Y + 1 end,   %Confuse things.
 
103
    ?line false = erlang:check_process_code(self(), my_code_test),
 
104
    ?line 4 = MyFun(1, 2),
 
105
    t_check_process_code2(Code, Fakes).
 
106
 
 
107
t_check_process_code2(Code, _) ->
 
108
    ?line false = erlang:check_process_code(self(), my_code_test),
 
109
    ?line true = erlang:purge_module(my_code_test),
 
110
 
 
111
    %% In the next test we will load the same module twice.
 
112
    ?line {module,my_code_test} = code:load_abs(Code),
 
113
    ?line F = my_code_test:make_fun(37),
 
114
    ?line 2 = fun_refc(F),
 
115
    ?line false = erlang:check_process_code(self(), my_code_test),
 
116
    ?line {module,my_code_test} = code:load_abs(Code),
 
117
    ?line 2 = fun_refc(F),
 
118
 
 
119
    %% Still false because the fun with the same identify is found
 
120
    %% in the current code.
 
121
    ?line false = erlang:check_process_code(self(), my_code_test),
 
122
    
 
123
    %% Some fake funs in the same module should not do any difference.
 
124
    ?line false = erlang:check_process_code(self(), my_code_test),
 
125
 
 
126
    38 = F(1),
 
127
    t_check_process_code3(Code, F, []).
 
128
 
 
129
t_check_process_code3(Code, F, Fakes) ->
 
130
    Pid = spawn_link(fun() -> body(F, Fakes) end),
 
131
    ?line true = erlang:purge_module(my_code_test),
 
132
    ?line false = erlang:check_process_code(self(), my_code_test),
 
133
    ?line false = erlang:check_process_code(Pid, my_code_test),
 
134
 
 
135
    ?line true = erlang:delete_module(my_code_test),
 
136
    ?line true = erlang:check_process_code(self(), my_code_test),
 
137
    ?line true = erlang:check_process_code(Pid, my_code_test),
 
138
    39 = F(2),
 
139
    t_check_process_code4(Code, Pid).
 
140
 
 
141
t_check_process_code4(_Code, Pid) ->
 
142
    Pid ! drop_funs,
 
143
    receive after 1 -> ok end,
 
144
    ?line false = erlang:check_process_code(Pid, my_code_test),
 
145
    ok.
 
146
 
 
147
body(F, Fakes) ->
 
148
    receive
 
149
        jog ->
 
150
            40 = F(3),
 
151
            erlang:garbage_collect(),
 
152
            body(F, Fakes);
 
153
        drop_funs ->
 
154
            dropped_body()
 
155
    end.
 
156
 
 
157
dropped_body() ->
 
158
    receive
 
159
        X -> exit(X)
 
160
    end.
 
161
 
 
162
gc() ->
 
163
    erlang:garbage_collect(),
 
164
    gc1().
 
165
gc1() -> ok.
 
166
 
 
167
t_check_process_code_ets(doc) ->
 
168
    "Test check_process_code/2 in combination with a fun obtained from an ets table.";
 
169
t_check_process_code_ets(Config) when is_list(Config) ->
 
170
    case {test_server:is_native(?MODULE),erlang:system_info(heap_type)} of
 
171
        {true,_} ->
 
172
            {skipped,"Native code"};
 
173
        {_,hybrid} ->
 
174
            {skipped,"Hybrid heap"};
 
175
        {false,private} ->
 
176
            do_check_process_code_ets(Config)
 
177
    end.
 
178
 
 
179
do_check_process_code_ets(Config) ->
 
180
    ?line Priv = ?config(priv_dir, Config),
 
181
    ?line Data = ?config(data_dir, Config),
 
182
    ?line File = filename:join(Data, "my_code_test"),
 
183
 
 
184
    ?line erlang:purge_module(my_code_test),
 
185
    ?line erlang:delete_module(my_code_test),
 
186
    ?line {ok,my_code_test} = c:c(File, [{outdir,Priv}]),
 
187
 
 
188
    ?line T = ets:new(my_code_test, []),
 
189
    ?line ets:insert(T, {7,my_code_test:make_fun(107)}),
 
190
    ?line ets:insert(T, {8,my_code_test:make_fun(108)}),
 
191
    ?line erlang:delete_module(my_code_test),
 
192
    ?line false = erlang:check_process_code(self(), my_code_test),
 
193
    Body = fun() ->
 
194
                   [{7,F1}] = ets:lookup(T, 7),
 
195
                   [{8,F2}] = ets:lookup(T, 8),
 
196
                   IdleLoop = fun() -> receive _X -> ok end end,
 
197
                   RecLoop = fun(Again) ->
 
198
                                     receive
 
199
                                         call -> 110 = F1(3),
 
200
                                                 100 = F2(-8),
 
201
                                                 Again(Again);
 
202
                                         {drop_funs,To} ->
 
203
                                             To ! funs_dropped,
 
204
                                             IdleLoop()
 
205
                                     end
 
206
                             end,
 
207
                   true = erlang:check_process_code(self(), my_code_test),
 
208
                   RecLoop(RecLoop)
 
209
           end,
 
210
    ?line Pid = spawn_link(Body),
 
211
    receive after 1 -> ok end,
 
212
    ?line true = erlang:check_process_code(Pid, my_code_test),
 
213
    Pid ! call,
 
214
    Pid ! {drop_funs,self()},
 
215
 
 
216
    receive
 
217
        funs_dropped -> ok;
 
218
        Other -> ?t:fail({unexpected,Other})
 
219
    after 10000 ->
 
220
            ?line ?t:fail(no_funs_dropped_answer)
 
221
    end,
 
222
 
 
223
    ?line false = erlang:check_process_code(Pid, my_code_test),
 
224
    ok.
 
225
 
 
226
fun_refc(F) ->
 
227
    {refc,Count} = erlang:fun_info(F, refc),
 
228
    Count.
 
229
 
 
230
 
 
231
external_fun(Config) when is_list(Config) ->
 
232
    ?line false = erlang:function_exported(another_code_test, x, 1),
 
233
    ?line ExtFun = erlang:make_fun(id(another_code_test), x, 1),
 
234
    ?line {'EXIT',{undef,_}} = (catch ExtFun(answer)),
 
235
    ?line false = erlang:function_exported(another_code_test, x, 1),
 
236
    ?line false = lists:member(another_code_test, erlang:loaded()),
 
237
    ?line Data = ?config(data_dir, Config),
 
238
    ?line File = filename:join(Data, "another_code_test"),
 
239
    ?line {ok,another_code_test,Code} = compile:file(File, [binary,report]),
 
240
    ?line {module,another_code_test} = erlang:load_module(another_code_test, Code),
 
241
    ?line 42 = ExtFun(answer),
 
242
    ok.
 
243
 
 
244
get_chunk(Config) when is_list(Config) ->
 
245
    ?line Data = ?config(data_dir, Config),
 
246
    ?line File = filename:join(Data, "my_code_test"),
 
247
    ?line {ok,my_code_test,Code} = compile:file(File, [binary]),
 
248
 
 
249
    %% Should work.
 
250
    ?line Chunk = get_chunk_ok("Atom", Code),
 
251
    ?line Chunk = get_chunk_ok("Atom", make_sub_binary(Code)),
 
252
    ?line Chunk = get_chunk_ok("Atom", make_unaligned_sub_binary(Code)),
 
253
 
 
254
    %% Should fail.
 
255
    ?line {'EXIT',{badarg,_}} = (catch code:get_chunk(bit_sized_binary(Code), "Atom")),
 
256
    ?line {'EXIT',{badarg,_}} = (catch code:get_chunk(Code, "bad chunk id")),
 
257
 
 
258
    %% Invalid beam code or missing chunk should return 'undefined'.
 
259
    ?line undefined = code:get_chunk(<<"not a beam module">>, "Atom"),
 
260
    ?line undefined = code:get_chunk(Code, "XXXX"),
 
261
 
 
262
    ok.
 
263
 
 
264
get_chunk_ok(Chunk, Code) ->
 
265
    case code:get_chunk(Code, Chunk) of
 
266
        Bin when is_binary(Bin) -> Bin
 
267
    end.
 
268
 
 
269
module_md5(Config) when is_list(Config) ->
 
270
    ?line Data = ?config(data_dir, Config),
 
271
    ?line File = filename:join(Data, "my_code_test"),
 
272
    ?line {ok,my_code_test,Code} = compile:file(File, [binary]),
 
273
 
 
274
    %% Should work.
 
275
    ?line Chunk = module_md5_ok(Code),
 
276
    ?line Chunk = module_md5_ok(make_sub_binary(Code)),
 
277
    ?line Chunk = module_md5_ok(make_unaligned_sub_binary(Code)),
 
278
 
 
279
    %% Should fail.
 
280
    ?line {'EXIT',{badarg,_}} = (catch code:module_md5(bit_sized_binary(Code))),
 
281
 
 
282
    %% Invalid beam code should return 'undefined'.
 
283
    ?line undefined = code:module_md5(<<"not a beam module">>),
 
284
    ok.
 
285
    
 
286
module_md5_ok(Code) ->
 
287
    case code:module_md5(Code) of
 
288
        Bin when is_binary(Bin), size(Bin) =:= 16 -> Bin
 
289
    end.
 
290
 
 
291
 
 
292
make_stub(Config) when is_list(Config) ->
 
293
    %% No old code to purge if hybrid heap because of skipped test cases,
 
294
    %% so we'll need a catch here.
 
295
    ?line (catch erlang:purge_module(my_code_test)),
 
296
 
 
297
    ?line Data = ?config(data_dir, Config),
 
298
    ?line File = filename:join(Data, "my_code_test"),
 
299
    ?line {ok,my_code_test,Code} = compile:file(File, [binary]),
 
300
 
 
301
    ?line my_code_test = code:make_stub_module(my_code_test, Code, {[],[]}),
 
302
    ?line true = erlang:delete_module(my_code_test),
 
303
    ?line true = erlang:purge_module(my_code_test),
 
304
 
 
305
    ?line my_code_test = code:make_stub_module(my_code_test, 
 
306
                                               make_unaligned_sub_binary(Code),
 
307
                                               {[],[]}),
 
308
    ?line true = erlang:delete_module(my_code_test),
 
309
    ?line true = erlang:purge_module(my_code_test),
 
310
 
 
311
    ?line my_code_test = code:make_stub_module(my_code_test, zlib:gzip(Code),
 
312
                                               {[],[]}),
 
313
    ?line true = erlang:delete_module(my_code_test),
 
314
    ?line true = erlang:purge_module(my_code_test),
 
315
 
 
316
    %% Should fail.
 
317
    ?line {'EXIT',{badarg,_}} =
 
318
        (catch code:make_stub_module(my_code_test, <<"bad">>, {[],[]})),
 
319
    ?line {'EXIT',{badarg,_}} =
 
320
        (catch code:make_stub_module(my_code_test,
 
321
                                     bit_sized_binary(Code),
 
322
                                     {[],[]})),
 
323
    ok.
 
324
 
 
325
make_stub_many_funs(Config) when is_list(Config) ->
 
326
    %% No old code to purge if hybrid heap because of skipped test cases,
 
327
    %% so we'll need a catch here.
 
328
    ?line (catch erlang:purge_module(many_funs)),
 
329
 
 
330
    ?line Data = ?config(data_dir, Config),
 
331
    ?line File = filename:join(Data, "many_funs"),
 
332
    ?line {ok,many_funs,Code} = compile:file(File, [binary]),
 
333
 
 
334
    ?line many_funs = code:make_stub_module(many_funs, Code, {[],[]}),
 
335
    ?line true = erlang:delete_module(many_funs),
 
336
    ?line true = erlang:purge_module(many_funs),
 
337
    ?line many_funs = code:make_stub_module(many_funs, 
 
338
                                               make_unaligned_sub_binary(Code),
 
339
                                               {[],[]}),
 
340
    ?line true = erlang:delete_module(many_funs),
 
341
    ?line true = erlang:purge_module(many_funs),
 
342
 
 
343
    %% Should fail.
 
344
    ?line {'EXIT',{badarg,_}} =
 
345
        (catch code:make_stub_module(many_funs, <<"bad">>, {[],[]})),
 
346
    ?line {'EXIT',{badarg,_}} =
 
347
        (catch code:make_stub_module(many_funs,
 
348
                                     bit_sized_binary(Code),
 
349
                                     {[],[]})),
 
350
    ok.
 
351
 
 
352
constant_pools(Config) when is_list(Config) ->
 
353
    ?line Data = ?config(data_dir, Config),
 
354
    ?line File = filename:join(Data, "literals"),
 
355
    ?line {ok,literals,Code} = compile:file(File, [report,binary,constant_pool]),
 
356
    ?line {module,literals} = erlang:load_module(literals,
 
357
                                                 make_sub_binary(Code)),
 
358
 
 
359
    %% Initialize.
 
360
    ?line A = literals:a(),
 
361
    ?line B = literals:b(),
 
362
    ?line C = literals:huge_bignum(),
 
363
    ?line process_flag(trap_exit, true),
 
364
    Self = self(),
 
365
 
 
366
    %% Have a process WITHOUT old heap that references the literals
 
367
    %% in the 'literals' module.
 
368
    ?line NoOldHeap = spawn_link(fun() -> no_old_heap(Self) end),
 
369
    receive go -> ok end,
 
370
    ?line true = erlang:delete_module(literals),
 
371
    ?line false = erlang:check_process_code(NoOldHeap, literals),
 
372
    ?line erlang:check_process_code(self(), literals),
 
373
    ?line true = erlang:purge_module(literals),
 
374
    ?line NoOldHeap ! done,
 
375
    ?line receive
 
376
              {'EXIT',NoOldHeap,{A,B,C}} ->
 
377
                  ok;
 
378
              Other ->
 
379
                  ?line ?t:fail({unexpected,Other})
 
380
          end,
 
381
    ?line {module,literals} = erlang:load_module(literals, Code),
 
382
 
 
383
    %% Have a process WITH an old heap that references the literals
 
384
    %% in the 'literals' module.
 
385
    ?line OldHeap = spawn_link(fun() -> old_heap(Self) end),
 
386
    receive go -> ok end,
 
387
    ?line true = erlang:delete_module(literals),
 
388
    ?line false = erlang:check_process_code(OldHeap, literals),
 
389
    ?line erlang:check_process_code(self(), literals),
 
390
    ?line erlang:purge_module(literals),
 
391
    ?line OldHeap ! done,
 
392
    receive
 
393
        {'EXIT',OldHeap,{A,B,C,[1,2,3|_]=Seq}} when length(Seq) =:= 16 ->
 
394
            ok
 
395
    end.
 
396
 
 
397
no_old_heap(Parent) ->
 
398
    A = literals:a(),
 
399
    B = literals:b(),
 
400
    Res = {A,B,literals:huge_bignum()},
 
401
    Parent ! go,
 
402
    receive
 
403
        done ->
 
404
            exit(Res)
 
405
    end.
 
406
 
 
407
old_heap(Parent) ->
 
408
    A = literals:a(),
 
409
    B = literals:b(),
 
410
    Res = {A,B,literals:huge_bignum(),lists:seq(1, 16)},
 
411
    create_old_heap(),
 
412
    Parent ! go,
 
413
    receive
 
414
        done ->
 
415
            exit(Res)
 
416
    end.
 
417
 
 
418
create_old_heap() ->
 
419
    case process_info(self(), [heap_size,total_heap_size]) of
 
420
        [{heap_size,Sz},{total_heap_size,Total}] when Sz < Total ->
 
421
            ok;
 
422
        _ ->
 
423
            create_old_heap()
 
424
    end.
 
425
 
 
426
%% OTP-7559: c_p->cp could contain garbage and create a false dependency
 
427
%% to a module in a process. (Thanks to Richard Carlsson.)
 
428
false_dependency(Config) when is_list(Config) ->
 
429
    ?line Data = ?config(data_dir, Config),
 
430
    ?line File = filename:join(Data, "cpbugx"),
 
431
    ?line {ok,cpbugx,Code} = compile:file(File, [binary,report]),
 
432
 
 
433
    do_false_dependency(fun cpbugx:before/0, Code),
 
434
    do_false_dependency(fun cpbugx:before2/0, Code),
 
435
    do_false_dependency(fun cpbugx:before3/0, Code),
 
436
 
 
437
%%     %% Spawn process. Make sure it has called cpbugx:before/0 and returned.
 
438
%%     Parent = self(),
 
439
%%     ?line Pid = spawn_link(fun() -> false_dependency_loop(Parent) end),
 
440
%%     ?line receive initialized -> ok end,
 
441
 
 
442
%%     %% Reload the module. Make sure the process is still alive.
 
443
%%     ?line {module,cpbugx} = erlang:load_module(cpbugx, Bin),
 
444
%%     ?line io:put_chars(binary_to_list(element(2, process_info(Pid, backtrace)))),
 
445
%%     ?line true = is_process_alive(Pid),
 
446
 
 
447
%%     %% There should not be any dependency to cpbugx.
 
448
%%     ?line false = erlang:check_process_code(Pid, cpbugx),
 
449
    
 
450
 
 
451
 
 
452
 
 
453
%%     %% Kill the process.
 
454
%%     ?line unlink(Pid), exit(Pid, kill),
 
455
    ok.
 
456
 
 
457
do_false_dependency(Init, Code) ->
 
458
    ?line {module,cpbugx} = erlang:load_module(cpbugx, Code),
 
459
 
 
460
    %% Spawn process. Make sure it has the appropriate init function
 
461
    %% and returned. CP should not contain garbage after the return.
 
462
    Parent = self(),
 
463
    ?line Pid = spawn_link(fun() -> false_dependency_loop(Parent, Init) end),
 
464
    ?line receive initialized -> ok end,
 
465
 
 
466
    %% Reload the module. Make sure the process is still alive.
 
467
    ?line {module,cpbugx} = erlang:load_module(cpbugx, Code),
 
468
    ?line io:put_chars(binary_to_list(element(2, process_info(Pid, backtrace)))),
 
469
    ?line true = is_process_alive(Pid),
 
470
 
 
471
    %% There should not be any dependency to cpbugx.
 
472
    ?line false = erlang:check_process_code(Pid, cpbugx),
 
473
 
 
474
    %% Kill the process and completely unload the code.
 
475
    ?line unlink(Pid), exit(Pid, kill),
 
476
    ?line true = erlang:purge_module(cpbugx),
 
477
    ?line true = erlang:delete_module(cpbugx),
 
478
    ?line true = erlang:purge_module(cpbugx),
 
479
    ok.
 
480
    
 
481
false_dependency_loop(Parent, Init) ->
 
482
    Init(),
 
483
    Parent ! initialized,
 
484
    receive
 
485
        _ -> false_dependency_loop(Parent, Init)
 
486
    end.
 
487
 
 
488
coverage(Config) when is_list(Config) ->
 
489
    ?line code:is_module_native(?MODULE),
 
490
    ?line {'EXIT',{badarg,_}} = (catch erlang:purge_module({a,b,c})),
 
491
    ?line {'EXIT',{badarg,_}} = (catch code:is_module_native({a,b,c})),
 
492
    ?line {'EXIT',{badarg,_}} = (catch erlang:check_process_code(not_a_pid, ?MODULE)),
 
493
    ?line {'EXIT',{badarg,_}} = (catch erlang:check_process_code(self(), [not_a_module])),
 
494
    ?line {'EXIT',{badarg,_}} = (catch erlang:delete_module([a,b,c])),
 
495
    ?line {'EXIT',{badarg,_}} = (catch erlang:module_loaded(42)),
 
496
    ok.
 
497
 
 
498
%% Utilities.
 
499
 
 
500
make_sub_binary(Bin) when is_binary(Bin) ->
 
501
    {_,B1} = split_binary(list_to_binary([0,1,3,Bin,4,5,6,7]), 3),
 
502
    {B,_} = split_binary(B1, size(Bin)),
 
503
    B;
 
504
make_sub_binary(List) ->
 
505
    make_sub_binary(list_to_binary(List)).
 
506
 
 
507
make_unaligned_sub_binary(Bin0) ->
 
508
    Bin1 = <<0:3,Bin0/binary,31:5>>,
 
509
    Sz = size(Bin0),
 
510
    <<0:3,Bin:Sz/binary,31:5>> = id(Bin1),
 
511
    Bin.
 
512
 
 
513
%% Add 1 bit to the size of the binary.
 
514
bit_sized_binary(Bin0) ->
 
515
    Bin = <<Bin0/binary,1:1>>,
 
516
    BitSize = bit_size(Bin),
 
517
    BitSize = 8*size(Bin) + 1,
 
518
    Bin.
 
519
 
 
520
id(I) -> I.