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

« back to all changes in this revision

Viewing changes to erts/emulator/test/statistics_SUITE.erl

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2010-03-09 17:34:57 UTC
  • mfrom: (10.1.2 sid)
  • Revision ID: james.westby@ubuntu.com-20100309173457-4yd6hlcb2osfhx31
Tags: 1:13.b.4-dfsg-3
Manpages in section 1 are needed even if only arch-dependent packages are
built. So, re-enabled them.

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
1
%%
2
2
%% %CopyrightBegin%
3
 
%% 
4
 
%% Copyright Ericsson AB 1997-2009. All Rights Reserved.
5
 
%% 
 
3
%%
 
4
%% Copyright Ericsson AB 1997-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
 
25
25
         init_per_testcase/2,
26
26
         fin_per_testcase/2,
27
27
         wall_clock/1, wall_clock_zero_diff/1, wall_clock_update/1,
28
 
         runtime/1, runtime_zero_diff/1, runtime_zero_update/1,
 
28
         runtime/1, runtime_zero_diff/1,
29
29
         runtime_update/1, runtime_diff/1,
30
30
         run_queue/1, run_queue_one/1,
31
31
         reductions/1, reductions_big/1, garbage_collection/1, io/1,
99
99
 
100
100
%%% Test statistics(runtime).
101
101
 
102
 
runtime(suite) -> [runtime_zero_diff, runtime_zero_update, runtime_update,
103
 
                   runtime_diff].
 
102
runtime(suite) -> [runtime_zero_diff, runtime_update, runtime_diff].
104
103
 
105
104
runtime_zero_diff(doc) ->
106
105
    "Tests that the difference between the times returned from two consectuitive "
117
116
runtime_zero_diff1(0) ->
118
117
    ?line test_server:fail("statistics(runtime) never returned zero difference").
119
118
 
120
 
runtime_zero_update(doc) ->
121
 
    "Test that the time differences returned by two calls to "
122
 
    "statistics(runtime) several seconds apart is zero.";
123
 
runtime_zero_update(Config) when is_list(Config) ->
124
 
    case ?t:is_debug() of
125
 
        false -> ?line runtime_zero_update1(6);
126
 
        true -> {skip,"Unreliable in DEBUG build"}
127
 
    end.
128
 
 
129
 
runtime_zero_update1(N) when N > 0 ->
130
 
    ?line {T1, _} = statistics(runtime),
131
 
    ?line receive after 7000 -> ok end,
132
 
    ?line case statistics(runtime) of
133
 
              {T, Td} when Td =< 80 ->
134
 
                  test_server:format("ok, Runtime before: {~p, _} after: {~p, ~p}",
135
 
                                     [T1, T, Td]),
136
 
                  ok;
137
 
              {T, R} ->
138
 
                  test_server:format("nok, Runtime before: {~p, _} after: {~p, ~p}", 
139
 
                                     [T1, T, R]),
140
 
                  runtime_zero_update1(N-1)
141
 
          end;
142
 
runtime_zero_update1(0) ->
143
 
    ?line test_server:fail("statistics(runtime) never returned zero difference").
144
 
 
145
119
runtime_update(doc) ->
146
 
    "Test that the statistics(runtime) returns a substanstially updated difference "
147
 
    "after running a process that takes all CPU power of the Erlang process "
148
 
    "for a second.";
 
120
    "Test that the statistics(runtime) returns a substanstially "
 
121
        "updated difference after running a process that takes all CPU "
 
122
        " power of the Erlang process for a second.";
149
123
runtime_update(Config) when is_list(Config) ->
150
124
    case ?t:is_cover() of
151
125
        false ->
152
126
            ?line process_flag(priority, high),
153
 
            ?line test_server:m_out_of_n(1, 10, fun runtime_update/0);
 
127
            do_runtime_update(10);
154
128
        true ->
155
129
            {skip,"Cover-compiled"}
156
130
    end.
157
131
 
158
 
runtime_update() ->
159
 
    ?line {T1,_} = statistics(runtime),
 
132
do_runtime_update(0) ->
 
133
    {comment,"Never close enough"};
 
134
do_runtime_update(N) ->
 
135
    ?line {T1,Diff0} = statistics(runtime),
160
136
    ?line spawn_link(fun cpu_heavy/0),
161
137
    receive after 1000 -> ok end,
162
138
    ?line {T2,Diff} = statistics(runtime),
163
 
    ?line Delta = abs(Diff-1000),
164
 
    ?line test_server:format("T1 = ~p, T2 = ~p, Diff = ~p, abs(Diff-1000) = ~p",
165
 
                             [T1,T2,Diff,Delta]),
 
139
    ?line true = is_integer(T1+T2+Diff0+Diff),
 
140
    ?line test_server:format("T1 = ~p, T2 = ~p, Diff = ~p, T2-T1 = ~p",
 
141
                             [T1,T2,Diff,T2-T1]),
166
142
    ?line if
167
 
              abs(Diff-1000) =:= Delta, Delta =< 100 ->
168
 
                  ok
 
143
              T2 - T1 =:= Diff, 900 =< Diff, Diff =< 1500 -> ok;
 
144
              true -> do_runtime_update(N-1)
169
145
          end.
170
146
    
171
147
cpu_heavy() ->
212
188
    %% 300 * 4 is more than CONTEXT_REDS (1000).  Thus, there will be one or
213
189
    %% more context switches.
214
190
 
215
 
    reductions(300, Reductions).
 
191
    Mask = (1 bsl erlang:system_info(wordsize)*8) - 1,
 
192
    reductions(300, Reductions, Mask).
216
193
 
217
 
reductions(N, Previous) when N > 0 ->
 
194
reductions(N, Previous, Mask) when N > 0 ->
218
195
    ?line {Reductions, Diff} = statistics(reductions),
219
196
    ?line build_some_garbage(),
220
197
    ?line if Reductions > 0 -> ok end,
221
198
    ?line if Diff >= 0 -> ok end,
222
199
    io:format("Previous = ~p, Reductions = ~p, Diff = ~p, DiffShouldBe = ~p",
223
 
              [Previous, Reductions, Diff, Reductions-Previous]),
224
 
    ?line if Reductions == Previous+Diff -> reductions(N-1, Reductions) end;
225
 
reductions(0, _) ->
 
200
              [Previous, Reductions, Diff, (Reductions-Previous) band Mask]),
 
201
    ?line if Reductions == ((Previous+Diff) band Mask) -> reductions(N-1, Reductions, Mask) end;
 
202
reductions(0, _, _) ->
226
203
    ok.
227
204
 
228
205
build_some_garbage() ->