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

« back to all changes in this revision

Viewing changes to lib/debugger/src/int.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:
64
64
%% link/1 and spawn_link/1), and external code which is not
65
65
%% interpreted.
66
66
%%
67
 
%% dbg_icmd, dbg_ieval, dbg_imeta
68
 
%% ------------------------------
 
67
%% dbg_icmd, dbg_ieval
 
68
%% -------------------
69
69
%% Code for the meta process.
70
70
%%
71
71
%% dbg_iserver
87
87
%%====================================================================
88
88
 
89
89
%%--------------------------------------------------------------------
90
 
%% i(AbsMods)
91
 
%% i(AbsMods, Options) -> {module,Mod} | error
92
 
%% ni(AbsMods)
93
 
%% ni(AbsMods, Options) -> {module,Mod} | error
 
90
%% i(AbsMods) -> {module,Mod} | error | ok
 
91
%% ni(AbsMods) -> {module,Mod} | error | ok
94
92
%%   AbsMods = AbsMod | [AbsMod]
95
93
%%     AbsMod = atom() | string()
96
94
%%     Mod = atom()
101
99
ni(AbsMods) -> i2(AbsMods, distributed).
102
100
ni(AbsMods, _Options) -> i2(AbsMods, distributed).
103
101
    
104
 
i2([AbsMod|AbsMods], Dist) when atom(AbsMod); list(AbsMod) ->
 
102
i2([AbsMod|AbsMods], Dist) when is_atom(AbsMod); is_list(AbsMod) ->
105
103
    int_mod(AbsMod, Dist),
106
104
    i2(AbsMods, Dist);
107
 
i2([AbsMod], Dist) when atom(AbsMod); list(AbsMod) ->
108
 
    int_mod(AbsMod, Dist);
109
 
i2(AbsMod, Dist) when atom(AbsMod); list(AbsMod) ->
 
105
i2([AbsMod], Dist) when is_atom(AbsMod); is_list(AbsMod) ->
110
106
    int_mod(AbsMod, Dist);
111
107
i2([], _Dist) ->
112
 
    error.
 
108
    ok;
 
109
i2(AbsMod, Dist) when is_atom(AbsMod); is_list(AbsMod) ->
 
110
    int_mod(AbsMod, Dist).
113
111
 
114
112
%%--------------------------------------------------------------------
115
113
%% n(AbsMods) -> ok
118
116
n(AbsMods) -> n2(AbsMods, local).
119
117
nn(AbsMods) -> n2(AbsMods, distributed).
120
118
 
121
 
n2([AbsMod|AbsMods], Dist) when atom(AbsMod); list(AbsMod) ->
 
119
n2([AbsMod|AbsMods], Dist) when is_atom(AbsMod); is_list(AbsMod) ->
122
120
    del_mod(AbsMod, Dist),
123
121
    n2(AbsMods, Dist);
124
 
n2([AbsMod], Dist) when atom(AbsMod); list(AbsMod) ->
125
 
    del_mod(AbsMod, Dist);
126
 
n2(AbsMod, Dist) when atom(AbsMod); list(AbsMod) ->
 
122
n2([AbsMod], Dist) when is_atom(AbsMod); is_list(AbsMod) ->
127
123
    del_mod(AbsMod, Dist);
128
124
n2([], _Dist) ->
129
 
    error.
 
125
    ok;
 
126
n2(AbsMod, Dist) when is_atom(AbsMod); is_list(AbsMod) ->
 
127
    del_mod(AbsMod, Dist).
130
128
 
131
129
%%--------------------------------------------------------------------
132
130
%% interpreted() -> [Mod]
139
137
%%   Mod = atom()
140
138
%%   File = string()
141
139
%%--------------------------------------------------------------------
142
 
file(Mod) when atom(Mod) ->
 
140
file(Mod) when is_atom(Mod) ->
143
141
    dbg_iserver:safe_call({file, Mod}).
144
142
 
145
143
%%--------------------------------------------------------------------
146
 
%% interpretable(File) -> true | {error, Reason}
147
 
%%   File = string()
148
 
%%   Reason = no_src | no_beam | no_debug_info | badarg
 
144
%% interpretable(AbsMod) -> true | {error, Reason}
 
145
%%   AbsMod = Mod | File
 
146
%%   Reason = no_src | no_beam | no_debug_info | badarg | {app, App}
149
147
%%--------------------------------------------------------------------
150
 
interpretable(File) when list(File) ->
151
 
    case check_file(File) of
152
 
        {ok, _Res} -> true;
153
 
        Error -> Error
154
 
    end;
155
 
interpretable(Mod) when atom(Mod) ->
156
 
    case check_module(Mod) of
 
