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

« back to all changes in this revision

Viewing changes to lib/debugger/src/dbg_imeta.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:
1
 
%% ``The contents of this file are subject to the Erlang Public License,
2
 
%% Version 1.1, (the "License"); you may not use this file except in
3
 
%% compliance with the License. You should have received a copy of the
4
 
%% Erlang Public License along with this software. If not, it can be
5
 
%% retrieved via the world wide web at http://www.erlang.org/.
6
 
%% 
7
 
%% Software distributed under the License is distributed on an "AS IS"
8
 
%% basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
9
 
%% the License for the specific language governing rights and limitations
10
 
%% under the License.
11
 
%% 
12
 
%% The Initial Developer of the Original Code is Ericsson Utvecklings AB.
13
 
%% Portions created by Ericsson are Copyright 1999, Ericsson Utvecklings
14
 
%% AB. All Rights Reserved.''
15
 
%% 
16
 
%%     $Id$
17
 
%%
18
 
-module(dbg_imeta).
19
 
 
20
 
%% External exports
21
 
-export([eval/3, exit_info/5]).
22
 
 
23
 
%% External exports used by dbg_ieval
24
 
-export([main_meta_loop/7]).
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
 
 
34
 
%%====================================================================
35
 
%% External exports
36
 
%%====================================================================
37
 
 
38
 
%%--------------------------------------------------------------------
39
 
%% eval(Mod, Func, Args) -> Meta
40
 
%%   Mod = Func = atom()
41
 
%%   Args = [term()]
42
 
%%   Meta = pid()
43
 
%% Entry point from process being debugged.
44
 
%% Immediately returns the pid for the meta process.
45
 
%% The evaluated value will later be sent as a message to
46
 
%% process that called this function.
47
 
%%--------------------------------------------------------------------
48
 
eval(Mod, Func, Args) ->
49
 
    Debugged = self(),
50
 
    Int = dbg_iserver:find(),
51
 
    ?DBG("Eval ~p:~p~n", [Mod, Func]),
52
 
    case dbg_iserver:call(Int, {get_meta, Debugged}) of
53
 
        {ok, Meta} ->
54
 
            Meta ! {error_handler,Debugged,{eval,{Mod,Func,Args}}},
55
 
            Meta;
56
 
        {error, not_interpreted} ->
57
 
            spawn_link(fun() -> int(Int, Debugged, Mod, Func, Args) end)
58
 
    end.
59
 
 
60
 
%%--------------------------------------------------------------------
61
 
%% exit_info(Int, AttPid, OrigPid, Reason, Info)
62
 
%%  Int = AttPid = OrigPid = pid()
63
 
%%  Reason = term()
64
 
%%  Info = {{Mod,Line}, Bs, Stack} | {}
65
 
%% Meta process started when attaching to a terminated process.
66
 
%%--------------------------------------------------------------------
67
 
exit_info(Int, AttPid, OrigPid, Reason, Info) ->
68
 
    put(int, Int),
69
 
    put(attached, [AttPid]),
70
 
    put(breakpoints, dbg_iserver:call(Int, all_breaks)),
71
 
    put(self, OrigPid),
72
 
    
73
 
    case Info of
74
 
        {{Mod,Line},Bs,Stack} ->
75
 
            S = binary_to_term(Stack),
76
 
            put(stack, S),
77
 
            Sp = sp(S),
78
 
            dbg_icmd:tell_attached({exit_at, {Mod, Line}, Reason, Sp+1}),
79
 
            exit_loop(OrigPid, Reason, Mod, Line, Bs);
80
 
        _ ->
81
 
            put(stack, []),
82
 
            dbg_icmd:tell_attached({exit_at, null, Reason, 1}),
83
 
            exit_loop(OrigPid, Reason, null, null, [])
84
 
    end.
85
 
 
86
 
 
87
 
%%====================================================================
88
 
%% Internal functions
89
 
%%====================================================================
90
 
 
91
 
%% Entry point for first-time initialization of meta process
92
 
int(Int, Debugged, M, F, As) ->
93
 
    process_flag(trap_exit, true),
94
 
 
95
 
    %% Inform dbg_iserver, get the initial status in return
96
 
    Status = dbg_iserver:call(Int,
97
 
                              {new_process, Debugged, self(), {M, F, As}}),
98
 
 
99
 
    %% Initiate process dictionary
100
 
    put(int, Int),
101
 
    put(attached, []),
102
 
    put(breakpoints, dbg_iserver:call(Int, all_breaks)),
103
 
    put(cache, []),
104
 
    put(catch_lev, []),
105
 
    put(error, none),
106
 
    put(next_break, Status),
