~rdoering/ubuntu/karmic/erlang/fix-535090

« back to all changes in this revision

Viewing changes to lib/test_server/src/test_server_ctrl.erl

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-02-15 16:42:52 UTC
  • mfrom: (3.1.2 squeeze)
  • Revision ID: james.westby@ubuntu.com-20090215164252-q5x4rcf8a5pbesb1
Tags: 1:12.b.5-dfsg-2
Upload to unstable after lenny is released.

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
1
%%<copyright>
2
 
%% <year>2002-2007</year>
 
2
%% <year>2002-2008</year>
3
3
%% <holder>Ericsson AB, All Rights Reserved</holder>
4
4
%%</copyright>
5
5
%%<legalnotice>
157
157
-export([add_module_with_skip/2,add_module_with_skip/3,
158
158
         add_case_with_skip/3,add_case_with_skip/4,
159
159
         add_cases_with_skip/3,add_cases_with_skip/4]).
160
 
-export([jobs/0,run_test/1,wait_finish/0,idle_notify/1,abort/0]).
 
160
-export([jobs/0,run_test/1,wait_finish/0,idle_notify/1,
 
161
         abort_current_testcase/1,abort/0]).
161
162
-export([start_get_totals/1,stop_get_totals/0]).
162
163
-export([get_levels/0,set_levels/3]).
163
164
-export([multiply_timetraps/1]).
433
434
    process_flag(trap_exit,OldTrap),
434
435
    ok.
435
436
 
 
437
abort_current_testcase(Reason) ->
 
438
    controller_call({abort_current_testcase,Reason}),
 
439
    ok.
 
440
 
436
441
abort() ->
437
442
    OldTrap = process_flag(trap_exit,true),
438
443
    {ok, Pid} = finish(abort),
578
583
    %% Local target! The global test_server process implemented by
579
584
    %% test_server.erl will not be started, so we simulate it by 
580
585
    %% globally registering this process instead.
581
 
    global:register_name(test_server,self()),
 
586
    global:sync(),
 
587
    case global:whereis_name(test_server) of
 
588
        undefined ->
 
589
            global:register_name(test_server,self());
 
590
        Pid ->
 
591
            case node() of
 
592
                N when N == node(Pid) ->
 
593
                    io:format(user, "Warning: test_server already running!\n", []),
 
594
                    global:re_register_name(test_server,self());
 
595
                _ ->
 
596
                    ok
 
597
            end
 
598
    end,            
582
599
    TI = test_server:init_target_info(),
583
600
    TargetHost = test_server_sup:hoststr(),
584
601
    {ok,TI#target_info{where=local,
758
775
 
759
776
 
760
777
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
778
%% handle_call({abort_current_testcase,Reason},_,State) -> Result
 
779
%% Reason = term()
 
780
%% Result = ok | {error,no_testcase_running}
 
781
%% 
 
782
%% Attempts to abort the test case that's currently running.
 
783
 
 
784
handle_call({abort_current_testcase,Reason},_From,State) ->
 
785
    case State#state.jobs of
 
786
        [{_,Pid}|_] ->
 
787
            Pid ! {abort_current_testcase,Reason,self()},
 
788
            receive
 
789
                {Pid,abort_current_testcase,Result} ->
 
790
                    {reply, Result, State}
 
791
            after 10000 ->
 
792
                    {reply, {error,no_testcase_running}, State}
 
793
            end;
 
794
        _ ->
 
795
            {reply, {error,no_testcase_running}, State}
 
796
    end;
 
797
 
 
798
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
761
799
%% handle_call({finish,Fini},_,State) -> {ok,Pid}
762
800
%% Fini = true | abort
 
801
%%
763
802
%% Tells the test_server to stop as soon as there are no test suites
764
803
%% running. Immediately if none are running. Abort is handled as soon
765
804
%% as current test finishes.
1450
1489
 
1451
1490
    PrivDir = filename:join(TestDir, ?priv_dir),
1452
1491
    ok = file:make_dir(PrivDir),
1453
 
    put(test_server_priv_dir,PrivDir),
 
1492
    put(test_server_priv_dir,PrivDir++"/"),
1454
1493
    print_timestamp(13,"Suite started at "),
1455
1494
    ok.
1456
1495
 
1818
1857
                               {data_dir,get_data_dir(Mod)}]),
