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

« back to all changes in this revision

Viewing changes to lib/test_server/src/test_server.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(test_server).
35
35
-export([fail/0,fail/1,format/1,format/2,format/3]).
36
36
-export([capture_start/0,capture_stop/0,capture_get/0]).
37
37
-export([messages_get/0]).
38
 
-export([hours/1,minutes/1,seconds/1,sleep/1,timecall/3]).
 
38
-export([hours/1,minutes/1,seconds/1,sleep/1,adjusted_sleep/1,timecall/3]).
39
39
-export([timetrap_scale_factor/0,timetrap/1,timetrap_cancel/1]).
40
40
-export([m_out_of_n/3,do_times/4,do_times/2]).
41
41
-export([call_crash/3,call_crash/4,call_crash/5]).
89
89
    global:register_name(?MODULE,self()),
90
90
    process_flag(trap_exit,true),
91
91
    test_server_sup:cleanup_crash_dumps(),
92
 
    case gen_tcp:connect(Host,Port, [binary, 
93
 
                                     {reuseaddr,true}, 
 
92
    case gen_tcp:connect(Host,Port, [binary,
 
93
                                     {reuseaddr,true},
94
94
                                     {packet,2}]) of
95
 
        {ok,MainSock} -> 
 
95
        {ok,MainSock} ->
96
96
            Starter ! {self(),started},
97
97
            request(MainSock,{target_info,init_target_info()}),
98
98
            loop(#state{controller={Host,MainSock}});
99
 
        Error -> 
 
99
        Error ->
100
100
            Starter ! {self(),{error,
101
101
                               {could_not_contact_controller,Error}}}
102
102
    end.
127
127
            halt();
128
128
        {'EXIT',Pid,Reason} ->
129
129
            case lists:keysearch(Pid,1,State#state.jobs) of
130
 
                {value,{Pid,Name}} -> 
 
130
                {value,{Pid,Name}} ->
131
131
                    case Reason of
132
132
                        normal -> ignore;
133
133
                        _other -> request(MainSock,{job_proc_killed,Name,Reason})
157
157
job(Host,Port,Starter) ->
158
158
    process_flag(trap_exit,true),
159
159
    init_purify(),
160
 
    case gen_tcp:connect(Host,Port, [binary, 
161
 
                                     {reuseaddr,true}, 
 
160
    case gen_tcp:connect(Host,Port, [binary,
 
161
                                     {reuseaddr,true},
162
162
                                     {packet,4},
163
163
                                     {active,false}]) of
164
164
        {ok,JobSock} ->
165
165
            Starter ! {self(),started},
166
166
            job(JobSock);
167
 
        Error -> 
 
167
        Error ->
168
168
            Starter ! {self(),{error,
169
169
                               {could_not_contact_controller,Error}}}
170
170
    end.
192
192
        true ->
193
193
            {ok,Cwd} = file:get_cwd(),
194
194
            Cwd ++ "/" ++ Basename;
195
 
        false ->            
 
195
        false ->
196
196
            filename:absname(Basename)
197
197
    end.
198
198
 
216
216
 
217
217
del_dir(Dir) ->
218
218
    case file:read_file_info(Dir) of
219
 
        {ok,#file_info{type=directory}} -> 
 
219
        {ok,#file_info{type=directory}} ->
220
220
            {ok,Cont} = file:list_dir(Dir),
221
221
            lists:foreach(fun(F) -> del_dir(filename:join(Dir,F)) end, Cont),
222
222
            ok = file:del_dir(Dir);
227
227
            catch file:delete(Dir),
228
228
            ok
229
229
    end.
230
 
    
 
230
 
231
231
%%
232
232
%% Receive and decode request on job socket
233
233
%%
237
237
        ok -> job_loop(JobSock);
238
238
        {stop,R} -> R
239
239
    end.
240
 
    
 
240
 
241
241
decode_job({{beam,Mod,Which},Beam}) ->
242
242
    % FIXME, shared directory structure on host and target required,
243
243
    % "Library beams" are not loaded from HOST... /Patrik
254
254
    ok = erl_tar:extract(Tarfile,[compressed,{cwd,JobDir}]),
255
255
    ok = file:delete(Tarfile),
256
256
    ok;
257
 
decode_job({test_case,Case}) -> 
 
257
decode_job({test_case,Case}) ->
258
258
    Result = run_test_case_apply(Case),
259
259
    JobSock = get(test_server_job_sock),
260
260
    request(JobSock,{test_case_result,Result}),
266
266
            request(JobSock,{{crash_dumps,filename:basename(TarFile)},TarBin})
267
267
    end,
268
268
    ok;
269
 
decode_job({sync_apply,{M,F,A}}) -> 
 
269
decode_job({sync_apply,{M,F,A}}) ->
270
270
    R = apply(M,F,A),
271
271
    request(get(test_server_job_sock),{sync_result,R}),
272
272
    ok;
273
 
decode_job(job_done) -> 
 
273
decode_job(job_done) ->
274
274
    {stop,stopped}.
275
275
 
276
276
%%
282
282
 
283
283
 
284
284
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
285
 
%% cover_compile({App,Include,Exclude,Cross}) -> 
 
285
%% cover_compile({App,Include,Exclude,Cross}) ->
286
286
%%                                          {ok,AnalyseModules} | {error,Reason}
287
 
%% 
 
287
%%
288
288
%% App = atom() , name of application to be compiled
289
289
%% Exclude = [atom()], list of modules to exclude
290
290
%% Include = [atom()], list of modules outside of App that should be included
293
293
%%                 in the cover compilation, but that shall not be part of
294
294
%%                 the cover analysis for this application.
295
295
%%
296
 
%% Cover compile the given application. Return {ok,AnalyseMods} if application 
 
296
%% Cover compile the given application. Return {ok,AnalyseMods} if application
297
297
%% is found, else {error,application_not_found}.
298
298
 
299
299
cover_compile({none,_Exclude,Include,Cross}) ->
330
330
    end;
331
331
cover_compile({App,Exclude,Include,Cross}) ->
332
332
    case code:lib_dir(App) of
333
 
        {error,bad_name} -> 
 
333
        {error,bad_name} ->
334
334
            case Include++Cross of
335
335
                [] ->
336
336
                    io:format("\nWARNING: Can't find lib_dir for \'~w\'\n"
366
366
                    {ok,AnalyseMods}
367
367
            end
368
368
    end.
369
 
    
 
369
 
370
370
 
371
371
module_names(Beams) ->
372
372
    [list_to_atom(filename:basename(filename:rootname(Beam))) || Beam <- Beams].
380
380
                                    Dont=:=test_server_ctrl ->
381
381
    do_cover_compile1(Rest);
382
382
do_cover_compile1([M|Rest]) ->
383
 
    case {code:is_sticky(M),code:is_loaded(M)} of 
 
383
    case {code:is_sticky(M),code:is_loaded(M)} of
384
384
        {true,_} ->
385
385
            code:unstick_mod(M),
386
386
            case cover:compile_beam(M) of
387
 
                {ok,_} -> 
 
387
                {ok,_} ->
388
388
                    ok;
389
389
                Error ->
390
390
                    io:fwrite("\nWARNING: Could not cover compile ~w: ~p\n",
402
402
            end;
403
403
        {false,_} ->
404
404
            case cover:compile_beam(M) of
405
 
                {ok,_} -> 
 
405
                {ok,_} ->
406
406
                    ok;
407
407
                Error ->
408
408
                    io:fwrite("\nWARNING: Could not cover compile ~w: ~p\n",
415
415
 
416
416
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
417
417
%% cover_analyse(Analyse,Modules) -> [{M,{Cov,NotCov,Details}}]
418
 
%% 
 
418
%%
419
419
%% Analyse = {details,Dir} | details | {overview,void()} | overview
420
420
%% Modules = [atom()], the modules to analyse
421
421
%%
422
422
%% Cover analysis. If this is a remote target, analyse_to_file can not be used.
423
423
%% In that case the analyse level 'line' is used instead if Analyse==details.
424
424
%%
425
 
%% If this is a local target, the test directory is given 
 
425
%% If this is a local target, the test directory is given
426
426
%% (Analyse=={details,Dir}) and analyse_to_file can be used directly.
427
427
%%
428
428
%% If Analyse==overview | {overview,Dir} analyse_to_file is not used, only
432
432
%% all.coverdata in that directory.
433
433
cover_analyse(Analyse,Modules) ->
434
434
    io:fwrite("Cover analysing...\n",[]),
435
 
    DetailsFun = 
 
435
    DetailsFun =
436
436
        case Analyse of
437
437
            {details,Dir} ->
438
438
                case cover:export(filename:join(Dir,"all.coverdata")) of
439
439
                    ok ->
440
 
                        fun(M) -> 
 
440
                        fun(M) ->
441
441
                                OutFile = filename:join(Dir,
442
442
                                                        atom_to_list(M) ++
443
443
                                                        ".COVER.html"),
451
451
                    Error ->
452
452
                        fun(_) -> Error end
453
453
                end;
454
 
            details -> 
 
454
            details ->
455
455
                fun(M) ->
456
456
                        case cover:analyse(M,line) of
457
457
                            {ok,Lines} ->
470
470
            overview ->
471
471
                fun(_) -> undefined end
472
472
        end,
473
 
    R = lists:map(
 
473
    R = pmap(
474
474
          fun(M) ->
475
475
                  case cover:analyse(M,module) of
476
476
                      {ok,{M,{Cov,NotCov}}} ->
486
486
    stick_all_sticky(node(),Sticky),
487
487
    R.
488
488
 
 
489
pmap(Fun,List) ->
 
490
    Collector = self(),
 
491
    Pids = lists:map(fun(E) ->
 
492
                             spawn(fun() ->
 
493
                                           Collector ! {res,self(),Fun(E)} 
 
494
                                   end) 
 
495
                     end, List),
 
496
    lists:map(fun(Pid) ->
 
497
                      receive
 
498
                          {res,Pid,Res} ->
 
499
                              Res
 
500
                      end
 
501
              end, Pids).
489
502
 
490
503
unstick_all_sticky(Node) ->
491
504
    lists:filter(
492
 
      fun(M) -> 
 
505
      fun(M) ->
493
506
              case code:is_sticky(M) of
494
507
                  true ->
495
508
                      rpc:call(Node,code,unstick_mod,[M]),
502
515
 
503
516
stick_all_sticky(Node,Sticky) ->
504
517
    lists:foreach(
505
 
      fun(M) -> 
 
518
      fun(M) ->
506
519
              rpc:call(Node,code,stick_mod,[M])
507
520
      end,
508
521
      Sticky).
509
522
 
510
523
 
511
524
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
512
 
%% run_test_case_apply(Mod,Func,Args,Name,RunInit,MultiplyTimetrap) -> 
 
525
%% run_test_case_apply(Mod,Func,Args,Name,RunInit,TimetrapData) ->
513
526
%%               {Time,Value,Loc,Opts,Comment} | {died,Reason,unknown,Comment}
514
 
%% 
 
527
%%
515
528
%% Time = float()   (seconds)
516
529
%% Value = term()
517
530
%% Loc = term()
518
531
%% Comment = string()
519
532
%% Reason = term()
520
533
%%
521
 
%% Spawns off a process (case process) that actually runs the test suite. 
522
 
%% The case process will have the job process as group leader, which makes 
 
534
%% Spawns off a process (case process) that actually runs the test suite.
 
535
%% The case process will have the job process as group leader, which makes
523
536
%% it possible to capture all it's output from io:format/2, etc.
524
537
%%
525
538
%% The job process then sits down and waits for news from the case process.
535
548
%% called or the comment given by the return value {comment,Comment} from
536
549
%% a test case.
537
550
%%
538
 
%% {died,Reason,unknown,Comment} is returned if the test case was killed 
 
551
%% {died,Reason,unknown,Comment} is returned if the test case was killed
539
552
%% by some other process. Reason is the kill reason provided.
540
553
%%
541
 
%% MultiplyTimetrap indicates a possible extension of all timetraps
542
 
%% Timetraps will be multiplied by this integer. If it is infinity, no
543
 
%% timetraps will be started at all.
 
554
%% TimetrapData = {MultiplyTimetrap,ScaleTimetrap}, which indicates a
 
555
%% possible extension of all timetraps. Timetraps will be multiplied by
 
556
%% MultiplyTimetrap. If it is infinity, no timetraps will be started at all.
 
557
%% ScaleTimetrap indicates if test_server should attemp to automatically
 
558
%% compensate timetraps for runtime delays introduced by e.g. tools like
 
559
%% cover.
544
560
 
545
 
run_test_case_apply({CaseNum,Mod,Func,Args,Name,RunInit,MultiplyTimetrap}) ->
 
561
run_test_case_apply({CaseNum,Mod,Func,Args,Name,RunInit,TimetrapData}) ->
546
562
    purify_format("Test case #~w ~w:~w/1", [CaseNum, Mod, Func]),
547
563
    case os:getenv("TS_RUN_VALGRIND") of
548
 
        false -> 
 
564
        false ->
549
565
            ok;
550
566
        _ ->
551
567
            os:putenv("VALGRIND_LOGFILE_INFIX",atom_to_list(Mod)++"."++
552
568
                      atom_to_list(Func)++"-")
553
569
    end,
554
570
    test_server_h:testcase({Mod,Func,1}),
555
 
    ProcBef = erlang:system_info(process_count),    
556
 
    Result = run_test_case_apply(Mod, Func, Args, Name, RunInit, MultiplyTimetrap),
 
571
    ProcBef = erlang:system_info(process_count),
 
572
    Result = run_test_case_apply(Mod, Func, Args, Name, RunInit, TimetrapData),
557
573
    ProcAft = erlang:system_info(process_count),
558
574
    purify_new_leaks(),
559
575
    DetFail = get(test_server_detected_fail),
560
576
    {Result,DetFail,ProcBef,ProcAft}.
561
 
    
562
 
run_test_case_apply(Mod, Func, Args, Name, RunInit, MultiplyTimetrap) ->
 
577
 
 
578
run_test_case_apply(Mod, Func, Args, Name, RunInit, TimetrapData) ->
563
579
    case get(test_server_job_dir) of
564
580
        undefined ->
565
581
            %% i'm a local target
566
 
            do_run_test_case_apply(Mod, Func, Args, Name, RunInit, MultiplyTimetrap);
 
582
            do_run_test_case_apply(Mod, Func, Args, Name, RunInit, TimetrapData);
567
583
        JobDir ->
568
584
            %% i'm a remote target
569
585
            case Args of
570
586
                [Config] when is_list(Config) ->
571
 
                    {value,{data_dir,HostDataDir}} = 
 
587
                    {value,{data_dir,HostDataDir}} =
572
588
                        lists:keysearch(data_dir, 1, Config),
573
589
                    DataBase = filename:basename(HostDataDir),
574
590
                    TargetDataDir = filename:join(JobDir, DataBase),
578
594
                    Config2 = lists:keyreplace(priv_dir, 1, Config1,
579
595
                                               {priv_dir,TargetPrivDir}),
580
596
                    do_run_test_case_apply(Mod, Func, [Config2], Name, RunInit,
581
 
                                           MultiplyTimetrap);
 
597
                                           TimetrapData);
582
598
                _other ->
583
599
                    do_run_test_case_apply(Mod, Func, Args, Name, RunInit,
584
 
                                           MultiplyTimetrap)
 
600
                                           TimetrapData)
585
601
            end
586
602
    end.
587
 
do_run_test_case_apply(Mod, Func, Args, Name, RunInit, MultiplyTimetrap) ->
 
603
do_run_test_case_apply(Mod, Func, Args, Name, RunInit, TimetrapData) ->
588
604
    {ok,Cwd} = file:get_cwd(),
589
605
    Args2Print = case Args of
590
 
                     [Args1] when is_list(Args1) -> 
 
606
                     [Args1] when is_list(Args1) ->
591
607
                         lists:keydelete(tc_group_result, 1, Args1);
592
 
                     _ -> 
 
608
                     _ ->
593
609
                         Args
594
610
                 end,
595
611
    print(minor, "Test case started with:\n~s:~s(~p)\n", [Mod,Func,Args2Print]),
600
616
    OldGLeader = group_leader(),
601
617
    %% Set ourself to group leader for the spawned process
602
618
    group_leader(self(),self()),
603
 
    Pid = 
 
619
    Pid =
604
620
        spawn_link(
605
 
          fun() -> 
606
 
                  run_test_case_eval(Mod, Func, Args, Name, Ref, 
607
 
                                     RunInit, MultiplyTimetrap,
 
621
          fun() ->
 
622
                  run_test_case_eval(Mod, Func, Args, Name, Ref,
 
623
                                     RunInit, TimetrapData,
608
624
                                     TCCallback)
609
625
          end),
610
626
    group_leader(OldGLeader, self()),
611
627
    put(test_server_detected_fail, []),
612
 
    run_test_case_msgloop(Ref, Pid, false, false, "").
 
628
    run_test_case_msgloop(Ref, Pid, false, false, "", undefined).
613
629
 
614
630
%% Ugly bug (pre R5A):
615
631
%% If this process (group leader of the test case) terminates before
620
636
%% A test case is known to have failed if it returns {'EXIT', _} tuple,
621
637
%% or sends a message {failed, File, Line} to it's group_leader
622
638
%%
623
 
run_test_case_msgloop(Ref, Pid, CaptureStdout, Terminate, Comment) ->
 
639
run_test_case_msgloop(Ref, Pid, CaptureStdout, Terminate, Comment, CurrConf) ->
624
640
    %% NOTE: Keep job_proxy_msgloop/0 up to date when changes
625
641
    %%       are made in this function!
626
642
    {Timeout,ReturnValue} =
641
657
                receive
642
658
                    {'DOWN', Mon, process, Pid, _} ->
643
659
                        Comment
644
 
                    after 10000 ->                  
 
660
                    after 10000 ->
645
661
                            %% Pid is probably trapping exits, hit it harder...
646
662
                            exit(Pid, kill),
647
663
                            %% here's the only place we know Reason, so we save
648
664
                            %% it as a comment, potentially replacing user data
649
665
                            Error = lists:flatten(io_lib:format("Aborted: ~p",[Reason])),
650
 
                            Error1 = lists:flatten([string:strip(S,left) || 
 
666
                            Error1 = lists:flatten([string:strip(S,left) ||
651
667
                                                    S <- string:tokens(Error,[$\n])]),
652
668
                            if length(Error1) > 63 ->
653
669
                                    string:substr(Error1,1,60) ++ "...";
655
671
                                    Error1
656
672
                            end
657
673
                    end,
658
 
            run_test_case_msgloop(Ref,Pid,CaptureStdout,Terminate,NewComment);
 
674
            run_test_case_msgloop(Ref,Pid,CaptureStdout,Terminate,NewComment,CurrConf);
659
675
        {io_request,From,ReplyAs,{put_chars,io_lib,Func,[Format,Args]}}
660
676
        when is_list(Format) ->
661
677
            Msg = (catch io_lib:Func(Format,Args)),
662
678
            run_test_case_msgloop_io(ReplyAs,CaptureStdout,Msg,From,Func),
663
 
            run_test_case_msgloop(Ref,Pid,CaptureStdout,Terminate,Comment);
 
679
            run_test_case_msgloop(Ref,Pid,CaptureStdout,Terminate,Comment,CurrConf);
664
680
        {io_request,From,ReplyAs,{put_chars,io_lib,Func,[Format,Args]}}
665
681
        when is_atom(Format) ->
666
682
            Msg = (catch io_lib:Func(Format,Args)),
667
683
            run_test_case_msgloop_io(ReplyAs,CaptureStdout,Msg,From,Func),
668
 
            run_test_case_msgloop(Ref,Pid,CaptureStdout,Terminate,Comment);
 
684
            run_test_case_msgloop(Ref,Pid,CaptureStdout,Terminate,Comment,CurrConf);
669
685
        {io_request,From,ReplyAs,{put_chars,Bytes}} ->
670
686
            run_test_case_msgloop_io(
671
687
              ReplyAs,CaptureStdout,Bytes,From,put_chars),
672
 
            run_test_case_msgloop(Ref,Pid,CaptureStdout,Terminate,Comment);
673
 
        {io_request,From,ReplyAs,{put_chars,unicode,io_lib,Func,[Format,Args]}}
674
 
        when is_list(Format) ->
675
 
            Msg = unicode_to_latin1(catch io_lib:Func(Format,Args)),
676
 
            run_test_case_msgloop_io(ReplyAs,CaptureStdout,Msg,From,Func),
677
 
            run_test_case_msgloop(Ref,Pid,CaptureStdout,Terminate,Comment);
678
 
        {io_request,From,ReplyAs,{put_chars,latin1,io_lib,Func,[Format,Args]}}
679
 
        when is_list(Format) ->
680
 
            Msg = (catch io_lib:Func(Format,Args)),
681
 
            run_test_case_msgloop_io(ReplyAs,CaptureStdout,Msg,From,Func),
682
 
            run_test_case_msgloop(Ref,Pid,CaptureStdout,Terminate,Comment);
683
 
        {io_request,From,ReplyAs,{put_chars,unicode,io_lib,Func,[Format,Args]}}
684
 
        when is_atom(Format) ->
685
 
            Msg = unicode_to_latin1(catch io_lib:Func(Format,Args)),
686
 
            run_test_case_msgloop_io(ReplyAs,CaptureStdout,Msg,From,Func),
687
 
            run_test_case_msgloop(Ref,Pid,CaptureStdout,Terminate,Comment);
688
 
        {io_request,From,ReplyAs,{put_chars,latin1,io_lib,Func,[Format,Args]}}
689
 
        when is_atom(Format) ->
690
 
            Msg = (catch io_lib:Func(Format,Args)),
691
 
            run_test_case_msgloop_io(ReplyAs,CaptureStdout,Msg,From,Func),
692
 
            run_test_case_msgloop(Ref,Pid,CaptureStdout,Terminate,Comment);
 
688
            run_test_case_msgloop(Ref,Pid,CaptureStdout,Terminate,Comment,CurrConf);
 
689
        {io_request,From,ReplyAs,{put_chars,unicode,io_lib,Func,[Format,Args]}}
 
690
        when is_list(Format) ->
 
691
            Msg = unicode_to_latin1(catch io_lib:Func(Format,Args)),
 
692
            run_test_case_msgloop_io(ReplyAs,CaptureStdout,Msg,From,Func),
 
693
            run_test_case_msgloop(Ref,Pid,CaptureStdout,Terminate,Comment,CurrConf);
 
694
        {io_request,From,ReplyAs,{put_chars,latin1,io_lib,Func,[Format,Args]}}
 
695
        when is_list(Format) ->
 
696
            Msg = (catch io_lib:Func(Format,Args)),
 
697
            run_test_case_msgloop_io(ReplyAs,CaptureStdout,Msg,From,Func),
 
698
            run_test_case_msgloop(Ref,Pid,CaptureStdout,Terminate,Comment,CurrConf);
 
699
        {io_request,From,ReplyAs,{put_chars,unicode,io_lib,Func,[Format,Args]}}
 
700
        when is_atom(Format) ->
 
701
            Msg = unicode_to_latin1(catch io_lib:Func(Format,Args)),
 
702
            run_test_case_msgloop_io(ReplyAs,CaptureStdout,Msg,From,Func),
 
703
            run_test_case_msgloop(Ref,Pid,CaptureStdout,Terminate,Comment,CurrConf);
 
704
        {io_request,From,ReplyAs,{put_chars,latin1,io_lib,Func,[Format,Args]}}
 
705
        when is_atom(Format) ->
 
706
            Msg = (catch io_lib:Func(Format,Args)),
 
707
            run_test_case_msgloop_io(ReplyAs,CaptureStdout,Msg,From,Func),
 
708
            run_test_case_msgloop(Ref,Pid,CaptureStdout,Terminate,Comment,CurrConf);
693
709
        {io_request,From,ReplyAs,{put_chars,unicode,Bytes}} ->
694
710
            run_test_case_msgloop_io(
695
711
              ReplyAs,CaptureStdout,unicode_to_latin1(Bytes),From,put_chars),
696
 
            run_test_case_msgloop(Ref,Pid,CaptureStdout,Terminate,Comment);
 
712
            run_test_case_msgloop(Ref,Pid,CaptureStdout,Terminate,Comment,CurrConf);
697
713
        {io_request,From,ReplyAs,{put_chars,latin1,Bytes}} ->
698
714
            run_test_case_msgloop_io(
699
715
              ReplyAs,CaptureStdout,Bytes,From,put_chars),
700
 
            run_test_case_msgloop(Ref,Pid,CaptureStdout,Terminate,Comment);
 
716
            run_test_case_msgloop(Ref,Pid,CaptureStdout,Terminate,Comment,CurrConf);
701
717
        IoReq when element(1, IoReq) == io_request ->
702
718
            %% something else, just pass it on
703
719
            group_leader() ! IoReq,
704
 
            run_test_case_msgloop(Ref,Pid,CaptureStdout,Terminate,Comment);
 
720
            run_test_case_msgloop(Ref,Pid,CaptureStdout,Terminate,Comment,CurrConf);
705
721
        {structured_io,ClientPid,Msg} ->
706
722
            output(Msg, ClientPid),
707
 
            run_test_case_msgloop(Ref,Pid,CaptureStdout,Terminate,Comment);
 
723
            run_test_case_msgloop(Ref,Pid,CaptureStdout,Terminate,Comment,CurrConf);
708
724
        {capture,NewCapture} ->
709
 
            run_test_case_msgloop(Ref,Pid,NewCapture,Terminate,Comment);
 
725
            run_test_case_msgloop(Ref,Pid,NewCapture,Terminate,Comment,CurrConf);
710
726
        {sync_apply,From,MFA} ->
711
727
            sync_local_or_remote_apply(false,From,MFA),
712
 
            run_test_case_msgloop(Ref,Pid,CaptureStdout,Terminate,Comment);
 
728
            run_test_case_msgloop(Ref,Pid,CaptureStdout,Terminate,Comment,CurrConf);
713
729
        {sync_apply_proxy,Proxy,From,MFA} ->
714
730
            sync_local_or_remote_apply(Proxy,From,MFA),
715
 
            run_test_case_msgloop(Ref,Pid,CaptureStdout,Terminate,Comment);
 
731
            run_test_case_msgloop(Ref,Pid,CaptureStdout,Terminate,Comment,CurrConf);
716
732
        {printout,Detail,Format,Args} ->
717
733
            print(Detail,Format,Args),
718
 
            run_test_case_msgloop(Ref,Pid,CaptureStdout,Terminate,Comment);
 
734
            run_test_case_msgloop(Ref,Pid,CaptureStdout,Terminate,Comment,CurrConf);
719
735
        {comment,NewComment} ->
720
736
            Terminate1 =
721
737
                case Terminate of
722
 
                    {true,{Time,Value,Loc,Opts,_OldComment}} -> 
 
738
                    {true,{Time,Value,Loc,Opts,_OldComment}} ->
723
739
                        {true,{Time,Value,mod_loc(Loc),Opts,NewComment}};
724
740
                    Other ->
725
741
                        Other
726
742
                end,
727
 
            run_test_case_msgloop(Ref,Pid,CaptureStdout,Terminate1,NewComment);
 
743
            run_test_case_msgloop(Ref,Pid,CaptureStdout,Terminate1,NewComment,CurrConf);
 
744
        {set_curr_conf,NewCurrConf} ->
 
745
            run_test_case_msgloop(Ref,Pid,CaptureStdout,Terminate,Comment,NewCurrConf);
728
746
        {'EXIT',Pid,{Ref,Time,Value,Loc,Opts}} ->
729
747
            RetVal = {Time/1000000,Value,mod_loc(Loc),Opts,Comment},
730
 
            run_test_case_msgloop(Ref,Pid,CaptureStdout,{true,RetVal},Comment);
 
748
            run_test_case_msgloop(Ref,Pid,CaptureStdout,{true,RetVal},Comment,undefined);
731
749
        {'EXIT',Pid,Reason} ->
732
750
            case Reason of
733
751
                {timetrap_timeout,TVal,Loc} ->
734
752
                    %% convert Loc to form that can be formatted
735
 
                    Loc1 = mod_loc(Loc),
736
 
                    {Mod,Func} = get_mf(Loc1),
737
 
                    %% The framework functions mustn't execute on this
738
 
                    %% group leader process or io will cause deadlock,
739
 
                    %% so we spawn a dedicated process for the operation
740
 
                    %% and let the group leader go back to handle io.
741
 
                    spawn_fw_call(Mod,Func,Pid,{timetrap_timeout,TVal},
742
 
                                  Loc1,self(),Comment),
743
 
                    run_test_case_msgloop(Ref,Pid,CaptureStdout,Terminate,Comment);
 
753
                    case mod_loc(Loc) of
 
754
                        {FwMod,FwFunc,framework} ->
 
755
                            %% timout during framework call
 
756
                            spawn_fw_call(FwMod,FwFunc,Pid,
 
757
                                          {framework_error,{timetrap,TVal}},
 
758
                                          unknown,self(),Comment),
 
759
                            run_test_case_msgloop(Ref,Pid,CaptureStdout,Terminate,
 
760
                                                  Comment,undefined);
 
761
                        Loc1 ->
 
762
                            {Mod,Func} = get_mf(Loc1),
 
763
                            %% call end_per_testcase on a separate process,
 
764
                            %% only so that the user has a chance to clean up
 
765
                            %% after init_per_testcase, even after a timetrap timeout
 
766
                            NewCurrConf =
 
767
                                case CurrConf of
 
768
                                    {{Mod,Func},Conf} ->
 
769
                                        EndConfPid =
 
770
                                            call_end_conf(Mod,Func,Pid,
 
771
                                                          {timetrap_timeout,TVal},
 
772
                                                          Loc1,[{tc_status,
 
773
                                                                 {failed,
 
774
                                                                  timetrap_timeout}}|Conf],
 
775
                                                          TVal),
 
776
                                        {EndConfPid,{Mod,Func},Conf};
 
777
                                    _ ->
 
778
                                        %% The framework functions mustn't execute on this
 
779
                                        %% group leader process or io will cause deadlock,
 
780
                                        %% so we spawn a dedicated process for the operation
 
781
                                        %% and let the group leader go back to handle io.
 
782
                                        spawn_fw_call(Mod,Func,Pid,{timetrap_timeout,TVal},
 
783
                                                      Loc1,self(),Comment),
 
784
                                        undefined
 
785
                                end,
 
786
                            run_test_case_msgloop(Ref,Pid,CaptureStdout,Terminate,
 
787
                                                  Comment,NewCurrConf)
 
788
                    end;
744
789
                {timetrap_timeout,TVal,Loc,InitOrEnd} ->
745
 
                    Loc1 = mod_loc(Loc),
746
 
                    {Mod,_Func} = get_mf(Loc1),
747
 
                    spawn_fw_call(Mod,InitOrEnd,Pid,{timetrap_timeout,TVal},
748
 
                                  Loc1,self(),Comment),
749
 
                    run_test_case_msgloop(Ref,Pid,CaptureStdout,Terminate,Comment);                 
750
 
                {testcase_aborted,Reason,Loc} ->
751
 
                    Loc1 = mod_loc(Loc),
752
 
                    {Mod,Func} = get_mf(Loc1),
753
 
                    spawn_fw_call(Mod,Func,Pid,{testcase_aborted,Reason},
754
 
                                  Loc1,self(),Comment),
755
 
                    run_test_case_msgloop(Ref,Pid,CaptureStdout,Terminate,Comment);
756
 
                killed ->                       
 
790
                    case mod_loc(Loc) of
 
791
                        {FwMod,FwFunc,framework} ->
 
792
                            %% timout during framework call
 
793
                            spawn_fw_call(FwMod,FwFunc,Pid,
 
794
                                          {framework_error,{timetrap,TVal}},
 
795
                                          unknown,self(),Comment);
 
796
                        Loc1 ->
 
797
                            {Mod,_Func} = get_mf(Loc1),
 
798
                            spawn_fw_call(Mod,InitOrEnd,Pid,{timetrap_timeout,TVal},
 
799
                                          Loc1,self(),Comment)
 
800
                    end,
 
801
                    run_test_case_msgloop(Ref,Pid,CaptureStdout,Terminate,Comment,CurrConf);
 
802
                {testcase_aborted,AbortReason,AbortLoc} ->
 
803
                    ErrorMsg = {testcase_aborted,AbortReason},
 
804
                    case mod_loc(AbortLoc) of
 
805
                        {FwMod,FwFunc,framework} ->
 
806
                            %% abort during framework call
 
807
                            spawn_fw_call(FwMod,FwFunc,Pid,
 
808
                                          {framework_error,ErrorMsg},
 
809
                                          unknown,self(),Comment),
 
810
                            run_test_case_msgloop(Ref,Pid,CaptureStdout,Terminate,
 
811
                                                  Comment,undefined);
 
812
                        Loc1 ->
 
813
                            {Mod,Func} = get_mf(Loc1),
 
814
                            %% call end_per_testcase on a separate process, only so
 
815
                            %% that the user has a chance to clean up after init_per_testcase,
 
816
                            %% even after abortion
 
817
                            NewCurrConf =
 
818
                                case CurrConf of
 
819
                                    {{Mod,Func},Conf} ->
 
820
                                        TVal = case lists:keysearch(default_timeout,1,Conf) of
 
821
                                                   {value,{default_timeout,Tmo}} -> Tmo;
 
822
                                                   _ -> ?DEFAULT_TIMETRAP_SECS*1000
 
823
                                               end,
 
824
                                        EndConfPid =
 
825
                                            call_end_conf(Mod,Func,Pid,ErrorMsg,
 
826
                                                          Loc1,
 
827
                                                          [{tc_status,{failed,ErrorMsg}}|Conf],
 
828
                                                          TVal),
 
829
                                        {EndConfPid,{Mod,Func},Conf};
 
830
                                    _ ->
 
831
                                        spawn_fw_call(Mod,Func,Pid,ErrorMsg,
 
832
                                                      Loc1,self(),Comment),
 
833
                                        undefined
 
834
                                end,
 
835
                            run_test_case_msgloop(Ref,Pid,CaptureStdout,Terminate,
 
836
                                                  Comment,NewCurrConf)
 
837
                    end;
 
838
                killed ->
757
839
                    %% result of an exit(TestCase,kill) call, which is the
758
 
                    %% only way to abort a testcase process that traps exits 
 
840
                    %% only way to abort a testcase process that traps exits
759
841
                    %% (see abort_current_testcase)
760
842
                    spawn_fw_call(undefined,undefined,Pid,testcase_aborted_or_killed,
761
843
                                  unknown,self(),Comment),
762
 
                    run_test_case_msgloop(Ref,Pid,CaptureStdout,Terminate,Comment);
763
 
                _ ->
 
844
                    run_test_case_msgloop(Ref,Pid,CaptureStdout,Terminate,Comment,CurrConf);
 
845
                {fw_error,{FwMod,FwFunc,FwError}} ->
 
846
                    spawn_fw_call(FwMod,FwFunc,Pid,{framework_error,FwError},
 
847
                                  unknown,self(),Comment),
 
848
                    run_test_case_msgloop(Ref,Pid,CaptureStdout,Terminate,Comment,CurrConf);
 
849
                _Other ->
764
850
                    %% the testcase has terminated because of Reason (e.g. an exit
765
851
                    %% because a linked process failed)
766
852
                    spawn_fw_call(undefined,undefined,Pid,Reason,
767
853
                                  unknown,self(),Comment),
768
 
                    run_test_case_msgloop(Ref,Pid,CaptureStdout,Terminate,Comment)
 
854
                    run_test_case_msgloop(Ref,Pid,CaptureStdout,Terminate,Comment,CurrConf)
 
855
            end;
 
856
        {EndConfPid,{call_end_conf,Data,_Result}} ->
 
857
            case CurrConf of
 
858
                {EndConfPid,{Mod,Func},_Conf} ->
 
859
                    {_Mod,_Func,TCPid,TCExitReason,Loc} = Data,
 
860
                    spawn_fw_call(Mod,Func,TCPid,TCExitReason,Loc,self(),Comment),
 
861
                    run_test_case_msgloop(Ref,Pid,CaptureStdout,Terminate,Comment,undefined);
 
862
                _ ->
 
863
                    run_test_case_msgloop(Ref,Pid,CaptureStdout,Terminate,Comment,CurrConf)
769
864
            end;
770
865
        {_FwCallPid,fw_notify_done,RetVal} ->
771
866
            %% the framework has been notified, we're finished
772
 
            run_test_case_msgloop(Ref,Pid,CaptureStdout,{true,RetVal},Comment);     
 
867
            run_test_case_msgloop(Ref,Pid,CaptureStdout,{true,RetVal},Comment,undefined);
773
868
        {'EXIT',_FwCallPid,{fw_notify_done,Func,Error}} ->
774
869
            %% a framework function failed
775
870
            CB = os:getenv("TEST_SERVER_FRAMEWORK"),
776
871
            Loc = case CB of
777
 
                      false -> 
 
872
                      FW when FW =:= false; FW =:= "undefined" ->
778
873
                          {test_server,Func};
779
 
                      _ -> 
 
874
                      _ ->
780
875
                          {list_to_atom(CB),Func}
781
876
                  end,
782
877
            RetVal = {died,{framework_error,Loc,Error},Loc,"Framework error"},
783
 
            run_test_case_msgloop(Ref,Pid,CaptureStdout,{true,RetVal},Comment);
 
878
            run_test_case_msgloop(Ref,Pid,CaptureStdout,{true,RetVal},Comment,undefined);
784
879
        {failed,File,Line} ->
785
 
            put(test_server_detected_fail, 
 
880
            put(test_server_detected_fail,
786
881
                [{File, Line}| get(test_server_detected_fail)]),
787
 
            run_test_case_msgloop(Ref,Pid,CaptureStdout,Terminate,Comment);
 
882
            run_test_case_msgloop(Ref,Pid,CaptureStdout,Terminate,Comment,CurrConf);
788
883
        _Other when not is_tuple(_Other) ->
789
884
            %% ignore anything not generated by test server
790
 
            run_test_case_msgloop(Ref,Pid,CaptureStdout,Terminate,Comment);         
 
885
            run_test_case_msgloop(Ref,Pid,CaptureStdout,Terminate,Comment,CurrConf);
791
886
        _Other when element(1, _Other) /= 'EXIT',
792
887
                    element(1, _Other) /= started,
793
888
                    element(1, _Other) /= finished,
794
889
                    element(1, _Other) /= print ->
795
890
            %% ignore anything not generated by test server
796
 
            run_test_case_msgloop(Ref,Pid,CaptureStdout,Terminate,Comment)
 
891
            run_test_case_msgloop(Ref,Pid,CaptureStdout,Terminate,Comment,CurrConf)
797
892
    after Timeout ->
798
893
            ReturnValue
799
894
    end.
815
910
output(Msg,Sender) ->
816
911
    local_or_remote_apply({test_server_ctrl,output,[Msg,Sender]}).
817
912
 
 
913
call_end_conf(Mod,Func,TCPid,TCExitReason,Loc,Conf,TVal) ->
 
914
    Starter = self(),
 
915
    Data = {Mod,Func,TCPid,TCExitReason,Loc},
 
916
    EndConfProc =
 
917
        fun() ->
 
918
                Supervisor = self(),
 
919
                EndConfApply =
 
920
                    fun() ->
 
921
                            case catch apply(Mod,end_per_testcase,[Func,Conf]) of
 
922
                                {'EXIT',Why} ->
 
923
                                    group_leader() ! {printout,12,
 
924
                                                      "ERROR! ~p:end_per_testcase(~p, ~p)"
 
925
                                                      " crashed!\n\tReason: ~p\n",
 
926
                                                      [Mod,Func,Conf,Why]};
 
927
                                _ ->
 
928
                                    ok
 
929
                            end,
 
930
                            Supervisor ! {self(),end_conf}
 
931
                       end,
 
932
                Pid = spawn_link(EndConfApply),
 
933
                receive
 
934
                    {Pid,end_conf} ->
 
935
                        Starter ! {self(),{call_end_conf,Data,ok}};
 
936
                    {'EXIT',Pid,Reason} ->
 
937
                        Starter ! {self(),{call_end_conf,Data,{error,Reason}}}
 
938
                after TVal ->
 
939
                        Starter ! {self(),{call_end_conf,Data,{error,timeout}}}
 
940
                end
 
941
        end,
 
942
    spawn_link(EndConfProc).
 
943
 
818
944
spawn_fw_call(Mod,{init_per_testcase,Func},Pid,{timetrap_timeout,TVal}=Why,
819
945
              Loc,SendTo,Comment) ->
820
946
    FwCall =
821
947
        fun() ->
822
948
            Skip = {skip,{failed,{Mod,init_per_testcase,Why}}},
823
 
            %% if init_per_testcase fails, the test case 
 
949
            %% if init_per_testcase fails, the test case
824
950
            %% should be skipped
825
 
            case catch test_server_sup:framework_call(
826
 
                         end_tc,[?pl2a(Mod),Func,{Pid,Skip,[[]]}]) of
 
951
            case catch do_end_tc_call(Mod,Func,{Pid,Skip,[[]]},Why) of
827
952
                {'EXIT',FwEndTCErr} ->
828
953
                    exit({fw_notify_done,end_tc,FwEndTCErr});
829
954
                _ ->
834
959
                      {TVal/1000,Skip,Loc,[],Comment}}
835
960
        end,
836
961
    spawn_link(FwCall);
 
962
 
837
963
spawn_fw_call(Mod,{end_per_testcase,Func},Pid,{timetrap_timeout,TVal}=Why,
838
964
              Loc,SendTo,_Comment) ->
839
965
    FwCall =
841
967
            Conf = [{tc_status,ok}],
842
968
            %% if end_per_testcase fails, the test case should be
843
969
            %% reported successful with a warning printed as comment
844
 
            case catch test_server_sup:framework_call(end_tc,
845
 
                                                      [?pl2a(Mod),Func,
846
 
                                                       {Pid,
847
 
                                                        {failed,{Mod,end_per_testcase,Why}},
848
 
                                                        [Conf]}]) of
 
970
            case catch do_end_tc_call(Mod,Func,{Pid,
 
971
                                                {failed,{Mod,end_per_testcase,Why}},
 
972
                                                [Conf]}, Why) of
849
973
                {'EXIT',FwEndTCErr} ->
850
974
                    exit({fw_notify_done,end_tc,FwEndTCErr});
851
975
                _ ->
859
983
                        "</font>"]}}
860
984
        end,
861
985
    spawn_link(FwCall);
 
986
 
 
987
spawn_fw_call(FwMod,FwFunc,_Pid,{framework_error,FwError},_,SendTo,_Comment) ->
 
988
    FwCall =
 
989
        fun() ->
 
990
                test_server_sup:framework_call(report, [framework_error,
 
991
                                                        {{FwMod,FwFunc},FwError}]),
 
992
                Comment =
 
993
                    lists:flatten(
 
994
                      io_lib:format("<font color=\"red\">"
 
995
                                    "WARNING! ~w:~w failed!</font>", [FwMod,FwFunc])),
 
996
            %% finished, report back
 
997
            SendTo ! {self(),fw_notify_done,
 
998
                      {died,{error,{FwMod,FwFunc,FwError}},{FwMod,FwFunc},[],Comment}}
 
999
        end,
 
1000
    spawn_link(FwCall);
 
1001
 
862
1002
spawn_fw_call(Mod,Func,Pid,Error,Loc,SendTo,Comment) ->
863
1003
    FwCall =
864
1004
        fun() ->
871
1011
                        ok
872
1012
                end,
873
1013
                Conf = [{tc_status,{failed,timetrap_timeout}}],
874
 
                case catch test_server_sup:framework_call(end_tc,
875
 
                                                          [?pl2a(Mod),Func,
876
 
                                                           {Pid,Error,[Conf]}]) of
 
1014
                case catch do_end_tc_call(Mod,Func,{Pid,Error,[Conf]},Error) of
877
1015
                    {'EXIT',FwEndTCErr} ->
878
1016
                        exit({fw_notify_done,end_tc,FwEndTCErr});
879
1017
                    _ ->
933
1071
%% A test case is known to have failed if it returns {'EXIT', _} tuple,
934
1072
%% or sends a message {failed, File, Line} to it's group_leader
935
1073
 
936
 
run_test_case_eval(Mod, Func, Args0, Name, Ref, RunInit, 
937
 
                   MultiplyTimetrap, TCCallback) ->
938
 
    put(test_server_multiply_timetraps,MultiplyTimetrap),
 
1074
run_test_case_eval(Mod, Func, Args0, Name, Ref, RunInit,
 
1075
                   TimetrapData, TCCallback) ->
 
1076
    put(test_server_multiply_timetraps,TimetrapData),
 
1077
 
939
1078
    {{Time,Value},Loc,Opts} =
940
1079
        case test_server_sup:framework_call(init_tc,[?pl2a(Mod),Func,Args0],
941
 
                                            {ok,Args0}) of
 
1080
                                            {ok, Args0}) of
942
1081
            {ok,Args} ->
943
1082
                run_test_case_eval1(Mod, Func, Args, Name, RunInit, TCCallback);
944
1083
            Error = {error,_Reason} ->
945
 
                test_server_sup:framework_call(end_tc,[?pl2a(Mod),Func,{Error,Args0}]),
946
 
                {{0,{skip,{failed,Error}}},{Mod,Func},[]};
 
1084
                NewResult = do_end_tc_call(Mod,Func,{Error,Args0},
 
1085
                                           {skip,{failed,Error}}),
 
1086
                {{0,NewResult},{Mod,Func},[]};
947
1087
            {fail,Reason} ->
948
1088
                [Conf] = Args0,
949
1089
                Conf1 = [{tc_status,{failed,Reason}} | Conf],
950
1090
                fw_error_notify(Mod, Func, Conf, Reason),
951
 
                test_server_sup:framework_call(end_tc,[?pl2a(Mod),Func,
952
 
                                                       {{error,Reason},[Conf1]}]),
953
 
                {{0,{failed,Reason}},{Mod,Func},[]};
 
1091
                NewResult = do_end_tc_call(Mod,Func, {{error,Reason},[Conf1]},
 
1092
                                           {fail, Reason}),
 
1093
                {{0,NewResult},{Mod,Func},[]};
954
1094
            Skip = {skip,_Reason} ->
955
 
                test_server_sup:framework_call(end_tc,[?pl2a(Mod),Func,{Skip,Args0}]),
956
 
                {{0,Skip},{Mod,Func},[]};
 
1095
                NewResult = do_end_tc_call(Mod,Func,{Skip,Args0},Skip),
 
1096
                {{0,NewResult},{Mod,Func},[]};
957
1097
            {auto_skip,Reason} ->
958
 
                test_server_sup:framework_call(end_tc,[?pl2a(Mod),
959
 
                                                       Func,
960
 
                                                       {{skip,Reason},Args0}]),
961
 
                {{0,{skip,{fw_auto_skip,Reason}}},{Mod,Func},[]}
 
1098
                NewResult = do_end_tc_call(Mod, Func, {{skip,Reason},Args0},
 
1099
                                           {skip, {fw_auto_skip,Reason}}),
 
1100
                {{0,NewResult},{Mod,Func},[]}
962
1101
        end,
963
1102
    exit({Ref,Time,Value,Loc,Opts}).
964
1103
 
972
1111
                Skip = {skip,Reason} ->
973
1112
                    Line = get_loc(),
974
1113
                    Conf = [{tc_status,{skipped,Reason}}],
975
 
                    test_server_sup:framework_call(end_tc,[?pl2a(Mod),Func,{Skip,[Conf]}]),
976
 
                    {{0,{skip,Reason}},Line,[]};
 
1114
                    NewRes = do_end_tc_call(Mod,Func,{Skip,[Conf]}, Skip),
 
1115
                    {{0,NewRes},Line,[]};
977
1116
                {skip_and_save,Reason,SaveCfg} ->
978
1117
                    Line = get_loc(),
979
1118
                    Conf = [{tc_status,{skipped,Reason}},{save_config,SaveCfg}],
980
 
                    test_server_sup:framework_call(end_tc,[?pl2a(Mod),Func,
981
 
                                                           {{skip,Reason},[Conf]}]),
982
 
                    {{0,{skip,Reason}},Line,[]};
 
1119
                    NewRes = do_end_tc_call(Mod, Func, {{skip, Reason}, [Conf]},
 
1120
                                            {skip, Reason}),
 
1121
                    {{0,NewRes},Line,[]};
983
1122
                {ok,NewConf} ->
984
1123
                    put(test_server_init_or_end_conf,undefined),
985
1124
                    %% call user callback function if defined
986
1125
                    NewConf1 = user_callback(TCCallback, Mod, Func, init, NewConf),
 
1126
                    %% save current state in controller loop
 
1127
                    group_leader() ! {set_curr_conf,{{Mod,Func},NewConf1}},
987
1128
                    put(test_server_loc, {Mod,Func}),
988
1129
                    %% execute the test case
989
1130
                    {{T,Return},Loc} = {ts_tc(Mod, Func, [NewConf1]),get_loc()},
1005
1146
                            _ ->
1006
1147
                                {[{tc_status,ok}|NewConf1],Return,ok}
1007
1148
                        end,
 
1149
                    %% clear current state in controller loop
 
1150
                    group_leader() ! {set_curr_conf,undefined},
1008
1151
                    %% call user callback function if defined
1009
1152
                    EndConf1 = user_callback(TCCallback, Mod, Func, 'end', EndConf),
1010
1153
                    {FWReturn1,TSReturn1,EndConf2} =
1016
1159
                                {{error,ReasonToFail},{failed,ReasonToFail},EndConf1};
1017
1160
                            {failed,{_,end_per_testcase,_}} = Failure -> % unexpected termination
1018
1161
                                {Failure,TSReturn,EndConf1};
1019
 
                            _ -> 
 
1162
                            _ ->
1020
1163
                                {FWReturn,TSReturn,EndConf1}
1021
1164
                        end,
1022
 
                    case test_server_sup:framework_call(end_tc, [?pl2a(Mod), Func,
1023
 
                                                                 {FWReturn1,[EndConf2]}]) of
1024
 
                        {fail,Reason} ->
1025
 
                            fw_error_notify(Mod, Func, EndConf2, Reason),
1026
 
                            {{T,{failed,Reason}},{Mod,Func},[]};
1027
 
                        _ ->
1028
 
                            {{T,TSReturn1},Loc,[]}
 
1165
                    put(test_server_init_or_end_conf,undefined),
 
1166
                    case do_end_tc_call(Mod, Func, {FWReturn1,[EndConf2]}, TSReturn1) of
 
1167
                        {failed,Reason} = NewReturn ->
 
1168
                            fw_error_notify(Mod,Func,EndConf2, Reason),
 
1169
                            {{T,NewReturn},{Mod,Func},[]};
 
1170
                        NewReturn ->
 
1171
                            {{T,NewReturn},Loc,[]}
1029
1172
                    end
1030
1173
            end;
1031
1174
        skip_init ->
1043
1186
            {{T,Return},Loc} = {ts_tc(Mod, Func, Args2),get_loc()},
1044
1187
            %% call user callback function if defined
1045
1188
            Return1 = user_callback(TCCallback, Mod, Func, 'end', Return),
1046
 
            {Return2,Opts} = process_return_val([Return1], Mod,Func,Args1, Loc, Return1),
 
1189
            {Return2,Opts} = process_return_val([Return1], Mod, Func,
 
1190
                                                Args1, Loc, Return1),
1047
1191
            {{T,Return2},Loc,Opts}
1048
1192
    end.
1049
1193
 
1050
 
%% the return value is a list and we have to check if it contains 
 
1194
do_end_tc_call(M,F,Res,Return) ->
 
1195
    Ref = make_ref(),
 
1196
    case test_server_sup:framework_call(
 
1197
           end_tc, [?pl2a(M),F,Res], Ref) of
 
1198
        {fail,FWReason} ->
 
1199
            {failed,FWReason};
 
1200
        Ref ->
 
1201
            case test_server_sup:framework_call(
 
1202
                   end_tc, [?pl2a(M),F,Res, Return], ok) of
 
1203
                {fail,FWReason} ->
 
1204
                    {failed,FWReason};
 
1205
                ok ->
 
1206
                    case Return of
 
1207
                        {fail,Reason} ->
 
1208
                            {failed,Reason};
 
1209
                        Return ->
 
1210
                            Return
 
1211
                    end;
 
1212
                NewReturn ->
 
1213
                    NewReturn
 
1214
            end;
 
1215
        _ ->
 
1216
            Return
 
1217
    end.
 
1218
 
 
1219
%% the return value is a list and we have to check if it contains
1051
1220
%% the result of an end conf case or if it's a Config list
1052
1221
process_return_val([Return], M,F,A, Loc, Final) when is_list(Return) ->
1053
1222
    ReturnTags = [skip,skip_and_save,save_config,comment,return_group_result],
1061
1230
                   end, Return) of
1062
1231
        true ->              % must be return value from end conf case
1063
1232
            process_return_val1(Return, M,F,A, Loc, Final, []);
1064
 
        false ->             % must be Config value from init conf case
1065
 
            test_server_sup:framework_call(end_tc, [?pl2a(M),F,{ok,A}]),
1066
 
            {Return,[]}
 
1233
        false -> % must be Config value from init conf case
 
1234
            case do_end_tc_call(M,F,{ok,A}, Return) of
 
1235
                {failed, FWReason} = Failed ->
 
1236
                    fw_error_notify(M,F,A, FWReason),
 
1237
                    {Failed, []};
 
1238
                NewReturn ->
 
1239
                    {NewReturn, []}
 
1240
            end
1067
1241
    end;
1068
1242
%% the return value is not a list, so it's the return value from an
1069
1243
%% end conf case or it's a dummy value that can be ignored
1070
1244
process_return_val(Return, M,F,A, Loc, Final) ->
1071
1245
    process_return_val1(Return, M,F,A, Loc, Final, []).
1072
1246
 
1073
 
process_return_val1([Failed={E,TCError}|_], M,F,A=[Args], Loc, _, SaveOpts) when E=='EXIT'; 
1074
 
                                                                                 E==failed ->
 
1247
process_return_val1([Failed={E,TCError}|_], M,F,A=[Args], Loc, _, SaveOpts)
 
1248
  when E=='EXIT';
 
1249
       E==failed ->
1075
1250
    fw_error_notify(M,F,A, TCError, mod_loc(Loc)),
1076
 
    test_server_sup:framework_call(end_tc,
1077
 
                                   [?pl2a(M),F,{{error,TCError},
1078
 
                                                [[{tc_status,{failed,TCError}}|Args]]}]),
1079
 
    {Failed,SaveOpts};
1080
 
process_return_val1([SaveCfg={save_config,_}|Opts], M,F,[Args], Loc, Final, SaveOpts) ->    
 
1251
    case do_end_tc_call(M,F,{{error,TCError},
 
1252
                             [[{tc_status,{failed,TCError}}|Args]]}, Failed) of
 
1253
        {failed,FWReason} ->
 
1254
            {{failed,FWReason},SaveOpts};
 
1255
        NewReturn ->
 
1256
            {NewReturn,SaveOpts}
 
1257
    end;
 
1258
process_return_val1([SaveCfg={save_config,_}|Opts], M,F,[Args], Loc, Final, SaveOpts) ->
1081
1259
    process_return_val1(Opts, M,F,[[SaveCfg|Args]], Loc, Final, SaveOpts);
1082
 
process_return_val1([{skip_and_save,Why,SaveCfg}|Opts], M,F,[Args], Loc, _, SaveOpts) ->    
 
1260
process_return_val1([{skip_and_save,Why,SaveCfg}|Opts], M,F,[Args], Loc, _, SaveOpts) ->
1083
1261
    process_return_val1(Opts, M,F,[[{save_config,SaveCfg}|Args]], Loc, {skip,Why}, SaveOpts);
1084
1262
process_return_val1([GR={return_group_result,_}|Opts], M,F,A, Loc, Final, SaveOpts) ->
1085
1263
    process_return_val1(Opts, M,F,A, Loc, Final, [GR|SaveOpts]);
1089
1267
process_return_val1([_|Opts], M,F,A, Loc, Final, SaveOpts) ->
1090
1268
    process_return_val1(Opts, M,F,A, Loc, Final, SaveOpts);
1091
1269
process_return_val1([], M,F,A, _Loc, Final, SaveOpts) ->
1092
 
    test_server_sup:framework_call(end_tc, [?pl2a(M),F,{Final,A}]),
1093
 
    {Final,lists:reverse(SaveOpts)}.
 
1270
    case do_end_tc_call(M,F,{Final,A}, Final) of
 
1271
        {failed,FWReason} ->
 
1272
            {{failed,FWReason},SaveOpts};
 
1273
        NewReturn ->
 
1274
            {NewReturn,lists:reverse(SaveOpts)}
 
1275
    end.
1094
1276
 
1095
1277
user_callback(undefined, _, _, _, Args) ->
1096
1278
    Args;
1114
1296
        false -> code:load_file(Mod);
1115
1297
        _ -> ok
1116
1298
    end,
1117
 
    %% init_per_testcase defined, returns new configuration
 
1299
%% init_per_testcase defined, returns new configuration
1118
1300
    case erlang:function_exported(Mod,init_per_testcase,2) of
1119
1301
        true ->
1120
1302
            case catch my_apply(Mod, init_per_testcase, [Func|Args]) of
1121
 
                {'$test_server_ok',{Skip,Reason}} when Skip==skip; 
 
1303
                {'$test_server_ok',{Skip,Reason}} when Skip==skip;
1122
1304
                                                       Skip==skipped ->
1123
1305
                    {skip,Reason};
1124
1306
                {'$test_server_ok',Res={skip_and_save,_,_}} ->
1129
1311
                        [] ->
1130
1312
                            {ok,NewConf};
1131
1313
                        Bad ->
1132
 
                            group_leader() ! {printout,12, 
 
1314
                            group_leader() ! {printout,12,
1133
1315
                                              "ERROR! init_per_testcase has returned "
1134
 
                                              "bad elements in Config: ~p\n",[Bad]},  
 
1316
                                              "bad elements in Config: ~p\n",[Bad]},
1135
1317
                            {skip,{failed,{Mod,init_per_testcase,bad_return}}}
1136
1318
                    end;
1137
1319
                {'$test_server_ok',_Other} ->
1138
 
                    group_leader() ! {printout,12, 
 
1320
                    group_leader() ! {printout,12,
1139
1321
                                      "ERROR! init_per_testcase did not return "
1140
 
                                      "a Config list.\n",[]},   
 
1322
                                      "a Config list.\n",[]},
1141
1323
                    {skip,{failed,{Mod,init_per_testcase,bad_return}}};
1142
1324
                {'EXIT',Reason} ->
1143
1325
                    Line = get_loc(),
1144
1326
                    FormattedLoc = test_server_sup:format_loc(mod_loc(Line)),
1145
 
                    group_leader() ! {printout,12, 
 
1327
                    group_leader() ! {printout,12,
1146
1328
                                      "ERROR! init_per_testcase crashed!\n"
1147
1329
                                      "\tLocation: ~s\n\tReason: ~p\n",
1148
 
                                      [FormattedLoc,Reason]},  
 
1330
                                      [FormattedLoc,Reason]},
1149
1331
                    {skip,{failed,{Mod,init_per_testcase,Reason}}};
1150
1332
                Other ->
1151
1333
                    Line = get_loc(),
1152
1334
                    FormattedLoc = test_server_sup:format_loc(mod_loc(Line)),
1153
 
                    group_leader() ! {printout,12, 
 
1335
                    group_leader() ! {printout,12,
1154
1336
                                      "ERROR! init_per_testcase thrown!\n"
1155
1337
                                      "\tLocation: ~s\n\tReason: ~p\n",
1156
 
                                      [FormattedLoc, Other]},  
 
1338
                                      [FormattedLoc, Other]},
1157
1339
                    {skip,{failed,{Mod,init_per_testcase,Other}}}
1158
1340
            end;
1159
1341
        false ->
1160
 
            %% Optional init_per_testcase not defined
1161
 
            %% keep quiet.
 
1342
%% Optional init_per_testcase not defined
 
1343
%% keep quiet.
1162
1344
            [Config] = Args,
1163
1345
            {ok, Config}
1164
1346
    end.
1165
 
            
 
1347
 
1166
1348
end_per_testcase(Mod, Func, Conf) ->
1167
1349
    case erlang:function_exported(Mod,end_per_testcase,2) of
1168
1350
        true ->
1191
1373
            comment(io_lib:format("<font color=\"red\">"
1192
1374
                                  "WARNING: ~w crashed!"
1193
1375
                                  "</font>\n",[EndFunc])),
1194
 
            group_leader() ! {printout,12, 
 
1376
            group_leader() ! {printout,12,
1195
1377
                              "WARNING: ~w crashed!\n"
1196
1378
                              "Reason: ~p\n"
1197
1379
                              "Line: ~s\n",
1198
 
                              [EndFunc, Reason, 
 
1380
                              [EndFunc, Reason,
1199
1381
                               test_server_sup:format_loc(
1200
1382
                                 mod_loc(get_loc()))]},
1201
1383
            {failed,{Mod,end_per_testcase,Why}};
1203
1385
            comment(io_lib:format("<font color=\"red\">"
1204
1386
                                  "WARNING: ~w thrown!"
1205
1387
                                  "</font>\n",[EndFunc])),
1206
 
            group_leader() ! {printout,12, 
 
1388
            group_leader() ! {printout,12,
1207
1389
                              "WARNING: ~w thrown!\n"
1208
1390
                              "Reason: ~p\n"
1209
1391
                              "Line: ~s\n",
1210
 
                              [EndFunc, Other, 
 
1392
                              [EndFunc, Other,
1211
1393
                               test_server_sup:format_loc(
1212
 
                                 mod_loc(get_loc()))]},  
 
1394
                                 mod_loc(get_loc()))]},
1213
1395
            {failed,{Mod,end_per_testcase,Other}}
1214
1396
    end.
1215
1397
 
1234
1416
 
1235
1417
mod_loc(Loc) ->
1236
1418
    %% handle diff line num versions
1237
 
    case Loc of 
 
1419
    case Loc of
1238
1420
        [{{_M,_F},_L}|_] ->
1239
1421
            [{?pl2a(M),F,L} || {{M,F},L} <- Loc];
1240
1422
        [{_M,_F}|_] ->
1266
1448
%% Args = [term()]
1267
1449
%%
1268
1450
%% Just like io:format, except that depending on the Detail value, the output
1269
 
%% is directed to console, major and/or minor log files. 
 
1451
%% is directed to console, major and/or minor log files.
1270
1452
 
1271
1453
print(Detail,Format,Args) ->
1272
1454
    local_or_remote_apply({test_server_ctrl,print,[Detail,Format,Args]}).
1276
1458
%%
1277
1459
%% Prints Leader followed by a time stamp (date and time). Depending on
1278
1460
%% the Detail value, the output is directed to console, major and/or minor
1279
 
%% log files. 
 
1461
%% log files.
1280
1462
 
1281
1463
print_timestamp(Detail,Leader) ->
1282
1464
    local_or_remote_apply({test_server_ctrl,print_timestamp,[Detail,Leader]}).
1283
 
    
 
1465
 
1284
1466
 
1285
1467
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1286
1468
%% lookup_config(Key,Config) -> {value,{Key,Value}} | undefined
1306
1488
    Val = (catch my_apply(M, F, A)),
1307
1489
    After = erlang:now(),
1308
1490
    Result = case Val of
1309
 
                 {'$test_server_ok', R} -> 
 
1491
                 {'$test_server_ok', R} ->
1310
1492
                     R; % test case ok
1311
 
                 {'EXIT',_Reason} = R -> 
 
1493
                 {'EXIT',_Reason} = R ->
1312
1494
                     R; % test case crashed
1313
 
                 Other -> 
 
1495
                 Other ->
1314
1496
                     {failed, {thrown,Other}} % test case was thrown
1315
1497
          end,
1316
1498
    Elapsed =
1332
1514
%%       in an attempt to keep this modules small (yeah, right!)    %%
1333
1515
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1334
1516
unicode_to_latin1(Chars) when is_list(Chars); is_binary(Chars) ->
1335
 
    lists:flatten( 
 
1517
    lists:flatten(
1336
1518
      [ case X of
1337
1519
            High when High > 255 ->
1338
1520
                io_lib:format("\\{~.8B}",[X]);
1440
1622
    ok.
1441
1623
 
1442
1624
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
1625
%% adjusted_sleep(Time) -> ok
 
1626
%% Time = integer() | float() | infinity
 
1627
%%
 
1628
%% Sleeps the specified number of milliseconds, multiplied by the
 
1629
%% 'multiply_timetraps' value (if set) and possibly also automatically scaled
 
1630
%% up if 'scale_timetraps' is set to true (which is default).
 
1631
%% This function also accepts floating point numbers (which are truncated) and
 
1632
%% the atom 'infinity'.
 
1633
adjusted_sleep(infinity) ->
 
1634
    receive
 
1635
    after infinity ->
 
1636
            ok
 
1637
    end;
 
1638
adjusted_sleep(MSecs) ->
 
1639
    {Multiplier,ScaleFactor} =
 
1640
        case test_server_ctrl:get_timetrap_parameters() of
 
1641
            {undefined,undefined} ->
 
1642
                {1,1};
 
1643
            {undefined,false} ->
 
1644
                {1,1};
 
1645
            {undefined,true} ->
 
1646
                {1,timetrap_scale_factor()};
 
1647
            {infinity,_} ->
 
1648
                {infinity,1};
 
1649
            {Mult,undefined} ->
 
1650
                {Mult,1};
 
1651
            {Mult,false} ->
 
1652
                {Mult,1};
 
1653
            {Mult,true} ->
 
1654
                {Mult,timetrap_scale_factor()}
 
1655
        end,
 
1656
    receive
 
1657
    after trunc(MSecs*Multiplier*ScaleFactor) ->
 
1658
            ok
 
1659
    end,
 
1660
    ok.
 
1661
 
 
1662
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1443
1663
%% fail(Reason) -> exit({suite_failed,Reason})
1444
1664
%%
1445
1665
%% Immediately calls exit. Included because test suites are easier
1489
1709
    receive continue -> ok end.
1490
1710
 
1491
1711
spawn_break_process(Pid) ->
1492
 
    spawn(fun() -> 
 
1712
    spawn(fun() ->
1493
1713
                  register(test_server_break_process,self()),
1494
 
                  receive 
 
1714
                  receive
1495
1715
                      continue -> continue(Pid);
1496
1716
                      cancel -> ok
1497
1717
                  end
1541
1761
%% timetrap(Timeout) -> Handle
1542
1762
%% Handle = term()
1543
1763
%%
1544
 
%% Creates a time trap, that will kill the calling process if the 
 
1764
%% Creates a time trap, that will kill the calling process if the
1545
1765
%% trap is not cancelled with timetrap_cancel/1, within Timeout milliseconds.
1546
 
 
1547
1766
timetrap(Timeout0) ->
1548
1767
    Timeout = time_ms(Timeout0),
1549
1768
    cancel_default_timetrap(),
1550
1769
    case get(test_server_multiply_timetraps) of
1551
 
        undefined -> timetrap1(Timeout);
1552
 
        infinity -> infinity;
1553
 
        Int -> timetrap1(Timeout*Int)
 
1770
        undefined -> timetrap1(Timeout, true);
 
1771
        {undefined,false} -> timetrap1(Timeout, false);
 
1772
        {undefined,_} -> timetrap1(Timeout, true);
 
1773
        {infinity,_} -> infinity;
 
1774
        {Int,Scale} -> timetrap1(Timeout*Int, Scale)
1554
1775
    end.
1555
1776
 
1556
 
timetrap1(Timeout) ->
1557
 
    Ref = spawn_link(test_server_sup,timetrap,[Timeout,self()]),
 
1777
timetrap1(Timeout, Scale) ->
 
1778
    Ref = spawn_link(test_server_sup,timetrap,[Timeout,Scale,self()]),
1558
1779
    case get(test_server_timetraps) of
1559
1780
        undefined -> put(test_server_timetraps,[Ref]);
1560
1781
        List -> put(test_server_timetraps,[Ref|List])
1562
1783
    Ref.
1563
1784
 
1564
1785
ensure_timetrap(Config) ->
1565
 
    %format("ensure_timetrap:~p~n",[Config]),
1566
1786
    case get(test_server_timetraps) of
1567
1787
        [_|_] ->
1568
1788
            ok;
1603
1823
time_ms({hours,N}) -> hours(N);
1604
1824
time_ms({minutes,N}) -> minutes(N);
1605
1825
time_ms({seconds,N}) -> seconds(N);
1606
 
time_ms({Other,_N}) -> 
 
1826
time_ms({Other,_N}) ->
1607
1827
    format("=== ERROR: Invalid time specification: ~p. "
1608
1828
           "Should be seconds, minutes, or hours.~n", [Other]),
1609
1829
    exit({invalid_time_spec,Other});
1743
1963
%% Slave and Peer:
1744
1964
%% {remote, true}         - Start the node on a remote host. If not specified,
1745
1965
%%                          the node will be started on the local host (with
1746
 
%%                          some exceptions, as for the case of VxWorks and OSE,
 
1966
%%                          some exceptions, for instance VxWorks,
1747
1967
%%                          where all nodes are started on a remote host).
1748
1968
%% {args, Arguments}      - Arguments passed directly to the node.
1749
1969
%% {cleanup, false}       - Nodes started with this option will not be killed
1750
1970
%%                          by the test server after completion of the test case
1751
1971
%%                          Therefore it is IMPORTANT that the USER terminates
1752
1972
%%                          the node!!
1753
 
%% {erl, ReleaseList}     - Use an Erlang emulator determined by ReleaseList 
1754
 
%%                          when starting nodes, instead of the same emulator 
 
1973
%% {erl, ReleaseList}     - Use an Erlang emulator determined by ReleaseList
 
1974
%%                          when starting nodes, instead of the same emulator
1755
1975
%%                          as the test server is running. ReleaseList is a list
1756
 
%%                          of specifiers, where a specifier is either 
1757
 
%%                          {release, Rel}, {prog, Prog}, or 'this'. Rel is 
1758
 
%%                          either the name of a release, e.g., "r7a" or 
1759
 
%%                          'latest'. 'this' means using the same emulator as 
1760
 
%%                          the test server. Prog is the name of an emulator 
 
1976
%%                          of specifiers, where a specifier is either
 
1977
%%                          {release, Rel}, {prog, Prog}, or 'this'. Rel is
 
1978
%%                          either the name of a release, e.g., "r7a" or
 
1979
%%                          'latest'. 'this' means using the same emulator as
 
1980
%%                          the test server. Prog is the name of an emulator
1761
1981
%%                          executable.  If the list has more than one element,
1762
1982
%%                          one of them is picked randomly. (Only
1763
1983
%%                          works on Solaris and Linux, and the test
1772
1992
%%                          peer nodes.
1773
1993
%%                          Note that slave nodes always act as if they had
1774
1994
%%                          fail_on_error==false.
1775
 
%% 
 
1995
%%
1776
1996
 
1777
1997
start_node(Name, Type, Options) ->
1778
1998
    lists:foreach(
1779
 
      fun(N) -> 
 
1999
      fun(N) ->
1780
2000
              case firstname(N) of
1781
 
                  Name -> 
 
2001
                  Name ->
1782
2002
                      format("=== WARNING: Trying to start node \'~w\' when node"
1783
2003
                             " with same first name exists: ~w", [Name, N]);
1784
2004
                  _other -> ok
1797
2017
            %% Cannot run cover on shielded node or on a node started
1798
2018
            %% by a shielded node.
1799
2019
            Cover = case is_cover() of
1800
 
                        true -> 
 
2020
                        true ->
1801
2021
                            not is_shielded(Name) andalso same_version(Node);
1802
 
                        false -> 
 
2022
                        false ->
1803
2023
                            false
1804
2024
                    end,
1805
2025
 
1806
2026
            net_adm:ping(Node),
1807
2027
            case Cover of
1808
 
                true -> 
 
2028
                true ->
1809
2029
                    Sticky = unstick_all_sticky(Node),
1810
2030
                    cover:start(Node),
1811
2031
                    stick_all_sticky(Node,Sticky);
1812
 
                _ -> 
 
2032
                _ ->
1813
2033
                    ok
1814
2034
            end,
1815
2035
            {ok,Node};
1837
2057
                      self(),
1838
2058
                      {test_server_ctrl,wait_for_node,[Slave]}},
1839
2059
    receive {sync_result,R} -> R end.
1840
 
    
 
2060
 
1841
2061
 
1842
2062
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1843
2063
%% stop_node(Name) -> true|false
1847
2067
stop_node(Slave) ->
1848
2068
    Nocover = is_shielded(Slave) orelse not same_version(Slave),
1849
2069
    case is_cover() of
1850
 
        true when not Nocover -> 
 
2070
        true when not Nocover ->
1851
2071
            Sticky = unstick_all_sticky(Slave),
1852
2072
            cover:stop(Slave),
1853
2073
            stick_all_sticky(Slave,Sticky);
1875
2095
            %% with the {cleanup,false} option, or it was started
1876
2096
            %% in some other way than test_server:start_node/3
1877
2097
            format("=== WARNING: Attempt to stop a nonexisting slavenode (~p)~n"
1878
 
                   "===          Trying to kill it anyway!!!", 
 
2098
                   "===          Trying to kill it anyway!!!",
1879
2099
                   [Slave]),
1880
2100
            case net_adm:ping(Slave)of
1881
 
                pong -> 
 
2101
                pong ->
1882
2102
                    slave:stop(Slave),
1883
2103
                    true;
1884
2104
                pang ->
1898
2118
                      self(),
1899
2119
                      {test_server_ctrl,is_release_available,[Release]}},
1900
2120
    receive {sync_result,R} -> R end.
1901
 
    
 
2121
 
1902
2122
 
1903
2123
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
1904
2124
%% run_on_shielded_node(Fun, CArgs) -> term()
1917
2137
%%
1918
2138
%% Fun    -  Function to execute
1919
2139
%% CArg   -  Extra command line arguments to use when starting
1920
 
%%           the shielded node. 
 
2140
%%           the shielded node.
1921
2141
%%
1922
2142
%% If Fun is successfully executed, the result is returned.
1923
2143
%%
1994
2214
app_test(App) ->
1995
2215
    app_test(App, pedantic).
1996
2216
app_test(App, Mode) ->
1997
 
    case os:type() of
1998
 
        {ose,_} -> 
1999
 
            Comment = "Skipping app_test on OSE",
2000
 
            comment(Comment), % in case user ignores the return value
2001
 
            {skip,Comment};
2002
 
        _other -> 
2003
 
            test_server_sup:app_test(App, Mode)
2004
 
    end.
 
2217
    test_server_sup:app_test(App, Mode).
 
2218
 
2005
2219
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
2006
2220
 
2007
2221
 
2023
2237
%% The given String will occur in the comment field
2024
2238
%% of the table on the test suite result page. If
2025
2239
%% called several times, only the last comment is
2026
 
%% printed. 
2027
 
%% comment/1 is also overwritten by the return value 
 
2240
%% printed.
 
2241
%% comment/1 is also overwritten by the return value
2028
2242
%% {comment,Comment} or fail/1 (which prints Reason
2029
2243
%% as a comment).
2030
2244
comment(String) ->
2140
2354
        {'EXIT', _} -> false;
2141
2355
        Inuse when is_integer(Inuse) -> Inuse
2142
2356
    end.
2143
 
    
 
2357
 
2144
2358
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
2145
2359
%% purify_format(Format, Args) -> ok
2146
2360
%% Format = string()
2188
2402
request(Sock,Request) ->
2189
2403
    gen_tcp:send(Sock,<<1,(term_to_binary(Request))/binary>>).
2190
2404
 
2191
 
%% 
 
2405
%%
2192
2406
%% Generic receive function for communication with host
2193
 
%% 
 
2407
%%
2194
2408
recv(Sock) ->
2195
2409
    case gen_tcp:recv(Sock,0) of
2196
2410
        {error,closed} ->