148
interpretable(AbsMod) ->
 
149
    case check(AbsMod) of
157
150
        {ok, _Res} -> true;
158
151
        Error -> Error
159
152
    end.
179
172
    auto_attach(false);
180
173
auto_attach(Flags, {Mod, Func}) ->
181
174
    auto_attach(Flags, {Mod, Func, []});
182
 
auto_attach(Flags, {Mod, Func, Args}) when atom(Mod),atom(Func),list(Args) ->
 
175
auto_attach(Flags, {Mod, Func, Args}) when is_atom(Mod),is_atom(Func),is_list(Args) ->
183
176
    check_flags(Flags),
184
177
    dbg_iserver:safe_cast({set_auto_attach, Flags, {Mod, Func, Args}}).
185
178
 
234
227
%%       Status = active | inactive
235
228
%%       Cond = null | Function
236
229
%%--------------------------------------------------------------------
237
 
break(Mod, Line) when atom(Mod), integer(Line) ->
 
230
break(Mod, Line) when is_atom(Mod), is_integer(Line) ->
238
231
    dbg_iserver:safe_call({new_break, {Mod, Line},
239
232
                           [active, enable, null, null]}).
240
233
 
241
 
delete_break(Mod, Line) when atom(Mod), integer(Line) ->
 
234
delete_break(Mod, Line) when is_atom(Mod), is_integer(Line) ->
242
235
    dbg_iserver:safe_cast({delete_break, {Mod, Line}}).
243
236
 
244
 
break_in(Mod, Func, Arity) when atom(Mod), atom(Func), integer(Arity) ->
 
237
break_in(Mod, Func, Arity) when is_atom(Mod), is_atom(Func), is_integer(Arity) ->
245
238
    case dbg_iserver:safe_call({is_interpreted, Mod, Func, Arity}) of
246
239
        {true, Clauses} ->
247
240
            Lines = first_lines(Clauses),
250
243
            {error, function_not_found}
251
244
    end.
252
245
 
253
 
del_break_in(Mod, Func, Arity) when atom(Mod), atom(Func), integer(Arity) ->
 
246
del_break_in(Mod, Func, Arity) when is_atom(Mod), is_atom(Func), is_integer(Arity) ->
254
247
    case dbg_iserver:safe_call({is_interpreted, Mod, Func, Arity}) of
255
248
        {true, Clauses} ->
256
249
            Lines = first_lines(Clauses),
267
260
no_break() ->
268
261
    dbg_iserver:safe_cast(no_break).
269
262
 
270
 
no_break(Mod) when atom(Mod) ->
 
263
no_break(Mod) when is_atom(Mod) ->
271
264
    dbg_iserver:safe_cast({no_break, Mod}).
272
265
 
273
 
disable_break(Mod, Line) when atom(Mod), integer(Line) ->
 
266
disable_break(Mod, Line) when is_atom(Mod), is_integer(Line) ->
274
267
    dbg_iserver:safe_cast({break_option, {Mod, Line}, status, inactive}).
275
268
    
276
 
enable_break(Mod, Line) when atom(Mod), integer(Line) ->
 
269
enable_break(Mod, Line) when is_atom(Mod), is_integer(Line) ->
277
270
    dbg_iserver:safe_cast({break_option, {Mod, Line}, status, active}).
278
271
 
279
 
action_at_break(Mod, Line, Action) when atom(Mod), integer(Line) ->
 
272
action_at_break(Mod, Line, Action) when is_atom(Mod), is_integer(Line) ->
280
273
    check_action(Action),
281
274
    dbg_iserver:safe_cast({break_option, {Mod, Line}, action, Action}).
282
275
 
284
277
check_action(disable) -> true;
285
278
check_action(delete) -> true.
286
279
 
287
 
test_at_break(Mod, Line, Function) when atom(Mod), integer(Line) ->
 
280
test_at_break(Mod, Line, Function) when is_atom(Mod), is_integer(Line) ->
288
281
    check_function(Function),
289
282
    dbg_iserver:safe_cast({break_option, {Mod, Line}, condition, Function}).
290
283
 
291
 
check_function({Mod, Func}) when atom(Mod), atom(Func) -> true.
 
284
check_function({Mod, Func}) when is_atom(Mod), is_atom(Func) -> true.
292
285
 
293
286
get_binding(Var, Bs) ->
294
287
    dbg_icmd:get_binding(Var, Bs).
295
288
 
296
289
all_breaks() ->
297
290
    dbg_iserver:safe_call(all_breaks).
298
 
all_breaks(Mod) when atom(Mod) ->
 
291
all_breaks(Mod) when is_atom(Mod) ->
299
292
    dbg_iserver:safe_call({all_breaks, Mod}).