1819
1858
    case run_test_case(Mod,Func,[ActualCfg], skip_init, target, 
1820
1859
                       MultiplyTimetrap) of
1821
 
        NewCfg when Func == init_per_suite, is_list(NewCfg) ->
 
1860
        {_,NewCfg} when Func == init_per_suite, is_list(NewCfg) ->
1822
1861
            case lists:filter(fun({_,_}) -> false;
1823
1862
                                 (_) -> true end, NewCfg) of
1824
1863
                [] ->
1831
1870
                    stop_minor_log_file(),
1832
1871
                    run_test_cases_loop(Cases, Config, MultiplyTimetrap)
1833
1872
            end;                
1834
 
        NewCfg when is_list(NewCfg) ->
 
1873
        {_,NewCfg} when is_list(NewCfg) ->
1835
1874
            stop_minor_log_file(),
1836
1875
            run_test_cases_loop(Cases0, {Cfg0,NewCfg}, MultiplyTimetrap);           
1837
 
        {Skip,Reason} when Skip==skip; Skip==skipped ->
1838
 
            print(minor,"~n*** ~p skipped.~n"
1839
 
                  "    Skipping all other cases.", [Func]),
1840
 
            Cases = skip_cases_upto(Ref, Cases0, Reason),
1841
 
            stop_minor_log_file(),
1842
 
            run_test_cases_loop(Cases, Config, MultiplyTimetrap);
1843
 
        {skip_and_save,Reason,_SavedConfig} ->
1844
 
            print(minor,"~n*** ~p skipped.~n"
1845
 
                  "    Skipping all other cases.", [Func]),
1846
 
            Cases = skip_cases_upto(Ref, Cases0, Reason),
1847
 
            stop_minor_log_file(),
1848
 
            run_test_cases_loop(Cases, Config, MultiplyTimetrap);
1849
 
        Fail when element(1,Fail)=='EXIT'; 
1850
 
                  element(1,Fail)==timetrap_timeout ;
1851
 
                  element(1,Fail)==failed ->
1852
 
            print(minor,"~n*** ~p failed.~n"
1853
 
                  "    Skipping all other cases.", [Func]),
1854
 
            Reason = lists:flatten(io_lib:format("~p:~p/1 failed", [Mod,Func])),
1855
 
            Cases = skip_cases_upto(Ref, Cases0, Reason),
1856
 
            stop_minor_log_file(),
1857
 
            run_test_cases_loop(Cases, Config, MultiplyTimetrap);
1858
 
        _Other ->
1859
 
            if Func == init_per_suite ->
1860
 
                    print(minor,"~n*** init_per_suite failed to return a Config list.~n",[]),
1861
 
                    stop_minor_log_file(),
1862
 
                    Cases = skip_cases_upto(Ref, Cases0, "init_per_suite_bad_return"),
1863
 
                    run_test_cases_loop(Cases, Config, MultiplyTimetrap);                   
1864
 
               true ->
1865
 
                    stop_minor_log_file(),
1866
 
                    run_test_cases_loop(Cases0, Config, MultiplyTimetrap)
1867
 
            end
 
1876
        {_,{Skip,Reason}} when Skip==skip; Skip==skipped ->
 
1877
            Cases = 
 
1878
                if Func == end_per_suite -> Cases0;
 
1879
                   true ->
 
1880
                        print(minor,"~n*** ~p skipped.~n"
 
1881
                              "    Skipping all other cases.", [Func]),
 
1882
                        skip_cases_upto(Ref, Cases0, Reason)
 
1883
                end,
 
1884
            stop_minor_log_file(),
 
1885
            run_test_cases_loop(Cases, Config, MultiplyTimetrap);
 
1886
        {_,{skip_and_save,Reason,_SavedConfig}} ->
 
1887
            Cases = 
 
1888
                if Func == end_per_suite -> Cases0;
 
1889
                   true ->          
 
1890
                        print(minor,"~n*** ~p skipped.~n"
 
1891
                              "    Skipping all other cases.", [Func]),
 
