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

« back to all changes in this revision

Viewing changes to lib/os_mon/test/cpu_sup_SUITE.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
%%
 
2
%% %CopyrightBegin%
 
3
%%
 
4
%% Copyright Ericsson AB 2002-2011. All Rights Reserved.
 
5
%%
 
6
%% The contents of this file are subject to the Erlang Public License,
 
7
%% Version 1.1, (the "License"); you may not use this file except in
 
8
%% compliance with the License. You should have received a copy of the
 
9
%% Erlang Public License along with this software. If not, it can be
 
10
%% retrieved online at http://www.erlang.org/.
 
11
%%
 
12
%% Software distributed under the License is distributed on an "AS IS"
 
13
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
 
14
%% the License for the specific language governing rights and limitations
 
15
%% under the License.
 
16
%%
 
17
%% %CopyrightEnd%
 
18
%%
 
19
-module(cpu_sup_SUITE).
 
20
-include_lib("test_server/include/test_server.hrl").
 
21
 
 
22
%% Test server specific exports
 
23
-export([all/0, suite/0,groups/0,init_per_group/2,end_per_group/2]).
 
24
-export([init_per_suite/1, end_per_suite/1]).
 
25
-export([init_per_testcase/2, end_per_testcase/2]).
 
26
 
 
27
%% Test cases
 
28
-export([load_api/1]).
 
29
-export([util_api/1, util_values/1]).
 
30
-export([port/1]).
 
31
-export([terminate/1, unavailable/1, restart/1]).
 
32
 
 
33
%% Default timetrap timeout (set in init_per_testcase)
 
34
-define(default_timeout, ?t:minutes(1)).
 
35
 
 
36
init_per_suite(Config) when is_list(Config) ->
 
37
    ?line ok = application:start(os_mon),
 
38
    Config.
 
39
 
 
40
end_per_suite(Config) when is_list(Config) ->
 
41
    ?line ok = application:stop(os_mon),
 
42
    Config.
 
43
 
 
44
init_per_testcase(unavailable, Config) ->
 
45
    terminate(Config),
 
46
    init_per_testcase(dummy, Config);
 
47
init_per_testcase(_Case, Config) ->
 
48
    Dog = ?t:timetrap(?default_timeout),
 
49
    [{watchdog, Dog} | Config].
 
50
 
 
51
end_per_testcase(unavailable, Config) ->
 
52
    restart(Config),
 
53
    end_per_testcase(dummy, Config);
 
54
end_per_testcase(_Case, Config) ->
 
55
    Dog = ?config(watchdog, Config),
 
56
    ?t:timetrap_cancel(Dog),
 
57
    ok.
 
58
 
 
59
suite() -> [{ct_hooks,[ts_install_cth]}].
 
60
 
 
61
all() -> 
 
62
    case test_server:os_type() of
 
63
        {unix, sunos} ->
 
64
            [load_api, util_api, util_values, port, unavailable];
 
65
        {unix, linux} ->
 
66
            [load_api, util_api, util_values, port, unavailable];
 
67
        {unix, _OSname} -> [load_api];
 
68
        _OS -> [unavailable]
 
69
    end.
 
70
 
 
71
groups() -> 
 
72
    [].
 
73
 
 
74
init_per_group(_GroupName, Config) ->
 
75
    Config.
 
76
 
 
77
end_per_group(_GroupName, Config) ->
 
78
    Config.
 
79
 
 
80
 
 
81
load_api(suite) ->
 
82
    [];
 
83
load_api(doc) ->
 
84
    ["Test of load API functions"];
 
85
load_api(Config) when is_list(Config) ->
 
86
 
 
87
    %% nprocs()
 
88
    ?line N = cpu_sup:nprocs(),
 
89
    ?line true = is_integer(N),
 
90
    ?line true = N>0,
 
91
 
 
92
    %% avg1()
 
93
    ?line Load1 = cpu_sup:avg1(),
 
94
    ?line true = is_integer(Load1),
 
95
    ?line true = Load1>0,
 
96
 
 
97
    %% avg5()
 
98
    ?line Load5 = cpu_sup:avg5(),
 
99
    ?line true = is_integer(Load5),
 
100
    ?line true = Load5>0,
 
101
 
 
102
    %% avg15()
 
103
    ?line Load15 = cpu_sup:avg15(),
 
104
    ?line true = is_integer(Load15),
 
105
    ?line true = Load15>0,
 
106
 
 
107
    ok.
 
108
 
 
109
util_api(suite) ->
 
