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

« back to all changes in this revision

Viewing changes to lib/debugger/src/dbg_debugged.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:
20
20
%% External exports
21
21
-export([eval/3]).
22
22
 
23
 
%% Internal exports
24
 
-export([follow/4]).
25
 
 
26
 
%-define(DBGDBG, 1).
27
 
-ifdef(DBGDBG).
28
 
-define(DBG(F,A), io:format("~p~p[~p]:" ++ F,[self(),?MODULE,?LINE] ++ A)).
29
 
-else.
30
 
-define(DBG(F,A), ok).
31
 
-endif.
32
 
 
33
23
%%====================================================================
34
24
%% External exports
35
25
%%====================================================================
37
27
%%--------------------------------------------------------------------
38
28
%% eval(Mod, Func, Args) -> Value
39
29
%% Main entry point from external (non-interpreted) code.
40
 
%% Called via the error handler when a breakpoint is hit.
 
30
%% Called via the error handler.
41
31
%%--------------------------------------------------------------------
42
32
eval(Mod, Func, Args) ->
43
 
    Meta = dbg_imeta:eval(Mod, Func, Args),
44
 
    msg(Meta).
45
 
 
46
 
%%====================================================================
47
 
%% Internal exports
48
 
%%====================================================================
49
 
 
50
 
follow(_Fol, M, F, As) ->
51
 
    apply(M, F, As).
52
 
 
 
33
    SaveStacktrace = erlang:get_stacktrace(),
 
34
    Meta = dbg_ieval:eval(Mod, Func, Args),
 
35
    Mref = erlang:monitor(process, Meta),
 
36
    msg_loop(Meta, Mref, SaveStacktrace).
53
37
 
54
38
%%====================================================================
55
39
%% Internal functions
56
40
%%====================================================================
57
41
 
58
 
msg(Meta) ->
59
 
    case catch msg_loop(Meta) of
60
 
        {ready,Meta,Value} ->
61
 
            ?DBG("Result~n",[]),
62
 
            Value;
63
 
        {'EXIT',Reason0} ->
64
 
            ?DBG("EXIT ~p~n",[Reason0]),
65
 
            Reason = remove_debugger_calls(Reason0),
66
 
            Meta ! {sys,self(),{exited_nocatch,Reason}},
67
 
            wait_exit(Meta);
68
 
        {'EXIT',Meta,Reason} ->
69
 
            ?DBG("EXIT ~p~n",[Reason]),
70
 
            exit(Reason);
71
 
        Thrown ->
72
 
            ?DBG("Thrown ~p~n",[Thrown]),
73
 
            Meta ! {sys,self(),{thrown_nocatch,Thrown}},
74
 
            throw(Thrown)
75
 
    end.
76
 
 
77
 
msg_loop(Meta) ->
78
 
    receive
79
 
        {sys,Meta,Command} ->
80
 
            ?DBG("Command~p~n",[Command]),
81
 
            handle_command(Meta, Command);
82
 
        {'EXIT',Meta,Reason} ->
83
 
            {'EXIT',Meta,Reason}
84
 
    end.
85
 
 
86
 
handle_command(Meta, {ready,Val}) ->
87
 
    {ready,Meta,Val};
88
 
handle_command(Meta, {'receive',Msg}) ->
89
 
    receive
90
 
        Msg -> 
91
 
            Meta ! {self(),rec_acked}
92
 
    end,
93
 
    msg_loop(Meta);
94
 
handle_command(_Meta, {exit,Reason}) ->
95
 
    exit(Reason);
96
 
handle_command(Meta, {bif,Mod,Name,As,Where,Followed}) ->
97
 
    Res = bif(Mod, Name, As, Followed, Where),
98
 
    Meta ! {sys,self(),{apply_result,Res}},
99
 
    msg_loop(Meta);
100
 
handle_command(Meta, {catch_bif,Mod,Name,As,Where,Followed}) ->
101
 
    send_result(Meta, catch_bif(Meta, Mod, Name, As, Followed, Where)),
