~clint-fewbar/ubuntu/precise/erlang/merge-15b

« back to all changes in this revision

Viewing changes to lib/sasl/test/overload_SUITE.erl

  • Committer: Package Import Robot
  • Author(s): Sergei Golovan
  • Date: 2011-12-15 19:20:10 UTC
  • mfrom: (1.1.18) (3.5.15 sid)
  • mto: (3.5.16 sid)
  • mto: This revision was merged to the branch mainline in revision 33.
  • Revision ID: package-import@ubuntu.com-20111215192010-jnxcfe3tbrpp0big
Tags: 1:15.b-dfsg-1
* New upstream release.
* Upload to experimental because this release breaks external drivers
  API along with ABI, so several applications are to be fixed.
* Removed SSL patch because the old SSL implementation is removed from
  the upstream distribution.
* Removed never used patch which added native code to erlang beam files.
* Removed the erlang-docbuilder binary package because the docbuilder
  application was dropped by upstream.
* Documented dropping ${erlang-docbuilder:Depends} substvar in
  erlang-depends(1) manpage.
* Made erlang-base and erlang-base-hipe provide virtual package
  erlang-abi-15.b (the number means the first erlang version, which
  provides current ABI).

Show diffs side-by-side

added added

removed removed

Lines of Context:
 
1
%%
 
2
%% %CopyrightBegin%
 
3
%%
 
4
%% Copyright Ericsson AB 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
 
 
20
-module(overload_SUITE).
 
21
-include_lib("common_test/include/ct.hrl").
 
22
 
 
23
-compile(export_all).
 
24
 
 
25
%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
 
26
 
 
27
all() -> [info, set_config_data, set_env_vars, request, timeout].
 
28
 
 
29
init_per_testcase(_Case,Config) ->
 
30
    restart_sasl(),
 
31
    Config.
 
32
 
 
33
end_per_testcase(Case,Config) ->
 
34
    try apply(?MODULE,Case,[cleanup,Config])
 
35
    catch error:undef -> ok
 
36
    end,
 
37
    ok.
 
38
 
 
39
%%%-----------------------------------------------------------------
 
40
info(_Config) ->
 
41
    Info = overload:get_overload_info(),
 
42
    [{total_intensity,0.0},
 
43
     {accept_intensity,0.0},
 
44
     {max_intensity,0.8},
 
45
     {weight,0.1},
 
46
     {total_requests,0},
 
47
     {accepted_requests,0}] = Info.
 
48
 
 
49
%%%-----------------------------------------------------------------
 
50
set_config_data(_Config) ->
 
51
    InfoDefault = overload:get_overload_info(),
 
52
    ok = check_info(0.8,0.1,InfoDefault),
 
53
    ok = overload:set_config_data(0.5,0.4),
 
54
    Info1 = overload:get_overload_info(),
 
55
    ok = check_info(0.5,0.4,Info1),
 
56
    ok.
 
57
 
 
58
%%%-----------------------------------------------------------------
 
59
set_env_vars(_Config) ->
 
60
    InfoDefault = overload:get_overload_info(),
 
61
    ok = check_info(0.8,0.1,InfoDefault),
 
62
    ok = application:set_env(sasl,overload_max_intensity,0.5),
 
63
    ok = application:set_env(sasl,overload_weight,0.4),
 
64
    ok = application:stop(sasl),
 
65
    ok = application:start(sasl),
 
66
    Info1 = overload:get_overload_info(),
 
67
    ok = check_info(0.5,0.4,Info1),
 
68
    ok.
 
69
set_env_vars(cleanup,_Config) ->
 
70
    application:unset_env(sasl,overload_max_intensity),
 
71
    application:unset_env(sasl,overload_weight),
 
72
    ok.
 
73
 
 
74
%%%-----------------------------------------------------------------
 
75
request(_Config) ->
 
76
    %% Find number of request that can be done with default settings
 
77
    %% and no delay
 
