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

« back to all changes in this revision

Viewing changes to lib/inets/examples/httpd_load_test/hdlt_client.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 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
%% Purpose: The HDLT client module.
 
22
%%          This is the traffic generator
 
23
%%----------------------------------------------------------------------
 
24
 
 
25
-module(hdlt_client).
 
26
 
 
27
-export([
 
28
         start/1, 
 
29
         stop/0, 
 
30
         start_inets/0, 
 
31
         start_service/1, 
 
32
         release/0, 
 
33
         node_info/0
 
34
        ]).
 
35
 
 
36
-export([
 
37
         proxy/1
 
38
        ]).
 
39
 
 
40
-include("hdlt_logger.hrl").
 
41
 
 
42
-define(CTRL,   hdlt_ctrl).
 
43
-define(PROXY,  hdlt_proxy).
 
44
 
 
45
-record(state, 
 
46
        {
 
47
         mode = initial,
 
48
         send_rate,
 
49
         time, 
 
50
         stop_time, 
 
51
         url,
 
52
         nof_reqs = 0,
 
53
         nof_reps = 0,
 
54
         last_req,
 
55
         sizes,
 
56
         socket_type, 
 
57
         cert_file
 
58
        }).
 
59
 
 
60
 
 
61
 
 
62
start(Debug) ->
 
63
    proc_lib:start_link(?MODULE, proxy, [Debug]).
 
64
 
 
65
stop() ->
 
66
    (catch erlang:send(?PROXY, stop)),
 
67
    ok.
 
68
 
 
69
start_inets() ->
 
70
    ?PROXY ! start_inets.
 
71
 
 
72
start_service(Args) ->
 
73
    ?PROXY ! {start_client, Args, self()},
 
74
    receive
 
75
        client_started ->
 
76
            %% ?LOG("client service started"),
 
77
            ok
 
78
    end.
 
79
 
 
80
release() ->
 
81
    ?PROXY ! release.
 
82
 
 
83
node_info() ->
 
84
    ?PROXY ! {node_info, self()},
 
85
    receive 
 
86
        {node_info, NodeInfo} ->
 
87
            NodeInfo
 
88
    end.
 
89
 
 
90
 
 
91
%% ---------------------------------------------------------------------
 
92
%% 
 
93
%% The proxy process
 
94
%% 
 
95
 
 
96
proxy(Debug) ->
 
97
    process_flag(trap_exit, true),
 
98
    erlang:register(?PROXY, self()),
 
99
    SName = lists:flatten(
 
100
              io_lib:format("HDLT PROXY[~p,~p]", [self(), node()])), 
 
101
    ?SET_NAME(SName),
 
102
    ?SET_LEVEL(Debug), 
 
103
    ?LOG("starting", []),
 
104
    Ref = await_for_controller(10), 
 
105
    CtrlNode = node(Ref), 
 
106
    erlang:monitor_node(CtrlNode, true),
 
107
    proc_lib:init_ack({ok, self()}),
 
108
    ?DEBUG("started", []),
 
109
    proxy_loop(Ref, CtrlNode, undefined).
 
110
 
 
111
await_for_controller(N) when N > 0 ->
 
112
    case global:whereis_name(hdlt_ctrl) of
 
113
        Pid when is_pid(Pid) ->
 
114
            erlang:monitor(process, Pid);
 
115
        _ ->
 
116
            timer:sleep(1000),
 
117
            await_for_controller(N-1)
 
118
    end;
 
119
await_for_controller(_) ->
 
120
    proc_lib:init_ack({error, controller_not_found, nodes()}),
 
121
    timer:sleep(500),
 
122
    init:stop().
 
123
 
 
124
 
 
125
proxy_loop(Ref, CtrlNode, Client) ->
 
126
    ?DEBUG("await command", []),
 
127
    receive
 
128
        stop ->
 
129
            ?LOG("stop", []),
 
130
            timer:sleep(1000),
 
131
            halt();
 
132
 
 
133
        start_inets ->
 
134
            ?LOG("start the inets service framework", []),
 
135
            %% inets:enable_trace(max, "/tmp/inets-httpc-trace.log", all),
 
136
            case (catch inets:start()) of
 
137
                ok ->
 
138
                    ?LOG("framework started", []),
 
139
                    proxy_loop(Ref, CtrlNode, Client);
 
140
                Error ->
 
141
                    ?LOG("failed starting inets service framework: "
 
142
                        "~n   Error: ~p", [Error]),
 
143
                    timer:sleep(1000),
 
144
                    halt()
 
145
            end;
 
146
 
 
147
        {start_client, Args, From} ->
 
148
            ?LOG("start client with"
 
149
                "~n   Args: ~p", [Args]),
 
150
            Client2 = spawn_link(fun() -> client(Args) end),
 
151
            From ! client_started,
 
152
            proxy_loop(Ref, CtrlNode, Client2);
 
153
 
 
154
        release ->
 
155
            ?LOG("release", []),
 
156
            Client ! go,
 