300
293
 
301
294
%%--------------------------------------------------------------------
330
323
            Error
331
324
    end.
332
325
    
333
 
continue(X, Y, Z) when integer(X), integer(Y), integer(Z) ->
 
326
continue(X, Y, Z) when is_integer(X), is_integer(Y), is_integer(Z) ->
334
327
    continue(c:pid(X, Y, Z)).
335
328
 
336
329
 
436
429
meta(Meta, finish) -> dbg_icmd:finish(Meta);
437
430
meta(Meta, skip) -> dbg_icmd:skip(Meta);
438
431
meta(Meta, timeout) -> dbg_icmd:timeout(Meta);
439
 
meta(Meta, stop) -> dbg_icmd:stop(Meta, self());
 
432
meta(Meta, stop) -> dbg_icmd:stop(Meta);
440
433
meta(Meta, messages) -> dbg_icmd:get(Meta, messages, null).
441
434
 
442
435
meta(Meta, trace, Trace) -> dbg_icmd:set(Meta, trace, Trace);
485
478
int_mod(AbsMod, Dist) ->
486
479
    case check(AbsMod) of
487
480
        {ok, Res} -> load(Res, Dist);
 
481
        {error, {app, App}} ->
 
482
            io:format("** Cannot interpret ~p module: ~p~n",
 
483
                      [App, AbsMod]),
 
484
            error;
488
485
        _Error ->
489
486
            io:format("** Invalid beam file or no abstract code: ~p\n",
490
487
                      [AbsMod]),
491
488
            error
492
489
    end.
493
490
 
494
 
check(Mod) when atom(Mod) -> check_module(Mod);
495
 
check(File) when list(File) -> check_file(File).
 
491
check(Mod) when is_atom(Mod) -> catch check_module(Mod);
 
492
check(File) when is_list(File) -> catch check_file(File).
496
493
 
497
494
load({Mod, Src, Beam, Exp, Abst}, Dist) ->
498
495
    everywhere(Dist,
499
496
               fun() ->
500
497
                       code:purge(Mod),
501
498
                       erts_debug:breakpoint({Mod,'_','_'}, false),
502
 
                       {module,Mod} = code:load_abs(filename:rootname(Beam))
 
499
                       {module,Mod} = code:load_abs(filename:rootname(Beam),
 
500
                                                    Mod)
503
501
               end),
504
502
    {ok, SrcBin} = file:read_file(Src),
505
503
    {ok, BeamBin} = file:read_file(Beam),
514
512
 
515
513
check_module(Mod) ->
516
514
    case code:which(Mod) of
517
 
        Beam when list(Beam) ->
 
515
        Beam when is_list(Beam) ->
518
516
            case find_src(Beam) of
519
 
                Src when list(Src) ->
 
517
                Src when is_list(Src) ->
 
518
                    check_application(Src),
520
519
                    case check_beam(Beam) of
521
520
                        {ok, Exp, Abst} ->
522
521
                            {ok, {Mod, Src, Beam, Exp, Abst}};
538
537
                  end
539
538
          end,
540
539
    if
541
 
        list(Src) ->
542
 
            Mod = list_to_atom(filename:basename(Src, ".erl")),
 
540
        is_list(Src) ->
 
541
            check_application(Src),
 
542
            Mod = scan_module_name(Src),
543
543
            case find_beam(Mod, Src) of
544
 
                Beam when list(Beam) ->
 
544
                Beam when is_list(Beam) ->
545
545
                    case check_beam(Beam) of
546
546
                        {ok, Exp, Abst} ->
547
547
                            {ok, {Mod, Src, Beam, Exp, Abst}};
552
552
        true -> {error, badarg}
553
553
    end.
554
554
 
 
555
%% Try to avoid interpreting a kernel, stdlib, gs or debugger module.
 
556
check_application(Src) ->
 
557
    case lists:reverse(filename:split(filename:absname(Src))) of
 
558
        [_Mod,"src",AppS|_] ->
 
559
            check_application2(AppS);
 
560
        _ -> ok
 
561
    end.
 
562
check_application2("kernel-"++_) -> throw({error,{app,kernel}});
 
563
check_application2("stdlib-"++_) -> throw({error,{app,stdlib}});
 
564
check_application2("gs-"++_) -> throw({error,{app,gs}});
 
565
check_application2("debugger-"++_) -> throw({error,{app,debugger}});
 
566
check_application2(_) -> ok.
 
567
 
555
568
find_src(Beam) ->
556
569
    Src0 = filename:rootname(Beam) ++ ".erl",
557
570
    case is_file(Src0) of
567
580
    end.
568
581
 
569
582
find_beam(Mod, Src) ->
570
 
    ModS = atom_to_list(Mod),
