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

« back to all changes in this revision

Viewing changes to lib/inets/test/httpd_load.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 2005-2010. 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
 
 
21
-module(httpd_load).
 
22
 
 
23
-include("test_server.hrl").
 
24
-include("test_server_line.hrl").
 
25
 
 
26
%% General testcases bodies called from httpd_SUITE
 
27
-export([load_test/5]).
 
28
 
 
29
%% Help functions 
 
30
-export([load_test_client/8]).
 
31
 
 
32
%%-------------------------------------------------------------------------
 
33
%% Test cases starts here.
 
34
%%-------------------------------------------------------------------------
 
35
load_test(Type, Port, Host, Node,  NofTesters) ->
 
36
    URIs = 
 
37
        [
 
38
         "/index.html", 
 
39
         "/echo.shtml", 
 
40
         "/",
 
41
         "/flastmod.shtml", 
 
42
         "/misc/"
 
43
        ],
 
44
    Fun = fun(Mod, Host1, Port1, Node1, Req, Exp) -> 
 
45
                  ok = httpd_test_lib:verify_request(Mod, Host1, Port1,
 
46
                                                     Node1, Req, Exp)
 
47
          end,
 
48
    load_test(Fun, URIs ++ URIs, Type, Host, Port, Node, NofTesters, []).
 
49
%%--------------------------------------------------------------------
 
50
%% Internal functions
 
51
%%--------------------------------------------------------------------
 
52
 
 
53
load_test(_, _, _, _, _, _, 0, []) ->
 
54
    ok;
 
55
load_test(Fun, URIs, Type, Host, Port, Node,  0, List) ->
 
56
    receive 
 
57
        {Pid, done} ->
 
58
            load_test(Fun, URIs, Type, Host, Port, Node,  0, 
 
59
                      lists:delete(Pid, List));
 
60
        {'EXIT', Pid, normal} ->
 
61
            load_test(Fun, URIs, Type, Host, Port, Node,  0, 
 
62
                      lists:delete(Pid, List));
 
63
        {'EXIT', Pid, Reason} ->
 
64
            Str = lists:flatten(io_lib:format("client ~p exited: ~p", 
 
65
                                              [Pid,Reason])),
 
66
            test_server:fail(Str);
 
67
        _ ->
 
68
            load_test(Fun, URIs, Type, Host, Port, Node,  0, List)
 
69
    end;
 
70
 
 
71
load_test(Fun, URIs, Type, Host, Port, Node,  X, List) ->
 
72
    Pid = spawn_link(?MODULE, load_test_client,
 
73
                     [Fun, URIs, Type,  Host,  Port,  Node,  self(), 100]),
 
74
    load_test(Fun, lists:reverse(URIs), Type, Host, Port, Node,  X-1,
 
75
              [Pid | List]).
 
76
 
 
77
load_test_client(_Fun, [], _Type, _Host, _Port, _Node,  Boss, _Timeout) ->
 
78
    load_test_client_done(Boss);
 
79
load_test_client(Fun, [URI|URIs], Type, Host, Port, Node,  Boss, Timeout) ->  
 
80
    Req = "GET "++URI++" HTTP/1.0\r\nConnection: Close\r\n"
 
81
        "From: m@erix\r\nReferer: http://www.ericsson.se/\r\n\r\n",
 
82
    Timeout1 = 
 
83
        case (catch Fun(Type,  Host,  Port,  Node,  Req, 
 
84
                        [{statuscode, 200}, {statuscode, 500}, 
 
85
                         {statuscode, 503}, {version, "HTTP/1.0"}])) of
 
86
            {'EXIT', {suite_failed, connection_closed, _, _}} ->
 
87
                %% Some platforms seems to handle heavy load badly.
 
88
                %% So, back off and see if this helps
 
89
                %%?LOG("load_test_client->requestfailed:connection_closed"[]),
 
90
                2 * Timeout;
 
91
            _ ->
 
92
                Timeout
 
93
        end,
 
94
    test_server:sleep(Timeout1),
 
95
    load_test_client(Fun, URIs, Type, Host, Port, Node, Boss, Timeout1).
 
96
 
 
97
load_test_client_done(Boss) ->
 
98
    Boss ! {self(), done}.
 
99