102
 
    msg_loop(Meta);
103
 
handle_command(Meta, {apply,Mod,Fnk,As}) ->
104
 
    Res = apply(Mod, Fnk, As),
105
 
    Meta ! {sys,self(),{apply_result,Res}},
106
 
    msg_loop(Meta);
107
 
handle_command(Meta, {catch_apply,Mod,Fnk,As}) ->
108
 
    send_result(Meta, catch_apply(Meta, Mod, Fnk, As)),
109
 
    msg_loop(Meta);
110
 
handle_command(Meta, {eval,Expr,Bs0}) ->
111
 
    Ref = make_ref(),
112
 
    case catch {Ref,erl_eval:expr(Expr, Bs0)} of
113
 
        {Ref,{value,V,Bs}} ->
114
 
            Meta ! {sys,self(),{eval_result,V,Bs}};
115
 
        Other ->
116
 
            Meta ! {sys,self(),{thrown,Other}}
117
 
    end,
118
 
    msg_loop(Meta).
119
 
 
120
 
send_result(Meta, {catch_normal,Meta,Res}) ->
121
 
    Meta ! {sys,self(),{apply_result,Res}};
122
 
send_result(Meta, Thrown) ->
123
 
    Meta ! {sys,self(),{thrown,Thrown}}.
124
 
 
125
 
%%-- Return tuple if apply evaluates normally, otherwise the
126
 
%%-- surrounding catch notices the unnormal exit.
127
 
 
128
 
catch_apply(Meta, Mod, Fnk, As) ->
129
 
    Ref = make_ref(),
130
 
    Res0 = (catch {Ref, apply(Mod, Fnk, As)}),
131
 
    case Res0 of
132
 
        {'EXIT', Reason} -> {'EXIT', remove_debugger_calls(Reason)};
133
 
        {Ref, Res} -> 
134
 
            {catch_normal,Meta,Res};
135
 
        _ ->
136
 
            Res0
137
 
    end.
138
 
 
139
 
catch_bif(Meta, Mod, Name, As, Followed, Where) ->
140
 
    Res = (catch bif(Mod, Name, As, Followed, Where)),
141
 
    case Res of
142
 
        {'EXIT', Reason} -> {'EXIT', remove_debugger_calls(Reason)};
143
 
        _ ->
144
 
            {catch_normal,Meta,Res}
145
 
    end.
146
 
 
147
 
remove_debugger_calls({Reason,BT}) when is_list(BT) ->
148
 
    {Reason, remove_debugger_calls(BT, [])};
149
 
remove_debugger_calls(Reason) ->
150
 
    Reason.
151
 
remove_debugger_calls([{?MODULE, _F, _A}|R], Acc) ->
152
 
    remove_debugger_calls(R,Acc);
153
 
remove_debugger_calls([Other|R], Acc) ->
154
 
    remove_debugger_calls(R, [Other|Acc]);
155
 
remove_debugger_calls([],Acc) -> 
156
 
    lists:reverse(Acc);
157
 
remove_debugger_calls(What, Acc) ->
158
 
    lists:reverse([What|Acc]).
159
 
 
160
 
%% bif(Mod, Name, Arguments)
161
 
%%  Evaluate a BIF.
162
 
 
163
 
bif(Mod, Name, As, false, Where) ->
164
 
    erts_debug:apply(Mod, Name, As, Where);
165
 
bif(erlang, spawn, [M,F,As], Attached, _Where) ->
166
 
    spawn(?MODULE,follow,[Attached,M,F,As]);
167
 
bif(erlang, spawn_link, [M,F,As], Attached, _Where) ->
168
 
    spawn_link(?MODULE,follow,[Attached,M,F,As]);
169
 
bif(erlang, spawn, [N,M,F,As], Attached, _Where) ->
170
 
    spawn(N,?MODULE,follow,[Attached,M,F,As]);
171
 
bif(erlang, spawn_link, [N,M,F,As], Attached, _Where) ->
172
 
    spawn_link(N,?MODULE,follow,[Attached,M,F,As]).
