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

« back to all changes in this revision

Viewing changes to lib/kernel/test/code_SUITE.erl

  • Committer: Bazaar Package Importer
  • Author(s): Clint Byrum
  • Date: 2011-05-05 15:48:43 UTC
  • mfrom: (3.5.13 sid)
  • Revision ID: james.westby@ubuntu.com-20110505154843-0om6ekzg6m7ugj27
Tags: 1:14.b.2-dfsg-3ubuntu1
* Merge from debian unstable.  Remaining changes:
  - Drop libwxgtk2.8-dev build dependency. Wx isn't in main, and not
    supposed to.
  - Drop erlang-wx binary.
  - Drop erlang-wx dependency from -megaco, -common-test, and -reltool, they
    do not really need wx. Also drop it from -debugger; the GUI needs wx,
    but it apparently has CLI bits as well, and is also needed by -megaco,
    so let's keep the package for now.
  - debian/patches/series: Do what I meant, and enable build-options.patch
    instead.
* Additional changes:
  - Drop erlang-wx from -et
* Dropped Changes:
  - patches/pcre-crash.patch: CVE-2008-2371: outer level option with
    alternatives caused crash. (Applied Upstream)
  - fix for ssl certificate verification in newSSL: 
    ssl_cacertfile_fix.patch (Applied Upstream)
  - debian/patches/series: Enable native.patch again, to get stripped beam
    files and reduce the package size again. (build-options is what
    actually accomplished this)
  - Remove build-options.patch on advice from upstream and because it caused
    odd build failures.

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
1
%%
2
2
%% %CopyrightBegin%
3
 
%% 
4
 
%% Copyright Ericsson AB 1996-2009. All Rights Reserved.
5
 
%% 
 
3
%%
 
4
%% Copyright Ericsson AB 1996-2011. 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
-module(code_SUITE).
20
20
 
21
 
-include("test_server.hrl").
 
21
-include_lib("test_server/include/test_server.hrl").
22
22
 
23
 
-export([all/1]).
 
23
-export([all/0, suite/0,groups/0,init_per_group/2,end_per_group/2]).
24
24
-export([set_path/1, get_path/1, add_path/1, add_paths/1, del_path/1,
25
25
         replace_path/1, load_file/1, load_abs/1, ensure_loaded/1,
26
26
         delete/1, purge/1, soft_purge/1, is_loaded/1, all_loaded/1,
27
27
         load_binary/1, dir_req/1, object_code/1, set_path_file/1,
28
28
         sticky_dir/1, pa_pz_option/1, add_del_path/1,
29
 
         dir_disappeared/1, ext_mod_dep/1,
 
29
         dir_disappeared/1, ext_mod_dep/1, clash/1,
30
30
         load_cached/1, start_node_with_cache/1, add_and_rehash/1,
31
31
         where_is_file_cached/1, where_is_file_no_cache/1,
32
32
         purge_stacktrace/1, mult_lib_roots/1, bad_erl_libs/1,
33
33
         code_archive/1, code_archive2/1, on_load/1,
34
 
         on_load_embedded/1]).
 
34
         big_boot_embedded/1,
 
35
         on_load_embedded/1, on_load_errors/1, native_early_modules/1]).
35
36
 
36
 