157
            proxy_loop(Ref, CtrlNode, Client);
 
158
 
 
159
        {node_info, Pid} ->
 
160
            ?LOG("received requets for node info", []),
 
161
            NodeInfo = get_node_info(),
 
162
            Pid ! {node_info, NodeInfo}, 
 
163
            proxy_loop(Ref, CtrlNode, Client);
 
164
 
 
165
        {'EXIT', Client, normal} ->
 
166
            ?LOG("received normal exit message from client (~p)", 
 
167
                 [Client]),
 
168
            exit(normal);
 
169
        
 
170
        {'EXIT', Client, Reason} ->
 
171
            ?INFO("received exit message from client (~p)"
 
172
                 "~n   Reason: ~p", [Client, Reason]),
 
173
            %% Unexpected client termination, inform the controller and die
 
174
            global:send(hdlt_ctrl, {client_exit, Client, node(), Reason}),
 
175
            exit({client_exit, Reason});
 
176
 
 
177
        {nodedown, CtrlNode} ->
 
178
            ?LOG("received nodedown for controller node - terminate", []), 
 
179
            halt();
 
180
 
 
181
        {'DOWN', Ref, process, _, _} ->
 
182
            ?INFO("received DOWN message for controller - terminate", []),
 
183
            %% The controller has terminated, dont care why, time to die
 
184
            halt()
 
185
 
 
186
    end.
 
187
 
 
188
 
 
189
 
 
190
%% ---------------------------------------------------------------------
 
191
%% 
 
192
%% The client process
 
193
%% 
 
194
 
 
195
client([SocketType, CertFile, URLBase, Sizes, Time, SendRate, Debug]) ->
 
196
    SName = lists:flatten(
 
197
              io_lib:format("HDLT CLIENT[~p,~p]", [self(), node()])), 
 
198
    ?SET_NAME(SName),
 
199
    ?SET_LEVEL(Debug), 
 
200
    ?LOG("starting with"
 
201
         "~n   SocketType: ~p"
 
202
         "~n   Time:       ~p"
 
203
         "~n   SendRate:   ~p", [SocketType, Time, SendRate]),
 
204
    httpc:set_options([{max_pipeline_length, 0}]),
 
205
    if
 
206
        (SocketType =:= ssl) orelse
 
207
        (SocketType =:= ossl) orelse
 
208
        (SocketType =:= essl) ->
 
209
            %% Ensure crypto and ssl started:
 
210
            crypto:start(),
 
211
            ssl:start();
 
212
        true ->
 
213
            ok
 
214
    end,
 
215
    State = #state{mode        = idle, 
 
216
                   url         = URLBase, 
 
217
                   time        = Time, 
 
218
                   send_rate   = SendRate,
 
219
                   sizes       = Sizes,
 
220
                   socket_type = SocketType,
 
221
                   cert_file   = CertFile},
 
222
    ?DEBUG("started", []),
 
223
    client_loop(State).
 
224
 
 
225
%% The point is to first start all client nodes and then this
 
226
%% process. Then, when they are all started, the go-ahead, go, 
 
227
%% message is sent to let them lose at the same time.
 
228
client_loop(#state{mode      = idle, 
 
229
                   time      = Time, 
 
230
                   send_rate = SendRate} = State) ->
 
231
    ?DEBUG("[idle] awaiting the go command", []),
 
232
    receive 
 
233
        go ->
 
234
            ?LOG("[idle] received go", []),
 
235
            erlang:send_after(Time, self(), stop),
 
236
            NewState = send_requests(State, SendRate),      
 
237
            client_loop(NewState#state{mode     = generating, 
 
238
                                       nof_reqs = SendRate})
 
239
    end;
 
240
 
 
241
%% In this mode the client is generating traffic.
 
242
%% It will continue to do so until the stop message
 
243
%% is received. 
 
