~statik/ubuntu/maverick/erlang/erlang-merge-testing

« back to all changes in this revision

Viewing changes to lib/inets/src/inets_app/inets.erl

  • Committer: Bazaar Package Importer
  • Author(s): Martin Pitt
  • Date: 2009-11-06 18:54:42 UTC
  • mfrom: (3.3.4 sid)
  • Revision ID: james.westby@ubuntu.com-20091106185442-bqxb11qghumvmvx2
Tags: 1:13.b.2.1-dfsg-1ubuntu1
* Merge with Debian testing; remaining Ubuntu changes:
  - Drop libwxgtk2.8-dev build dependency. Wx isn't in main, and not
    supposed to. (LP #438365)
  - 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.

Show diffs side-by-side

added added

removed removed

Lines of Context:
28
28
         stop/0, stop/2, 
29
29
         services/0, services_info/0,
30
30
         service_names/0]).
 
31
-export([enable_trace/2, disable_trace/0, set_trace/1, 
 
32
         report_event/4]).
 
33
-export([versions/0,
 
34
         print_version_info/0, print_version_info/1]).
 
35
 
31
36
 
32
37
%%====================================================================
33
38
%% API
47
52
start(Type) -> 
48
53
    application:start(inets, Type).
49
54
 
 
55
 
50
56
%%--------------------------------------------------------------------
51
57
%% Function: start(Service, ServiceConfig [, How]) -> {ok, Pid} | 
52
58
%%                                                {error, Reason}
89
95
stop() -> 
90
96
    application:stop(inets).
91
97
 
 
98
 
92
99
%%--------------------------------------------------------------------
93
100
%% Function: stop(Service, Pid) -> ok
94
101
%%
105
112
    Module = service_module(Service),
106
113
    call_service(Module, stop_service, Pid).
107
114
 
 
115
 
108
116
%%--------------------------------------------------------------------
109
117
%% Function: services() -> [{Service, Pid}]
110
118
%%
124
132
            {error, inets_not_started}
125
133
    end.
126
134
                                               
 
135
 
127
136
%%--------------------------------------------------------------------
128
137
%% Function: services_info() -> [{Service, Pid, Info}]
129
138
%%
148
157
                   end,
149
158
            lists:flatten(lists:map(Fun, Services))
150
159
    end.
 
160
 
 
161
 
 
162
 
 
163
%%--------------------------------------------------------------------
 
164
%% Function: print_version_info() 
 
165
%%
 
166
%% Description: Simple utility function to print information 
 
167
%%              about versions (system, OS and modules). 
 
168
%%--------------------------------------------------------------------
 
169
 
 
170
print_version_info() ->
 
171
    {ok, Versions} = inets:versions(),
 
172
    print_version_info(Versions).
 
173
 
 
174
print_version_info(Versions) when is_list(Versions) ->
 
175
    print_sys_info(Versions),
 
176
    print_os_info(Versions),
 
177
    print_mods_info(Versions).
 
178
 
 
179
print_sys_info(Versions) ->
 
180
    case key1search(sys_info, Versions) of
 
181
        {value, SysInfo} when is_list(SysInfo) ->
 
182
            {value, Arch} = key1search(arch, SysInfo, "Not found"),
 
183
            {value, Ver}  = key1search(ver, SysInfo, "Not found"),
 
184
            io:format("System info: "
 
185
                      "~n   Arch: ~s"
 
186
                      "~n   Ver:  ~s"
 
187
                      "~n", [Arch, Ver]),
 
188
            ok;
 
189
        _ ->
 
190
            io:format("System info: Not found~n", []),
 
191
            not_found
 
192
    end.
 
193
 
 
194
print_os_info(Versions) ->
 
195
    case key1search(os_info, Versions) of
 
196
        {value, OsInfo} when is_list(OsInfo) ->
 
197
            Fam =
 
198
                case key1search(fam, OsInfo, "Not found") of
 
199
                    {value, F} when is_atom(F) ->
 
200
                        atom_to_list(F);
 