110
    [];
 
111
util_api(doc) ->
 
112
    ["Test of utilization API functions"];
 
113
util_api(Config) when is_list(Config) ->
 
114
    %% Some useful funs when testing util/1
 
115
    BusyP = fun({user, _Share}) -> true;
 
116
               ({nice_user, _Share}) -> true;
 
117
               ({kernel, _Share}) -> true;
 
118
               ({hard_irq, _Share}) -> true;
 
119
               ({soft_irq, _Share}) -> true;
 
120
               (_) -> false
 
121
            end,
 
122
    NonBusyP = fun({wait, _Share}) -> true;
 
123
                  ({idle, _Share}) -> true;
 
124
                  ({steal, _Share}) -> true;
 
125
                  (_) -> false
 
126
               end,
 
127
    Sum = fun({_Tag, X}, Acc) -> Acc+X end,
 
128
 
 
129
    %% util()
 
130
    ?line Util1 = cpu_sup:util(),
 
131
    ?line true = is_number(Util1),
 
132
    ?line true = Util1>0,
 
133
    ?line Util2 = cpu_sup:util(),
 
134
    ?line true = is_number(Util2),
 
135
    ?line true = Util2>0,
 
136
 
 
137
    %% util([])
 
138
    ?line {all, Busy1, NonBusy1, []} = cpu_sup:util([]),
 
139
    ?line 100.00 = Busy1 + NonBusy1,
 
140
 
 
141
    %% util([detailed])
 
142
    ?line {Cpus2, Busy2, NonBusy2, []} = cpu_sup:util([detailed]),
 
143
    ?line true = lists:all(fun(X) -> is_integer(X) end, Cpus2),
 
144
    ?line true = lists:all(BusyP, Busy2),
 
145
    ?line true = lists:all(NonBusyP, NonBusy2),
 
146
    ?line 100.00 = lists:foldl(Sum,0,Busy2)+lists:foldl(Sum,0,NonBusy2),
 
147
 
 
148
    %% util([per_cpu])
 
149
    ?line [{Cpu3, Busy3, NonBusy3, []}|_] = cpu_sup:util([per_cpu]),
 
150
    ?line true = is_integer(Cpu3),
 
151
    ?line 100.00 = Busy3 + NonBusy3,
 
152
 
 
153
    %% util([detailed, per_cpu])
 
154
    ?line [{Cpu4, Busy4, NonBusy4, []}|_] =
 
155
        cpu_sup:util([detailed, per_cpu]),
 
156
    ?line true = is_integer(Cpu4),
 
157
    ?line true = lists:all(BusyP, Busy2),
 
158
    ?line true = lists:all(NonBusyP, NonBusy2),
 
159
    ?line 100.00 = lists:foldl(Sum,0,Busy4)+lists:foldl(Sum,0,NonBusy4),
 
160
 
 
161
    %% bad util/1 calls
 
162
    ?line {'EXIT',{badarg,_}} = (catch cpu_sup:util(detailed)),
 
163
    ?line {'EXIT',{badarg,_}} = (catch cpu_sup:util([detialed])),
 
164
 
 
165
    ok.
 
166
 
 
167
-define(SPIN_TIME, 1000).
 
168
 
 
169
util_values(suite) ->
 
170
    [];
 
171
util_values(doc) ->
 
172
    ["Test utilization values"];
 
173
util_values(Config) when is_list(Config) ->
 
174
 
 
175
    Tester = self(),
 
176
    Ref = make_ref(),
 
177
    Loop = fun (L) -> L(L) end,
 
178
    Spinner = fun () ->
 
179
                      Looper = spawn_link(fun () -> Loop(Loop) end),
 
180
                      receive after ?SPIN_TIME -> ok end,
 
181
                      unlink(Looper),
 
182
                      exit(Looper, kill),
 
183
                      Tester ! Ref
 
184
              end,
 
185
 
 
186
    ?line cpu_sup:util(),
 
187
 
 
188
    ?line spawn_link(Spinner),
 
189
    ?line receive Ref -> ok end,
 
190
    ?line HighUtil1 = cpu_sup:util(),
 
191
 
 
192
    ?line receive after ?SPIN_TIME -> ok end,
 
193
    ?line LowUtil1 = cpu_sup:util(),
 
194
 
 
195
    ?line spawn_link(Spinner),
 
196
    ?line receive Ref -> ok end,
 
197
    ?line HighUtil2 = cpu_sup:util(),
 
