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

« back to all changes in this revision

Viewing changes to system/doc/efficiency_guide/bench.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
%% ``The contents of this file are subject to the Erlang Public License,
 
2
%% Version 1.1, (the "License"); you may not use this file except in
 
3
%% compliance with the License. You should have received a copy of the
 
4
%% Erlang Public License along with this software. If not, it can be
 
5
%% retrieved via the world wide web at http://www.erlang.org/.
 
6
%% 
 
7
%% Software distributed under the License is distributed on an "AS IS"
 
8
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
 
9
%% the License for the specific language governing rights and limitations
 
10
%% under the License.
 
11
%% 
 
12
%% The Initial Developer of the Original Code is Ericsson Utvecklings AB.
 
13
%% Portions created by Ericsson are Copyright 1999, Ericsson Utvecklings
 
14
%% AB. All Rights Reserved.''
 
15
%% 
 
16
%%     $Id$
 
17
%%
 
18
 
 
19
-module(bench).
 
20
 
 
21
%% User interface
 
22
-export([run/0]).
 
23
 
 
24
%% Exported to be used in spawn
 
25
-export([measure/4]).
 
26
 
 
27
%% Internal constants 
 
28
-define(MAX, 999999999999999).
 
29
-define(RANGE_MAX, 16#7ffffff).
 
30
 
 
31
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
32
%%%     Interface 
 
33
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
34
 
 
35
%%---------------------------------------------------------------------------
 
36
%% run() -> _
 
37
%%
 
38
%% Compiles and runs all benchmarks in the current directory,
 
39
%% and creates a report
 
40
%%---------------------------------------------------------------------------
 
41
run() ->
 
42
    run(compiler_options()).
 
43
 
 
44
 
 
45
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
46
%%%     Generic Benchmark functions
 
47
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
48
 
 
49
%%---------------------------------------------------------------------------
 
50
%% compiler_options() -> OptionsList
 
51
%%      OptionsList = list() - See Erlang/OTP module compile
 
52
%%---------------------------------------------------------------------------
 
53
compiler_options() ->
 
54
    [report_errors, report_warnings].
 
55
 
 
56
%%---------------------------------------------------------------------------
 
57
%% run(OptionsList) ->
 
58
%%      OptionsList = list() - See Erlang/OTP module compile
 
59
%%
 
60
%% Help function to run/0.
 
61
%%---------------------------------------------------------------------------
 
62
run(OptionsList) ->
 
63
    Bms = compile_benchmarks(OptionsList),
 
64
    run_benchmarks(Bms),
 
65
    report().
 
66
 
 
67
%%---------------------------------------------------------------------------
 
68
%% compile_benchmarks(OptionsList) -> [BmInfo| _]
 
69
%%      OptionsList = list() - See Erlang/OTP module compile
 
70
%%      BmInfo = {Module, Iterations, [BmFunctionName| _]}
 
71
%%      Module = atom()
 
72
%%      Iterations = integer()
 
73
%%      BmFunctionName = atom()
 
74
%%  
 
75
%% Compiles all benchmark modules in the current directory and
 
76
%% returns info about the benchmarks. 
 
77
%%---------------------------------------------------------------------------
 
78
compile_benchmarks(OptionsList) ->
 
79
    {ok, FilesInCurrentDir} = file:list_dir("."),
 
80
    ErlFiles = [ErlFile || ErlFile <- lists:sort(FilesInCurrentDir), 
 
81
                         lists:suffix(".erl", ErlFile)],
 
82
    lists:foldr(fun(File, BmInfoAcc) -> 
 
83
                        case lists:suffix("_bm.erl", File) of
 
84
                            true ->
 
85
                                BmInfo = bm_compile(File, OptionsList),
 
86
                                [BmInfo | BmInfoAcc];
 
87
                            false ->
 
88
                                just_compile(File, OptionsList),
 
89
                                BmInfoAcc
 
90
                        end
 
91
                end, [], ErlFiles).
 
92
    
 
93
%%---------------------------------------------------------------------------
 
94
%%  just_compile(FileName, OptionsList) -> ok
 
95
%%      FileName = string() 
 
96
%%      OptionsList = list() - See Erlang/OTP module compile
 
97
%%  
 
98
%% Compiles a support module.
 
99
%%---------------------------------------------------------------------------
 
100
just_compile(FileName, OptionsList) ->
 
101
    io:format("Compiling ~s...\n", [FileName]), % Progress info to user
 
102
    case c:c(FileName, OptionsList) of
 
103
        {ok, _Mod} ->
 
104
            ok;
 
105
        %% If compilation fails there is no point in trying to continue
 
106
        error -> 
 
107
            Reason = 
 
108
                lists:flatten(
 
109
                  io_lib:format("Could not compile file ~s", [FileName])),
 
110
            exit(self(), Reason)
 
111
    end.
 
112
%%---------------------------------------------------------------------------
 
113
%%  bm_compile(FileName, OptionsList) -> BmInfo
 
114
%%      FileName = string() 
 
115
%%      OptionsList = list() - See Erlang/OTP module compile
 
116
%%      BmInfo = {Module, Iterations, [BmFunctionName| _]}
 
117
%%      Iterations = integer()
 
118
%%      Module = atom()
 
119
%%      BmFunctionName = atom()
 
120
%%  
 
121
%% Compiles the benchmark module implemented in <FileName> and returns
 
122
%% information about the benchmark tests. 
 
123
%%---------------------------------------------------------------------------
 
124
bm_compile(FileName, OptionsList) ->
 
125
    io:format("Compiling ~s...\n", [FileName]), % Progress info to user
 
126
    case c:c(FileName, OptionsList) of
 
127
        {ok, Mod} ->
 
128
            bm_cases(Mod);
 
129
        %% If compilation fails there is no point in trying to continue
 
130
        error -> 
 
131
            Reason = 
 
132
                lists:flatten(
 
133
                  io_lib:format("Could not compile file ~s", [FileName])),
 
134
            exit(self(), Reason)
 
135
    end.
 
136
%%---------------------------------------------------------------------------
 
137
%% bm_cases(Module) -> {Module, Iter, [BmFunctionName |_]}
 
138
%%      Module = atom() 
 
139
%%      Iter = integer()
 
140
%%      BmFunctionName = atom()
 
141
%%
 
142
%% Fetches the number of iterations and the names of the benchmark
 
143
%% functions for the module <Module>. 
 
144
%%---------------------------------------------------------------------------
 
145
bm_cases(Module) ->
 
146
    case catch Module:benchmarks() of
 
147
        {Iter, BmList} when integer(Iter), list(BmList) ->
 
148
            {Module, Iter, BmList};
 
149
        %% The benchmark is incorrect implemented there is no point in
 
150
        %% trying to continue
 
151
        Other -> 
 
152
            Reason = 
 
153
                lists:flatten(
 
154
                  io_lib:format("Incorrect return value: ~p " 
 
155
                                "from ~p:benchmarks()",
 
156
                                [Other, Module])),
 
157
            exit(self(), Reason)
 
158
    end.
 
159
%%---------------------------------------------------------------------------
 
160
%% run_benchmarks(Bms) ->   
 
161
%%      Bms = [{Module, Iter, [BmFunctionName |_]} | _] 
 
162
%%      Module = atom() 
 
163
%%      Iter = integer()
 
164
%%      BmFunctionName = atom()
 
165
%%          
 
166
%% Runs all the benchmark tests described in <Bms>.
 
167
%%---------------------------------------------------------------------------
 
168
run_benchmarks(Bms) ->
 
169
    Ver = erlang:system_info(version),
 
170
    Machine = erlang:system_info(machine),
 
171
    SysInfo = {Ver,Machine},
 
172
   
 
173
    Res = [bms_run(Mod, Tests, Iter, SysInfo) || {Mod,Iter,Tests} <- Bms],
 
174
 
 
175
    %% Create an intermediate file that is later used to generate a bench
 
176
    %% mark report.
 
177
    Name = Ver ++ [$.|Machine] ++ ".bmres",
 
178
    {ok, IntermediatFile} = file:open(Name, [write]),
 
179
 
 
180
    %% Create mark that identifies version of the benchmark modules
 
181
    io:format(IntermediatFile, "~p.\n", [erlang:phash(Bms, ?RANGE_MAX)]),
 
182
    
 
183
    io:format(IntermediatFile, "~p.\n", [Res]),
 
184
    file:close(IntermediatFile).
 
185
 
 
186
%%---------------------------------------------------------------------------
 
187
%% bms_run(Module, BmTests, Iter, Info) ->  
 
188
%%      Module = atom(),
 
189
%%      BmTests = [BmFunctionName|_],
 
190
%%      BmFunctionName = atom()
 
191
%%      Iter = integer(),
 
192
%%      SysInfo = {Ver, Machine}
 
193
%%      Ver = string()
 
194
%%      Machine = string()
 
195
%%  
 
196
%% Runs all benchmark tests in module <Module>. 
 
197
%%---------------------------------------------------------------------------
 
198
bms_run(Module, BmTests, Iter, SysInfo) ->
 
199
    io:format("Running ~s:", [Module]),  % Progress info to user
 
200
    Res =
 
201
        {Module,{SysInfo,[{Bm, bm_run(Module, Bm, Iter)} || Bm <- BmTests]}},
 
202
    io:nl(),
 
203
    Res.
 
204
%%---------------------------------------------------------------------------
 
205
%% bm_run(Module, BmTest, Iter) -> Elapsed
 
206
%%      Module = atom(),
 
207
%%      BmTest = atom(),
 
208
%%      Iter = integer()
 
209
%%      Elapsed = integer()  - elapsed time in milliseconds.
 
210
%%  
 
211
%% Runs the benchmark Module:BmTest(Iter)  
 
212
%%---------------------------------------------------------------------------
 
213
bm_run(Module, BmTest, Iter) ->
 
214
    io:format(" ~s", [BmTest]),  % Progress info to user
 
215
    spawn_link(?MODULE, measure, [self(), Module, BmTest, Iter]),
 
216
    receive
 
217
        {Elapsed, ok} ->
 
218
            Elapsed;
 
219
        {_Elapsed, Fault} ->
 
220
            io:nl(),
 
221
            Reason = 
 
222
                lists:flatten(
 
223
                  io_lib:format("~w", [Fault])),
 
224
            exit(self(), Reason)
 
225
    end.
 
226
%%---------------------------------------------------------------------------
 
227
%% measure(Parent, Module, BmTest, Iter) -> _ 
 
228
%%      Parent = pid(),
 
229
%%      Module = atom(),
 
230
%%      BmTest = atom(),
 
231
%%      Iter = integer()
 
232
%%
 
233
%% Measures the time it take to execute Module:Bm(Iter)  
 
234
%% and send the result to <Parent>.
 
235
%%---------------------------------------------------------------------------
 
236
measure(Parent, Module, BmTest, Iter) ->
 
237
    statistics(runtime),
 
238
    Res = (catch apply(Module, BmTest, [Iter])), 
 
239
    {_TotalRunTime, TimeSinceLastCall} = statistics(runtime),
 
240
    Parent ! {TimeSinceLastCall, Res}.
 
241
    
 
242
 
 
243
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
244
%%%     Report functions
 
245
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
246
 
 
247
%%---------------------------------------------------------------------------
 
248
%% report() -> _
 
249
%%  
 
250
%% Creates a report of the bench marking test that appeals to a human.
 
251
%% Currently this means creating a html-file. (Other formats could be added) 
 
252
%%---------------------------------------------------------------------------
 
253
report() ->
 
254
    {ok, AllFiles} = file:list_dir("."),
 
255
    BmResultFiles = [File || File <- AllFiles, lists:suffix(".bmres", File)],
 
256
 
 
257
    Results = fetch_bmres_data(BmResultFiles),
 
258
    create_report(Results).
 
259
 
 
260
%%---------------------------------------------------------------------------
 
261
%% fetch_bmres_data(BmResultFiles) -> Results 
 
262
%%      BmResultFiles = [FileName | _]
 
263
%%      FileName = string()
 
264
%%      Results = [[{Bm, Res} | _]]
 
265
%%      Bm   =  atom() - Name of benchmark module
 
266
%%      Res  = [{VersionInfo, [{Test, Time} | _]}]
 
267
%%      VersionInfo = {Ver, Machine}
 
268
%%      Ver = string()
 
269
%%      Machine = string()
 
270
%%      Test = atom()
 
271
%%      Time = integer()
 
272
%%
 
273
%% Reads result data from intermediate files
 
274
%%---------------------------------------------------------------------------
 
275
fetch_bmres_data(BmResultFiles) ->
 
276
    fetch_bmres_data(BmResultFiles, [], undefined).
 
277
 
 
278
%%---------------------------------------------------------------------------
 
279
%% fetch_bmres_data(BmResultFiles, AccResData, Check) -> Results 
 
280
%%      BmResultFiles = [FileName | _]
 
281
%%      FileName = string()
 
282
%%      AccResData = see Results fetch_bmres_data/1
 
283
%%      Check = integer() | undefined (first time)
 
284
%%
 
285
%% Help function to fetch_bmres_data/1
 
286
%%---------------------------------------------------------------------------
 
287
fetch_bmres_data([], AccResData, _Check) ->
 
288
    AccResData;
 
289
 
 
290
fetch_bmres_data([Name | BmResultFiles], AccResData, Check) ->
 
291
    {DataList, NewCheck} = read_bmres_file(Name, Check),
 
292
    fetch_bmres_data(BmResultFiles, [DataList| AccResData], NewCheck).
 
293
 
 
294
%%---------------------------------------------------------------------------
 
295
%% read_bmres_file(Name, Check) -> 
 
296
%%      Name = string()  
 
297
%%      Check = integer() | undefined  
 
298
%%
 
299
%%  Reads the data from the result files. Checks that all result
 
300
%%  files where created with the same set of tests.
 
301
%%---------------------------------------------------------------------------
 
302
read_bmres_file(Name, Check) ->
 
303
    case file:consult(Name) of
 
304
        {ok, [Check1, List]} when Check =:= undefined, integer(Check1) ->
 
305
            {List, Check1};
 
306
        {ok, [Check, List]} when integer(Check) ->
 
307
            {List, Check};
 
308
        {ok, [Check1, _List]} when integer(Check1) ->
 
309
            Reason = 
 
310
                lists:flatten(
 
311
                  io_lib:format("Different test setup, remove old setup "
 
312
                                "result by removing *.bmres files and "
 
313
                                "try again", [])),
 
314
            exit(self(), Reason); 
 
315
        {error, Reason} when atom(Reason) ->
 
316
            exit(self(), Reason); 
 
317
        {error, Reason} ->
 
318
            exit(self(), file:format(Reason))
 
319
    end.
 
320
 
 
321
%%---------------------------------------------------------------------------
 
322
%% create_report(Results) ->
 
323
%%      Results =  see Results fetch_bmres_data/1
 
324
%%  
 
325
%%  Organizes <Result> so it will be right for create_html_report/1  
 
326
%%  i.e. group results for the same benchmark test, run on different versions
 
327
%%  of erlang.
 
328
%%---------------------------------------------------------------------------
 
329
create_report(Results) -> 
 
330
    Dictionary = 
 
331
        lists:foldl(fun(BmResultList, Dict0) ->
 
332
                            lists:foldl(fun({Bm, VerResult}, Dict1) ->
 
333
                                                dict:append(Bm, VerResult, 
 
334
                                                            Dict1) 
 
335
                                        end,Dict0, BmResultList) 
 
336
                    end,
 
337
                    dict:new(), Results),
 
338
 
 
339
    create_html_report(dict:to_list(Dictionary)).
 
340
%%---------------------------------------------------------------------------
 
341
%%  create_html_report(ResultList) -> _
 
342
%%      ResultList = [{Bm, Res} | _]
 
343
%%      Bm   =  atom() - Name of benchmark module
 
344
%%      Res  = [{VersionInfo, [{Test, Time} | _]} | _] 
 
345
%%      VersionInfo = {Ver, Machine}
 
346
%%      Ver = string()
 
347
%%      Machine = string()
 
348
%%      Test = atom()
 
349
%%      Time = integer()
 
350
%%
 
351
%% Writes the result to an html-file 
 
352
%%---------------------------------------------------------------------------
 
353
create_html_report(ResultList) ->
 
354
 
 
355
    {ok, OutputFile} = file:open("index.html", [write]),
 
356
 
 
357
    %% Create the begining of the result html-file.
 
358
    Head = Title = "Benchmark Results",
 
359
    io:put_chars(OutputFile, "<html>\n"),
 
360
    io:put_chars(OutputFile, "<head>\n"),
 
361
    io:format(OutputFile, "<title>~s</title>\n", [Title]),
 
362
    io:put_chars(OutputFile, "</head>\n"),
 
363
    io:put_chars(OutputFile, "<body bgcolor=\"#FFFFFF\" text=\"#000000\"" ++
 
364
                 " link=\"#0000FF\" vlink=\"#800080\" alink=\"#FF0000\">\n"),
 
365
    io:format(OutputFile, "<h1>~s</h1>\n", [Head]),
 
366
 
 
367
    %% Add the result tables
 
368
    lists:foreach(fun(Element) -> 
 
369
                          create_html_table(OutputFile, Element) end,
 
370
                  ResultList),
 
371
 
 
372
    %% Put in the end-html tags
 
373
    io:put_chars(OutputFile, "</body>\n"),
 
374
    io:put_chars(OutputFile, "</html>\n"),
 
375
    
 
376
    file:close(OutputFile).
 
377
 
 
378
%%---------------------------------------------------------------------------
 
379
%% create_html_table(File, {Bm, Res}) -> _
 
380
%%      File = file() - html file to write data to. 
 
381
%%      Bm  = atom() - Name of benchmark module
 
382
%%      Res = [{VersionInfo, [{Test, Time} | _]}]
 
383
%%      VersionInfo = {Ver, Machine}
 
384
%%      Ver = string()
 
385
%%      Machine = string()
 
386
%%      Test = atom()
 
387
%%      Time = integer()
 
388
%%
 
389
%% Creates a html table that displays the result of the benchmark <Bm>.
 
390
%%---------------------------------------------------------------------------
 
391
create_html_table(File, {Bm, Res}) ->
 
392
 
 
393
    {MinTime, Order} = min_time_and_sort(Res),  
 
394
        
 
395
    io:format(File, "<h2>~s</h2>\n" , [Bm]),
 
396
    
 
397
    %% Fun that calculates relative measure values and puts them in 
 
398
    %% a dictionary
 
399
    RelativeMesureFun =  fun({TestName, Time}, Dict1) ->
 
400
                                 dict:append(TestName, Time/MinTime, Dict1) 
 
401
                         end,
 
402
 
 
403
    %% For all erlang versions that the benchmark tests has been run, 
 
404
    %% calculate the relative measure values and put them in a dictionary.
 
405
    ResultDict = 
 
406
        lists:foldl(fun({_VerInfo, Bms}, Dict0) ->
 
407
                            lists:foldl(RelativeMesureFun, Dict0, Bms) end,
 
408
                    dict:new(), Res),
 
409
 
 
410
    %% Create the table and its headings
 
411
    io:put_chars(File, "<table border=0 cellpadding=1><tr>"
 
412
                 "<td bgcolor=\"#000000\">\n"),
 
413
    io:put_chars(File, "<table cellpadding=3 border=0 cellspacing=1>\n"),
 
414
    io:put_chars(File, "<tr bgcolor=white>"),
 
415
    io:put_chars(File, "<td>Test</td>"),
 
416
    Heads = table_headers(Res),
 
417
    lists:foreach(fun({Ver,Machine}) -> io:format(File, "<td>~s<br>~s</td>",
 
418
                                                  [Ver,Machine]) end, Heads),
 
419
    io:put_chars(File, "</tr>\n"),
 
420
    
 
421
    %% Create table rows
 
422
    lists:foreach(fun(Name) -> 
 
423
                          create_html_row(File, Name, ResultDict) 
 
424
                  end, Order),
 
425
 
 
426
    %% Tabel end-tags
 
427
    io:put_chars(File, "</table></td></tr></table>\n"),
 
428
    
 
429
    %% Create link to benchmark source code
 
430
    io:format(File, "<p><a href=\"~s.erl\">Source for ~s.erl</a>\n",
 
431
              [Bm,Bm]).
 
432
 
 
433
%%---------------------------------------------------------------------------
 
434
%% create_html_row(File, Name, Dict) -> _
 
435
%%      File = file() - html file to write data to. 
 
436
%%      Name = atom() - Name of benchmark test 
 
437
%%      Dict = dict() - Dictonary where the relative time measures for 
 
438
%%      the test can be found.
 
439
%%
 
440
%% Creates an actual html table-row.
 
441
%%---------------------------------------------------------------------------
 
442
create_html_row(File, Name, Dict) ->
 
443
    ReletiveTimes = dict:fetch(Name, Dict),
 
444
    io:put_chars(File, "<tr bgcolor=white>\n"),
 
445
    io:format(File, "<td>~s</td>", [Name]),
 
446
    lists:foreach(fun(Time) -> 
 
447
                          io:format(File, "<td>~-8.2f</td>", [Time]) end, 
 
448
                  ReletiveTimes),
 
449
    io:put_chars(File, "</tr>\n").
 
450
 
 
451
%%---------------------------------------------------------------------------
 
452
%% min_time_and_sort(ResultList) -> {MinTime, Order}
 
453
%%      ResultList = [{VersionInfo, [{Test, Time} | _]}] 
 
454
%%      MinTime = integer() - The execution time of the fastes test 
 
455
%%      Order = [BmFunctionName|_] - the order of the testcases in
 
456
%%      increasing execution time.
 
457
%%      BmFunctionName = atom()   
 
458
%%---------------------------------------------------------------------------
 
459
min_time_and_sort(ResultList) ->
 
460
    
 
461
    %% Use the results from the run on the highest version
 
462
    %% of Erlang as norm.
 
463
    {_, TestRes} = 
 
464
        lists:foldl(fun ({{Ver, _}, ResList}, 
 
465
                         {CurrentVer, _}) when Ver > CurrentVer ->
 
466
                            {Ver, ResList};
 
467
                        (_, VerAndRes) ->
 
468
                            VerAndRes
 
469
                    end, {"0", []}, ResultList),
 
470
    
 
471
    {lists:foldl(fun ({_, Time0}, Min1) when Time0 < Min1 -> 
 
472
                         Time0;
 
473
                     (_, Min1) -> 
 
474
                         Min1
 
475
                 end, ?MAX, TestRes),
 
476
     [Name || {Name, _} <- lists:keysort(2, TestRes)]}.
 
477
 
 
478
%%---------------------------------------------------------------------------
 
479
%% table_headers(VerResultList) -> SysInfo
 
480
%%      VerResultList = [{{Ver, Machine},[{BmFunctionName, Time}]} | _]
 
481
%%      Ver = string()
 
482
%%      Machine = string()
 
483
%%      BmFunctionName = atom()
 
484
%%      Time = integer() 
 
485
%%      SysInfo = {Ver, Machine}
 
486
%%---------------------------------------------------------------------------
 
487
table_headers(VerResultList) ->
 
488
    [SysInfo || {SysInfo, _} <- VerResultList].