~statik/ubuntu/maverick/erlang/erlang-merge-testing

« back to all changes in this revision

Viewing changes to lib/hipe/tools/hipe_timer.erl

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-05-01 10:14:38 UTC
  • mfrom: (3.1.4 sid)
  • Revision ID: james.westby@ubuntu.com-20090501101438-6qlr6rsdxgyzrg2z
Tags: 1:13.b-dfsg-2
* Cleaned up patches: removed unneeded patch which helped to support
  different SCTP library versions, made sure that changes for m68k
  architecture applied only when building on this architecture.
* Removed duplicated information from binary packages descriptions.
* Don't require libsctp-dev build-dependency on solaris-i386 architecture
  which allows to build Erlang on Nexenta (thanks to Tim Spriggs for
  the suggestion).

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
1
%% -*- erlang-indent-level: 2 -*-
 
2
%%
 
3
%% %CopyrightBegin%
 
4
%% 
 
5
%% Copyright Ericsson AB 2002-2009. All Rights Reserved.
 
6
%% 
 
7
%% The contents of this file are subject to the Erlang Public License,
 
8
%% Version 1.1, (the "License"); you may not use this file except in
 
9
%% compliance with the License. You should have received a copy of the
 
10
%% Erlang Public License along with this software. If not, it can be
 
11
%% retrieved online at http://www.erlang.org/.
 
12
%% 
 
13
%% Software distributed under the License is distributed on an "AS IS"
 
14
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
 
15
%% the License for the specific language governing rights and limitations
 
16
%% under the License.
 
17
%% 
 
18
%% %CopyrightEnd%
 
19
%%
2
20
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
3
21
%% Copyright (c) 2001 by Erik Johansson.  All Rights Reserved 
4
22
%% Time-stamp: <2008-04-20 14:53:36 richard>
5
23
%% ====================================================================
6
 
%%  Filename :  hipe_timer.erl
7
24
%%  Module   :  hipe_timer
8
25
%%  Purpose  :  
9
26
%%  Notes    : 
10
 
%%  History  :  * 2001-03-15 Erik Johansson (happi@it.uu.se): 
11
 
%%               Created.
12
 
%%  CVS      :
13
 
%%              $Author: kostis $
14
 
%%              $Date: 2008/07/20 19:43:04 $
15
 
%%              $Revision: 1.5 $
 
27
%%  History  :  * 2001-03-15 Erik Johansson (happi@it.uu.se): Created.
16
28
%% ====================================================================
17
29
%%  Exports  :
18
30
%%
20
32
 
21
33
-module(hipe_timer).
22
34
 
23
 
-export([tr/1,t/1,timer/1,time/1,empty_time/0]).
 
35
-export([tr/1, t/1, timer/1, time/1, empty_time/0]).
24
36
-export([advanced/2]).
25
37
 
26
38
t(F) ->
59
71
advanced(_Fun, I) when I < 2 -> false;
60
72
advanced(Fun, Iterations) ->
61
73
  R = Fun(),
62
 
  Measurements = [t(Fun) || _ <- lists:seq(1,Iterations)],
 
74
  Measurements = [t(Fun) || _ <- lists:seq(1, Iterations)],
63
75
  {Wallclock, RunTime} = split(Measurements),
64
 
  WMin = min(Wallclock),
65
 
  RMin = min(RunTime),
66
 
  WMax = max(Wallclock),
67
 
  RMax = max(RunTime),
 
76
  WMin = lists:min(Wallclock),
 
77
  RMin = lists:min(RunTime),
 
78
  WMax = lists:max(Wallclock),
 
79
  RMax = lists:max(RunTime),
68
80
  WMean = mean(Wallclock),
69
81
  RMean = mean(RunTime),
70
82
  WMedian = median(Wallclock),
77
89
  RVarCoff = 100 * RStddev / RMean,
78
90
  WSum = lists:sum(Wallclock),
79
91
  RSum = lists:sum(RunTime),
80
 
  [{wallclock,[{min,WMin},
81
 
               {max,WMax},
82
 
               {mean,WMean},
83
 
               {median,WMedian},
84
 
               {variance,WVariance},
85
 
               {stdev,WStddev},
 
92
  [{wallclock,[{min, WMin},
 
93
               {max, WMax},
 
94
               {mean, WMean},
 
95
               {median, WMedian},
 
96
               {variance, WVariance},
 
97
               {stdev, WStddev},
86
98
               {varcoff, WVarCoff},
87
99
               {sum, WSum},
88
 
               {values,Wallclock}              
89
 
              ]},
90
 
   {runtime,[{min,RMin},
91
 
             {max,RMax},
92
 
             {mean,RMean},
93
 
             {median,RMedian},
94
 
             {variance,RVariance},
95
 
             {stdev,RStddev},
 
100
               {values, Wallclock}]},
 
101
   {runtime,[{min, RMin},
 
102
             {max, RMax},
 
103
             {mean, RMean},
 
104
             {median, RMedian},
 
105
             {variance, RVariance},
 
106
             {stdev, RStddev},
96
107
             {varcoff, RVarCoff},
97
108
             {sum, RSum},
98
 
             {values,RunTime}          
99
 
            ]},
 
109
             {values, RunTime}]},
100
110
   {iterations, Iterations},
101
 
   {result,R}
102
 
  ].
103
 
 
104
 
min([V|Vs]) ->
105
 
  min(Vs,V).
106
 
min([V|Vs], Min) when V >= Min ->
107
 
  min(Vs,Min);
108
 
min([V|Vs], _) ->
109
 
  min(Vs, V);
110
 
min([],Min) -> Min.
111
 
 
112
 
max([V|Vs]) ->
113
 
  max(Vs,V).
114
 
max([V|Vs], Max) when V =< Max ->
115
 
  max(Vs,Max);
116
 
max([V|Vs], _) ->
117
 
  max(Vs, V);
118
 
max([],Max) -> Max.
 
111
   {result, R}].
119
112
 
120
113
split(M) -> 
121
 
  split(M,[],[]).
 
114
  split(M, [], []).
122
115
 
123
116
split([{W,R}|More], AccW, AccR) ->
124
117
  split(More, [W|AccW], [R|AccR]);
125
 
split([],AccW, AccR) ->
 
118
split([], AccW, AccR) ->
126
119
  {AccW, AccR}.
127
120
 
128
121
mean(L) ->
129
 
  mean(L,0,0).
 
122
  mean(L, 0, 0).
130
123
 
131
124
mean([V|Vs], No, Sum) ->
132
 
  mean(Vs,No+1,Sum+V);
 
125
  mean(Vs, No+1, Sum+V);
133
126
mean([], No, Sum) when No > 0 ->
134
127
  Sum/No;
135
128
mean([], _No, _Sum) ->
140
133
  SL = lists:sort(L),
141
134
  case even(S) of
142
135
    true ->
143
 
      (lists:nth((S div 2),SL) +
144
 
       lists:nth((S div 2)+1,SL)) / 2;
 
136
      (lists:nth((S div 2), SL) + lists:nth((S div 2) + 1, SL)) / 2;
145
137
    false ->
146
 
       lists:nth((S div 2),SL)
 
138
      lists:nth((S div 2), SL)
147
139
  end.
148
140
 
149
141
even(S) ->