173
 
 
174
 
%%---------------------------------------------------
175
 
%%-- Sync on exit.
176
 
%%-- The Meta process shall initiate all exits!
177
 
%%---------------------------------------------------
178
 
 
179
 
wait_exit(Meta) ->
180
 
    receive
181
 
        {sys,Meta,{exit,Reason}} ->
182
 
            exit(Reason);
183
 
        {'EXIT',Meta,Reason} ->
184
 
            exit(Reason)
185
 
    end.
 
42
msg_loop(Meta, Mref, SaveStacktrace) ->
 
43
    receive
 
44
 
 
45
        %% Evaluated function has returned a value
 
46
        {sys, Meta, {ready, Val}} ->
 
47
            demonitor(Mref),
 
48
 
 
49
            %% Restore original stacktrace and return the value
 
50
            try erlang:raise(throw, stack, SaveStacktrace)
 
51
            catch
 
52
                throw:stack ->
 
53
                    case Val of
 
54
                        {dbg_apply,M,F,A} ->
 
55
                            apply(M, F, A);
 
56
                        _ ->
 
57
                            Val
 
58
                    end
 
59
            end;
 
60
 
 
61
        %% Evaluated function raised an (uncaught) exception
 
62
        {sys, Meta, {exception,{Class,Reason,Stacktrace}}} ->
 
63
            demonitor(Mref),
 
64
 
 
65
            %% ...raise the same exception
 
66
            erlang:error(erlang:raise(Class, Reason, Stacktrace), 
 
67
                         [Class,Reason,Stacktrace]);
 
68
 
 
69
        %% Meta is evaluating a receive, must be done within context
 
70
        %% of real (=this) process
 
71
        {sys, Meta, {'receive',Msg}} ->
 
72
            receive Msg -> Meta ! {self(), rec_acked} end,
 
73
            msg_loop(Meta, Mref, SaveStacktrace);
 
74
 
 
75
        %% Meta needs something evaluated within context of real process
 
76
        {sys, Meta, {command, Command, Stacktrace}} ->
 
77
            Reply = handle_command(Command, Stacktrace),
 
78
            Meta ! {sys, self(), Reply},
 
79
            msg_loop(Meta, Mref, SaveStacktrace);
 
80
 
 
81
        %% Meta has terminated
 
82
        %% Must be due to int:stop() (or -heaven forbid- a debugger bug)
 
83
        {'DOWN', Mref, _, _, Reason} ->
 
84
 
 
85
            %% Restore original stacktrace and return a dummy value
 
86
            try erlang:raise(throw, stack, SaveStacktrace)
 
87
            catch
 
88
                throw:stack ->
 
89
                    {interpreter_terminated, Reason}
 
90
            end
 
91
    end.
 
92
 
 
93
handle_command(Command, Stacktrace) ->
 
94
    try reply(Command)
 
95
    catch Class:Reason ->
 
96
            Stacktrace2 = stacktrace_f(erlang:get_stacktrace()),
 
97
            {exception, {Class,Reason,Stacktrace2++Stacktrace}}
 
98
    end.
 
99
 
 
100
reply({apply,M,F,As}) ->
 
101
    {value, erlang:apply(M,F,As)};
 
102
reply({eval,Expr,Bs}) ->
 
103
    erl_eval:expr(Expr, Bs). % {value, Value, Bs2}
 
104
 
 
105
%% Demonitor and delete message from inbox
 
106
%%
 
107
demonitor(Mref) ->
 
108
    erlang:demonitor(Mref),
 
109
    receive {'DOWN',Mref,_,_,_} -> ok
 
110
    after 0 -> ok
 
111
    end.
 
112
 
 
113
%% Fix stacktrace - keep all above call to this module.
 
114
%%
 
115
stacktrace_f([]) -> [];
 
116
stacktrace_f([{?MODULE,_,_}|_]) -> [];
 
117
stacktrace_f([F|S]) -> [F|stacktrace_f(S)].