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

« back to all changes in this revision

Viewing changes to lib/common_test/src/ct_logs.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 2003-2009. All Rights Reserved.
5
 
%% 
 
3
%%
 
4
%% Copyright Ericsson AB 2003-2010. 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
 
36
36
-export([make_all_suites_index/1,make_all_runs_index/1]).
37
37
 
38
38
%% Logging stuff directly from testcase
39
 
-export([tc_log/3,tc_print/3,tc_pal/3]).
 
39
-export([tc_log/3,tc_print/3,tc_pal/3,
 
40
         basic_html/0]).
40
41
 
41
42
%% Simulate logger process for use without ct environment running
42
43
-export([simulate/0]).
57
58
-define(table_color2,"#E4F0FE").
58
59
-define(table_color3,"#F0F8FF").
59
60
 
60
 
-define(testname_width, 70).
 
61
-define(testname_width, 60).
61
62
 
62
63
-define(abs(Name), filename:absname(Name)).
63
64
 
80
81
    MRef = erlang:monitor(process,Pid),
81
82
    receive 
82
83
        {started,Pid,Result} -> 
83
 
            erlang:demonitor(MRef),
 
84
            erlang:demonitor(MRef, [flush]),
84
85
            Result;
85
86
        {'DOWN',MRef,process,_,Reason} ->
86
87
            exit({could_not_start_process,?MODULE,Reason})
163
164
            ?MODULE ! {Msg,{self(),Ref}},
164
165
            receive
165
166
                {Ref, Result} -> 
166
 
                    erlang:demonitor(MRef),
 
167
                    erlang:demonitor(MRef, [flush]),
167
168
                    Result;
168
169
                {'DOWN',MRef,process,_,Reason}  -> 
169
170
                    {error,{process_down,?MODULE,Reason}}
383
384
                  [{"<i>~s</i>",[log_timestamp({MS,S,US})]}]})
384
385
    end.
385
386
 
386
 
log_timestamp(Now) ->
387
 
    put(log_timestamp,Now),
388
 
    {_,{H,M,S}} = calendar:now_to_local_time(Now),
389
 
    lists:flatten(io_lib:format("~2.2.0w:~2.2.0w:~2.2.0w",
390
 
                                [H,M,S])).
 
387
log_timestamp({MS,S,US}) ->
 
388
    put(log_timestamp, {MS,S,US}),
 
389
    {{Year,Month,Day}, {Hour,Min,Sec}} =
 
390
        calendar:now_to_local_time({MS,S,US}),
 
391
    MilliSec = trunc(US/1000),
 
392
    lists:flatten(io_lib:format("~4.10.0B-~2.10.0B-~2.10.0B "
 
393
                                "~2.10.0B:~2.10.0B:~2.10.0B.~3.10.0B",
 
394
                                [Year,Month,Day,Hour,Min,Sec,MilliSec])).
391
395
 
392
396
%%%-----------------------------------------------------------------
393
397
%%% The logger server
460
464
                                            {'EXIT',_Reason} ->
461
465
                                                Fd = State#logger_state.ct_log_fd,
462
466
                                                io:format(Fd, 
463
 
                                                          "Logging fails! Str: ~p, Args: ~p~n",
 
467
                                                          "Logging fails! "
 
468
                                                          "Str: ~p, Args: ~p~n",
464
469
                                                          [Str,Args]),
465
 
                                                %% stop the testcase, we need to see the fault
 
470
                                                %% stop the testcase, we need
 
471
                                                %% to see the fault
466
472
                                                exit(Pid,logging_failed),
467
473
                                                ok;
468
474
                                            IoStr when IoList == [] ->
505
511
            logger_loop(State);
506
512
        {set_stylesheet,TC,SSFile} ->
507
513
            Fd = State#logger_state.ct_log_fd,
508
 
            io:format(Fd, "~p uses external style sheet: ~s~n", [TC,SSFile]),
 
514
            io:format(Fd, "~p loading external style sheet: ~s~n", [TC,SSFile]),
