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

« back to all changes in this revision

Viewing changes to lib/inets/test/httpd_poll.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
%%
 
2
%% %CopyrightBegin%
 
3
%% 
 
4
%% Copyright Ericsson AB 2000-2009. 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_poll).
 
22
-behaviour(gen_server).
 
23
 
 
24
 
 
25
%% External API
 
26
-export([start/0, start_appup/2, start/3,stop/0,verbosity/1,poll_time/1]).
 
27
 
 
28
%% gen_server exports
 
29
-export([init/1, 
 
30
         handle_call/3, handle_cast/2, handle_info/2, terminate/2]).
 
31
 
 
32
 
 
33
-define(default_verbosity,error).
 
34
-define(default_poll_time,60000). %% 60 seconds
 
35
 
 
36
 
 
37
-record(state,{host = "", port = -1, ptime = -1, tref = none, uris = []}).
 
38
 
 
39
 
 
40
%% start/0
 
41
%%
 
42
%% Description: Start polling HTTPD with default values
 
43
%%
 
44
start() -> 
 
45
    Options = default_options(otp), 
 
46
    start("gandalf", 8000, Options).
 
47
 
 
48
start_appup(Host, Port) ->
 
49
    Options = default_options(top), 
 
50
    start(Host, Port, Options).
 
51
 
 
52
%% start/3
 
53
%%
 
54
%% Description: Start polling HTTPD
 
55
%%
 
56
%% Parameters:
 
57
%%              Host        = string()
 
58
%%                            Host name of HTTPD
 
59
%%              Port        = integer()
 
60
%%                            Port number of HTTPD
 
61
%%              Options     = [Option]
 
62
%%              Option      = {poll_time,integer()} | {verbosity,verbosity()} |
 
63
%%                            {log_file,string()}   | {uris,[uri()]}
 
64
%%              verbosity() = silence | error | log | debug | trace
 
65
%%              uri()       = {string(),string}
 
66
%%                            First part is a descriptive string and the second
 
67
%%                            part is the actual URI.
 
68
%%
 
69
start(Host,Port,Options) ->
 
70
    gen_server:start({local,httpd_tester},?MODULE,[Host,Port,Options],[]).
 
71
    
 
72
stop() ->
 
73
    gen_server:call(httpd_tester,stop).
 
74
 
 
75
 
 
76
default_options(UriDesc) ->
 
77
    Verbosity = {verbosity,?default_verbosity},
 
78
    Uris      = {uris,uris(UriDesc)},
 
79
    PollTime  = {poll_time,?default_poll_time},
 
80
    Logging   = {log_file,"httpd_poll.log"},
 
81
    [Verbosity, Uris, PollTime, Logging].
 
82
 
 
83
 
 
84
options(Options) ->
 
85
    options(Options, default_options(otp), []).
 
86
 
 
87
options([], Defaults, Options) ->
 
88
    Options ++ Defaults;
 
89
options([{Key,Val} = Opt|Opts], Defaults, Options) ->
 
90
    options(Opts, lists:keydelete(Key, 1, Defaults), [Opt|Options]).
 
91
 
 
92
 
 
93
verbosity(silence) ->
 
94
    set_verbosity(silence);
 
95
verbosity(error) ->
 
96
    set_verbosity(error);
 
97
verbosity(log) ->
 
98
    set_verbosity(log);
 
99
verbosity(debug) ->
 
100
    set_verbosity(debug);
 
101
verbosity(trace) ->
 
102
    set_verbosity(trace).
 
103
 
 
104
set_verbosity(Verbosity) ->
 
105
    gen_server:cast(httpd_tester,{verbosity,Verbosity}).
 
106
 
 
107
poll_time(NewTime) ->
 
108
    gen_server:call(httpd_tester,{poll_time,NewTime}).
 
109
 
 
110
 
 
111
%% ----------------------------------------------------------------------
 
112
 
 
113
 
 
114
init([Host, Port, Options0]) ->
 
115
    process_flag(trap_exit,true),
 
116
    Options = options(Options0),
 
117
    put(verbosity,get_verbosity(Options)),
 
118
    log_open(get_log_file(Options)),
 
119
    tstart(),
 
120
    PollTime = get_poll_time(Options),
 
121
    Ref = tcreate(PollTime),
 
122
    log("created"),
 