201
                    {value, LF} when is_list(LF) ->
 
202
                        LF;
 
203
                    {value, XF} ->
 
204
                        lists:flatten(io_lib:format("~p", [XF]))
 
205
                end,
 
206
            Name =
 
207
                case key1search(name, OsInfo) of
 
208
                    {value, N} when is_atom(N) ->
 
209
                        "[" ++ atom_to_list(N) ++ "]";
 
210
                    {value, LN} when is_list(LN) ->
 
211
                        "[" ++ LN ++ "]";
 
212
                    not_found ->
 
213
                        ""
 
214
                end,
 
215
            Ver =
 
216
                case key1search(ver, OsInfo, "Not found") of
 
217
                    {value, T} when is_tuple(T) ->
 
218
                        tversion(T);
 
219
                    {value, LV} when is_list(LV) ->
 
220
                        LV;
 
221
                    {value, XV} ->
 
222
                        lists:flatten(io_lib:format("~p", [XV]))
 
223
                end,
 
224
            io:format("OS info: "
 
225
                      "~n   Family: ~s ~s"
 
226
                      "~n   Ver:    ~s"
 
227
                      "~n", [Fam, Name, Ver]),
 
228
            ok;
 
229
        _ ->
 
230
            io:format("OS info:     Not found~n", []),
 
231
            not_found
 
232
    end.
 
233
 
 
234
versions() ->
 
235
    App    = inets, 
 
236
    LibDir = code:lib_dir(App),
 
237
    File   = filename:join([LibDir, "ebin", atom_to_list(App) ++ ".app"]),
 
238
    case file:consult(File) of
 
239
        {ok, [{application, App, AppFile}]} ->
 
240
            case lists:keysearch(modules, 1, AppFile) of
 
241
                {value, {modules, Mods}} ->
 
242
                    {ok, version_info(Mods)};
 
243
                _ ->
 
244
                    {error, {invalid_format, modules}}
 
245
            end;
 
246
        Error ->
 
247
            {error, {invalid_format, Error}}
 
248
    end.
 
249
 
 
250
version_info(Mods) ->
 
251
    SysInfo = sys_info(),
 
252
    OsInfo  = os_info(),
 
253
    ModInfo = [mod_version_info(Mod) || Mod <- Mods],
 
254
    [{sys_info, SysInfo}, {os_info, OsInfo}, {mod_info, ModInfo}].
 
255
 
 
256
mod_version_info(Mod) ->
 
257
    Info = Mod:module_info(),
 
258
    {value, {attributes, Attr}}   = lists:keysearch(attributes, 1, Info),
 
259
    {value, {vsn,        [Vsn]}}  = lists:keysearch(vsn,        1, Attr),
 
260
    {value, {app_vsn,    AppVsn}} = lists:keysearch(app_vsn,    1, Attr),
 
261
    {value, {compile,    Comp}}   = lists:keysearch(compile,    1, Info),
 
262
    {value, {version,    Ver}}    = lists:keysearch(version,    1, Comp),
 
263
    {value, {time,       Time}}   = lists:keysearch(time,       1, Comp),
 
264
    {Mod, [{vsn,              Vsn},
 
265
           {app_vsn,          AppVsn},
 
266
           {compiler_version, Ver},
 
267
           {compile_time,     Time}]}.
 
268
 
 
269
sys_info() ->
 
270
    SysArch = string:strip(erlang:system_info(system_architecture),right,$\n),
 
271
    SysVer  = string:strip(erlang:system_info(system_version),right,$\n),
 
272
    [{arch, SysArch}, {ver, SysVer}].
 
273
 
 
274
os_info() ->
 
275
    V = os:version(),
 
276
    case os:type() of
 
277
        {OsFam, OsName} ->
 
278
            [{fam, OsFam}, {name, OsName}, {ver, V}];
 
279
        OsFam ->
 
280
            [{fam, OsFam}, {ver, V}]
 
281
    end.
 
282
 
 
283
 
 
284
print_mods_info(Versions) ->
 
285
    case key1search(mod_info, Versions) of
 