509
515
            logger_loop(State#logger_state{stylesheet=SSFile});
510
516
        {clear_stylesheet,_} when State#logger_state.stylesheet == undefined ->
511
517
            logger_loop(State);
716
722
                [Log];
717
723
            Logs ->
718
724
                case read_totals_file(?totals_name) of
719
 
                    {_Node,Logs0,_Totals} ->
 
725
                    {_Node,_Lbl,Logs0,_Totals} ->
720
726
                        insert_dirs(Logs,Logs0);
721
727
                    _ ->
722
728
                        %% someone deleted the totals file!?
728
734
            {ok,Bin} -> binary_to_term(Bin);
729
735
            _ -> []
730
736
        end,
731
 
    {ok,Index0,Totals} = make_last_run_index(Logs1, index_header(StartTime),
 
737
    Label = case application:get_env(common_test, test_label) of
 
738
                {ok,Lbl} -> Lbl;
 
739
                _ -> undefined
 
740
            end,
 
741
    {ok,Index0,Totals} = make_last_run_index(Logs1,
 
742
                                             index_header(Label,StartTime),
732
743
                                             0, 0, 0, 0, 0, Missing),
733
744
    %% write current Totals to file, later to be used in all_runs log
734
 
    write_totals_file(?totals_name,Logs1,Totals),
 
745
    write_totals_file(?totals_name,Label,Logs1,Totals),
735
746
    Index = [Index0|index_footer()],
736
747
    case force_write_file(IndexName, Index) of
737
748
        ok ->
761
772
                                TotNotBuilt, Missing);
762
773
        LastLogDir ->
763
774
            SuiteName = filename:rootname(filename:basename(Name)),
764
 
            case make_one_index_entry(SuiteName, LastLogDir, false, Missing) of
 
775
            case make_one_index_entry(SuiteName, LastLogDir, "-", false, Missing) of
765
776
                {Result1,Succ,Fail,USkip,ASkip,NotBuilt} ->
766
777
                    %% for backwards compatibility
767
778
                    AutoSkip1 = case catch AutoSkip+ASkip of
780
791
    {ok, [Result|total_row(TotSucc, TotFail, UserSkip, AutoSkip, TotNotBuilt, false)],
781
792
     {TotSucc,TotFail,UserSkip,AutoSkip,TotNotBuilt}}.
782
793
 
783
 
make_one_index_entry(SuiteName, LogDir, All, Missing) ->
 
794
make_one_index_entry(SuiteName, LogDir, Label, All, Missing) ->
784
795
    case count_cases(LogDir) of
785
796
        {Succ,Fail,UserSkip,AutoSkip} ->
786
797
            NotBuilt = not_built(SuiteName, LogDir, All, Missing),
787
 
            NewResult = make_one_index_entry1(SuiteName, LogDir, Succ, Fail, 
 
798
            NewResult = make_one_index_entry1(SuiteName, LogDir, Label, Succ, Fail,
788
799
                                              UserSkip, AutoSkip, NotBuilt, All),
789
800
            {NewResult,Succ,Fail,UserSkip,AutoSkip,NotBuilt};
790
801
        error ->
791
802
            error
792
803
    end.
793
804
 
794
 
make_one_index_entry1(SuiteName, Link, Success, Fail, UserSkip, AutoSkip, 
 
805
make_one_index_entry1(SuiteName, Link, Label, Success, Fail, UserSkip, AutoSkip,
795
806
                      NotBuilt, All) ->
796
807
    LogFile = filename:join(Link, ?suitelog_name ++ ".html"),
797
808
    CrashDumpName = SuiteName ++ "_erl_crash.dump",
803
814
            false ->
804
815
                ""
805
816
        end,
806
 
    {Timestamp,Node,AllInfo} = 
 
817
    {Lbl,Timestamp,Node,AllInfo} =
807
818
        case All of
808
819
            {true,OldRuns} -> 
809
820
                [_Prefix,NodeOrDate|_] = string:tokens(Link,"."),
811
822
                            0 -> "-";
812
823
                            _ -> NodeOrDate
813
824
                        end,
814
 
                N = ["<TD ALIGN=right>",Node1,"</TD>\n"],
 
825
                N = ["<TD ALIGN=right><FONT SIZE=-1>",Node1,"</FONT></TD>\n"],
815
826
                CtRunDir = filename:dirname(filename:dirname(Link)),
816
 
                T = ["<TD>",timestamp(CtRunDir),"</TD>\n"],
 
827
                L = ["<TD ALIGN=center><FONT SIZE=-1><B>",Label,"</FONT></B></TD>\n"],
 
828
                T = ["<TD><FONT SIZE=-1>",timestamp(CtRunDir),"</FONT></TD>\n"],
817
829
                CtLogFile = filename:join(CtRunDir,?ct_log_name),
818
830
                OldRunsLink = 
819
831
                    case OldRuns of
820
832
                        [] -> "none";
821
833
                        _ ->  "<A HREF=\""++?all_runs_name++"\">Old Runs</A>"
822
834
                    end,
823
 
                A=["<TD><A HREF=\"",CtLogFile,"\">CT Log</A></TD>\n",
824
 
                   "<TD>",OldRunsLink,"</TD>\n"],
825
 
                {T,N,A};
 
835
                A=["<TD><FONT SIZE=-1><A HREF=\"",CtLogFile,"\">CT Log</A></FONT></TD>\n",
 
836
                   "<TD><FONT SIZE=-1>",OldRunsLink,"</FONT></TD>\n"],
 
837
                {L,T,N,A};
826
838
            false ->
827
 
                {"","",""}
 
839
                {"","","",""}
828
840
        end,
829
841
    NotBuiltStr =
830
842
        if NotBuilt == 0 ->
851
863
                {UserSkip+AutoSkip,integer_to_list(UserSkip),ASStr}
852
864
        end,
853
865
    ["<TR valign=top>\n",
854
 
     "<TD><A HREF=\"",LogFile,"\">",SuiteName,"</A>",CrashDumpLink,"</TD>\n",
 
866
     "<TD><FONT SIZE=-1><A HREF=\"",LogFile,"\">",SuiteName,"</A>",CrashDumpLink,"</FONT></TD>\n",
 
867
     Lbl,
855
868
     Timestamp,
856
869
     "<TD ALIGN=right>",integer_to_list(Success),"</TD>\n",
857
870
     "<TD ALIGN=right>",FailStr,"</TD>\n",
862
875
     AllInfo,
863
876
     "</TR>\n"].
864
877
total_row(Success, Fail, UserSkip, AutoSkip, NotBuilt, All) ->
865
 
    {TimestampCell,AllInfo} = 
 
878
    {Label,TimestampCell,AllInfo} =
866
879
        case All of
867
 
            true -> 
868
 
                {"<TD>&nbsp;</TD>\n","<TD>&nbsp;</TD>\n<TD>&nbsp;</TD>\n"};
 
880
            true ->
 
881
                {"<TD>&nbsp;</TD>\n",
 
882
                 "<TD>&nbsp;</TD>\n",
 
883
                 "<TD>&nbsp;</TD>\n<TD>&nbsp;</TD>\n"};
869
884
            false ->
870
 
                {"",""}
 
885
                {"","",""}
871
886
        end,
872
887
 
873
888
    {AllSkip,UserSkipStr,AutoSkipStr} =
877
892
        end,
878
893
    ["<TR valign=top>\n",
879
894
     "<TD><B>Total</B></TD>",
 
895
     Label,
880
896
     TimestampCell,
881
897
     "<TD ALIGN=right><B>",integer_to_list(Success),"<B></TD>\n",
882
898
     "<TD ALIGN=right><B>",integer_to_list(Fail),"<B></TD>\n",
937
953
 
938
954
%%% Headers and footers.
939
955
 
940
 
index_header(StartTime) ->
941
 
    [header("Test Results " ++ format_time(StartTime)) | 
 
956
index_header(Label, StartTime) ->
 
957
    Head =
 
958
        case Label of
 
959
            undefined ->
 
960
                header("Test Results", format_time(StartTime));
 
961
            _ ->
 
962
                header("Test Results for \"" ++ Label ++ "\"",
 
963
                       format_time(StartTime))
 
964
        end,
 
965
    [Head |
942
966
     ["<CENTER>\n",
943
967
      "<P><A HREF=\"",?ct_log_name,"\">Common Test Framework Log</A></P>",
944
968
      "<TABLE border=\"3\" cellpadding=\"5\" "
945
969
      "BGCOLOR=\"",?table_color3,"\">\n"
946
 
      "<th><B>Name</B></th>\n",
 
970
      "<th><B>Test Name</B></th>\n",
947
971
            "<th><font color=\"",?table_color3,"\">_</font>Ok"
948
972
          "<font color=\"",?table_color3,"\">_</font></th>\n"
949
973
      "<th>Failed</th>\n",
952
976
      "\n"]].
953
977
 
954
978
all_suites_index_header() ->
 
979
    {ok,Cwd} = file:get_cwd(),
 
980
    LogDir = filename:basename(Cwd),
 
981
    AllRuns = "All test runs in \"" ++ LogDir ++ "\"",
955
982
    [header("Test Results") | 
956
983
     ["<CENTER>\n",
957
 
      "<A HREF=\"",?all_runs_name,"\">All Test Runs in this directory</A>\n",
 
984
      "<A HREF=\"",?all_runs_name,"\">",AllRuns,"</A>\n",
958
985
      "<br><br>\n",
959
986
      "<TABLE border=\"3\" cellpadding=\"5\" "
960
987
      "BGCOLOR=\"",?table_color2,"\">\n"
961
 
      "<th>Name</th>\n",
 
988
      "<th>Test Name</th>\n",
 
989
      "<th>Label</th>\n",
962
990
      "<th>Test Run Started</th>\n",
963
991
      "<th><font color=\"",?table_color2,"\">_</font>Ok"
964
992
          "<font color=\"",?table_color2,"\">_</font></th>\n"
971
999
      "\n"]].
972
1000
 
973
1001
all_runs_header() ->
974
 
    [header("All test runs in current directory") |
 
1002
    {ok,Cwd} = file:get_cwd(),
 
1003
    LogDir = filename:basename(Cwd),
 
1004
    Title = "All test runs in \"" ++ LogDir ++ "\"",
 
1005
    [header(Title) |
975
1006
     ["<CENTER><TABLE border=\"3\" cellpadding=\"5\" "
976
1007
      "BGCOLOR=\"",?table_color1,"\">\n"
977
1008
      "<th><B>History</B></th>\n"
978
1009
      "<th><B>Node</B></th>\n"
 
1010
      "<th><B>Label</B></th>\n"
979
1011
      "<th>Tests</th>\n"
980
 
      "<th><B>Names</B></th>\n"
 
1012
      "<th><B>Test Names</B></th>\n"
981
1013
      "<th>Total</th>\n"
982
1014
      "<th><font color=\"",?table_color1,"\">_</font>Ok"
983
1015
          "<font color=\"",?table_color1,"\">_</font></th>\n"
987
1019
      "\n"]].
988
1020
 
989
1021
header(Title) ->
 
1022
    header1(Title, "").
 
1023
header(Title, SubTitle) ->
 
1024
    header1(Title, SubTitle).
 
1025
 
 
1026
header1(Title, SubTitle) ->
 
1027
    SubTitleHTML = if SubTitle =/= "" ->
 
1028
                           ["<CENTER>\n",
 
1029
                            "<H2>" ++ SubTitle ++ "</H2>\n",
 
1030
                            "</CENTER>\n<BR>\n"];
 
1031
                      true -> "<BR>\n"
 
1032
                   end,
990
1033
    ["<!DOCTYPE HTML PUBLIC \"-//W3C//DTD HTML 3.2 Final//EN\">\n"
991
1034
     "<!-- autogenerated by '"++atom_to_list(?MODULE)++"'. -->\n"
992
1035
     "<HTML>\n",
993
1036
     "<HEAD>\n",
994
1037
 
995
 
     "<TITLE>" ++ Title ++ "</TITLE>\n",
 
1038
     "<TITLE>" ++ Title ++ " " ++ SubTitle ++ "</TITLE>\n",
996
1039
     "<META HTTP-EQUIV=\"CACHE-CONTROL\" CONTENT=\"NO-CACHE\">\n",
997
1040
 
998
1041
     "</HEAD>\n",
1004
1047
     "<CENTER>\n",
1005
1048
     "<H1>" ++ Title ++ "</H1>\n",
1006
1049
     "</CENTER>\n",
 
1050
     SubTitleHTML,
1007
1051
 
1008
1052
     "<!-- ---- CONTENT ---- -->\n"].
1009
1053
 
1013
1057
 
1014
1058
footer() ->
1015
1059
     ["<P><CENTER>\n"
1016
 
     "<HR>\n"
1017
 
     "<P><FONT SIZE=-1>\n"
1018
 
     "Copyright &copy; ", year(),
1019
 
     " <A HREF=\"http://erlang.ericsson.se\">Open Telecom Platform</A><BR>\n"
1020
 
     "Updated: <!date>", current_time(), "<!/date><BR>\n"
1021
 
     "</FONT>\n"
1022
 
     "</CENTER>\n"
1023
 
     "</body>\n"].
 
1060
      "<BR><BR>\n"
 
1061
      "<HR>\n"
 
1062
      "<P><FONT SIZE=-1>\n"
 
1063
      "Copyright &copy; ", year(),
 
1064
      " <A HREF=\"http://erlang.ericsson.se\">Open Telecom Platform</A><BR>\n"
 
1065
      "Updated: <!date>", current_time(), "<!/date><BR>\n"
 
1066
      "</FONT>\n"
 
1067
      "</CENTER>\n"
 
1068
      "</body>\n"].
1024
1069
 
1025
1070
 
1026
1071
body_tag() ->
1027
 
    "<body bgcolor=\"#FFFFFF\" text=\"#000000\" link=\"#0000FF\""
1028
 
        "vlink=\"#800080\" alink=\"#FF0000\">\n".
 
1072
    case basic_html() of
 
1073
        true ->
 
1074
            "<body bgcolor=\"#FFFFFF\" text=\"#000000\" link=\"#0000FF\" "
 
1075
                "vlink=\"#800080\" alink=\"#FF0000\">\n";
 
1076
        false ->
 
1077
            CTPath = code:lib_dir(common_test),
 
1078
            TileFile = filename:join(filename:join(CTPath,"priv"),"tile1.jpg"),
 
1079
            "<body background=\"" ++ TileFile ++ "\" bgcolor=\"#FFFFFF\" text=\"#000000\" link=\"#0000FF\" "
 
1080
                "vlink=\"#800080\" alink=\"#FF0000\">\n"
 
1081
    end.
1029
1082
 
1030
1083
current_time() ->
1031
1084
    format_time(calendar:local_time()).
1217
1270
    TotalsFile = filename:join(Dir,?totals_name),
1218
1271
    TotalsStr =
1219
1272
        case read_totals_file(TotalsFile) of
1220
 
            {Node,Logs,{TotSucc,TotFail,UserSkip,AutoSkip,NotBuilt}} ->
 
1273
            {Node,Label,Logs,{TotSucc,TotFail,UserSkip,AutoSkip,NotBuilt}} ->
1221
1274
                TotFailStr =
1222
1275
                    if TotFail > 0 ->  
1223
1276
                            ["<FONT color=\"red\">",
1263
1316
                    end,
1264
1317
                Total = TotSucc+TotFail+AllSkip,
1265
1318
                A = ["<TD ALIGN=center><FONT SIZE=-1>",Node,"</FONT></TD>\n",
 
1319
                     "<TD ALIGN=center><FONT SIZE=-1><B>",Label,"</B></FONT></TD>\n",
1266
1320
                     "<TD ALIGN=right>",NoOfTests,"</TD>\n"],
1267
1321
                B = if BasicHtml ->
1268
1322
                            ["<TD ALIGN=center><FONT SIZE=-1>",TestNamesTrunc,"</FONT></TD>\n"];
1283
1337
        end,        
1284
1338
    Index = filename:join(Dir,?index_name),
1285
1339
    ["<TR>\n"
1286
 
     "<TD><A HREF=\"",Index,"\">",timestamp(Dir),"</A>",TotalsStr,"</TD>\n"
 
1340
     "<TD><FONT SIZE=-1><A HREF=\"",Index,"\">",timestamp(Dir),"</A>",TotalsStr,"</FONT></TD>\n"
1287
1341
     "</TR>\n"].
1288
1342
 
1289
 
write_totals_file(Name,Logs,Totals) ->
 
1343
write_totals_file(Name,Label,Logs,Totals) ->
1290
1344
    AbsName = ?abs(Name),
1291
1345
    notify_and_lock_file(AbsName),
1292
1346
    force_write_file(AbsName,
1293
1347
                     term_to_binary({atom_to_list(node()),
1294
 
                                     Logs,Totals})),
 
1348
                                     Label,Logs,Totals})),
1295
1349
    notify_and_unlock_file(AbsName).
1296
1350
 
 
1351
%% this function needs to convert from old formats to new so that old
 
1352
%% test results (prev ct versions) can be listed together with new
1297
1353
read_totals_file(Name) ->
1298
1354
    AbsName = ?abs(Name),
1299
1355
    notify_and_lock_file(AbsName),
1303
1359
                case catch binary_to_term(Bin) of
1304
1360
                    {'EXIT',_Reason} ->         % corrupt file
1305
1361
                        {"-",[],undefined};
1306
 
                    R = {Node,Ls,Tot} -> 
1307
 
                        case Tot of
1308
 
                            {_,_,_,_,_} ->      % latest format
1309
 
                                R;              
1310
 
                            {TotSucc,TotFail,AllSkip,NotBuilt} ->
1311
 
                                {Node,Ls,{TotSucc,TotFail,AllSkip,undefined,NotBuilt}}
 
1362
                    {Node,Label,Ls,Tot} ->      % all info available
 
1363
                        Label1 = case Label of
 
1364
                                     undefined -> "-";
 
1365
                                     _         -> Label
 
1366
                                 end,
 
1367
                        case Tot of
 
1368
                            {_Ok,_Fail,_USkip,_ASkip,_NoBuild} ->  % latest format
 
1369
                                {Node,Label1,Ls,Tot};
 
1370
                            {TotSucc,TotFail,AllSkip,NotBuilt} ->
 
1371
                                {Node,Label1,Ls,{TotSucc,TotFail,AllSkip,undefined,NotBuilt}}
 
1372
                        end;
 
1373
                    {Node,Ls,Tot} ->            % no label found
 
1374
                        case Tot of
 
1375
                            {_Ok,_Fail,_USkip,_ASkip,_NoBuild} ->  % latest format
 
1376
                                {Node,"-",Ls,Tot};
 
1377
                            {TotSucc,TotFail,AllSkip,NotBuilt} ->
 
1378
                                {Node,"-",Ls,{TotSucc,TotFail,AllSkip,undefined,NotBuilt}}
1312
1379
                        end;
1313
1380
                    %% for backwards compatibility
1314
1381
                    {Ls,Tot}    -> {"-",Ls,Tot};
1411
1478
make_all_suites_index2(IndexName,AllSuitesLogDirs) ->
1412
1479
    {ok,Index0,_Totals} = make_all_suites_index3(AllSuitesLogDirs,
1413
1480
                                                 all_suites_index_header(),
1414
 
                                                 0, 0, 0, 0, 0),
 
1481
                                                 0, 0, 0, 0, 0, []),
1415
1482
    Index = [Index0|index_footer()],
1416
1483
    case force_write_file(IndexName, Index) of
1417
1484
        ok ->
1421
1488
    end.
1422
1489
 
1423
1490
make_all_suites_index3([{SuiteName,[LastLogDir|OldDirs]}|Rest],
1424
 
                       Result, TotSucc, TotFail, UserSkip, AutoSkip, TotNotBuilt) ->
 
1491
                       Result, TotSucc, TotFail, UserSkip, AutoSkip, TotNotBuilt,
 
1492
                       Labels) ->
1425
1493
    [EntryDir|_] = filename:split(LastLogDir),
1426
1494
    Missing = 
1427
1495
        case file:read_file(filename:join(EntryDir,?missing_suites_info)) of
1428
1496
            {ok,Bin} -> binary_to_term(Bin);
1429
1497
            _ -> []
1430
1498
        end,
1431
 
    case make_one_index_entry(SuiteName, LastLogDir, {true,OldDirs}, Missing) of
 
1499
    {Label,Labels1} =
 
1500
        case proplists:get_value(EntryDir, Labels) of
 
1501
            undefined ->
 
1502
                case read_totals_file(filename:join(EntryDir,?totals_name)) of
 
1503
                    {_,Lbl,_,_} -> {Lbl,[{EntryDir,Lbl}|Labels]};
 
1504
                    _           -> {"-",[{EntryDir,"-"}|Labels]}
 
1505
                end;
 
1506
            Lbl ->
 
1507
                {Lbl,Labels}
 
1508
        end,
 
1509
    case make_one_index_entry(SuiteName, LastLogDir, Label, {true,OldDirs}, Missing) of
1432
1510
        {Result1,Succ,Fail,USkip,ASkip,NotBuilt} ->
1433
1511
            %% for backwards compatibility
1434
1512
            AutoSkip1 = case catch AutoSkip+ASkip of
1437
1515
                        end,
1438
1516
            make_all_suites_index3(Rest, [Result|Result1], TotSucc+Succ, 
1439
1517
                                   TotFail+Fail, UserSkip+USkip, AutoSkip1,
1440
 
                                   TotNotBuilt+NotBuilt);
 
1518
                                   TotNotBuilt+NotBuilt,Labels1);
1441
1519
        error ->
1442
1520
            make_all_suites_index3(Rest, Result, TotSucc, TotFail, 
1443
 
                                   UserSkip, AutoSkip, TotNotBuilt)
 
1521
                                   UserSkip, AutoSkip, TotNotBuilt,Labels1)
1444
1522
    end;
1445
1523
make_all_suites_index3([], Result, TotSucc, TotFail, UserSkip, AutoSkip, 
1446
 
                       TotNotBuilt) ->
 
1524
                       TotNotBuilt,_) ->
1447
1525
    {ok, [Result|total_row(TotSucc, TotFail, UserSkip, AutoSkip, TotNotBuilt,true)], 
1448
1526
     {TotSucc,TotFail,UserSkip,AutoSkip,TotNotBuilt}}.
1449
1527