571
583
    SrcDir = filename:dirname(Src),
572
 
    EbinDir = filename:join(filename:dirname(SrcDir), "ebin"),
573
 
    CodePath = [SrcDir, EbinDir | code:get_path()],
 
584
    BeamFile = packages:last(Mod) ++ code_aux:objfile_extension(),
 
585
    File = filename:join(SrcDir, BeamFile),
 
586
    case is_file(File) of
 
587
        true -> File;
 
588
        false -> find_beam_1(Mod, SrcDir)
 
589
    end.
 
590
 
 
591
find_beam_1(Mod, SrcDir) ->
 
592
    RootDir = find_root_dir(SrcDir, packages:first(Mod)),
 
593
    EbinDir = filename:join(RootDir, "ebin"),
 
594
    CodePath = [EbinDir | code:get_path()],
 
595
    BeamFile = code_aux:to_path(Mod) ++ code_aux:objfile_extension(),
574
596
    lists:foldl(fun(_, Beam) when is_list(Beam) -> Beam;
575
597
                   (Dir, error) ->
576
 
                        File = filename:join(Dir, ModS)++".beam",
 
598
                        File = filename:join(Dir, BeamFile),
577
599
                        case is_file(File) of
578
600
                            true -> File;
579
601
                            false -> error
582
604
                error,
583
605
                CodePath).
584
606
 
 
607
find_root_dir(Dir, [_|Ss]) ->
 
608
    find_root_dir(filename:dirname(Dir), Ss);
 
609
find_root_dir(Dir, []) ->
 
610
    filename:dirname(Dir).
 
611
 
585
612
check_beam(Beam) ->
586
 
    case beam_lib:chunks(Beam, [exports,"Abst"]) of
587
 
        {ok, {_Mod, [{exports, Exp}, {"Abst", Abst}]}} when Abst/=<<>> ->
588
 
            {ok, Exp, Abst};
 
613
    case beam_lib:chunks(Beam, [abstract_code,exports]) of
 
614
        {ok,{_Mod,[{abstract_code,no_abstract_code}|_]}} ->
 
615
            error;
 
616
        {ok,{_Mod,[{abstract_code,Abst},{exports,Exp}]}} ->
 
617
            {ok,Exp,Abst};
589
618
        _ -> error
590
619
    end.
591
620
 
605
634
everywhere(local, Fun) ->
606
635
    Fun().
607
636
 
 
637
scan_module_name(File) ->
 
638
    case file:open(File, [read]) of
 
639
        {ok, FD} ->
 
640
            R = (catch {ok, scan_module_name_1(FD)}),
 
641
            file:close(FD),
 
642
            case R of
 
643
                {ok, A} when is_atom(A) -> A;
 
644
                _ -> error
 
645
            end;
 
646
        _ ->
 
647
            error
 
648
    end.
 
649
 
 
650
scan_module_name_1(FD) ->
 
651
    case io:scan_erl_form(FD, "") of
 
652
        {ok, Ts, _} ->
 
653
            scan_module_name_2(Ts, FD);
 
654
        _ ->
 
655
            error
 
656
    end.
 
657
 
 
658
scan_module_name_2([{'-',_},{atom,_,module},{'(',_} | _]=Ts, _FD) ->
 
659
    scan_module_name_3(Ts);
 
660
scan_module_name_2([{'-',_},{atom,_,_} | _], FD) ->
 
661
    scan_module_name_1(FD);
 
662
scan_module_name_2(_, _) ->
 
663
    error.
 
664
 
 
665
scan_module_name_3(Ts) ->
 
666
    case erl_parse:parse_form(Ts) of
 
667
        {ok, {attribute,_,module,{M,_}}} -> module_atom(M);
 
668
        {ok, {attribute,_,module,M}} -> module_atom(M);
 
669
        _ -> error
 
670
    end.
 
671
 
 
672
module_atom(A) when is_atom(A) -> A;
 
673
module_atom(L) when is_list(L) -> list_to_atom(packages:concat(L)).
 
674
 
608
675
%%--Stop interpreting modules-----------------------------------------
609
676
 
610
677
del_mod(AbsMod, Dist) ->
611
678
    Mod = if
612
 
              atom(AbsMod) -> AbsMod;
613
 
              list(AbsMod) -> list_to_atom(filename:basename(AbsMod,".erl"))
 
679
              is_atom(AbsMod) -> AbsMod;
 
680
              is_list(AbsMod) ->
 
681
                  list_to_atom(filename:basename(AbsMod,".erl"))
614
682
          end,
615
683
    dbg_iserver:safe_cast({delete, Mod}),
616
684
    everywhere(Dist,