123
    {ok,#state{host  = Host,
 
124
               port  = Port,
 
125
               ptime = PollTime,
 
126
               tref  = Ref,
 
127
               uris  = get_uris(Options)}}.
 
128
 
 
129
uris(top) ->
 
130
    [uri_top_index()];
 
131
 
 
132
uris(otp) ->
 
133
    [
 
134
     uri_top_index(),
 
135
     uri_internal_product1(),
 
136
     uri_internal_product2(),
 
137
     uri_p7a_test_results(),
 
138
     uri_bjorn1(),
 
139
     uri_bjorn2(),
 
140
     uri_top_ronja()
 
141
    ].
 
142
 
 
143
uri_top_index() -> 
 
144
    {"top page","/"}.
 
145
 
 
146
uri_internal_product1() -> 
 
147
    {"product internal page (1)","/product/internal/"}.
 
148
 
 
149
uri_internal_product2() -> 
 
150
    {"product internal page (2)","/product/internal"}.
 
151
 
 
152
uri_p7a_test_results() ->
 
153
    {"test summery index page",
 
154
     "/product/internal/test/test_results/progress_P7A/index.html"}.
 
155
 
 
156
uri_bjorn1() ->
 
157
    {"bjorns home page (1)","/~bjorn/"}.
 
158
 
 
159
uri_bjorn2() ->
 
160
    {"bjorns home page (2)","/~bjorn"}.
 
161
 
 
162
uri_top_ronja() ->
 
163
    {"ronja top page","/ronja/"}.
 
164
 
 
165
 
 
166
handle_call(stop, _From, State) ->
 
167
    vlog("stop request"),
 
168
    {stop, normal, ok, State};
 
169
 
 
170
handle_call({poll_time,NewTime}, _From, State) ->
 
171
    vlog("set new poll time: ~p",[NewTime]),
 
172
    OldTime = State#state.ptime,
 
