~clint-fewbar/ubuntu/precise/erlang/merge-15b

« back to all changes in this revision

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

  • Committer: Bazaar Package Importer
  • Author(s): Martin Pitt
  • Date: 2009-11-06 18:54:42 UTC
  • mfrom: (3.3.4 sid)
  • Revision ID: james.westby@ubuntu.com-20091106185442-bqxb11qghumvmvx2
Tags: 1:13.b.2.1-dfsg-1ubuntu1
* Merge with Debian testing; remaining Ubuntu changes:
  - Drop libwxgtk2.8-dev build dependency. Wx isn't in main, and not
    supposed to. (LP #438365)
  - Drop erlang-wx binary.
  - Drop erlang-wx dependency from -megaco, -common-test, and -reltool, they
    do not really need wx. Also drop it from -debugger; the GUI needs wx,
    but it apparently has CLI bits as well, and is also needed by -megaco,
    so let's keep the package for now.

Show diffs side-by-side

added added

removed removed

Lines of Context:
116
116
            erlang:error({bad_installation,file:format_error(Reason)}, [Dir])
117
117
    end.
118
118
 
119
 
make_master_index(Platform, Dirname, {Succ, Fail, Skip}, Result) ->
 
119
make_master_index(Platform, Dirname, {Succ, Fail, UserSkip,AutoSkip}, Result) ->
120
120
    Link = filename:join(filename:basename(Dirname), "index.html"),
 
121
    FailStr =
 
122
        if Fail > 0 ->  
 
123
                ["<FONT color=\"red\">",
 
124
                 integer_to_list(Fail),"</FONT>"];
 
125
           true ->
 
126
                integer_to_list(Fail)
 
127
        end,
 
128
    AutoSkipStr =
 
129
        if AutoSkip > 0 ->
 
130
                ["<FONT color=\"brown\">",
 
131
                 integer_to_list(AutoSkip),"</FONT>"];
 
132
           true -> integer_to_list(AutoSkip)
 
133
        end,
121
134
    [Result,
122
135
     "<TR valign=top>\n",
123
136
     "<TD><A HREF=\"", Link, "\">", Platform, "</A></TD>", "\n",
124
137
     make_row(integer_to_list(Succ), false),
125
 
     make_row(integer_to_list(Fail), false),
126
 
     make_row(integer_to_list(Skip), false),
 
138
     make_row(FailStr, false),
 
139
     make_row(integer_to_list(UserSkip), false),
 
140
     make_row(AutoSkipStr, false),
127
141
     "</TR>\n"].
128
142
 
129
143
%% Make index page which points out individual test suites for a single platform.
161
175
            true  -> add_last_name(Logs0);
162
176
            false -> Logs0
163
177
        end,
164
 
    {ok, {Index0, Summary}} = make_index(Logs, header(Vars), 0, 0, 0, 0),
 
178
    {ok, {Index0, Summary}} = make_index(Logs, header(Vars), 0, 0, 0, 0, 0),
165
179
    Index = [Index0|footer()],
166
180
    case ts_lib:force_write_file(IndexName, Index) of
167
181
        ok ->
170
184
            error({index_write_error, Reason})
171
185
    end.
172
186
 
173
 
make_index([Name|Rest], Result, TotSucc, TotFail, TotSkip, TotNotBuilt) ->
 
187
make_index([Name|Rest], Result, TotSucc, TotFail, UserSkip, AutoSkip, TotNotBuilt) ->
174
188
    case ts_lib:last_test(Name) of
175
189
        false ->
176
190
            %% Silently skip.
177
 
            make_index(Rest, Result, TotSucc, TotFail, TotSkip, TotNotBuilt);
 
191
            make_index(Rest, Result, TotSucc, TotFail, UserSkip, AutoSkip, TotNotBuilt);
178
192
        Last ->
179
193
            case count_cases(Last) of
180
 
                {Succ, Fail, Skip} ->
 
194
                {Succ, Fail, USkip, ASkip} ->
181
195
                    Cov = 
182
196
                        case file:read_file(filename:join(Last,?cover_total)) of
183
197
                            {ok,Bin} -> 
190
204
                    JustTheName = rootname(basename(Name)),
191
205
                    NotBuilt = not_built(JustTheName),
192
206
                    NewResult = [Result, make_index1(JustTheName,
193
 
                                                     Link, Succ, Fail, Skip, 
 
207
                                                     Link, Succ, Fail, USkip, ASkip, 
194
208
                                                     NotBuilt, Cov, false)],
195
209
                    make_index(Rest, NewResult, TotSucc+Succ, TotFail+Fail, 
196
 
                               TotSkip+Skip, TotNotBuilt+NotBuilt );
 
210
                               UserSkip+USkip, AutoSkip+ASkip, TotNotBuilt+NotBuilt);
197
211
                error ->
198
 
                    make_index(Rest, Result, TotSucc, TotFail, TotSkip, 
 
212
                    make_index(Rest, Result, TotSucc, TotFail, UserSkip, AutoSkip,
199
213
                               TotNotBuilt)
200
214
            end
201
215
    end;
202
 
make_index([], Result, TotSucc, TotFail, TotSkip, TotNotBuilt) ->
 
216
make_index([], Result, TotSucc, TotFail, UserSkip, AutoSkip, TotNotBuilt) ->
203
217
    {ok, {[Result|make_index1("Total", no_link,
204
 
                              TotSucc, TotFail, TotSkip, TotNotBuilt, "", true)],
205
 
          {TotSucc, TotFail, TotSkip}}}.
 
218
                              TotSucc, TotFail, UserSkip, AutoSkip, 
 
219
                              TotNotBuilt, "", true)],
 