286
        {value, ModsInfo} when is_list(ModsInfo) ->
 
287
            io:format("Module info: ~n", []),
 
288
            lists:foreach(fun print_mod_info/1, ModsInfo);
 
289
        _ ->
 
290
            io:format("Module info: Not found~n", []),
 
291
            not_found
 
292
    end.
 
293
 
 
294
tversion(T) ->
 
295
    L = tuple_to_list(T),
 
296
    lversion(L).
 
297
 
 
298
lversion([]) ->
 
299
    "";
 
300
lversion([A]) ->
 
301
    integer_to_list(A);
 
302
lversion([A|R]) ->
 
303
    integer_to_list(A) ++ "." ++ lversion(R).
 
304
 
 
305
print_mod_info({Module, Info}) ->
 
306
    % Maybe a asn1 generated module
 
307
    Asn1Vsn =
 
308
        case (catch Module:info()) of
 
309
            AI when is_list(AI) ->
 
310
                case (catch key1search(vsn, AI)) of
 
311
                    {value, V} when is_atom(V) ->
 
312
                        atom_to_list(V);
 
313
                    _ ->
 
314
                        "-"
 
315
                end;
 
316
            _ ->
 
317
                "-"
 
318
        end,
 
319
    Vsn =
 
320
        case key1search(vsn, Info) of
 
321
            {value, I} when is_integer(I) ->
 
322
                integer_to_list(I);
 
323
            _ ->
 
324
                "Not found"
 
325
        end,
 
326
    AppVsn =
 
327
        case key1search(app_vsn, Info) of
 
328
            {value, S1} when is_list(S1) ->
 
329
                S1;
 
330
            _ ->
 
331
                "Not found"
 
332
        end,
 
333
    CompVer =
 
334
        case key1search(compiler_version, Info) of
 
335
            {value, S2} when is_list(S2) ->
 
336
                S2;
 
337
            _ ->
 
338
                "Not found"
 
339
        end,
 
340
    CompDate =
 
341
        case key1search(compile_time, Info) of
 
342
            {value, {Year, Month, Day, Hour, Min, Sec}} ->
 
343
                lists:flatten(
 
344
                  io_lib:format("~w-~2..0w-~2..0w ~2..0w:~2..0w:~2..0w",
 
345
                                [Year, Month, Day, Hour, Min, Sec]));
 
346
            _ ->
 
347
                "Not found"
 
348
        end,
 
349
    io:format("   ~w:~n"
 
350
              "      Vsn:          ~s~n"
 
351
              "      App vsn:      ~s~n"
 
352
              "      ASN.1 vsn:    ~s~n"
 
353
              "      Compiler ver: ~s~n"
 
354
              "      Compile time: ~s~n",
 
355
              [Module, Vsn, AppVsn, Asn1Vsn, CompVer, CompDate]),
 
356
    ok.
 
357
 
 
358
 
 
359
key1search(Key, Vals) ->
 
360
    case lists:keysearch(Key, 1, Vals) of
 
361
        {value, {Key, Val}} ->
 
362
            {value, Val};
 
363
        false ->
 
364
            not_found
 
365
    end.
 
366
 
 
367
key1search(Key, Vals, Def) ->
 
368
    case key1search(Key, Vals) of
 
369
        not_found ->
 
370
            {value, Def};
 
371
        Value ->
 
372
            Value
 
373
    end.
 
374
 
 
375
 
151
376
%%--------------------------------------------------------------------
152
377
%% Function: service_names() -> [ServiceName]
153
378
%%  
158
383
service_names() ->
159
384
    [ftpc, tftpd, httpc, httpd].
160
385
 
 
386
 
 
387
%%-----------------------------------------------------------------
 
388
%% enable_trace(Level, Destination) -> void()
 
389
%%
 
390
%% Parameters:
 
391
%% Level -> max | min | integer()
 
392
%% Destination -> File | Port | io | {io, Verbosity} | HandlerSpec
 
393
%% File -> string()
 
394
%% Port -> integer()
 