244
client_loop(#state{mode = generating} = State) -> 
 
245
    receive 
 
246
        stop ->
 
247
            ?LOG("[generating] received stop", []),
 
248
            StopTime = timestamp(), 
 
249
            req_reply(State),
 
250
            client_loop(State#state{mode = stopping, stop_time = StopTime});
 
251
 
 
252
        {http, {_, {{_, 200, _}, _, _}}} ->
 
253
            %% ?DEBUG("[generating] received reply - send another request", []),
 
254
            NewState = send_requests(State, 1),
 
255
            client_loop(NewState#state{nof_reps = NewState#state.nof_reps + 1,
 
256
                                       nof_reqs = NewState#state.nof_reqs + 1});
 
257
 
 
258
        {http, {ReqId, {error, Reason}}} ->
 
259
            ?INFO("[generating] request ~p failed: "
 
260
                  "~n   Reason:  ~p"
 
261
                  "~n   NofReqs: ~p"
 
262
                  "~n   NofReps: ~p", 
 
263
                  [ReqId, Reason, State#state.nof_reqs, State#state.nof_reps]),
 
264
            exit({Reason, generating, State#state.nof_reqs, State#state.nof_reps});
 
265
 
 
266
        Else ->
 
267
            ?LOG("[generating] received unexpected message: "
 
268
                 "~n~p", [Else]),
 
269
            unexpected_data(Else), 
 
270
            client_loop(State)
 
271
    end;
 
272
 
 
273
%% The client no longer issues any new requests, instead it 
 
274
%% waits for replies for all the oustanding requests to 
 
275
%% arrive.
 
276
client_loop(#state{mode     = stopping, 
 
277
                   time     = Time, 
 
278
                   last_req = LastReqId} = State) ->
 
279
    receive 
 
280
        {http, {LastReqId, {{_, 200, _}, _, _}}} ->
 
281
            ?DEBUG("[stopping] received reply for last request (~p)", [LastReqId]),
 
282
            time_to_complete(State),
 
283
            ok;
 
284
 
 
285
        {http, {ReqId, {{_, 200, _}, _, _}}} ->
 
286
            ?DEBUG("[stopping] received reply ~p", [ReqId]),
 
287
            client_loop(State);
 
288
 
 
289
        {http, {ReqId, {error, Reason}}} ->
 
290
            ?INFO("[stopping] request ~p failed: "
 
291
                  "~n   Reason:  ~p"
 
292
                  "~n   NofReqs: ~p"
 
293
                  "~n   NofReps: ~p", 
 
294
                  [ReqId, Reason, State#state.nof_reqs, State#state.nof_reps]),
 
295
            exit({Reason, stopping, State#state.nof_reqs, State#state.nof_reps});
 
296
 
 
297
        Else ->
 
298
            ?LOG("[stopping] received unexpected message: "
 
299
                 "~n~p", [Else]),
 
300
            unexpected_data(Else), 
 
301
            client_loop(State)
 
302
 
 
303
    after Time ->
 
304
            ?INFO("timeout when"
 
305
                  "~n   Number of requests: ~p"
 
306
                  "~n   Number of replies:  ~p", 
 
307
                  [State#state.nof_reqs, State#state.nof_reps]),
 
308
            exit({timeout, State#state.nof_reqs, State#state.nof_reps})
 
309
    end.
 
310
 
 
311
req_reply(#state{nof_reqs = NofReqs, nof_reps = NofReps}) ->
 
312
    load_data({req_reply, node(), NofReqs, NofReps}).
 
313
 
 
314
time_to_complete(#state{stop_time = StopTime}) ->
 
315
    StoppedTime = os:timestamp(),
 
316
    load_data({time_to_complete, node(), StopTime, StoppedTime}).
 
317
 
 
318
load_data(Data) ->
 
319
    global:send(?CTRL, {load_data, Data}).
 
320
 
 
321
unexpected_data(Else) ->
 
322
    global:send(?CTRL, {unexpected_data, Else}).
 
323
 
 
324
 
 
325
send_requests(#state{sizes = Sizes} = State, N) ->
 
326
    send_requests(State, N, Sizes).
 
327
 
 
328
send_requests(State, 0, Sizes) ->
 
329
    State#state{sizes = Sizes};
 
330
send_requests(#state{socket_type = SocketType, 
 
331
                     cert_file   = CertFile} = State, N, [Sz | Sizes]) ->
 
332
    URL = lists:flatten(io_lib:format("~s~w", [State#state.url, Sz])),
 
333
    Method      = get,
 
334
    Request     = {URL, []},
 
335
    HTTPOptions = 
 
336
        case SocketType of
 
337
            ip_comm ->
 
338
                [];
 
339
            _ ->
 
340
                SslOpts = [{verify, 0},
 
341
                           {certfile, CertFile},
 
342
                           {keyfile,  CertFile}],
 
343
                case SocketType of
 
344
                    ssl ->
 
345
                        [{ssl, SslOpts}];
 
346
                    ossl ->
 
347
                        [{ssl, {ossl, SslOpts}}];
 
348
                    essl ->
 
349
                        [{ssl, {essl, SslOpts}}]
 
350
                end
 
351
        end,
 
352
    Options = [{sync, false}], 
 
353
    {ok, Ref} = httpc:request(Method, Request, HTTPOptions, Options), 
 
354
    send_requests(State#state{last_req = Ref}, N-1, lists:append(Sizes, [Sz])).
 
355
 
 
356
 
 
357
timestamp() ->
 
358
   os:timestamp().
 
359
 
 
360
 
 
361
get_node_info() ->
 
362
    [{cpu_topology,        erlang:system_info(cpu_topology)},
 
363
     {heap_type,           erlang:system_info(heap_type)},
 
364
     {nof_schedulers,      erlang:system_info(schedulers)},
 
365
     {otp_release,         erlang:system_info(otp_release)}, 
 
366
     {version,             erlang:system_info(version)}, 
 
367
     {system_version,      erlang:system_info(system_version)},
 
368
     {system_architecture, erlang:system_info(system_architecture)}].
 
369
 
 
370