220
          {TotSucc, TotFail, UserSkip, AutoSkip}}}.
206
221
 
207
 
make_index1(SuiteName, Link, Success, Fail, Skipped, NotBuilt, Coverage, Bold) ->
 
222
make_index1(SuiteName, Link, Success, Fail, UserSkip, AutoSkip, NotBuilt, Coverage, Bold) ->
208
223
    Name = test_suite_name(SuiteName),
 
224
    FailStr =
 
225
        if Fail > 0 ->  
 
226
                ["<FONT color=\"red\">",
 
227
                 integer_to_list(Fail),"</FONT>"];
 
228
           true ->
 
229
                integer_to_list(Fail)
 
230
        end,
 
231
    AutoSkipStr =
 
232
        if AutoSkip > 0 ->
 
233
                ["<FONT color=\"brown\">",
 
234
                 integer_to_list(AutoSkip),"</FONT>"];
 
235
           true -> integer_to_list(AutoSkip)
 
236
        end,
209
237
    ["<TR valign=top>\n",
210
238
     "<TD>",
211
239
     case Link of
226
254
              "</TD>\n"]
227
255
     end,
228
256
     make_row(integer_to_list(Success), Bold),
229
 
     make_row(integer_to_list(Fail), Bold),
230
 
     make_row(integer_to_list(Skipped), Bold),
 
257
     make_row(FailStr, Bold),
 
258
     make_row(integer_to_list(UserSkip), Bold),
 
259
     make_row(AutoSkipStr, Bold),
231
260
     make_row(integer_to_list(NotBuilt), Bold),
232
261
     make_row(Coverage, Bold),
233
262
     "</TR>\n"].
297
326
     "<th><B>Family</B></th>\n",
298
327
     "<th>Successful</th>\n",
299
328
     "<th>Failed</th>\n",
300
 
     "<th>Skipped</th>\n"
 
329
     "<th>User Skipped</th>\n"
 
330
     "<th>Auto Skipped</th>\n"
301
331
     "<th>Missing Suites</th>\n"
302
332
     "<th>Coverage</th>\n"
303
333
     "\n"].
374
404
     "<th><b>Platform</b></th>\n",
375
405
     "<th>Successful</th>\n",
376
406
     "<th>Failed</th>\n",
377
 
     "<th>Skipped</th>\n"
 
407
     "<th>User Skipped</th>\n"
 
408
     "<th>Auto Skipped</th>\n"
378
409
     "\n"].
379
410
 
380
411
master_footer() ->
432
463
count_cases(Dir) ->
433
464
    SumFile = filename:join(Dir, ?run_summary),
434
465
    case read_summary(SumFile, [summary]) of
 
466
        {ok, [{Succ,Fail,Skip}]} ->
 
467
            {Succ,Fail,Skip,0};
435
468
        {ok, [Summary]} ->
436
469
            Summary;
437
470
        {error, _} ->
438
471
            LogFile = filename:join(Dir, ?suitelog_name),
439
472
            case file:read_file(LogFile) of
440
473
                {ok, Bin} ->
441
 
                    Summary = count_cases1(binary_to_list(Bin), {0, 0, 0}),
 
474
                    Summary = count_cases1(binary_to_list(Bin), {0, 0, 0, 0}),
442
475
                    write_summary(SumFile, Summary),
443
476
                    Summary;
444
477
                {error, _Reason} ->
470
503
            {error, Reason}
471
504
    end.
472
505
 
473
 
count_cases1("=failed" ++ Rest, {Success, _Fail, Skipped}) ->
474
 
    {NextLine, Count} = get_number(Rest),
475
 
    count_cases1(NextLine, {Success, Count, Skipped});
476
 
count_cases1("=successful" ++ Rest, {_Success, Fail, Skipped}) ->
477
 
    {NextLine, Count} = get_number(Rest),
478
 
    count_cases1(NextLine, {Count, Fail, Skipped});
479
 
count_cases1("=skipped" ++ Rest, {Success, Fail, _Skipped}) ->
480
 
    {NextLine, Count} = get_number(Rest),
481
 
    count_cases1(NextLine, {Success, Fail, Count});
 
506
count_cases1("=failed" ++ Rest, {Success, _Fail, UserSkip,AutoSkip}) ->
 
507
    {NextLine, Count} = get_number(Rest),
 
508
    count_cases1(NextLine, {Success, Count, UserSkip,AutoSkip});
 
509
count_cases1("=successful" ++ Rest, {_Success, Fail, UserSkip,AutoSkip}) ->
 
510
    {NextLine, Count} = get_number(Rest),
 
511
    count_cases1(NextLine, {Count, Fail, UserSkip,AutoSkip});
 
512
count_cases1("=skipped" ++ Rest, {Success, Fail, _UserSkip,AutoSkip}) ->
 
513
    {NextLine, Count} = get_number(Rest),
 
514
    count_cases1(NextLine, {Success, Fail, Count,AutoSkip});
 
515
count_cases1("=user_skipped" ++ Rest, {Success, Fail, _UserSkip,AutoSkip}) ->
 
516
    {NextLine, Count} = get_number(Rest),
 
517
    count_cases1(NextLine, {Success, Fail, Count,AutoSkip});
 
518
count_cases1("=auto_skipped" ++ Rest, {Success, Fail, UserSkip,_AutoSkip}) ->
 
519
    {NextLine, Count} = get_number(Rest),
 
520
    count_cases1(NextLine, {Success, Fail, UserSkip,Count});
482
521
count_cases1([], Counters) ->
483
522
    Counters;
484
523
count_cases1(Other, Counters) ->