395
%% Verbosity -> true | false
 
396
%% HandlerSpec = {function(), Data}
 
397
%% Data = term()
 
398
%%
 
399
%% Description:
 
400
%% This function is used to start tracing at level Level and send
 
401
%% the result either to the file File, the port Port or to a 
 
402
%% trace handler. 
 
403
%% Note that it starts a tracer server.
 
404
%% When Destination is the atom io (or the tuple {io, Verbosity}),
 
405
%% all (printable) inets trace events (trace_ts events which has
 
406
%% Severity withing Limit) will be written to stdout using io:format.
 
407
%%
 
408
%%-----------------------------------------------------------------
 
409
enable_trace(Level, File) when is_list(File) ->
 
410
    case file:open(File, [write]) of
 
411
        {ok, Fd} ->
 
412
            HandleSpec = {fun handle_trace/2, Fd},
 
413
            do_enable_trace(Level, process, HandleSpec);
 
414
        Err ->
 
415
            Err
 
416
    end;
 
417
enable_trace(Level, Port) when is_integer(Port) ->
 
418
    do_enable_trace(Level, port, dbg:trace_port(ip, Port));
 
419
enable_trace(Level, io) ->
 
420
    HandleSpec = {fun handle_trace/2, standard_io},
 
421
    do_enable_trace(Level, process, HandleSpec);
 
422
enable_trace(Level, {Fun, _Data} = HandleSpec) when is_function(Fun) ->
 
423
    do_enable_trace(Level, process, HandleSpec).
 
424
 
 
425
do_enable_trace(Level, Type, HandleSpec) ->
 
426
    case dbg:tracer(Type, HandleSpec) of
 
427
        {ok, _} ->
 
428
            set_trace(Level),
 
429
            ok;
 
430
        Error ->
 
431
            Error
 
432
    end.    
 
433
 
 
434
 
 
435
%%-----------------------------------------------------------------
 
436
%% disable_trace() -> void()
 
437
%%
 
438
%% Description:
 
439
%% This function is used to stop tracing.
 
440
%%-----------------------------------------------------------------
 
441
disable_trace() ->
 
442
    %% This is to make handle_trace/2 close the output file (if the
 
443
    %% event gets there before dbg closes)
 
444
    inets:report_event(100, "stop trace", stop_trace, [stop_trace]),  
 
445
    dbg:stop().
 
446
 
 
447
 
 
448
 
 
449
%%-----------------------------------------------------------------
 
450
%% set_trace(Level) -> void()
 
451
%%
 
452
%% Parameters:
 
453
%% Level -> max | min | integer()
 
454
%%
 
455
%% Description:
 
456
%% This function is used to change the trace level when tracing has
 
457
%% already been started.
 
458
%%-----------------------------------------------------------------
 
459
set_trace(Level) ->
 
460
    set_trace(Level, all).
 
461
 
 
462
set_trace(Level, Service) ->
 
463
    Pat = make_pattern(?MODULE, Service, Level),
 
464
    change_pattern(Pat).
 
465
 
 
466
make_pattern(Mod, Service, Level) 
 
467
  when is_atom(Mod) andalso is_atom(Service) ->
 
468
    case Level of
 
469
        min ->
 
470
            {Mod, Service, []};
 
471
        max ->
 
472
            Head = ['$1', '_', '_', '_'],
 
473
            Body = [],
 
474
            Cond = [],
 
475
            {Mod, Service, [{Head, Cond, Body}]};
 
476
        DetailLevel when is_integer(DetailLevel) ->
 
477
            Head = ['$1', '_', '_', '_'],
 
478
            Body = [],
 
479
            Cond = [{ '=<', '$1', DetailLevel}],
 
480
            {Mod, Service, [{Head, Cond, Body}]};
 
481
        _ ->
 
482
            exit({bad_level, Level})
 
483
    end.
 
484
 
 
485
change_pattern({Mod, Service, Pattern}) 
 
486
  when is_atom(Mod) andalso is_atom(Service) ->
 
487
    MFA = {Mod, report_event, 4},
 