78
    overload:set_config_data(0.8, 0.1),
 
79
    NDefault = do_many_requests(0),
 
80
    restart_sasl(),
 
81
    ?t:format("NDefault: ~p",[NDefault]),
 
82
 
 
83
    %% Check that the number of requests increases when max_intensity
 
84
    %% increases
 
85
    overload:set_config_data(2, 0.1),
 
86
    NLargeMI = do_many_requests(0),
 
87
    restart_sasl(),
 
88
    ?t:format("NLargeMI: ~p",[NLargeMI]),
 
89
    true = NLargeMI > NDefault,
 
90
 
 
91
    %% Check that the number of requests decreases when weight
 
92
    %% increases
 
93
    overload:set_config_data(0.8, 1),
 
94
    NLargeWeight = do_many_requests(0),
 
95
    restart_sasl(),
 
96
    ?t:format("NLargeWeight: ~p",[NLargeWeight]),
 
97
    true = NLargeWeight < NDefault,
 
98
 
 
99
    %% Check that number of requests increases when delay between
 
100
    %% requests increases.
 
101
    %% (Keeping same config and comparing to large weight in order to
 
102
    %% minimize the time needed for this case.)
 
103
    overload:set_config_data(0.8, 1),
 
104
    NLargeTime = do_many_requests(500),
 
105
    restart_sasl(),
 
106
    ?t:format("NLargeTime: ~p",[NLargeTime]),
 
107
    true = NLargeTime > NLargeWeight,
 
108
    ok.
 
109
 
 
110
%%%-----------------------------------------------------------------
 
111
timeout(_Config) ->
 
112
    overload:set_config_data(0.8, 1),
 
113
    _N = do_many_requests(0),
 
114
 
 
115
    %% Check that the overload alarm is raised
 
116
    [{overload,_}] = alarm_handler:get_alarms(),
 
117
 
 
118
    %% Fake a clear timeout in overload.erl and check that, since it
 
119
    %% came very soon after the overload situation, the alarm is not
 
120
    %% cleared
 
121
    overload ! timeout,
 
122
    timer:sleep(1000),
 
123
    [{overload,_}] = alarm_handler:get_alarms(),
 
124
 
 
125
    %% A bit later, try again and check that this time the alarm is
 
126
    %% cleared
 
127
    overload ! timeout,
 
128
    timer:sleep(1000),
 
129
    [] = alarm_handler:get_alarms(),
 
130
 
 
131
    ok.
 
132
 
 
133
 
 
134
%%%-----------------------------------------------------------------
 
135
%%% INTERNAL FUNCTIONS
 
136
 
 
137
%%%-----------------------------------------------------------------
 
138
%%% Call overload:request/0 up to 30 times with the given time delay
 
139
%%% between. Stop when 'reject' is returned.
 
140
do_many_requests(T) ->
 
141
    30 - do_requests(30,T).
 
142
 
 
143
do_requests(0,_) ->
 
144
    ?t:fail(never_rejected);
 
145
do_requests(N,T) ->
 
146
    case overload:request() of
 
147
        accept ->
 
148
            timer:sleep(T),
 
149
            do_requests(N-1,T);
 
150
        reject ->
 
151
            N
 
152
    end.
 
153
 
 
154
%%%-----------------------------------------------------------------
 
155
%%% Restart the sasl application
 
156
restart_sasl() ->
 
157
    application:stop(sasl),
 
158
    application:start(sasl),
 
159
    ok.
 
160
 
 
161
%%%-----------------------------------------------------------------
 
162
%%% Check that max_intensity and weight is set as expected
 
163
check_info(MI,W,Info) -> 
 
164
    case {lists:keyfind(max_intensity,1,Info), lists:keyfind(weight,1,Info)} of
 
165
        {{_,MI},{_,W}} -> ok;
 
166
        _ -> ?t:fail({unexpected_info,MI,W,Info})
 
167
    end.