-export([init_per_testcase/2, fin_per_testcase/2, 
 
37
-export([init_per_testcase/2, end_per_testcase/2, 
37
38
         init_per_suite/1, end_per_suite/1,
38
39
         sticky_compiler/1]).
39
40
 
40
 
all(suite) ->
 
41
%% error_logger
 
42
-export([init/1,
 
43
         handle_event/2, handle_call/2, handle_info/2,
 
44
         terminate/2]).
 
45
 
 
46
suite() -> [{ct_hooks,[ts_install_cth]}].
 
47
 
 
48
all() -> 
41
49
    [set_path, get_path, add_path, add_paths, del_path,
42
50
     replace_path, load_file, load_abs, ensure_loaded,
43
51
     delete, purge, soft_purge, is_loaded, all_loaded,
44
52
     load_binary, dir_req, object_code, set_path_file,
45
 
     pa_pz_option, add_del_path,
46
 
     dir_disappeared, ext_mod_dep,
47
 
     load_cached, start_node_with_cache, add_and_rehash,
48
 
     where_is_file_no_cache, where_is_file_cached,
49
 
     purge_stacktrace, mult_lib_roots, bad_erl_libs,
50
 
     code_archive, code_archive2, on_load, on_load_embedded].
 
53
     pa_pz_option, add_del_path, dir_disappeared,
 
54
     ext_mod_dep, clash, load_cached, start_node_with_cache,
 
55
     add_and_rehash, where_is_file_no_cache,
 
56
     where_is_file_cached, purge_stacktrace, mult_lib_roots,
 
57
     bad_erl_libs, code_archive, code_archive2, on_load,
 
58
     on_load_embedded, big_boot_embedded, on_load_errors, 
 
59
     native_early_modules].
 
60
 
 
61
groups() -> 
 
62
    [].
 
63
 
 
64
init_per_group(_GroupName, Config) ->
 
65
        Config.
 
66
 
 
67
end_per_group(_GroupName, Config) ->
 
68
        Config.
51
69
 
52
70
init_per_suite(Config) ->
53
71
    %% The compiler will no longer create a Beam file if
68
86
    P=code:get_path(),
69
87
    P=code:get_path(),
70
88
    [{watchdog, Dog}, {code_path, P}|Config].
71
 
fin_per_testcase(_Func, Config) ->
 
89
 
 
90
end_per_testcase(TC, Config) when TC == mult_lib_roots; 
 
91
                                  TC == big_boot_embedded ->
 
92
    {ok, HostName} = inet:gethostname(),
 
93
    NodeName = list_to_atom(atom_to_list(TC)++"@"++HostName),
 
94
    ?t:stop_node(NodeName),
 
95
    end_per_testcase(Config);
 
96
end_per_testcase(_Func, Config) ->
 
97
    end_per_testcase(Config).
 
98
 
 
99
end_per_testcase(Config) ->
 
100
    code:purge(code_b_test),
72
101
    Dog=?config(watchdog, Config),
73
102
    ?t:timetrap_cancel(Dog),
74
103
    P=?config(code_path, Config),
525
554
add_del_path(suite) ->
526
555
    [];
527
556
add_del_path(doc) -> ["add_path, del_path should not cause priv_dir(App) to fail"];
528
 
add_del_path(Config) ->
 
557
add_del_path(Config) when is_list(Config) ->
529
558
    DDir = ?config(data_dir,Config),
530
559
    Dir1 = filename:join(DDir,"dummy_app-1.0/ebin"),
531
560
    Dir2 = filename:join(DDir,"dummy_app-2.0/ebin"),
537
566
    ?line code:del_path(Dir2),
538
567
    ?line PrivDir1 = code:priv_dir(dummy_app),
539
568
    ok.
540
 
    
541
 
    
 
569
 
 
570
 
 
571
clash(Config) when is_list(Config) ->
 
572
    DDir = ?config(data_dir,Config)++"clash/",
 
573
    P = code:get_path(),
 
574
 
 
575
    %% test non-clashing entries
 
576
 
 
577
    %% remove "." to prevent clash with test-server path
 
578
    ?line true = code:del_path("."),
 
579
    ?line true = code:add_path(DDir++"foobar-0.1/ebin"),
 
580
    ?line true = code:add_path(DDir++"zork-0.8/ebin"),
 
581
    test_server:capture_start(),
 
582
    ?line ok = code:clash(),
 
583
    test_server:capture_stop(),
 
584
    ?line [OKMsg|_] = test_server:capture_get(),
 
585
    ?line true = lists:prefix("** Found 0 name clashes", OKMsg),
 
586
    ?line true = code:set_path(P),
 
587
 
 
588
    %% test clashing entries
 
589
 
 
590
    %% remove "." to prevent clash with test-server path
 
591
    ?line true = code:del_path("."),
 
592
    ?line true = code:add_path(DDir++"foobar-0.1/ebin"),
 
593
    ?line true = code:add_path(DDir++"foobar-0.1.ez/foobar-0.1/ebin"),
 
594
    test_server:capture_start(),
 
595
    ?line ok = code:clash(),
 
596
    test_server:capture_stop(),
 
597
    ?line [ClashMsg|_] = test_server:capture_get(),
 
598
    ?line {match, [" hides "]} = re:run(ClashMsg, "\\*\\* .*( hides ).*",
 
599
                                        [{capture,all_but_first,list}]),
 
600
    ?line true = code:set_path(P),
 
601
 
 
602
    %% test "Bad path can't read"
 
603
 
 
604
    %% remove "." to prevent clash with test-server path
 
605
    Priv = ?config(priv_dir, Config),
 
606
    ?line true = code:del_path("."),
 
607
    TmpEzFile = Priv++"foobar-0.tmp.ez",
 
608
    ?line {ok, _} = file:copy(DDir++"foobar-0.1.ez", TmpEzFile),
 
609
    ?line true = code:add_path(TmpEzFile++"/foobar-0.1/ebin"),
 
610
    case os:type() of
 
611
        {win32,_} ->
 
612
            %% The file wont be deleted on windows until it's closed, why we 
 
613
            %% need to rename instead.
 
614
            ?line ok = file:rename(TmpEzFile,TmpEzFile++".moved");
 
615
         _ ->
 
616
            ?line ok = file:delete(TmpEzFile)
 
617
    end,
 
618
    test_server:capture_start(),
 
619
    ?line ok = code:clash(),
 
620
    test_server:capture_stop(),
 
621
    ?line [BadPathMsg|_] = test_server:capture_get(),
 
622
    ?line true = lists:prefix("** Bad path can't read", BadPathMsg),
 
623
    ?line true = code:set_path(P),
 
624
    file:delete(TmpEzFile++".moved"), %% Only effect on windows
 
625
    ok.
 
626
 
542
627
ext_mod_dep(suite) ->
543
628
    [];
544
 
ext_mod_dep(doce) -> 
 
629
ext_mod_dep(doc) ->
545
630
    ["Every module that the code_server uses should be preloaded, "
546
631
     "this test case verifies that"];
547
632
ext_mod_dep(Config) when is_list(Config) ->
581
666
    %% These modules should be loaded by code.erl before 
582
667
    %% the code_server is started.
583
668
    OK = [erlang, os, prim_file, erl_prim_loader, init, ets,
584
 
          code_server, lists, lists_sort, filename, packages, 
 
669
          code_server, lists, lists_sort, unicode, binary, filename, packages, 
585
670
          gb_sets, gb_trees, hipe_unified_loader, hipe_bifs,
586
671
          prim_zip, zlib],
587
672
    ErrCnt1 = 
610
695
%%%% We need to check these manually...
611
696
% fun's are ok as long as they are defined locally.
612
697
check_funs({'$M_EXPR','$F_EXPR',_},
 
698
           [{unicode,characters_to_binary_int,3},
 
699
            {unicode,characters_to_binary,3},
 
700
            {filename,filename_string_to_binary,1}|_]) -> 0;
 
701
check_funs({'$M_EXPR','$F_EXPR',_},
 
702
           [{unicode,ml_map,3},
 
703
            {unicode,characters_to_binary_int,3},
 
704
            {unicode,characters_to_binary,3},
 
705
            {filename,filename_string_to_binary,1}|_]) -> 0;
 
706
check_funs({'$M_EXPR','$F_EXPR',_},
 
707
           [{unicode,do_o_binary2,2},
 
708
            {unicode,do_o_binary,2},
 
709
            {unicode,o_trans,1},
 
710
            {unicode,characters_to_binary_int,3},
 
711
            {unicode,characters_to_binary,3},
 
712
            {filename,filename_string_to_binary,1}|_]) -> 0;
 
713
check_funs({'$M_EXPR','$F_EXPR',_},
613
714
           [{code_server,load_native_code,4},
614
715
            {code_server,load_native_code_1,2},
615
716
            {code_server,load_native_code,2},
671
772
check_funs({'$M_EXPR','$F_EXPR',1},
672
773
           [{lists,foreach,2},
673
774
            {hipe_unified_loader,patch_consts,3} | _]) -> 0;
 
775
check_funs({'$M_EXPR',warning_msg,2},
 
776
           [{code_server,finish_on_load_report,2} | _]) -> 0;
674
777
%% This is cheating! /raimo
675
778
%% 
676
779
%% check_funs(This = {M,_,_}, Path) ->
824
927
    ?line true = rpc:call(Node, code, add_path, [OkDir]),
825
928
    ?line {error,_} = rpc:call(Node, code, add_path, [BadDir]),
826
929
    ?line ok = rpc:call(Node, code, rehash, []),
 
930
 
 
931
    ?t:stop_node(Node),
827
932
    ok.
828
933
    
829
934
where_is_file_no_cache(suite) ->
925
1030
        ?t:start_node(mult_lib_roots, slave,
926
1031
                      [{args,"-env ERL_LIBS "++ErlLibs}]),
927
1032
 
928
 
    ?line {ok,Cwd} = file:get_cwd(),
 
1033
    ?line TSPath = filename:dirname(code:which(test_server)),
929
1034
    ?line Path0 = rpc:call(Node, code, get_path, []),
930
 
    ?line [Cwd,"."|Path1] = Path0,
 
1035
    ?line [TSPath,"."|Path1] = Path0,
931
1036
    ?line [Kernel|Path2] = Path1,
932
1037
    ?line [Stdlib|Path3] = Path2,
933
1038
    ?line mult_lib_verify_lib(Kernel, "kernel"),
946
1051
 
947
1052
    ?line true = rpc:call(Node, code_SUITE_mult_root_module, works_fine, []),
948
1053
 
949
 
    ?line ?t:stop_node(Node),
950
1054
    ok.
951
1055
 
952
1056
mult_lib_compile(Root, Last) ->
1089
1193
compile_files([], _, _) ->
1090
1194
    ok.
1091
1195
 
 
1196
big_boot_embedded(suite) ->
 
1197
    [];
 
1198
big_boot_embedded(doc) ->
 
1199
    ["Test that a boot file with (almost) all of OTP can be used to start an"
 
1200
     " embeddedd system."];
 
1201
big_boot_embedded(Config) when is_list(Config) ->
 
1202
    ?line {BootArg,AppsInBoot} = create_big_boot(Config),
 
1203
    ?line {ok, Node} = 
 
1204
        ?t:start_node(big_boot_embedded, slave,
 
1205
                      [{args,"-boot "++BootArg++" -mode embedded"}]),
 
1206
    ?line RemoteNodeApps = 
 
1207
        [ {X,Y} || {X,_,Y} <- 
 
1208
                       rpc:call(Node,application,loaded_applications,[]) ],
 
1209
    ?line true = lists:sort(AppsInBoot) =:=  lists:sort(RemoteNodeApps),
 
1210
    ok.
 
1211
 
1092
1212
on_load(Config) when is_list(Config) ->
1093
1213
    Master = on_load_test_case_process,
1094
1214
 
1170
1290
    ?line LibRoot = code:lib_dir(),
1171
1291
    ?line LinkName = filename:join(LibRoot, "on_load_app-1.0"),
1172
1292
    ?line OnLoadApp = filename:join(DataDir, "on_load_app-1.0"),
1173
 
    ?line file:delete(LinkName),
 
1293
    ?line del_link(LinkName),
 
1294
    io:format("LinkName :~p, OnLoadApp: ~p~n",[LinkName,OnLoadApp]),
1174
1295
    case file:make_symlink(OnLoadApp, LinkName) of
1175
1296
        {error,enotsup} ->
1176
1297
            throw({skip,"Support for symlinks required"});
1199
1320
 
1200
1321
    %% Clean up.
1201
1322
    ?line stop_node(Node),
1202
 
    ?line ok = file:delete(LinkName).
 
1323
    ?line ok = del_link(LinkName).
 
1324
 
 
1325
del_link(LinkName) ->
 
1326
   case file:delete(LinkName) of
 
1327
       {error,eperm} ->
 
1328
             file:del_dir(LinkName);
 
1329
       Other ->
 
1330
             Other
 
1331
   end.                    
1203
1332
 
1204
1333
create_boot(Config, Options) ->
1205
1334
    ?line {ok, OldDir} = file:get_cwd(),
1225
1354
    ?line file:close(Fd),
1226
1355
    {filename:dirname(Name),filename:basename(Name)}.
1227
1356
 
 
1357
create_big_boot(Config) ->
 
1358
    ?line {ok, OldDir} = file:get_cwd(),
 
1359
    ?line {Options,Local} = case is_source_dir() of 
 
1360
                                true -> {[no_module_tests,local],true}; 
 
1361
                                _ -> {[no_module_tests],false} 
 
1362
                            end,
 
1363
    ?line {LatestDir,LatestName,Apps} = create_big_script(Config,Local),
 
1364
    ?line ok = file:set_cwd(LatestDir),
 
1365
    ?line ok = systools:make_script(LatestName, Options),
 
1366
    ?line ok = file:set_cwd(OldDir),
 
1367
    {filename:join(LatestDir, LatestName),Apps}.
 
1368
 
 
1369
% The following apps cannot be loaded 
 
1370
% hipe .app references (or can reference) files that have no
 
1371
% corresponding beam file (if hipe is not enabled)
 
1372
filter_app("hipe",_) ->
 
1373
    false;
 
1374
% Dialyzer and typer depends on hipe
 
1375
filter_app("dialyzer",_) ->
 
1376
    false;
 
1377
filter_app("typer",_) ->
 
1378
    false;
 
1379
% Orber requires explicit configuration
 
1380
filter_app("orber",_) ->
 
1381
    false;
 
1382
% cos* depends on orber
 
1383
filter_app("cos"++_,_) ->
 
1384
    false;
 
1385
% ic has a mod instruction in the app file but no corresponding start function
 
1386
filter_app("ic",_) ->
 
1387
    false;
 
1388
% Netconf has some dependency that I really do not understand (maybe like orber)
 
1389
filter_app("netconf",_) ->
 
1390
    false;
 
1391
% Safe has the same kind of error in the .app file as ic
 
1392
filter_app("safe",_) ->
 
1393
    false;
 
1394
% OS_mon does not find it's port program when running cerl
 
1395
filter_app("os_mon",true) ->
 
1396
    false;
 
1397
% Other apps should be OK.
 
1398
filter_app(_,_) ->
 
1399
    true.
 
1400
create_big_script(Config,Local) ->
 
1401
    ?line PrivDir = ?config(priv_dir, Config),
 
1402
    ?line Name = filename:join(PrivDir,"full_script_test"),
 
1403
    ?line InitialApplications=application:loaded_applications(),
 
1404
    %% Applications left loaded by the application suite, unload them!
 
1405
    ?line UnloadFix=[app0,app1,app2,group_leader,app_start_error],
 
1406
    ?line [application:unload(Leftover) || 
 
1407
              Leftover <- UnloadFix,
 
1408
              lists:keymember(Leftover,1,InitialApplications) ],
 
1409
    %% Now we should have only "real" applications...
 
1410
    ?line [application:load(list_to_atom(Y)) || {match,[Y]} <- [ re:run(X,code:lib_dir()++"/"++"([^/-]*).*/ebin",[{capture,[1],list}]) || X <- code:get_path()],filter_app(Y,Local)],
 
1411
    ?line Apps = [ {N,V} || {N,_,V} <- application:loaded_applications()],
 
1412
    ?line {ok,Fd} = file:open(Name ++ ".rel", write),
 
1413
    ?line io:format(Fd,
 
1414
                    "{release, {\"Test release 3\", \"P2A\"}, \n"
 
1415
                    " {erts, \"9.42\"}, \n"
 
1416
                    " ~p}.\n",
 
1417
                    [Apps]),
 
1418
    ?line file:close(Fd),
 
1419
    ?line NewlyLoaded = 
 
1420
        application:loaded_applications() -- InitialApplications,
 
1421
    ?line [ application:unload(N) || {N,_,_} <- NewlyLoaded],
 
1422
    {filename:dirname(Name),filename:basename(Name),Apps}.
 
1423
 
1228
1424
is_source_dir() ->
1229
1425
    filename:basename(code:lib_dir(kernel)) =:= "kernel" andalso
1230
1426
        filename:basename(code:lib_dir(stdlib)) =:= "stdlib".
1231
1427
 
 
1428
on_load_errors(Config) when is_list(Config) ->
 
1429
    Master = on_load_error_test_case_process,
 
1430
    ?line register(Master, self()),
 
1431
 
 
1432
    ?line Data = filename:join([?config(data_dir, Config),"on_load_errors"]),
 
1433
    ?line ok = file:set_cwd(Data),
 
1434
    ?line up_to_date = make:all([{d,'MASTER',Master}]),
 
1435
 
 
1436
    ?line do_on_load_error(an_atom),
 
1437
 
 
1438
    ?line error_logger:add_report_handler(?MODULE, self()),
 
1439
 
 
1440
    ?line do_on_load_error({something,terrible,is,wrong}),
 
1441
    receive
 
1442
        Any1 ->
 
1443
            ?line {_, "The on_load function"++_,
 
1444
                   [on_load_error,
 
1445
                    {something,terrible,is,wrong},_]} = Any1
 
1446
    end,
 
1447
 
 
1448
    ?line do_on_load_error(fail),               %Cause exception.
 
1449
    receive
 
1450
        Any2 ->
 
1451
            ?line {_, "The on_load function"++_,
 
1452
                   [on_load_error,{failed,[_|_]},_]} = Any2
 
1453
    end,
 
1454
 
 
1455
    %% There should be no more messages.
 
1456
    receive
 
1457
        Unexpected ->
 
1458
            ?line ?t:fail({unexpected,Unexpected})
 
1459
    after 10 ->
 
1460
            ok
 
1461
    end,
 
1462
 
 
1463
    ok.
 
1464
 
 
1465
do_on_load_error(ReturnValue) ->
 
1466
    ?line {_,Ref} = spawn_monitor(fun() ->
 
1467
                                          exit(on_load_error:main())
 
1468
                                  end),
 
1469
    receive {on_load_error,ErrorPid} -> ok end,
 
1470
    ?line ErrorPid ! ReturnValue,
 
1471
    receive
 
1472
        {'DOWN',Ref,process,_,Exit} ->
 
1473
            ?line {undef,[{on_load_error,main,[]}|_]} = Exit
 
1474
    end.
 
1475
 
 
1476
native_early_modules(suite) -> [];
 
1477
native_early_modules(doc) -> ["Test that the native code of early loaded modules is loaded"];
 
1478
native_early_modules(Config) when is_list(Config) ->
 
1479
    case erlang:system_info(hipe_architecture) of
 
1480
        undefined ->
 
1481
            {skip,"Native code support is not enabled"};
 
1482
        Architecture ->
 
1483
            native_early_modules_1(Architecture)
 
1484
    end.
 
1485
 
 
1486
native_early_modules_1(Architecture) ->
 
1487
    ?line {lists, ListsBinary, _ListsFilename} = code:get_object_code(lists),
 
1488
    ?line ChunkName = hipe_unified_loader:chunk_name(Architecture),
 
1489
    ?line NativeChunk = beam_lib:chunks(ListsBinary, [ChunkName]),
 
1490
    ?line IsHipeCompiled = case NativeChunk of
 
1491
        {ok,{_,[{_,Bin}]}} when is_binary(Bin) -> true;
 
1492
        {error, beam_lib, _} -> false
 
1493
    end,
 
1494
    case IsHipeCompiled of
 
1495
        false ->
 
1496
            {skip,"OTP apparently not configured with --enable-native-libs"};
 
1497
        true ->
 
1498
            ?line true = lists:all(fun code:is_module_native/1,
 
1499
                                   [ets,file,filename,gb_sets,gb_trees,
 
1500
                                    hipe_unified_loader,lists,os,packages]),
 
1501
            ok
 
1502
    end.
 
1503
 
 
1504
%%-----------------------------------------------------------------
 
1505
%% error_logger handler.
 
1506
%% (Copied from stdlib/test/proc_lib_SUITE.erl.)
 
1507
%%-----------------------------------------------------------------
 
1508
init(Tester) ->
 
1509
    {ok, Tester}.
 
1510
 
 
1511
handle_event({error, _GL, {emulator, _, _}}, Tester) ->
 
1512
    {ok, Tester};
 
1513
handle_event({error, _GL, Msg}, Tester) ->
 
1514
    Tester ! Msg,
 
1515
    {ok, Tester};
 
1516
handle_event(_Event, State) ->
 
1517
    {ok, State}.
 
1518
 
 
1519
handle_info(_, State) ->
 
1520
    {ok, State}.
 
1521
 
 
1522
handle_call(_Query, State) -> {ok, {error, bad_query}, State}.
 
1523
 
 
1524
terminate(_Reason, State) ->
 
1525
    State.
 
1526
 
 
1527
%%%
 
1528
%%% Common utility functions.
 
1529
%%%
 
1530
 
1232
1531
start_node(Name, Param) ->
1233
1532
    ?t:start_node(Name, slave, [{args, Param}]).
1234
1533