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

« back to all changes in this revision

Viewing changes to lib/sasl/src/rb.erl

  • Committer: Bazaar Package Importer
  • Author(s): Erlang Packagers, Sergei Golovan
  • Date: 2006-12-03 17:07:44 UTC
  • mfrom: (2.1.11 feisty)
  • Revision ID: james.westby@ubuntu.com-20061203170744-rghjwupacqlzs6kv
Tags: 1:11.b.2-4
[ Sergei Golovan ]
Fixed erlang-base and erlang-base-hipe prerm scripts.

Show diffs side-by-side

added added

removed removed

Lines of Context:
36
36
%%% Formats Error reports written by log_mf_h
37
37
%%%-----------------------------------------------------------------
38
38
 
39
 
-record(state, {dir, data, device, max, type}).
 
39
-record(state, {dir, data, device, max, type, abort, log}).
40
40
 
41
41
%%-----------------------------------------------------------------
42
42
%% Interface functions.
121
121
    io:format("      {type, ReportType}~n"),
122
122
    io:format("         - ReportType should be a supported type, 'all'~n"),
123
123
    io:format("         - or a list of supported types~n"),
124
 
    io:format("         - default: all~n").
 
124
    io:format("         - default: all~n"),
 
125
    io:format("      {abort_on_error, Bool}~n"),
 
126
    io:format("         - Bool: true | false~n"),
 
127
    io:format("         - default: false~n").
125
128
 
126
129
print_types() ->
127
130
    io:format("         - crash_report~n"),
138
141
    Dir = get_report_dir(Options),
139
142
    Max = get_option(Options, max, all),
140
143
    Type = get_option(Options, type, all),
 
144
    Abort = get_option(Options, abort_on_error, false),
141
145
    Data = scan_files(Dir ++ "/", Max, Type),
142
146
    {ok, #state{dir = Dir ++ "/", data = Data, device = Device,
143
 
                max = Max, type = Type}}.
 
147
                max = Max, type = Type, abort = Abort, log = Log}}.
144
148
 
145
 
%% (All those 'catch' are probably unnecessary now that we catch the
146
 
%% formatting in read_rep/4.)
147
149
handle_call({rescan, Options}, _From, State) ->
148
 
    Device = 
 
150
    {Device,Log1} = 
149
151
        case get_option(Options, start_log, {undefined}) of
150
 
            {undefined} -> State#state.device;
 
152
            {undefined} -> 
 