198
 
 
199
    ?line receive after ?SPIN_TIME -> ok end,
 
200
    ?line LowUtil2 = cpu_sup:util(),
 
201
 
 
202
    Utils = [{high1,HighUtil1}, {low1,LowUtil1},
 
203
             {high2,HighUtil2}, {low2,LowUtil2}],
 
204
    ?t:format("Utils: ~p~n", [Utils]),
 
205
 
 
206
    ?line false = LowUtil1 > HighUtil1,
 
207
    ?line false = LowUtil1 > HighUtil2,
 
208
    ?line false = LowUtil2 > HighUtil1,
 
209
    ?line false = LowUtil2 > HighUtil2,
 
210
 
 
211
    ok.
 
212
 
 
213
 
 
214
% Outdated
 
215
% The portprogram is now restarted if killed, and not by os_mon...
 
216
 
 
217
port(suite) ->
 
218
    [];
 
219
port(doc) ->
 
220
    ["Test that cpu_sup handles a terminating port program"];
 
221
port(Config) when is_list(Config) ->
 
222
    case cpu_sup_os_pid() of
 
223
        {ok, PidStr} ->
 
224
            %% Monitor cpu_sup
 
225
            ?line MonRef = erlang:monitor(process, cpu_sup),
 
226
            ?line N1 = cpu_sup:nprocs(),
 
227
            ?line true = N1>0,
 
228
 
 
229
            %% Kill the port program
 
230
            case os:cmd("kill -9 " ++ PidStr) of
 
231
                [] ->
 
232
                    %% cpu_sup should not terminate
 
233
                    receive
 
234
                        {'DOWN', MonRef, _, _, Reason} ->
 
235
                            ?line ?t:fail({unexpected_exit_reason, Reason})
 
236
                    after 3000 ->
 
237
                        ok
 
238
                    end,
 
239
 
 
240
                    %% Give cpu_sup time to restart cpu_sup port
 
241
                    ?t:sleep(?t:seconds(3)),
 
242
                    ?line N2 = cpu_sup:nprocs(),
 
243
                    ?line true = N2>0,
 
244
 
 
245
                    erlang:demonitor(MonRef),
 
246
                    ok;
 
247
 
 
248
                Line ->
 
249
                    erlang:demonitor(MonRef),
 
250
                    {skip, {not_killed, Line}}
 
251
            end;
 
252
        _ ->
 
253
            {skip, os_pid_not_found }
 
254
    end.
 
255
 
 
256
terminate(suite) ->
 
257
    [];
 
258
terminate(Config) when is_list(Config) ->
 
259
    ?line ok = application:set_env(os_mon, start_cpu_sup, false),
 
260
    ?line ok = supervisor:terminate_child(os_mon_sup, cpu_sup),
 
261
    ok.
 
262
 
 
263
unavailable(suite) ->
 
264
    [];
 
265
unavailable(doc) ->
 
266
    ["Test correct behaviour when service is unavailable"];
 
267
unavailable(Config) when is_list(Config) ->
 
268
 
 
269
    %% Make sure all API functions return their dummy values
 
270
    ?line 0 = cpu_sup:nprocs(),
 
271
    ?line 0 = cpu_sup:avg1(),
 
272
    ?line 0 = cpu_sup:avg5(),
 
273
    ?line 0 = cpu_sup:avg15(),
 
274
    ?line 0 = cpu_sup:util(),
 
275
    ?line {all,0,0,[]} = cpu_sup:util([]),
 
276
    ?line {all,0,0,[]} = cpu_sup:util([detailed]),
 
277
    ?line {all,0,0,[]} = cpu_sup:util([per_cpu]),
 
278
    ?line {all,0,0,[]} = cpu_sup:util([detailed,per_cpu]),
 
279
 
 
280
    ok.
 
281
 
 
282
restart(suite) ->
 
283
    [];
 
284
restart(Config) when is_list(Config) ->
 
285
    ?line ok = application:set_env(os_mon, start_cpu_sup, true),
 
286
    ?line {ok, _Pid} = supervisor:restart_child(os_mon_sup, cpu_sup),
 
287
    ok.
 
288
 
 
289
%% Aux
 
290
 
 
291
cpu_sup_os_pid() ->
 
292
    Str = os:cmd("ps -e | grep '[c]pu_sup'"),
 
293
    case io_lib:fread("~s", Str) of
 
294
        {ok, [Pid], _Rest} -> {ok, Pid};
 
295
        _ -> {error, pid_not_found}
 
296
    end.