~ubuntu-branches/debian/squeeze/erlang/squeeze

« 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-08-05 20:54:29 UTC
  • mfrom: (6.1.2 sid)
  • Revision ID: james.westby@ubuntu.com-20090805205429-pm4pnwew8axraosl
Tags: 1:13.b.1-dfsg-5
* Fixed parentheses in Emacs mode (closes: #536891).
* Removed unnecessary conflicts with erlang-manpages package.
* Added workaround for #475459: disabled threads on sparc architecture.
  This breaks wxErlang, so it's only a temporary solution.

Show diffs side-by-side

added added

removed removed

Lines of Context:
69
69
%% process, and it will always be alive when testing is ongoing.
70
70
%% test_server_ctrl initiates testing and monitors JobProc(s).
71
71
%% 
72
 
%% When target is local, the test_server_ctrl process is also globally
73
 
%% registered as test_server and simulates the {global,test_server}
74
 
%% process on remote target.
 
72
%% When target is local, and Test Server is *not* being used by a framework 
 
73
%% application (where it might cause duplicate name problems in a distributed 
 
74
%% test environment), the process is globally registered as 'test_server' 
 
75
%% to be able to simulate the {global,test_server} process on a remote target.
75
76
%% 
76
77
%% JobProc is spawned for each 'job' added to the test_server_ctrl. 
77
78
%% A job can mean one test case, one test suite or one spec.
565
566
    case os:getenv("TEST_SERVER_CALL_TRACE") of
566
567
        false ->
567
568
            ok;
 
569
        "" ->
 
570
            ok;
568
571
        TraceSpec ->
569
572
            test_server_sup:call_trace(TraceSpec)
570
573
    end,
598
601
%% If the test is to be run at a remote target, this function sets up
599
602
%% a socket communication with the target.
600
603
contact_main_target(local) ->
601
 
    %% Local target! The global test_server process implemented by
602
 
    %% test_server.erl will not be started, so we simulate it by 
603
 
    %% globally registering this process instead.
604
 
    global:sync(),
605
 
    case global:whereis_name(test_server) of
606
 
        undefined ->
607
 
            global:register_name(test_server, self());
608
 
        Pid ->
609
 
            case node() of
610
 
                N when N == node(Pid) ->
611
 
                    io:format(user, "Warning: test_server already running!\n", []),
612
 
                    global:re_register_name(test_server,self());
613
 
                _ ->
614
 
                    ok
615
 
            end
616
 
    end,            
 
604
    %% When used by a general framework, global registration of
 
605
    %% test_server should not be required.
 
606
    case os:getenv("TEST_SERVER_FRAMEWORK") of
 
607
        false ->
 
608
            %% Local target! The global test_server process implemented by
 
609
            %% test_server.erl will not be started, so we simulate it by 
 
610
            %% globally registering this process instead.
 
611
            global:sync(),
 
612
            case global:whereis_name(test_server) of
 
613
                undefined ->
 
614
                    global:register_name(test_server, self());
 
615
                Pid ->
 
616
                    case node() of
 
617
                        N when N == node(Pid) ->
 
618
                            io:format(user, "Warning: test_server already running!\n", []),
 
619
                            global:re_register_name(test_server,self());
 
620
                        _ ->
 
621
                            ok
 
622
                    end
 
623
            end;
 
624
        _ ->
 
625
            ok
 
626
    end,
617
627
    TI = test_server:init_target_info(),
618
628
    TargetHost = test_server_sup:hoststr(),
619
629
    {ok,TI#target_info{where=local,
2154
2164
                    %% buffered io can be flushed
2155
2165
                    handle_test_case_io_and_status(),
2156
2166
                    set_io_buffering(undefined),
2157
 
                    {Mod,Func} = skip_case(Ref, 0, Case, Comment, false, SkipMode),
 
2167
                    {Mod,Func} = skip_case(auto, Ref, 0, Case, Comment, false, SkipMode),
2158
2168
                    test_server_sup:framework_call(report, [tc_auto_skip,{?pl2a(Mod),Func,Comment}]),
2159
2169
                    run_test_cases_loop(Cases, Config, MultiplyTimetrap, tl(Mode), 
2160
2170
                                        delete_status(Ref, Status));
2162
2172
                    %% this is a skipped end conf for a parallel group nested under a 
2163
2173
                    %% parallel group (io buffering is active)
2164
2174
                    wait_for_cases(Ref),
2165
 
                    {Mod,Func} = skip_case(Ref, 0, Case, Comment, true, SkipMode),
 
2175
                    {Mod,Func} = skip_case(auto, Ref, 0, Case, Comment, true, SkipMode),
2166
2176
                    test_server_sup:framework_call(report, [tc_auto_skip,{?pl2a(Mod),Func,Comment}]),
2167
2177
                    case CurrIOHandler of
2168
2178
                        {Ref,_} -> 
2179
2189
        {Ref,false} ->
2180
2190
            %% this is a skipped end conf for a non-parallel group that's not
2181
2191
            %% nested under a parallel group
2182
 
            {Mod,Func} = skip_case(Ref, 0, Case, Comment, false, SkipMode),
 
2192
            {Mod,Func} = skip_case(auto, Ref, 0, Case, Comment, false, SkipMode),
2183
2193
            test_server_sup:framework_call(report, [tc_auto_skip,{?pl2a(Mod),Func,Comment}]),
2184
2194
            run_test_cases_loop(Cases, Config, MultiplyTimetrap, tl(Mode), 
2185
2195
                                delete_status(Ref, Status));
2186
2196
        {Ref,_} ->
2187
2197
            %% this is a skipped end conf for a non-parallel group nested under
2188
2198
            %% a parallel group (io buffering is active)
2189
 
            {Mod,Func} = skip_case(Ref, 0, Case, Comment, true, SkipMode),
 
2199
            {Mod,Func} = skip_case(auto, Ref, 0, Case, Comment, true, SkipMode),
2190
2200
            test_server_sup:framework_call(report, [tc_auto_skip,{?pl2a(Mod),Func,Comment}]),
2191
2201
            case CurrIOHandler of
2192
2202
                {Ref,_} ->  
2202
2212
        {_,false} ->
2203
2213
            %% this is a skipped start conf for a group which is not nested
2204
2214
            %% under a parallel group
2205
 
            {Mod,Func} = skip_case(Ref, 0, Case, Comment, false, SkipMode),
 
2215
            {Mod,Func} = skip_case(auto, Ref, 0, Case, Comment, false, SkipMode),
2206
2216
            test_server_sup:framework_call(report, [tc_auto_skip,{?pl2a(Mod),Func,Comment}]),
2207
2217
            run_test_cases_loop(Cases, Config, MultiplyTimetrap, [conf(Ref,[])|Mode], Status);
2208
2218
        {_,Ref0} when is_reference(Ref0) ->
2213
2223
               true ->
2214
2224
                    ok
2215
2225
            end,
2216
 
            {Mod,Func} = skip_case(Ref, 0, Case, Comment, true, SkipMode),
 
2226
            {Mod,Func} = skip_case(auto, Ref, 0, Case, Comment, true, SkipMode),
2217
2227
            test_server_sup:framework_call(report, [tc_auto_skip,{?pl2a(Mod),Func,Comment}]),
2218
2228
            run_test_cases_loop(Cases, Config, MultiplyTimetrap, [conf(Ref,[])|Mode], Status)
2219
2229
    end; 
2220
2230
 
2221
2231
run_test_cases_loop([{auto_skip_case,{Case,Comment},SkipMode}|Cases],
2222
2232
                    Config, MultiplyTimetrap, Mode, Status) ->
2223
 
    {Mod,Func} = skip_case(undefined, get(test_server_case_num)+1, Case, Comment,
 
2233
    {Mod,Func} = skip_case(auto, undefined, get(test_server_case_num)+1, Case, Comment,
2224
2234
                           (undefined /= get(test_server_common_io_handler)), SkipMode),
2225
2235
    test_server_sup:framework_call(report, [tc_auto_skip,{?pl2a(Mod),Func,Comment}]),
2226
2236
    run_test_cases_loop(Cases, Config, MultiplyTimetrap, Mode, 
2228
2238
 
2229
2239
run_test_cases_loop([{skip_case,{conf,Ref,Case,Comment}}|Cases0],
2230
2240
                    Config, MultiplyTimetrap, Mode, Status) ->
2231
 
    {Mod,Func} = skip_case(Ref, 0, Case, Comment,
 
2241
    {Mod,Func} = skip_case(user, Ref, 0, Case, Comment,
2232
2242
                           (undefined /= get(test_server_common_io_handler))),
2233
2243
    {Cases,Config1} =
2234
2244
        case curr_ref(Mode) of
2245
2255
 
2246
2256
run_test_cases_loop([{skip_case,{Case,Comment}}|Cases],
2247
2257
                    Config, MultiplyTimetrap, Mode, Status) ->
2248
 
    {Mod,Func} = skip_case(undefined, get(test_server_case_num)+1, Case, Comment,
 
2258
    {Mod,Func} = skip_case(user, undefined, get(test_server_case_num)+1, Case, Comment,
2249
2259
                           (undefined /= get(test_server_common_io_handler))),
2250
2260
    test_server_sup:framework_call(report, [tc_user_skip,{?pl2a(Mod),Func,Comment}]),
2251
2261
    run_test_cases_loop(Cases, Config, MultiplyTimetrap, Mode,
2887
2897
 
2888
2898
 
2889
2899
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
2890
 
%% skip_case(Ref, CaseNum, Case, Comment, SendSync) -> {Mod,Func}
 
2900
%% skip_case(Type, Ref, CaseNum, Case, Comment, SendSync) -> {Mod,Func}
2891
2901
%%
2892
2902
%% Prints info about a skipped case in the major and html log files.
2893
2903
%% SendSync determines if start and finished messages must be sent so 
2894
2904
%% that the printouts can be buffered and handled in order with io from
2895
2905
%% parallel processes.
2896
2906
 
2897
 
skip_case(Ref, CaseNum, Case, Comment, SendSync) ->
2898
 
    skip_case(Ref, CaseNum, Case, Comment, SendSync, []).
 
2907
skip_case(Type, Ref, CaseNum, Case, Comment, SendSync) ->
 
2908
    skip_case(Type, Ref, CaseNum, Case, Comment, SendSync, []).
2899
2909
 
2900
 
skip_case(Ref, CaseNum, Case, Comment, SendSync, Mode) ->
 
2910
skip_case(Type, Ref, CaseNum, Case, Comment, SendSync, Mode) ->
2901
2911
    MF = {Mod,Func} = case Case of
2902
2912
                          {M,F,_A} -> {M,F};
2903
2913
                          {M,F} -> {M,F}
2905
2915
    if SendSync ->
2906
2916
            queue_test_case_io(Ref, self(), CaseNum, Mod, Func),
2907
2917
            self() ! {started,Ref,self(),CaseNum,Mod,Func},
2908
 
            skip_case1(CaseNum, Mod, Func, Comment, Mode),
 
2918
            skip_case1(Type, CaseNum, Mod, Func, Comment, Mode),
2909
2919
            self() ! {finished,Ref,self(),CaseNum,Mod,Func,skipped,{0,skipped,[]}};
2910
2920
       not SendSync ->
2911
 
            skip_case1(CaseNum, Mod, Func, Comment, Mode)
 
2921
            skip_case1(Type, CaseNum, Mod, Func, Comment, Mode)
2912
2922
    end,
2913
2923
    MF.     
2914
2924
 
2915
 
skip_case1(CaseNum, Mod, Func, Comment, Mode) ->
 
2925
skip_case1(Type, CaseNum, Mod, Func, Comment, Mode) ->
2916
2926
    {{Col0,Col1},_} = get_font_style((CaseNum > 0), Mode),
 
2927
    ResultCol = if Type == auto -> "#ffcc99";
 
2928
                   Type == user -> "#ff9933"
 
2929
                end,
2917
2930
    print(major, "~n=case          ~p:~p", [Mod,Func]),
2918
2931
    print(major, "=started         ~s", [lists:flatten(timestamp_get(""))]),
2919
2932
    print(major, "=result          skipped: ~s", [Comment]),
2925
2938
          "<td>" ++ Col0 ++ "~p" ++ Col1 ++ "</td>"
2926
2939
          "<td>" ++ Col0 ++ "< >" ++ Col1 ++ "</td>"
2927
2940
          "<td>" ++ Col0 ++ "0.000s" ++ Col1 ++ "</td>"
2928
 
          "<td><font color=\"orange\">SKIPPED</font></td>"
 
2941
          "<td><font color=\"~s\">SKIPPED</font></td>"
2929
2942
          "<td>~s</td></tr>\n",
2930
 
          [num2str(CaseNum),Mod,Func,Comment]),
 
2943
          [num2str(CaseNum),Mod,Func,ResultCol,Comment]),
2931
2944
    if CaseNum > 0 ->
2932
2945
            put(test_server_skipped, get(test_server_skipped)+1),
2933
2946
            put(test_server_case_num, CaseNum);
3591
3604
          [get_info_str(Func, CaseNum, get(test_server_cases))]),
3592
3605
    test_server_sup:framework_call(report, [tc_done,{?pl2a(Mod),Func,
3593
3606
                                                     {skipped,ReasonStr}}]),
 
3607
    ReasonStr1 = lists:flatten([string:strip(S,left) || 
 
3608
                                S <- string:tokens(ReasonStr,[$\n])]),
 
3609
    ReasonStr2 =
 
3610
        if length(ReasonStr1) > 80 ->
 
3611
                string:substr(ReasonStr1, 1, 77) ++ "...";
 
3612
           true ->
 
3613
                ReasonStr1
 
3614
        end,
3594
3615
    Comment1 = case Comment of
3595
3616
                   "" -> "";
3596
 
                   _ -> "(" ++ Comment ++ ")"
 
3617
                   _ -> "<br>(" ++ Comment ++ ")"
3597
3618
               end,
3598
3619
    print(html,
3599
3620
          "<td>" ++ St0 ++ "~.3fs" ++ St1 ++ "</td>"
3600
 
          "<td><font color=\"orange\">SKIPPED</font></td>"
3601
 
          "<td>~s ~s</td></tr>\n",
3602
 
          [Time,lists:flatten(ReasonStr),Comment1]),
 
3621
          "<td><font color=\"#ff9933\">SKIPPED</font></td>"
 
3622
          "<td>~s~s</td></tr>\n",
 
3623
          [Time,ReasonStr2,Comment1]),
3603
3624
    FormatLoc = test_server_sup:format_loc(Loc),
3604
3625
    print(minor, "=== location ~s", [FormatLoc]),
3605
 
    print(minor, "=== reason = ~p", [lists:flatten(ReasonStr)]),
 
3626
    print(minor, "=== reason = ~s", [ReasonStr1]),    
3606
3627
    skip;
3607
3628
    
3608
3629
progress(failed, CaseNum, Mod, Func, Loc, timetrap_timeout, T,