173
    {stop, normal, OldTime, State#state{ptime = NewTime}};
 
174
 
 
175
handle_call(Request, _From, State) ->
 
176
    vlog("unexpected request(call): ~p",[Request]),
 
177
    {reply, ok, State}.
 
178
 
 
179
 
 
180
handle_cast({verbosity,Verbosity}, State) ->
 
181
    vlog("set (new) verbosity to: ~p",[Verbosity]),
 
182
    put(verbosity,Verbosity),
 
183
    {noreply, State};
 
184
 
 
185
handle_cast(Message, State) ->
 
186
    vlog("unexpected message(call): ~p",[Message]),
 
187
    {noreply, State}.
 
188
 
 
189
 
 
190
handle_info(poll_time,State) ->
 
191
    {{Description,Uri},Uris} = get_uri(State#state.uris),
 
192
    vlog("poll time for ~s",[Description]),
 
193
    do_poll(State#state.host,State#state.port,Uri),
 
194
    Ref = tcreate(State#state.ptime),
 
195
    {noreply, State#state{tref = Ref, uris = Uris}};
 
196
 
 
197
handle_info(Info, State) ->
 
198
    vlog("unexpected message(info): ~p",[Info]),
 
199
    {noreply, State}.
 
200
 
 
201
 
 
202
terminate(Reason,State) ->
 
203
    tcancel(State#state.tref),
 
204
    log_close(get(log_file)),
 
205
    ok.
 
206
 
 
207
 
 
208
get_uri([Uri|Uris]) ->
 
209
    {Uri,Uris++[Uri]}.
 
210
 
 
211
    
 
212
do_poll(Host,Port,Uri) ->
 
213
    (catch poll(create(Host,Port),Uri,"200")).
 
214
 
 
215
poll({ok,Socket},Uri,ExpStatus) ->
 
216
    vtrace("poll -> entry with Socket: ~p",[Socket]),
 
217
    put(latest_requested_uri,Uri),
 
218
    Req = "GET " ++ Uri ++ " HTTP/1.0\r\n\r\n",
 
219
    await_poll_response(send(Socket,Req),Socket,ExpStatus);
 
220
poll({error,Reason},_Req,_ExpStatus) ->
 
221
    verror("failed creating socket: ~p",[Reason]),
 
222
    log("failed creating socket: ~p",[Reason]),
 
223
    exit({error,Reason});
 
224
poll(O,_Req,_ExpStatus) ->
 
225
    verror("unexpected result from socket create: ~p",[O]),
 
226
    log("unexpected result from socket create: ~p",[O]),
 
227
    exit({unexpected_result,O}).
 
228
 
 
229
await_poll_response(ok,Socket,ExpStatusCode) ->
 
230
    vtrace("await_poll_response -> awaiting response with status ~s",
 
231
           [ExpStatusCode]),
 
232
    receive 
 
233
        {tcp_closed,Socket} ->
 
234
            verror("connection closed when awaiting poll response"),
 
235
            log("connection closed when awaiting reply to GET of '~s'",
 
236
                [get(latest_requested_uri)]),
 
237
            exit(connection_closed);
 
238
        {tcp,Socket,Response} ->
 
239
            vdebug("received response"),
 
240
            validate(ExpStatusCode,Socket,Response)
 
241
    after 10000 ->
 
242
            verror("connection timeout waiting for poll response",[]),
 
243
            log("connection timeout waiting for reply to GET of '~s'",
 
244
                [get(latest_requested_uri)]),
 
245
            exit(connection_timed_out)
 
246
    end;
 
247
await_poll_response(Error,_Socket,_ExpStatusCode) ->
 
248
    verror("failed sending GET request for '~s' for reason: ~p",
 
249
           [get(latest_requested_uri),Error]),
 
250
    log("failed sending GET request for '~s' for reason: ~p",
 
251
        [get(latest_requested_uri),Error]),
 
252
    exit(Error).
 
253
    
 
254
 
 
255
validate(ExpStatusCode,Socket,Response) ->
 
256
    Sz = sz(Response),
 
257
    vtrace("validate -> Entry with ~p bytes response",[Sz]),
 
258
    Size = trash_the_rest(Socket,Sz),
 
259
    close(Socket),
 
260
    case inets_regexp:split(Response," ") of
 
261
        {ok,["HTTP/1.0",ExpStatusCode|_]} ->
 
262
            vlog("response (~p bytes) was ok",[Size]),
 
263
            ok;
 
264
        {ok,["HTTP/1.0",StatusCode|_]} -> 
 
265
            verror("unexpected response status received: ~s => ~s",
 
266
                   [StatusCode,status_to_message(StatusCode)]),
 
267
            log("unexpected result to GET of '~s': ~s => ~s",
 
268
                [get(latest_requested_uri),StatusCode,
 
269
                 status_to_message(StatusCode)]),
 
270
            exit({unexpected_response_code,StatusCode,ExpStatusCode})
 
271
    end.
 
272
 
 
273
 
 
274
%% ------------------------------------------------------------------
 
275
 
 
276
trash_the_rest(Socket,N) ->
 
277
    receive
 
278
        {tcp, Socket, Trash} ->
 
279
            vtrace("trash_the_rest -> trash ~p bytes",[sz(Trash)]),
 
280
            trash_the_rest(Socket,add(N,sz(Trash)));
 
281
        {tcp_closed, Socket} ->
 
282
            vdebug("socket closed after receiving ~p bytes",[N]),
 
283
            N
 
284
    after 10000 ->
 
285
            verror("connection timeout waiting for message"),
 
286
            exit(connection_timed_out)
 
287
    end.
 
288
 
 
289
 
 
290
add(N1,N2) when integer(N1),integer(N2) ->
 
291
    N1 + N2;
 
292
add(N1,N2) when integer(N1) ->
 
293
    N1;
 
294
add(N1,N2) when integer(N2) ->
 
295
    N2.
 
296
 
 
297
sz(L) when list(L) ->
 
298
    length(lists:flatten(L));
 
299
sz(B) when binary(B) ->
 
300
    size(B);
 
301
sz(O) ->
 
302
    {unknown_size,O}.
 
303
 
 
304
 
 
305
%% --------------------------------------------------------------
 
306
%%
 
307
%% Status code to printable string
 
308
%%
 
309
 
 
310
status_to_message(L) when list(L) ->
 
311
    case (catch list_to_integer(L)) of
 
312
        I when integer(I) ->
 
313
            status_to_message(I);
 
314
        _ ->
 
315
            io_lib:format("UNKNOWN STATUS CODE: '~p'",[L])
 
316
    end;
 
317
status_to_message(100) -> "Section 10.1.1: Continue";
 
318
status_to_message(101) -> "Section 10.1.2: Switching Protocols";
 
319
status_to_message(200) -> "Section 10.2.1: OK";
 
320
status_to_message(201) -> "Section 10.2.2: Created";
 
321
status_to_message(202) -> "Section 10.2.3: Accepted";
 
322
status_to_message(203) -> "Section 10.2.4: Non-Authoritative Information";
 
323
status_to_message(204) -> "Section 10.2.5: No Content";
 
324
status_to_message(205) -> "Section 10.2.6: Reset Content";
 
325
status_to_message(206) -> "Section 10.2.7: Partial Content";
 
326
status_to_message(300) -> "Section 10.3.1: Multiple Choices";
 
327
status_to_message(301) -> "Section 10.3.2: Moved Permanently";
 
328
status_to_message(302) -> "Section 10.3.3: Found";
 
329
status_to_message(303) -> "Section 10.3.4: See Other";
 
330
status_to_message(304) -> "Section 10.3.5: Not Modified";
 
331
status_to_message(305) -> "Section 10.3.6: Use Proxy";
 
332
status_to_message(307) -> "Section 10.3.8: Temporary Redirect";
 
333
status_to_message(400) -> "Section 10.4.1: Bad Request";
 
334
status_to_message(401) -> "Section 10.4.2: Unauthorized";
 
335
status_to_message(402) -> "Section 10.4.3: Peyment Required";
 
336
status_to_message(403) -> "Section 10.4.4: Forbidden";
 
337
status_to_message(404) -> "Section 10.4.5: Not Found";
 
338
status_to_message(405) -> "Section 10.4.6: Method Not Allowed";
 
339
status_to_message(406) -> "Section 10.4.7: Not Acceptable";
 
340
status_to_message(407) -> "Section 10.4.8: Proxy Authentication Required";
 
341
status_to_message(408) -> "Section 10.4.9: Request Time-Out";
 
342
status_to_message(409) -> "Section 10.4.10: Conflict";
 
343
status_to_message(410) -> "Section 10.4.11: Gone";
 
344
status_to_message(411) -> "Section 10.4.12: Length Required";
 
345
status_to_message(412) -> "Section 10.4.13: Precondition Failed";
 
346
status_to_message(413) -> "Section 10.4.14: Request Entity Too Large";
 
347
status_to_message(414) -> "Section 10.4.15: Request-URI Too Large";
 
348
status_to_message(415) -> "Section 10.4.16: Unsupported Media Type";
 
349
status_to_message(416) -> "Section 10.4.17: Requested range not satisfiable";
 
350
status_to_message(417) -> "Section 10.4.18: Expectation Failed";
 
351
status_to_message(500) -> "Section 10.5.1: Internal Server Error";
 
352
status_to_message(501) -> "Section 10.5.2: Not Implemented";
 
353
status_to_message(502) -> "Section 10.5.3: Bad Gatteway";
 
354
status_to_message(503) -> "Section 10.5.4: Service Unavailable";
 
355
status_to_message(504) -> "Section 10.5.5: Gateway Time-out";
 
356
status_to_message(505) -> "Section 10.5.6: HTTP Version not supported";
 
357
status_to_message(Code) -> io_lib:format("Unknown status code: ~p",[Code]).
 
358
 
 
359
 
 
360
%% ----------------------------------------------------------------
 
361
 
 
362
create(Host,Port) ->
 
363
    vtrace("create -> ~n\tHost: ~s~n\tPort: ~p",[Host,Port]),
 
364
    case gen_tcp:connect(Host,Port,[{packet,0},{reuseaddr,true}]) of
 
365
        {ok,Socket} ->
 
366
            {ok,Socket};
 
367
        {error,{enfile,_}} ->
 
368
            {error,enfile};
 
369
        Error ->
 
370
            Error
 
371
    end.
 
372
 
 
373
close(Socket) ->
 
374
    gen_tcp:close(Socket).
 
375
 
 
376
 
 
377
send(Socket,Data) ->
 
378
    vtrace("send -> send ~p bytes of data",[length(Data)]),
 
379
    gen_tcp:send(Socket,Data).
 
380
 
 
381
    
 
382
%% ----------------------------------------------------------------
 
383
 
 
384
tstart() -> 
 
385
    timer:start().
 
386
 
 
387
tcreate(Time) -> 
 
388
    {ok,Ref} = timer:send_after(Time,poll_time),
 
389
    Ref.
 
390
 
 
391
tcancel(Ref) ->
 
392
    timer:cancel(Ref).
 
393
 
 
394
%% ----------------------------------------------------------------
 
395
 
 
396
log_open(undefined) ->
 
397
    ok;
 
398
log_open(FileName) ->
 
399
    put(log_file,fopen(FileName)).
 
400
 
 
401
log_close(undefined) ->
 
402
    ok;
 
403
log_close(Fd) ->
 
404
    fclose(Fd).
 
405
 
 
406
log(F) ->
 
407
    log(F,[]).
 
408
 
 
409
log(F,A) ->
 
410
    {{Year,Month,Day},{Hour,Min,Sec}} = local_time(),
 
411
    fwrite(get(log_file),
 
412
           "~w.~w.~w ~w.~w.~w " ++ F ++ "~n",
 
413
           [Year,Month,Day,Hour,Min,Sec] ++ A).
 
414
 
 
415
%% ----------------------------------------------------------------
 
416
 
 
417
fopen(Name) ->
 
418
    {ok,Fd} = file:open(Name,[write]),
 
419
    Fd.
 
420
 
 
421
fclose(Fd) ->
 
422
    file:close(Fd).
 
423
 
 
424
fwrite(undefined,_F,_A) ->
 
425
    ok;
 
426
fwrite(Fd,F,A) ->
 
427
    io:format(Fd,F,A).
 
428
 
 
429
    
 
430
%% ----------------------------------------------------------------
 
431
 
 
432
get_poll_time(Opts) ->
 
433
    get_option(poll_time,Opts,?default_poll_time).
 
434
 
 
435
get_log_file(Opts) ->
 
436
    get_option(log_file,Opts).
 
437
 
 
438
get_uris(Opts) ->
 
439
    get_option(uris,Opts,[]).
 
440
 
 
441
get_verbosity(Opts) ->
 
442
    get_option(verbosity,Opts,?default_verbosity).
 
443
 
 
444
get_option(Opt,Opts) ->
 
445
    get_option(Opt,Opts,undefined).
 
446
 
 
447
get_option(Opt,Opts,Default) ->
 
448
    case lists:keysearch(Opt,1,Opts) of
 
449
        {value,{Opt,Value}} ->
 
450
            Value;
 
451
        false ->
 
452
            Default
 
453
    end.
 
454
 
 
455
%% ----------------------------------------------------------------
 
456
 
 
457
%% sleep(T) -> receive after T -> ok end.
 
458
 
 
459
%% ----------------------------------------------------------------
 
460
 
 
461
%% vtrace(F)   -> vprint(get(verbosity),trace,F,[]).
 
462
vtrace(F,A) -> vprint(get(verbosity),trace,F,A).
 
463
 
 
464
vdebug(F)   -> vprint(get(verbosity),debug,F,[]).
 
465
vdebug(F,A) -> vprint(get(verbosity),debug,F,A).
 
466
 
 
467
vlog(F)     -> vprint(get(verbosity),log,F,[]).
 
468
vlog(F,A)   -> vprint(get(verbosity),log,F,A).
 
469
 
 
470
verror(F)   -> vprint(get(verbosity),error,F,[]).
 
471
verror(F,A) -> vprint(get(verbosity),error,F,A).
 
472
 
 
473
vprint(trace,Severity,F,A)         -> vprint(Severity,F,A);
 
474
vprint(debug,trace,F,A)            -> ok;
 
475
vprint(debug,Severity,F,A)         -> vprint(Severity,F,A);
 
476
vprint(log,log,F,A)                -> vprint(log,F,A);
 
477
vprint(log,error,F,A)              -> vprint(log,F,A);
 
478
vprint(error,error,F,A)            -> vprint(error,F,A);
 
479
vprint(_Verbosity,_Severity,_F,_A) -> ok.
 
480
 
 
481
vprint(Severity,F,A) -> 
 
482
    {{Year,Month,Day},{Hour,Min,Sec}} = local_time(),
 
483
    io:format("~w.~w.~w ~w.~w.~w " ++ image_of(Severity) ++ F ++ "~n",
 
484
              [Year,Month,Day,Hour,Min,Sec] ++ A).
 
485
 
 
486
image_of(error) -> "ERR: ";
 
487
image_of(log)   -> "LOG: "; 
 
488
image_of(debug) -> "DBG: ";
 
489
image_of(trace) -> "TRC: ".
 
490
   
 
491
local_time() -> calendar:local_time().
 
492
 
 
493
 
 
494
    
 
495
 
 
496