107
 
    put(self, Debugged),
108
 
    put(stack, []),
109
 
    put(stack_trace, dbg_iserver:call(Int, get_stack_trace)),
110
 
    put(trace, false),
111
 
    put(user_eval, []),
112
 
    
113
 
    eval_mfa(Debugged, M, F, As, 1),
114
 
 
115
 
    dbg_iserver:cast(Int, {set_status, self(), idle, {}}),
116
 
    dbg_icmd:tell_attached_if_break(idle),
117
 
 
118
 
    main_meta_loop(Debugged, [], 1, false, extern, -1, extern).
119
 
 
120
 
eval_mfa(Debugged, M, F, As, Le) ->
121
 
    dbg_ieval:trace(call, {Le,none,M,F,As}),
122
 
    ?DBG("eval_mfa[~p] ~p:~p ~n", [Le, M, F]),
123
 
    dbg_ieval:init_catch_lev(),
124
 
    Res = dbg_ieval:eval_function(M, F, As, Le),
125
 
    dbg_ieval:exit_catch_lev(),
126
 
    ?DBG("eval_res[~p] ~p:~p => ~p~n", [Le,M,F,Res]),
127
 
    case Res of
128
 
        {value, Val, _Bs} ->
129
 
            Debugged ! {sys, self(), {ready, Val}};
130
 
 
131
 
        {'EXIT', {Debugged, Reason}} ->
132
 
            dbg_ieval:pop(Le),
133
 
            if
134
 
                Le>1 -> exit({Debugged, Reason});
135
 
                true -> do_real_exit(Reason)
136
 
            end;
137
 
 
138
 
        {'EXIT', {confirmed, Reason}} ->
139
 
            Debugged ! {sys, self(), {exit, Reason}},
140
 
            dbg_ieval:pop(Le);
141
 
 
142
 
        {'EXIT', {int, Reason}} -> % Interpreter has terminated
143
 
            exit(Reason);
144
 
 
145
 
        {'EXIT', Reason} ->
146
 
            Debugged ! {sys, self(), {exit, Reason}},
147
 
            if   %% qqqq
148
 
                Le > 1 ->
149
 
                    receive
150
 
                        {sys, Debugged, {exited_nocatch, Reason}} ->
151
 
                            Debugged ! {sys, self(), {exit, Reason}}
152
 
                    end;
153
 
                true -> ignore
154
 
            end,            
155
 
            dbg_ieval:pop(Le);
156
 
        _Value ->  %% Thrown value
157
 
%           Debugged ! {sys, self(), {throw, Value}}, % qqqq
158
 
            dbg_ieval:pop(Le)
159
 
    end.
160
 
 
161
 
%%--Loops-------------------------------------------------------------
162
 
 
163
 
%% main_meta_loop(Debugged, Bs, Le, Lc, Cm, Line, F) -> {value, Value, Bs}
164
 
%%   Debugged = pid()      Debugged process
165
 
%%   Bs = [{Var,Val}]      Bindings
166
 
%%   Le = integer()        Level
167
 
%%   Lc = false            ?
168
 
%%   Cm = extern | atom()  Current module
169
 
%%   Line = integer() -1   Line number
170
 
%%   F = extern            ?
171
 
%%   Value = term()
172
 
%% Main receive loop for the meta process.
173
 
main_meta_loop(Debugged, Bs, Le, Lc, Cm, Line, F) when integer(Le) ->
174
 
    ?DBG("Loop [~p] ~n", [Le]),
175
 
    receive     
176
 
        %% The following messages can only be received when Meta is
177
 
        %% waiting for Debugged to evaluate non-interpreted code
178
 
        %% or a BIF. Le>1.
179
 
        {sys, Debugged, {apply_result, Val}} when Lc==false ->
180
 
            ?DBG("Loop [~p] apply_result~n", [Le]),
181
 
            dbg_ieval:trace(return, {Le,Val,Lc}),
182
 
            {value, Val, Bs};
183
 
        {sys, Debugged, {apply_result, Val}} ->
184
 
            ?DBG("Loop [~p] apply_result~n", [Le]),
185
 
            {value, Val, Bs};
186
 
        {sys, Debugged, {eval_result, Val, Bs2}} ->
187
 
            ?DBG("Loop [~p] eval_result~n", [Le]),
188
 
            {value, Val, Bs2};
189
 
        {sys, Debugged, {thrown, Value}} ->
190
 
            ?DBG("Loop [~p] thrown~n", [Le]),
191
 
            throw(Value);
192
 
        {sys, Debugged, {thrown_nocatch, Value}} ->