153
                {State#state.device,State#state.log};
151
154
            Log ->
152
155
                close_device(State#state.device),
153
 
                open_log_file(Log)
 
156
                {open_log_file(Log),Log}
154
157
        end,
155
158
    Max = get_option(Options, max, State#state.max),
156
159
    Type = get_option(Options, type, State#state.type),
 
160
    Abort = get_option(Options, abort_on_error, false),
157
161
    Data = scan_files(State#state.dir, Max, Type),
158
162
    NewState = State#state{data = Data, max = Max, type = Type,
159
 
                           device = Device},
 
163
                           device = Device, abort = Abort, log = Log1},
160
164
    {reply, ok, NewState};
161
165
handle_call(stop, _From, State) ->
162
166
    {stop, normal, stopped, State};
172
176
    close_device(State#state.device),
173
177
    {reply, ok, State#state{device = standard_io}};
174
178
handle_call({show_number, Number}, _From, State) ->
175
 
    #state{dir = Dir, data = Data, device = Device} = State,
176
 
    catch print_report(Dir, Data, Number, Device),
177
 
    {reply, ok, State};
 
179
    #state{dir = Dir, data = Data, device = Device, abort = Abort, log = Log} = State,
 
180
    NewDevice = print_report_by_num(Dir, Data, Number, Device, Abort, Log),
 
181
    {reply, ok, State#state{device = NewDevice}};
178
182
handle_call({show_type, Type}, _From, State) ->
179
 
    #state{dir = Dir, data = Data, device = Device} = State,
180
 
    catch print_typed_reports(Dir, Data, Type, Device),
181
 
    {reply, ok, State};
 
183
    #state{dir = Dir, data = Data, device = Device, abort = Abort, log = Log} = State,
 
184
    NewDevice = print_typed_reports(Dir, Data, Type, Device, Abort, Log),
 
185
    {reply, ok, State#state{device = NewDevice}};
182
186
handle_call(show, _From, State) ->
183
 
    #state{dir = Dir, data = Data, device = Device} = State,
184
 
    catch print_all_reports(Dir, Data, Device),
185
 
    {reply, ok, State};
 
187
    #state{dir = Dir, data = Data, device = Device, abort = Abort, log = Log} = State,
 
188
    NewDevice = print_all_reports(Dir, Data, Device, Abort, Log),
 
189
    {reply, ok, State#state{device = NewDevice}};
186
190
handle_call({grep, RegExp}, _From, State) ->
187
 
    #state{dir = Dir, data = Data, device = Device} = State,
188
 
    catch print_grep_reports(Dir, Data, RegExp, Device),
189
 
    {reply, ok, State}.
 
191
    #state{dir = Dir, data = Data, device = Device, abort = Abort, log = Log} = State,
 
192
    NewDevice = print_grep_reports(Dir, Data, RegExp, Device, Abort, Log),
 
193
    {reply, ok, State#state{device = NewDevice}}.
190
194
 
191
195
terminate(_Reason, #state{device = Device}) ->
192
196
    close_device(Device).
195
199
    {noreply, State}.
196
200
handle_info(_Info, State) ->
197
201
    {noreply, State}.
198
 
code_change(OldVsn, State, Extra) ->
 
202
code_change(_OldVsn, State, _Extra) ->
199
203
    {ok, State}.
200
204
 
201
205
%%-----------------------------------------------------------------
205
209
%%-----------------------------------------------------------------
206
210
open_log_file(standard_io) -> standard_io;
207
211
open_log_file(FileName) ->
208
 
    case file:open(FileName, write) of
 
212
    case file:open(FileName, [write,append]) of
209
213
        {ok, Fd} -> Fd;
210
214
        Error -> 
211
215
            io:format("rb: Cannot open file '~s' (~w).~n",
292
296
%%-----------------------------------------------------------------
293
297
scan_files(Dir, Files, Max, Type) ->
294
298
    scan_files(Dir, 1, Files, [], Max, Type).
295
 
scan_files(Dir, _, [], Res, Max, Type) -> Res;
296
 
scan_files(Dir, _, Files, Res, Max, Type) when Max =< 0 -> Res;
 
299
scan_files(_Dir, _, [], Res, _Max, _Type) -> Res;
 
300
scan_files(_Dir, _, _Files, Res, Max, _Type) when Max =< 0 -> Res;
297
301
scan_files(Dir, No, [H|T], Res, Max, Type) ->
298
302
    Data = get_report_data_from_file(Dir, No, H, Max, Type),
299
303
    Len = length(Data),
366
370
add_report_data([{Type, ShortDescr, Date, FilePos}|T], No, FName, Res) ->
367
371
    add_report_data(T, No+1, FName,
368
372
                    [{No, Type, ShortDescr, Date, FName, FilePos}|Res]);
369
 
add_report_data([], No, FName, Res) -> Res.
 
373
add_report_data([], _No, _FName, Res) -> Res.
370
374
 
371
375
read_reports(Fd, Res, Type) ->
372
376
    {ok, FilePos} = file:position(Fd, cur),
427
431
%% Update these functions with the reports that should be possible
428
432
%% to browse with rb.
429
433
%%-----------------------------------------------------------------
430
 
get_type({Time, {error_report, Pid, {_, crash_report, _}}}) ->
 
434
get_type({_Time, {error_report, _Pid, {_, crash_report, _}}}) ->
431
435
    crash_report;
432
 
get_type({Time, {error_report, Pid, {_, supervisor_report, _}}}) ->
 
436
get_type({_Time, {error_report, _Pid, {_, supervisor_report, _}}}) ->
433
437
    supervisor_report;
434
 
get_type({Time, {info_report, Pid, {_, progress, _}}}) ->
 
438
get_type({_Time, {info_report, _Pid, {_, progress, _}}}) ->
435
439
    progress;
436
 
get_type({Time, {Type, _, _}}) -> Type;
 
440
get_type({_Time, {Type, _, _}}) -> Type;
437
441
get_type(_) -> unknown.
438
442
 
439
443
get_short_descr({{Date, Time}, {error_report, Pid, {_, crash_report, Rep}}}) ->
442
446
        case lists:keysearch(registered_name, 1, OwnRep) of
443
447
            {value, {_Key, []}} ->
444
448
                case lists:keysearch(initial_call, 1, OwnRep) of
445
 
                    {value, {_K, {M,F,A}}} -> M;
 
449
                    {value, {_K, {M,_F,_A}}} -> M;
446
450
                    _ -> Pid
447
451
                end;
448
452
            {value, {_Key, N}} -> N;
458
462
        end,
459
463
    NameStr = lists:flatten(io_lib:format("~w", [Name])),
460
464
    {NameStr, date_str(Date,Time)};
461
 
get_short_descr({{Date, Time}, {Type, Pid, _}}) ->
 
465
get_short_descr({{Date, Time}, {_Type, Pid, _}}) ->
462
466
    NameStr = lists:flatten(io_lib:format("~w", [Pid])),
463
467
    {NameStr, date_str(Date,Time)};
464
468
get_short_descr(_) ->
468
472
    case application:get_env(sasl,utc_log) of 
469
473
        {ok,true} ->
470
474
            {{YY,MoMo,DD},{HH,MiMi,SS}} = 
471
 
                calendar:local_time_to_universal_time({Date,Time}),
 
475
                local_time_to_universal_time({Date,Time}),
472
476
            lists:flatten(io_lib:format("~w-~2.2.0w-~2.2.0w ~2.2.0w:"
473
477
                                        "~2.2.0w:~2.2.0w UTC", 
474
478
                                        [YY,MoMo,DD,HH,MiMi,SS]));
478
482
                                        [Y,Mo,D,H,Mi,S]))
479
483
    end.
480
484
 
481
 
 
 
485
local_time_to_universal_time({Date,Time}) ->
 
486
    case calendar:local_time_to_universal_time_dst({Date,Time}) of
 
487
        [UCT] ->
 
488
            UCT;
 
489
        [UCT1,_UCT2] ->
 
490
            UCT1;
 
491
        [] -> % should not happen
 
492
            {Date,Time}
 
493
    end.
482
494
 
483
495
 
484
496
print_list(Data, Type) ->
509
521
        true -> find_date_width(T, Width)
510
522
    end.
511
523
 
512
 
print_one_report({No, RealType, ShortDescr, Date, Fname, FilePosition},
 
524
print_one_report({No, RealType, ShortDescr, Date, _Fname, _FilePos},
513
525
                 WantedType,
514
526
                 Width, DateWidth) ->
515
527
    if
529
541
                       io_lib:format("~s", [ShortDescr]),
530
542
                       Date]).
531
543
 
532
 
print_typed_reports(Dir, [], Type, Device) ->
533
 
    ok;
534
 
print_typed_reports(Dir, Data, Type, Device) ->
535
 
    case element(2, hd(Data)) of
536
 
        Type -> print_report(Dir, Data, element(1, hd(Data)), Device);
537
 
        _ -> ok
538
 
    end,
539
 
    print_typed_reports(Dir, tl(Data), Type, Device).    
540
 
 
541
 
print_all_reports(Dir, [], Device) ->
542
 
    ok;
543
 
print_all_reports(Dir, Data, Device) ->
544
 
    print_report(Dir, Data, element(1, hd(Data)), Device),
545
 
    print_all_reports(Dir, tl(Data), Device).    
546
 
 
547
 
print_report(Dir, Data, Number, Device) ->
548
 
    {Fname, FilePosition, Type} = find_report(Data, Number),
549
 
    FileName = lists:concat([Dir, Fname]),
550
 
    case file:open(FileName, read) of
551
 
        {ok, Fd} -> read_rep(Fd, FilePosition, Type, Device);
552
 
        _ -> io:format("rb: can't open file ~p~n", [Fname])
553
 
    end.
554
 
 
555
 
find_report([{No, Type, ShortDescr, Date, Fname, FilePosition}|T], No) ->
556
 
    {Fname, FilePosition, Type};
557
 
find_report([H|T], No) -> find_report(T, No);
 
544
print_report_by_num(Dir, Data, Number, Device, Abort, Log) ->
 
545
    {_,Device1} = print_report(Dir, Data, Number, Device, Abort, Log),
 
546
    Device1.
 
547
    
 
548
print_typed_reports(_Dir, [], _Type, Device, _Abort, _Log) ->
 
549
    Device;
 
550
print_typed_reports(Dir, Data, Type, Device, Abort, Log) ->
 
551
    {Next,Device1} = 
 
552
        case element(2, hd(Data)) of
 
553
            Type -> 
 
554
                print_report(Dir, Data, element(1, hd(Data)), Device, Abort, Log);
 
555
            _ -> 
 
556
                {proceed,Device}
 
557
        end,
 
558
    if Next == abort ->
 
559
            Device1;
 
560
       true ->
 
561
            print_typed_reports(Dir, tl(Data), Type, Device1, Abort, Log)
 
562
    end.
 
563
 
 
564
print_all_reports(_Dir, [], Device, _Abort, _Log) ->
 
565
    Device;
 
566
print_all_reports(Dir, Data, Device, Abort, Log) ->
 
567
    {Next,Device1} = print_report(Dir, Data, element(1, hd(Data)), 
 
568
                                  Device, Abort, Log),
 
569
    if Next == abort ->
 
570
            Device1;
 
571
       true ->
 
572
            print_all_reports(Dir, tl(Data), Device1, Abort, Log)
 
573
    end.
 
574
 
 
575
print_report(Dir, Data, Number, Device, Abort, Log) ->
 
576
    case find_report(Data, Number) of
 
577
        {Fname, FilePosition} ->
 
578
            FileName = lists:concat([Dir, Fname]),
 
579
            case file:open(FileName, read) of
 
580
                {ok, Fd} -> 
 
581
                    read_rep(Fd, FilePosition, Device, Abort, Log);
 
582
                _ -> 
 
583
                    io:format("rb: can't open file ~p~n", [Fname]),
 
584
                    {proceed,Device}
 
585
            end;
 
586
        no_report ->
 
587
            {proceed,Device}
 
588
    end.
 
589
 
 
590
find_report([{No, _Type, _Descr, _Date, Fname, FilePosition}|_T], No) ->
 
591
    {Fname, FilePosition};
 
592
find_report([_H|T], No) -> 
 
593
    find_report(T, No);
558
594
find_report([], No) ->
559
 
    io:format("There is no report with number ~p.~n", [No]).
 
595
    io:format("There is no report with number ~p.~n", [No]),
 
596
    no_report.
560
597
    
561
 
print_grep_reports(Dir, [], RegExp, Device) ->
562
 
    ok;
563
 
print_grep_reports(Dir, Data, RegExp, Device) ->
564
 
    print_grep_report(Dir, Data, element(1, hd(Data)), Device, RegExp),
565
 
    print_grep_reports(Dir, tl(Data), RegExp, Device).    
 
598
print_grep_reports(_Dir, [], _RegExp, Device, _Abort, _Log) ->
 
599
    Device;
 
600
print_grep_reports(Dir, Data, RegExp, Device, Abort, Log) ->
 
601
    {Next,Device1} = print_grep_report(Dir, Data, element(1, hd(Data)), 
 
602
                                       Device, RegExp, Abort, Log),
 
603
    if Next == abort ->
 
604
            Device1;
 
605
       true ->
 
606
            print_grep_reports(Dir, tl(Data), RegExp, Device1, Abort, Log)
 
607
    end.
566
608
 
567
 
print_grep_report(Dir, Data, Number, Device, RegExp) ->
568
 
    {Fname, FilePosition, Type} = find_report(Data, Number),
 
609
print_grep_report(Dir, Data, Number, Device, RegExp, Abort, Log) ->
 
610
    {Fname, FilePosition} = find_report(Data, Number),
569
611
    FileName = lists:concat([Dir, Fname]),
570
612
    case file:open(FileName, read) of
571
613
        {ok, Fd} when pid(Fd) -> 
572
 
            check_rep(Fd, FilePosition, Type, Device, RegExp, Number);
 
614
            check_rep(Fd, FilePosition, Device, RegExp, Number, Abort, Log);
573
615
        _ -> 
574
 
            io:format("rb: can't open file ~p~n", [Fname])
 
616
            io:format("rb: can't open file ~p~n", [Fname]),
 
617
            {proceed,Device}
575
618
    end.
576
619
 
577
 
check_rep(Fd, FilePosition, Type, Device, RegExp, Number) ->
578
 
    case read_rep_msg(Fd, FilePosition, Type) of
 
620
check_rep(Fd, FilePosition, Device, RegExp, Number, Abort, Log) ->
 
621
    case read_rep_msg(Fd, FilePosition) of
579
622
        {Date, Msg} ->
580
623
            MsgStr = lists:flatten(io_lib:format("~p",[Msg])),
581
624
            case regexp:match(MsgStr, RegExp) of
582
625
                {match, _, _} ->
583
626
                    io:format("Found match in report number ~w~n", [Number]),
584
 
                    rb_format_supp:print(Date, Msg, Device);
585
 
                _ -> false
 
627
                    case catch rb_format_supp:print(Date, Msg, Device) of
 
628
                        {'EXIT', _} ->
 
629
                            handle_bad_form(Date, Msg, Device, Abort, Log);
 
630
                        _ ->
 
631
                            {proceed,Device}
 
632
                    end;                
 
633
                _ ->
 
634
                    {proceed,Device}
586
635
            end;
587
636
        _ ->
588
 
            io:format("rb: Cannot read from file~n")
 
637
            io:format("rb: Cannot read from file~n"),
 
638
            {proceed,Device}
589
639
    end.
590
640
 
591
 
read_rep(Fd, FilePosition, Type, Device) ->
592
 
    case read_rep_msg(Fd, FilePosition, Type) of
 
641
read_rep(Fd, FilePosition, Device, Abort, Log) ->
 
642
    case read_rep_msg(Fd, FilePosition) of
593
643
        {Date, Msg} ->
594
644
            case catch rb_format_supp:print(Date, Msg, Device) of
595
645
                {'EXIT', _} ->
596
 
                    io:format(Device, "ERROR: ~p ~p~n", [Date, Msg]);
 
646
                    handle_bad_form(Date, Msg, Device, Abort, Log);
597
647
                _ ->
598
 
                    ok
 
648
                    {proceed,Device}
599
649
            end;
600
650
        _ -> 
601
 
            io:format("rb: Cannot read from file~n")
 
651
            io:format("rb: Cannot read from file~n"),
 
652
            {proceed,Device}
602
653
    end.
603
654
    
604
 
read_rep_msg(Fd, FilePosition, Type) ->
 
655
handle_bad_form(Date, Msg, Device, Abort, Log) ->
 
656
    io:format("rb: ERROR! A report on bad form was encountered. " ++
 
657
              "It can not be printed to the log.~n~n"),
 
658
    io:format("Details:~n~p ~p~n~n", [Date,Msg]),
 
659
    case {Abort,Device,open_log_file(Log)} of
 
660
        {true,standard_io,standard_io} ->
 
661
            io:format("rb: Logging aborted.~n"),
 
662
            {abort,Device};
 
663
        {false,standard_io,standard_io} ->
 
664
            io:format("rb: Logging resumed...~n~n"),
 
665
            {proceed,Device};
 
666
        {_,_,standard_io} ->
 
667
            io:format("rb: Can not reopen ~p. Logging aborted.~n", [Log]),
 
668
            {abort,Device};
 
669
        {true,_,NewDevice} ->
 
670
            io:format(NewDevice,
 
671
                      "~n~n************************* RB ERROR ************************~n" ++
 
672
                      "A report on bad form was encountered here and the logging~n" ++
 
673
                      "process was aborted. Note that there may well be remaining~n" ++
 
674
                      "reports that haven't yet been logged. Please see the rb~n" ++
 
675
                      "manual for more info.~n" ++
 
676
                      "***********************************************************~n", []),
 
677
            io:format("rb: Logging aborted.~n"),
 
678
            {abort,NewDevice};
 
679
        {false,_,NewDevice} ->
 
680
            io:format(NewDevice, 
 
681
                      "~n   ********* RB: UNPRINTABLE REPORT ********~n~n", []),
 
682
            io:format("rb: Logging resumed...~n~n"),        
 
683
            {proceed,NewDevice}
 
684
    end.
 
685
 
 
686
read_rep_msg(Fd, FilePosition) ->
605
687
    file:position(Fd, {bof, FilePosition}),
606
688
    Res = 
607
689
        case catch read_report(Fd) of