1892
                        skip_cases_upto(Ref, Cases0, Reason)
 
1893
                end,
 
1894
            stop_minor_log_file(),
 
1895
            run_test_cases_loop(Cases, Config, MultiplyTimetrap);       
 
1896
        {_,{framework_error,{FwMod,FwFunc},Reason}} ->
 
1897
            print(minor,"~n*** ~p failed in ~p. Reason: ~p~n", [FwMod,FwFunc,Reason]),
 
1898
            print(1, "~p failed in ~p. Reason: ~p~n", [FwMod,FwFunc,Reason]),
 
1899
            exit(framework_error);
 
1900
        {_,Fail} when element(1,Fail)=='EXIT'; 
 
1901
                      element(1,Fail)==timetrap_timeout ;
 
1902
                      element(1,Fail)==failed ->
 
1903
            Cases = 
 
1904
                if Func == end_per_suite -> Cases0;
 
1905
                   true ->      
 
1906
                        print(minor,"~n*** ~p failed.~n"
 
1907
                              "    Skipping all other cases.", [Func]),
 
1908
                        Reason = lists:flatten(io_lib:format("~p:~p/1 failed", 
 
1909
                                                             [Mod,Func])),
 
1910
                        skip_cases_upto(Ref, Cases0, Reason)
 
1911
                end,
 
1912
            stop_minor_log_file(),
 
1913
            run_test_cases_loop(Cases, Config, MultiplyTimetrap);
 
1914
        {died,_Why} when Func == init_per_suite ->
 
1915
            print(minor,"~n*** Unexpected exit during init_per_suite.~n",[]),
 
1916
            stop_minor_log_file(),
 
1917
            Cases = skip_cases_upto(Ref, Cases0, "init_per_suite_crashed"),
 
1918
            run_test_cases_loop(Cases, Config, MultiplyTimetrap);                   
 
1919
        {_,_Other} when Func == init_per_suite ->
 
1920
            print(minor,"~n*** init_per_suite failed to return a Config list.~n",[]),
 
1921
            stop_minor_log_file(),
 
1922
            Cases = skip_cases_upto(Ref, Cases0, "init_per_suite_bad_return"),
 
1923
            run_test_cases_loop(Cases, Config, MultiplyTimetrap);
 
1924
        {_,_Other} ->
 
1925
            stop_minor_log_file(),
 
1926
            run_test_cases_loop(Cases0, Config, MultiplyTimetrap)
1868
1927
    end;
1869
1928
run_test_cases_loop([{make,Ref,{Mod,Func,Args}}|Cases0], Config, MultiplyTimetrap) ->
1870
1929
    case run_test_case(Mod, Func, Args, skip_init, host, MultiplyTimetrap) of
1871
 
        {'EXIT',_} ->
 
1930
        {_,{'EXIT',_}} ->
1872
1931
            print(minor,"~n*** ~p failed.~n"
1873
1932
                  "    Skipping all other cases.", [Func]),
1874
1933
            Reason = lists:flatten(io_lib:format("~p:~p/1 failed", [Mod,Func])),
1875
1934
            Cases = skip_cases_upto(Ref, Cases0, Reason),
1876
1935
            stop_minor_log_file(),
1877
1936
            run_test_cases_loop(Cases, Config, MultiplyTimetrap);
1878
 
        _Whatever ->
 
1937
        {_,_Whatever} ->
1879
1938
            stop_minor_log_file(),
1880
1939
            run_test_cases_loop(Cases0, Config, MultiplyTimetrap)
1881
1940
    end;
1888
1947
    run_test_cases_loop([{Mod,Case,[ActualCfg]}|Cases],Config,
1889
1948
                        MultiplyTimetrap);
1890
1949
run_test_cases_loop([{Mod,Func,Args}|Cases],Config,MultiplyTimetrap) ->
1891
 
    run_test_case(Mod, Func, Args, run_init, target, MultiplyTimetrap),
1892
 
    stop_minor_log_file(),
1893
 
    run_test_cases_loop(Cases,Config,MultiplyTimetrap);
 