488
    case Pattern of
 
489
        [] ->
 
490
            try
 
491
                error_to_exit(ctp, dbg:ctp(MFA)),
 
492
                error_to_exit(p,   dbg:p(all, clear))
 
493
            catch
 
494
                exit:{Where, Reason} ->
 
495
                    {error, {Where, Reason}}
 
496
            end;
 
497
        List when is_list(List) ->
 
498
            try
 
499
                error_to_exit(ctp, dbg:ctp(MFA)),
 
500
                error_to_exit(tp,  dbg:tp(MFA, Pattern)),
 
501
                error_to_exit(p,   dbg:p(all, [call, timestamp]))
 
502
            catch
 
503
                exit:{Where, Reason} ->
 
504
                    {error, {Where, Reason}}
 
505
            end;
 
506
        _ ->
 
507
            exit({bad_pattern, Pattern})
 
508
    end,
 
509
    ok.
 
510
 
 
511
error_to_exit(_Where, {ok, _} = OK) ->
 
512
    OK;
 
513
error_to_exit(Where, {error, Reason}) ->
 
514
    exit({Where, Reason}).
 
515
 
 
516
 
 
517
%%-----------------------------------------------------------------
 
518
%% report_event(Serverity, Label, Service, Content)
 
519
%%
 
520
%% Parameters:
 
521
%% Severity -> 0 =< integer() =< 100
 
522
%% Label -> string()
 
523
%% Service -> httpd | httpc | ftp | tftp
 
524
%% Content -> [{tag, term()}]
 
525
%%
 
526
%% Description:
 
527
%% This function is used to generate trace events, that is,  
 
528
%% put trace on this function.
 
529
%%-----------------------------------------------------------------
 
530
 
 
531
report_event(Severity, Label, Service, Content) 
 
532
  when (is_integer(Severity) andalso 
 
533
        (Severity >= 0) andalso (100 >= Severity)) andalso 
 
534
       is_list(Label) andalso 
 
535
       is_atom(Service) andalso 
 
536
       is_list(Content) ->
 
537
    hopefully_traced.
 
538
 
 
539
 
 
540
%% ----------------------------------------------------------------------
 
541
%% handle_trace(Event, Fd) -> Verbosity
 
542
%%
 
543
%% Parameters:
 
544
%% Event -> The trace event (only megaco 'trace_ts' events are printed)
 
545
%% Fd -> standard_io | file_descriptor() | trace_port()
 
546
%%
 
547
%% Description:
 
548
%% This function is used to "receive" and print the trace events.
 
549
%% Events are printed if:
 
550
%%   - Verbosity is max
 
551
%%   - Severity is =< Verbosity (e.g. Severity = 30, and Verbosity = 40)
 
552
%% Events are not printed if:
 
553
%%   - Verbosity is min
 
554
%%   - Severity is > Verbosity
 
555
%%-----------------------------------------------------------------
 
556
 
 
557
handle_trace(_, closed_file = Fd) ->
 
558
    Fd;
 
559
handle_trace({trace_ts, _Who, call,
 
560
              {?MODULE, report_event,
 
561
               [_Sev, "stop trace", stop_trace, [stop_trace]]},
 
562
              Timestamp},
 
563
             standard_io = Fd) ->
 
564
    (catch io:format(Fd, "stop trace at ~s~n", [format_timestamp(Timestamp)])),
 
565
    Fd;
 
566
handle_trace({trace_ts, _Who, call,
 
567
              {?MODULE, report_event,
 
568
               [_Sev, "stop trace", stop_trace, [stop_trace]]},
 
569
              Timestamp},
 
570
             Fd) ->
 
571
    (catch io:format(Fd, "stop trace at ~s~n", [format_timestamp(Timestamp)])),
 
572
    (catch file:close(Fd)),
 
573
    closed_file;
 
574
handle_trace({trace_ts, Who, call,
 
575
              {?MODULE, report_event,
 
576
               [Sev, Label, Service, Content]}, Timestamp},
 
577
             Fd) ->
 