193
 
            ?DBG("Loop [~p] thrown_nocatch~n", [Le]),
194
 
            throw(Value, Cm, Line, Bs);
195
 
 
196
 
        %% The following messages can be received any time.
197
 
        %% If Le==1, Meta is at the top level.
198
 
        %% If Le>1, Meta has been entered more than once from
199
 
        %% the error_handler module.
200
 
        {sys, Debugged, {exited_nocatch,Reason}} when Le==1->
201
 
            ?DBG("Loop [~p] exited_nocatch~n", [Le]),
202
 
            Debugged ! {sys, self(), {exit, Reason}},
203
 
            main_meta_loop(Debugged, Bs, Le, Lc, Cm, Line, F);
204
 
        {sys, Debugged, {exited_nocatch, Reason}} ->
205
 
            %% dbg_ieval:put_error(Reason, Cm, Line, Bs),
206
 
            %% exit({confirmed, Reason});
207
 
            ?DBG("Loop [~p] exited_nocatch~n", [Le]),
208
 
            dbg_ieval:exit({confirmed, Reason}, Cm, Line, Bs);
209
 
 
210
 
        %% Re-entry to Meta at top level.
211
 
        {error_handler, Debugged, {eval, {Mod,Func,Args}}} when Le==1 ->
212
 
            ?DBG("Loop [~p] reentry ~p~n", [Le,{Mod,Func}]),
213
 
            dbg_iserver:cast(get(int), {set_status, self(), running, {}}),
214
 
            dbg_icmd:tell_attached_if_break(running),
215
 
            %% Tell attached process(es) to update source code.
216
 
            dbg_icmd:tell_attached({re_entry, Mod, Func}),
217
 
            eval_mfa(Debugged, Mod, Func, Args, 1),
218
 
            dbg_iserver:cast(get(int), {set_status, self(), idle, {}}),
219
 
            dbg_icmd:tell_attached_if_break(idle),
220
 
            main_meta_loop(Debugged, Bs, Le, Lc, Cm, Line, F);
221
 
        {error_handler, Debugged, {eval, {Mod,Func,Args}}} ->
222
 
            ?DBG("Loop [~p] reentry ~p~n", [Le, {Mod,Func}]),
223
 
            eval_mfa(Debugged, Mod, Func, Args, Le),
224
 
            main_meta_loop(Debugged, Bs, Le, Lc, Cm, Line, F);
225
 
 
226
 
        %% Signal received from dying interpreted process
227
 
        %% (due to exit in non-interpreted code).
228
 
        {'EXIT', Debugged, Reason} when Le==1 ->
229
 
            ?DBG("Loop [~p] EXIT~n", [Le]),
230
 
            do_real_exit(Reason);
231
 
        {'EXIT', Debugged, Reason} ->
232
 
            ?DBG("Loop [~p] EXIT~n", [Le]),
233
 
            dbg_ieval:exit(Debugged, Reason, Cm, Line, Bs);
234
 
 
235
 
        %% Interpreter has terminated.
236
 
        %% XXX Can we be sure that the interpreter has terminated?
237
 
        %% It could be another process.
238
 
        {'EXIT',_Pid,Reason} ->
239
 
            ?DBG("Loop [~p] EXIT~n", [Le]),
240
 
            exit(Reason);
241
 
 
242
 
        Msg ->
243
 
            ?DBG("Loop [~p] Msg ~p~n", [Le, Msg]),
244
 
            dbg_icmd:handle_msg(Msg, {main, Bs, Le, Cm, Line}),
245
 
            main_meta_loop(Debugged, Bs, Le, Lc, Cm, Line, F)
246
 
    end.
247
 
 
248
 
exit_loop(OrigPid, Reason, Mod, Line, Bs) ->
249
 
    receive
250
 
        Msg ->
251
 
            dbg_icmd:handle_msg(Msg, {exit, Bs, null, Mod, Line}),
252
 
            exit_loop(OrigPid, Reason, Mod, Line, Bs)
253
 
    end.
254
 
    
255
 
%%--------------------------------------------------------------------
256
 
 
257
 
do_real_exit(Reason) ->
258
 
    case get(error) of
259
 
        {Reason, Where, Bs, Stack} ->
260
 
            exit({self(), Reason, Where, Bs, Stack});
261
 
        _ ->
262
 
            exit({self(), Reason})
263
 
    end.
264
 
 
265
 
sp([]) -> 0;
266
 
sp(S) -> element(1, hd(S)).
267
 
 
268
 
throw(Value, Cm, Line, Bs) ->
269
 
    dbg_ieval:do_put_error(nocatch, Cm, Line, Bs),
270
 
    throw(Value).