1950
    {_,Result} = run_test_case(Mod, Func, Args, run_init, target, MultiplyTimetrap),
 
1951
    case Result of
 
1952
        {framework_error,{FwMod,FwFunc},Reason} ->
 
1953
            print(minor,"~n*** ~p failed in ~p. Reason: ~p~n", [FwMod,FwFunc,Reason]),
 
1954
            print(1, "~p failed in ~p. Reason: ~p~n", [FwMod,FwFunc,Reason]),
 
1955
            stop_minor_log_file(),
 
1956
            exit(framework_error);
 
1957
        _ ->
 
1958
            stop_minor_log_file(),
 
1959
            run_test_cases_loop(Cases,Config,MultiplyTimetrap)
 
1960
    end;
1894
1961
run_test_cases_loop([],_Config,_MultiplyTimetrap) ->
1895
1962
    ok.
1896
1963
 
1918
1985
    put_no_conf(Func,test_server_case_num,CaseNum+1),
1919
1986
    {Mod,Func}.
1920
1987
 
1921
 
%% Skip all cases up to the matching reference.
 
1988
%% Skip all cases up to the matching reference (always only called for a conf case).
1922
1989
 
 
1990
%% next case is a conf with new ref (orig case was an end conf) = we're done already
1923
1991
skip_cases_upto(Ref,[{Type,Ref1,_MF}|_]=Cs,_Reason) when Type==conf, Ref/=Ref1 ->
1924
1992
    Cs;
 
1993
%% normal cases follow - mark them as skipped
1925
1994
skip_cases_upto(Ref,Cs,Reason) ->
1926
1995
    skip_cases_upto1(Ref,Cs,Reason).
1927
1996
 
 
1997
%% next case is a conf with same ref, must be end conf = we're done
1928
1998
skip_cases_upto1(Ref,[{Type,Ref,MF}|T],Reason) when Type==conf; Type==make ->
1929
1999
    [{auto_skip_case,{MF,Reason}}|T];
 
2000
%% next is a skip_case, could be one test case or 'all' in suite, we must proceed
1930
2001
skip_cases_upto1(Ref,[{skip_case,{_F,_Cmt}}=MF|T],Reason) ->
1931
2002
    [MF|skip_cases_upto1(Ref,T,Reason)];
 
2003
%% next is normal case, mark as skipped and proceed
1932
2004
skip_cases_upto1(Ref,[{_M,_F}=MF|T],Reason) ->
1933
2005
    [{auto_skip_case,{MF,Reason}}|skip_cases_upto1(Ref,T,Reason)];
 
2006
%% next is some other case, ignore and proceed
1934
2007
skip_cases_upto1(Ref,[_|T],Reason) ->
1935
2008
    skip_cases_upto1(Ref,T,Reason);
 
2009
%% found no end conf (or start of new), we're done
1936
2010
skip_cases_upto1(_Ref,[],_Reason) -> [].
1937
2011
 
1938
2012
get_data_dir(Mod) ->
2004
2078
    print_timestamp(minor, "Ended at "),
2005
2079
    print(major, "=ended   ~s", [lists:flatten(timestamp_get(""))]),
2006
2080
    file:set_cwd(Cwd),
 
2081
 
2007
2082
    case {Time,RetVal} of
2008
 
        {died,{timetrap_timeout, TimetrapTimeout, Line}} ->