578
    (catch print_inets_trace(Fd, Sev, Timestamp, Who, 
 
579
                             Label, Service, Content)),
 
580
    Fd;
 
581
handle_trace(Event, Fd) ->
 
582
    (catch print_trace(Fd, Event)),
 
583
    Fd.
 
584
 
 
585
 
 
586
print_inets_trace(Fd, Sev, Timestamp, Who, Label, Service, Content) ->
 
587
    Ts = format_timestamp(Timestamp),
 
588
    io:format(Fd, "[inets ~w trace ~w ~w ~s] ~s "
 
589
              "~n   Content: ~p"
 
590
              "~n",
 
591
              [Service, Sev, Who, Ts, Label, Content]).
 
592
 
 
593
 
 
594
print_trace(Fd, {trace, Who, What, Where}) ->
 
595
    io:format(Fd, "[trace]"
 
596
              "~n   Who:   ~p"
 
597
              "~n   What:  ~p"
 
598
              "~n   Where: ~p"
 
599
              "~n", [Who, What, Where]);
 
600
 
 
601
print_trace(Fd, {trace, Who, What, Where, Extra}) ->
 
602
    io:format(Fd, "[trace]"
 
603
              "~n   Who:   ~p"
 
604
              "~n   What:  ~p"
 
605
              "~n   Where: ~p"
 
606
              "~n   Extra: ~p"
 
607
              "~n", [Who, What, Where, Extra]);
 
608
 
 
609
print_trace(Fd, {trace_ts, Who, What, Where, When}) ->
 
610
    Ts = format_timestamp(When),
 
611
    io:format(Fd, "[trace ~s]"
 
612
              "~n   Who:   ~p"
 
613
              "~n   What:  ~p"
 
614
              "~n   Where: ~p"
 
615
              "~n", [Ts, Who, What, Where]);
 
616
 
 
617
print_trace(Fd, {trace_ts, Who, What, Where, Extra, When}) ->
 
618
    Ts = format_timestamp(When),
 
619
    io:format(Fd, "[trace ~s]"
 
620
              "~n   Who:   ~p"
 
621
              "~n   What:  ~p"
 
622
              "~n   Where: ~p"
 
623
              "~n   Extra: ~p"
 
624
              "~n", [Ts, Who, What, Where, Extra]);
 
625
 
 
626
print_trace(Fd, {seq_trace, What, Where}) ->
 
627
    io:format(Fd, "[seq trace]"
 
628
              "~n   What:       ~p"
 
629
              "~n   Where:      ~p"
 
630
              "~n", [What, Where]);
 
631
 
 
632
print_trace(Fd, {seq_trace, What, Where, When}) ->
 
633
    Ts = format_timestamp(When),
 
634
    io:format(Fd, "[seq trace ~s]"
 
635
              "~n   What:       ~p"
 
636
              "~n   Where:      ~p"
 
637
              "~n", [Ts, What, Where]);
 
638
 
 
639
print_trace(Fd, {drop, Num}) ->
 
640
    io:format(Fd, "[drop trace] ~p~n", [Num]);
 
641
 
 
642
print_trace(Fd, Trace) ->
 
643
    io:format(Fd, "[trace] "
 
644
              "~n   ~p"
 
645
              "~n", [Trace]).
 
646
 
 
647
 
 
648
format_timestamp({_N1, _N2, N3} = Now) ->
 
649
    {Date, Time}   = calendar:now_to_datetime(Now),
 
650
    {YYYY,MM,DD}   = Date,
 
651
    {Hour,Min,Sec} = Time,
 
652
    FormatDate =
 
653
        io_lib:format("~.4w:~.2.0w:~.2.0w ~.2.0w:~.2.0w:~.2.0w 4~w",
 
654
                      [YYYY,MM,DD,Hour,Min,Sec,round(N3/1000)]),
 
655
    lists:flatten(FormatDate).
 
656
 
 
657
 
161
658
%%--------------------------------------------------------------------
162
659
%%% Internal functions
163
660
%%--------------------------------------------------------------------