2009
 
            progress(failed,CaseNum,Mod,Func,Line,
 
2083
        {died,{timetrap_timeout,TimetrapTimeout}} ->
 
2084
            progress(failed,CaseNum,Mod,Func,Loc,
2010
2085
                     timetrap_timeout,TimetrapTimeout,Comment);
2011
2086
        {died,Reason} ->
2012
2087
            progress(failed,CaseNum,Mod,Func,Loc,Reason,
2082
2157
    end,
2083
2158
    check_new_crash_dumps(Where),
2084
2159
    put_no_conf(Func, test_server_case_num,CaseNum+1),
2085
 
    RetVal.
 
2160
    {Time,RetVal}.
2086
2161
 
2087
2162
num2str(init_per_suite, _) -> "";
2088
2163
num2str(end_per_suite, _) -> "";
2237
2312
    print(minor, "reason=timetrap timeout", []),
2238
2313
    put_no_conf(Func,test_server_failed, get(test_server_failed)+1);
2239
2314
 
 
2315
progress(failed,CaseNum,Mod,Func,Loc,{testcase_aborted,Reason},_T,Comment0) ->
 
2316
    print(major, "=result    failed:testcase_aborted, ~p", [Loc]),
 
2317
    print(1, "*** FAILED *** ~s",
 
2318
          [get_info_str(Func,CaseNum,get(test_server_cases))]),
 
2319
    test_server_sup:framework_call(report,
 
2320
                                   [tc_done,{?pl2a(Mod),Func,
 
2321
                                             {failed,testcase_aborted}}]),
 
2322
    FormatLastLoc = test_server_sup:format_loc(get_last_loc(Loc)),
 
2323
    ErrorReason = io_lib:format("{testcase_aborted,~s}",[FormatLastLoc]),
 
2324
    Comment = 
 
2325
        case Comment0 of
 
2326
            "" -> "<font color=\"red\">" ++ ErrorReason ++ "</font>";
 
2327
            _ -> "<font color=\"red\">" ++ ErrorReason ++ "</font><br>" ++ 
 
2328
                 Comment0
 
2329
        end,
 
2330
    print(html, 
 
2331
          "<td>died</td>"
 
2332
          "<td><font color=\"red\">FAILED</font></td>"
 
2333
          "<td>~s</td></tr>\n", 
 
2334
          [Comment]),
 
2335
    FormatLoc = test_server_sup:format_loc(Loc),
 
2336
    print(minor, "location ~s", [FormatLoc]),
 
2337
    print(minor, "reason={testcase_aborted,~p}", [Reason]),
 
2338
    put_no_conf(Func,test_server_failed, get(test_server_failed)+1);
 
2339
 
 
2340
progress(failed,CaseNum,Mod,Func,unknown,Reason,Time,Comment0) ->
 
2341
    print(major, "=result    failed:~p, ~p", [Reason,unknown]),
 
2342
    print(1,"*** FAILED *** ~s",
 
2343
          [get_info_str(Func,CaseNum,get(test_server_cases))]),
 
2344
    test_server_sup:framework_call(report,[tc_done,{?pl2a(Mod),Func,
 
2345
                                                    {failed,Reason}}]),
 
2346
    TimeStr = io_lib:format(if float(Time) -> "~.3fs";
 
2347
                               true -> "~w"          
 
2348
                            end, [Time]),
 
2349
    ErrorReason = lists:flatten(io_lib:format("~p",[Reason])),
 
2350
    ErrorReason1 = lists:flatten([string:strip(S,left) || 
 
2351
                                  S <- string:tokens(ErrorReason,[$\n])]),
 
2352
    ErrorReason2 =
 
2353
        if length(ErrorReason1) > 63 ->
 
2354
                string:substr(ErrorReason1,1,60) ++ "...";
 
2355
           true ->
 
2356
                ErrorReason1
 
2357
        end,
 
2358
    Comment = 
 
2359
        case Comment0 of
 
2360
            "" -> "<font color=\"red\">" ++ ErrorReason2 ++ "</font>";
 
2361
            _ -> "<font color=\"red\">" ++ ErrorReason2 ++ "</font><br>" ++ 
 
2362
                 Comment0
 
2363
        end,
 
2364
    print(html, 
 
2365
          "<td>~s</td>"
 
2366
          "<td><font color=\"red\">FAILED</font></td>"
 
2367
          "<td>~s</td></tr>\n",
 
2368
          [TimeStr,Comment]),
 
2369
    print(minor, "location ~s", [unknown]),
 
2370
    print(minor, "reason=~p", [Reason]),
 
2371
    put_no_conf(Func,test_server_failed,get(test_server_failed)+1);
 
2372
 
2240
2373
progress(failed,CaseNum,Mod,Func,Loc,Reason,Time,Comment0) ->
2241
2374
    print(major, "=result    failed:~p, ~p", [Reason,Loc]),
2242
2375
    print(1,"*** FAILED *** ~s",