~clint-fewbar/ubuntu/precise/erlang/merge-15b

« back to all changes in this revision

Viewing changes to lib/debugger/src/dbg_ieval.erl

  • Committer: Package Import Robot
  • Author(s): Sergei Golovan
  • Date: 2011-12-15 19:20:10 UTC
  • mfrom: (1.1.18) (3.5.15 sid)
  • mto: (3.5.16 sid)
  • mto: This revision was merged to the branch mainline in revision 33.
  • Revision ID: package-import@ubuntu.com-20111215192010-jnxcfe3tbrpp0big
Tags: 1:15.b-dfsg-1
* New upstream release.
* Upload to experimental because this release breaks external drivers
  API along with ABI, so several applications are to be fixed.
* Removed SSL patch because the old SSL implementation is removed from
  the upstream distribution.
* Removed never used patch which added native code to erlang beam files.
* Removed the erlang-docbuilder binary package because the docbuilder
  application was dropped by upstream.
* Documented dropping ${erlang-docbuilder:Depends} substvar in
  erlang-depends(1) manpage.
* Made erlang-base and erlang-base-hipe provide virtual package
  erlang-abi-15.b (the number means the first erlang version, which
  provides current ABI).

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
1
%%
2
2
%% %CopyrightBegin%
3
3
%% 
4
 
%% Copyright Ericsson AB 1998-2009. All Rights Reserved.
 
4
%% Copyright Ericsson AB 1998-2011. All Rights Reserved.
5
5
%% 
6
6
%% The contents of this file are subject to the Erlang Public License,
7
7
%% Version 1.1, (the "License"); you may not use this file except in
20
20
 
21
21
-export([eval/3,exit_info/5]).
22
22
-export([eval_expr/3]).
23
 
-export([check_exit_msg/3,exception/4,in_use_p/2]).
24
 
-export([stack_level/0, bindings/1, stack_frame/2, backtrace/1]).
 
23
-export([check_exit_msg/3,exception/4]).
25
24
 
26
25
-include("dbg_ieval.hrl").
27
26
 
71
70
    
72
71
    case ExitInfo of
73
72
        {{Mod,Line},Bs,S} ->
74
 
            Stack = binary_to_term(S),
75
 
            put(stack, Stack),
76
 
            Le = stack_level(Stack),
 
73
            dbg_istk:from_external(S),
 
74
            Le = dbg_istk:stack_level(),
77
75
            dbg_icmd:tell_attached({exit_at, {Mod, Line}, Reason, Le}),
78
76
            exit_loop(OrigPid, Reason, Bs,#ieval{module=Mod,line=Line});
79
77
        {} ->
80
 
            put(stack, []),
 
78
            dbg_istk:init(),
81
79
            dbg_icmd:tell_attached({exit_at, null, Reason, 1}),
82
80
            exit_loop(OrigPid, Reason, erl_eval:new_bindings(),#ieval{})
83
81
    end.
142
140
            undefined when Le =:= 1 -> % died outside interpreted code
143
141
                {};
144
142
            undefined when Le > 1 ->
145
 
                StackBin = term_to_binary(get(stack)),
146
 
                {{Mod, Li}, Bs, StackBin};
 
143
                StackExternal = (dbg_istk:delayed_to_external())(),
 
144
                {{Mod, Li}, Bs, StackExternal};
147
145
 
148
146
            %% Debugged has terminated due to an exception
149
 
            ExitInfo0 ->
150
 
                ExitInfo0
 
147
            ExitInfo0 when is_function(ExitInfo0, 0) ->
 
148
                ExitInfo0()
151
149
        end,
152
150
    dbg_iserver:cast(get(int), {set_exit_info,self(),ExitInfo}),
153
151
 
170
168
%% and then raise the exception.
171
169
%%--------------------------------------------------------------------
172
170
exception(Class, Reason, Bs, Ieval) ->
173
 
    exception(Class, Reason, fix_stacktrace(1), Bs, Ieval).
174
 
 
175
 
exception(Class, Reason, Stacktrace, Bs, #ieval{module=M, line=Line}) ->
176
 
    ExitInfo = {{M,Line}, Bs, term_to_binary(get(stack))},
 
171
    exception(Class, Reason, Bs, Ieval, false).
 
172
 
 
173
exception(Class, Reason, Bs, Ieval, false) ->
 
174
    do_exception(Class, Reason,
 
175
                 dbg_istk:delayed_stacktrace(no_args, Ieval),
 
176
                 Bs, Ieval);
 
177
exception(Class, Reason, Bs, Ieval, true) ->
 
178
    do_exception(Class, Reason,
 
179
                 dbg_istk:delayed_stacktrace(include_args, Ieval),
 
180
                 Bs, Ieval).
 
181
 
 
182
do_exception(Class, Reason, Stacktrace, Bs, #ieval{module=M, line=Line}) ->
 
183
    StackFun = dbg_istk:delayed_to_external(),
 
184
    ExitInfo = fun() ->
 
185
                       {{M,Line},Bs,StackFun()}
 
186
               end,
177
187
    put(exit_info, ExitInfo),
178
188
    put(stacktrace, Stacktrace),
179
189
    erlang:Class(Reason).
180
190
 
181
 
%%--------------------------------------------------------------------
182
 
%% in_use_p(Mod, Cm) -> boolean()
183
 
%%   Mod = Cm = atom()
184
 
%% Returns true if Mod is found on the stack, otherwise false.
185
 
%%--------------------------------------------------------------------
186
 
in_use_p(Mod, Mod) -> true;
187
 
in_use_p(Mod, _Cm) ->
188
 
    case get(trace_stack) of
189
 
        false -> true;
190
 
        _ -> %  all | no_tail
191
 
            lists:any(fun({_,{M,_,_,_}}) when M =:= Mod -> true;
192
 
                         (_) -> false
193
 
                      end,
194
 
                      get(stack))
195
 
    end.
196
 
 
197
191
%%====================================================================
198
192
%% Internal functions
199
193
%%====================================================================
225
219
    put(cache, []),
226
220
    put(next_break, Status), % break | running (other values later)
227
221
    put(self, Debugged),     % pid() interpreted process
228
 
    put(stack, []),
 
222
    dbg_istk:init(),
229
223
    put(stacktrace, []),
230
224
    put(trace_stack, dbg_iserver:call(Int, get_stack_trace)),
231
225
    put(trace, false),       % bool() Trace on/off
243
237
 
244
238
debugged_cmd(Cmd, Bs, Ieval) ->
245
239
    Debugged = get(self),
246
 
    Stacktrace = fix_stacktrace(2),
247
 
    Debugged ! {sys, self(), {command,Cmd,Stacktrace}},
 
240
    Debugged ! {sys, self(), {command,Cmd}},
248
241
    meta_loop(Debugged, Bs, Ieval).
249
242
 
250
243
meta_loop(Debugged, Bs, #ieval{level=Le} = Ieval) ->
257
250
            {value, Val, Bs};
258
251
        {sys, Debugged, {value,Val,Bs2}} ->
259
252
            {value, Val, Bs2};
260
 
        {sys, Debugged, {exception,{Class,Reason,Stacktrace}}} ->
 
253
        {sys, Debugged, {exception,{Class,Reason,Stk}}} ->
261
254
            case get(exit_info) of
262
255
 
263
 
                %% Error occured outside interpreted code
 
256
                %% Error occurred outside of interpreted code.
264
257
                undefined ->
265
 
                    exception(Class,Reason,Stacktrace,Bs,Ieval);
 
258
                    MakeStk0 = dbg_istk:delayed_stacktrace(),
 
259
                    MakeStk = fun(Depth0) ->
 
260
                                      Depth = max(0, Depth0 - length(Stk)),
 
261
                                      Stk ++ MakeStk0(Depth)
 
262
                              end,
 
263
                    do_exception(Class, Reason, MakeStk, Bs, Ieval);
266
264
 
267
265
                %% Error must have occured within a re-entry to
268
266
                %% interpreted code, simply raise the exception
275
273
            %% Reset process dictionary
276
274
            %% This is really only necessary if the process left
277
275
            %% interpreted code at a call level > 1
278
 
            put(stack, []),
 
276
            dbg_istk:init(),
279
277
            put(stacktrace, []),
280
278
            put(exit_info, undefined),
281
279
            
313
311
            exit_loop(OrigPid, Reason, Bs, Ieval)
314
312
    end.
315
313
 
316
 
%%--Stack emulation---------------------------------------------------
317
 
 
318
 
%% We keep track of a call stack that is used for
319
 
%%  1) saving stack frames that can be inspected from an Attached
320
 
%%     Process GUI (using dbg_icmd:get(Meta, stack_frame, {Dir, SP})
321
 
%%  2) generate an approximation of regular stacktrace -- sent to
322
 
%%     Debugged when it should raise an exception or evaluate a
323
 
%%     function (since it might possible raise an exception)
324
 
%%
325
 
%% Stack = [Entry]
326
 
%%   Entry = {Le, {MFA, Where, Bs}}
327
 
%%     Le = int()         % current call level
328
 
%%     MFA = {M,F,Args}   % called function (or fun)
329
 
%%         | {Fun,Args}   %
330
 
%%     Where = {M,Li}     % from where (module+line) function is called
331
 
%%     Bs = bindings()    % current variable bindings
332
 
%%
333
 
%% How to push depends on the "Stack Trace" option (value saved in
334
 
%% process dictionary item 'trace_stack').
335
 
%%   all - everything is pushed
336
 
%%   no_tail - tail recursive push
337
 
%%   false - nothing is pushed
338
 
%% Whenever a function returns, the corresponding call frame is popped.
339
 
 
340
 
push(MFA, Bs, #ieval{level=Le,module=Cm,line=Li,last_call=Lc}) ->
341
 
    Entry = {Le, {MFA, {Cm,Li}, Bs}},
342
 
    case get(trace_stack) of
343
 
        false -> ignore;
344
 
        no_tail when Lc ->
345
 
            case get(stack) of
346
 
                [] -> put(stack, [Entry]);
347
 
                [_Entry|Entries] -> put(stack, [Entry|Entries])
348
 
            end;
349
 
        _ -> % all | no_tail when Lc =:= false
350
 
            put(stack, [Entry|get(stack)])
351
 
    end.
352
 
 
353
 
pop() ->
354
 
    case get(trace_stack) of
355
 
        false -> ignore;
356
 
        _ -> % all � no_tail
357
 
            case get(stack) of
358
 
                [_Entry|Entries] ->
359
 
                    put(stack, Entries);
360
 
                [] ->
361
 
                    ignore
362
 
            end
363
 
    end.
364
 
 
365
 
pop(Le) ->
366
 
    case get(trace_stack) of
367
 
        false -> ignore;
368
 
        _ -> % all | no_tail
369
 
            put(stack, pop(Le, get(stack)))
370
 
    end.
371
 
 
372
 
pop(Level, [{Le, _}|Stack]) when Level=<Le ->
373
 
    pop(Level, Stack);
374
 
pop(_Level, Stack) ->
375
 
    Stack.
376
 
 
377
 
 
378
 
%% stack_level() -> Le
379
 
%% stack_level(Stack) -> Le
380
 
%% Top call level
381
 
stack_level() ->
382
 
    stack_level(get(stack)).
383
 
 
384
 
stack_level([]) -> 1;
385
 
stack_level([{Le,_}|_]) -> Le.
386
 
 
387
 
%% fix_stacktrace(Start) -> Stacktrace
388
 
%%   Start = 1|2
389
 
%%   Stacktrace = [{M,F,Args|Arity} | {Fun,Args}]
390
 
%% Convert internal stack format to imitation of regular stacktrace.
391
 
%% Max three elements, no repeated (recursive) calls to the same
392
 
%% function and convert argument lists to arity for all but topmost
393
 
%% entry (and funs).
394
 
%% 'Start' indicates where at get(stack) to start. This somewhat ugly
395
 
%% solution is because fix_stacktrace has two uses: 1) to imitate
396
 
%% the stacktrace in the case of an exception in the interpreted code,
397
 
%% in which case the current call (top of the stack = first of the list)
398
 
%% should be included, and 2) to send a current stacktrace to Debugged
399
 
%% when evaluation passes into non-interpreted code, in which case
400
 
%% the current call should NOT be included (as it is Debugged which
401
 
%% will make the actual function call).
402
 
fix_stacktrace(Start) ->
403
 
    case fix_stacktrace2(sublist(get(stack), Start, 3)) of
404
 
        [] ->
405
 
            [];
406
 
        [H|T] ->
407
 
            [H|args2arity(T)]
408
 
    end.
409
 
 
410
 
sublist([], _Start, _Length) ->
411
 
    []; % workaround, lists:sublist([],2,3) fails
412
 
sublist(L, Start, Length) ->
413
 
    lists:sublist(L, Start, Length).
414
 
 
415
 
fix_stacktrace2([{_,{{M,F,As1},_,_}}, {_,{{M,F,As2},_,_}}|_])
416
 
  when length(As1) =:= length(As2) ->
417
 
    [{M,F,As1}];
418
 
fix_stacktrace2([{_,{{Fun,As1},_,_}}, {_,{{Fun,As2},_,_}}|_])
419
 
  when length(As1) =:= length(As2) ->
420
 
    [{Fun,As1}];
421
 
fix_stacktrace2([{_,{MFA,_,_}}|Entries]) ->
422
 
    [MFA|fix_stacktrace2(Entries)];
423
 
fix_stacktrace2([]) ->
424
 
    [].
425
 
 
426
 
args2arity([{M,F,As}|Entries]) when is_list(As) ->
427
 
    [{M,F,length(As)}|args2arity(Entries)];
428
 
args2arity([Entry|Entries]) ->
429
 
    [Entry|args2arity(Entries)];
430
 
args2arity([]) ->
431
 
    [].
432
 
 
433
 
%% bindings(SP) -> Bs
434
 
%%   SP = Le  % stack pointer
435
 
%% Return the bindings for the specified call level
436
 
bindings(SP) ->
437
 
    bindings(SP, get(stack)).
438
 
 
439
 
bindings(SP, [{SP,{_MFA,_Wh,Bs}}|_]) ->
440
 
    Bs;
441
 
bindings(SP, [_Entry|Entries]) ->
442
 
    bindings(SP, Entries);
443
 
bindings(_SP, []) ->
444
 
    erl_eval:new_bindings().
445
 
 
446
 
%% stack_frame(Dir, SP) -> {Le, Where, Bs} | top | bottom
447
 
%%   Dir = up | down
448
 
%%   Where = {Cm, Li}
449
 
%%     Cm = Module | undefined  % module
450
 
%%     Li = int()  | -1         % line number
451
 
%%     Bs = bindings()
452
 
%% Return stack frame info one step up/down from given stack pointer
453
 
%%  up = to lower call levels
454
 
%%  down = to higher call levels
455
 
stack_frame(up, SP) ->
456
 
    stack_frame(SP, up, get(stack));
457
 
stack_frame(down, SP) ->
458
 
    stack_frame(SP, down, lists:reverse(get(stack))).
459
 
 
460
 
stack_frame(SP, up, [{Le, {_MFA,Where,Bs}}|_]) when Le<SP ->
461
 
    {Le, Where, Bs};
462
 
stack_frame(SP, down, [{Le, {_MFA,Where,Bs}}|_]) when Le>SP ->
463
 
    {Le, Where, Bs};
464
 
stack_frame(SP, Dir, [{SP, _}|Stack]) ->
465
 
    case Stack of
466
 
        [{Le, {_MFA,Where,Bs}}|_] ->
467
 
            {Le, Where, Bs};
468
 
        [] when Dir =:= up ->
469
 
            top;
470
 
        [] when Dir =:= down ->
471
 
            bottom
472
 
    end;
473
 
stack_frame(SP, Dir, [_Entry|Stack]) ->
474
 
    stack_frame(SP, Dir, Stack).
475
 
 
476
 
%% backtrace(HowMany) -> Backtrace
477
 
%%   HowMany = all | int()
478
 
%%   Backtrace = {Le, MFA}
479
 
%% Return all/the last N called functions, in reversed call order
480
 
backtrace(HowMany) ->
481
 
    Stack = case HowMany of
482
 
                all -> get(stack);
483
 
                N -> lists:sublist(get(stack), N)
484
 
            end,
485
 
    [{Le, MFA} || {Le,{MFA,_Wh,_Bs}} <- Stack].
486
 
 
487
314
%%--Trace function----------------------------------------------------
488
315
 
489
316
%%--------------------------------------------------------------------
558
385
 
559
386
%% Mimic catch behaviour
560
387
catch_value(error, Reason) ->
561
 
    {'EXIT',{Reason,get(stacktrace)}};
 
388
    {'EXIT',{Reason,get_stacktrace()}};
562
389
catch_value(exit, Reason) ->
563
390
    {'EXIT',Reason};
564
391
catch_value(throw, Reason) ->
570
397
%% Top level function of meta evaluator. 
571
398
%% Return message to be replied to the target process.
572
399
%%--------------------------------------------------------------------
573
 
eval_mfa(Debugged, M, F, As, Ieval) ->
 
400
eval_mfa(Debugged, M, F, As, #ieval{level=Le}=Ieval0) ->
574
401
    Int = get(int),
575
402
    Bs = erl_eval:new_bindings(),
576
 
    try eval_function(M,F,As,Bs,extern,Ieval#ieval{last_call=true}) of
 
403
    Ieval = Ieval0#ieval{level=Le+1,top=true},
 
404
    try do_eval_function(M, F, As, Bs, extern, Ieval) of
577
405
        {value, Val, _Bs} ->
 
406
            trace(return, {Le,Val}),
578
407
            {ready, Val}
579
408
    catch
580
409
        exit:{Debugged, Reason} ->
582
411
        exit:{Int, Reason} ->
583
412
            exit(Reason);
584
413
        Class:Reason ->
585
 
            {exception, {Class, Reason, get(stacktrace)}}
586
 
    end.
587
 
 
588
 
eval_function(Mod, Fun, As0, Bs0, _Called, Ieval) when is_function(Fun);
589
 
                                                       Mod =:= ?MODULE,
590
 
                                                       Fun =:= eval_fun ->
591
 
    #ieval{level=Le, line=Li, last_call=Lc} = Ieval,
 
414
            {exception, {Class, Reason, get_stacktrace()}}
 
415
    end.
 
416
 
 
417
eval_function(Mod, Name, As, Bs, Called, Ieval0, Lc) ->
 
418
    Tail = Lc andalso get(trace_stack) =:= no_tail,
 
419
    case Tail of
 
420
        false ->
 
421
            Ieval = dbg_istk:push(Bs, Ieval0, Lc),
 
422
            {value,Val,_} = do_eval_function(Mod, Name, As, Bs, Called, Ieval),
 
423
            dbg_istk:pop(),
 
424
            trace(return, {Ieval#ieval.level,Val}),
 
425
            {value,Val,Bs};
 
426
        true ->
 
427
            do_eval_function(Mod, Name, As, Bs, Called, Ieval0)
 
428
    end.
 
429
 
 
430
do_eval_function(Mod, Fun, As0, Bs0, _, Ieval0) when is_function(Fun);
 
431
                                                    Mod =:= ?MODULE,
 
432
                                                    Fun =:= eval_fun ->
 
433
    #ieval{level=Le,line=Li,top=Top} = Ieval0,
592
434
    case lambda(Fun, As0) of
593
 
        {Cs,Module,Name,As,Bs} ->
594
 
            push({Module,Name,As}, Bs0, Ieval),
 
435
        {[{clause,Fc,_,_,_}|_]=Cs,Module,Name,As,Bs} ->
 
436
            Ieval = Ieval0#ieval{module=Module,function=Name,
 
437
                                 arguments=As0,line=Fc},
595
438
            trace(call_fun, {Le,Li,Name,As}),
596
 
            {value, Val, _Bs} =
597
 
                fnk_clauses(Cs, Module, Name, As, Bs,
598
 
                            Ieval#ieval{level=Le+1}),
599
 
            pop(),
600
 
            trace(return, {Le,Val}),
601
 
            {value, Val, Bs0};
 
439
            fnk_clauses(Cs, As, Bs, Ieval);
602
440
 
603
 
        not_interpreted when Lc -> % We are leaving interpreted code
 
441
        not_interpreted when Top -> % We are leaving interpreted code
604
442
            trace(call_fun, {Le,Li,Fun,As0}),
605
443
            {value, {dbg_apply,erlang,apply,[Fun,As0]}, Bs0};
606
444
        not_interpreted ->
607
 
            push({Fun,As0}, Bs0, Ieval),
608
445
            trace(call_fun, {Le,Li,Fun,As0}),
609
 
            {value, Val, _Bs} =
610
 
                debugged_cmd({apply,erlang,apply,[Fun,As0]},Bs0,
611
 
                             Ieval#ieval{level=Le+1}),
612
 
            pop(),
613
 
            trace(return, {Le,Val}),
614
 
            {value, Val, Bs0};
 
446
            debugged_cmd({apply,erlang,apply,[Fun,As0]}, Bs0, Ieval0);
615
447
 
616
448
        {error,Reason} ->
617
449
            %% It's ok not to push anything in this case, the error
618
450
            %% reason contains information about the culprit
619
451
            %% ({badarity,{{Mod,Name},As}})
620
 
            exception(error, Reason, Bs0, Ieval)
 
452
            exception(error, Reason, Bs0, Ieval0)
621
453
    end;
622
454
 
623
455
%% Common Test adaptation
624
 
eval_function(ct_line, line, As, Bs, extern, #ieval{level=Le}=Ieval) ->
 
456
do_eval_function(ct_line, line, As, Bs, extern, #ieval{level=Le}=Ieval) ->
625
457
    debugged_cmd({apply,ct_line,line,As}, Bs, Ieval#ieval{level=Le+1}),
626
458
    {value, ignore, Bs};
627
459
 
628
 
eval_function(Mod, Name, As0, Bs0, Called, Ieval) ->
629
 
    #ieval{level=Le, line=Li, last_call=Lc} = Ieval,
630
 
 
631
 
    push({Mod,Name,As0}, Bs0, Ieval),
 
460
do_eval_function(Mod, Name, As0, Bs0, Called, Ieval0) ->
 
461
    #ieval{level=Le,line=Li,top=Top} = Ieval0,
632
462
    trace(call, {Called, {Le,Li,Mod,Name,As0}}),
633
 
 
 
463
    Ieval = Ieval0#ieval{module=Mod,function=Name,arguments=As0},
634
464
    case get_function(Mod, Name, As0, Called) of
635
 
        Cs when is_list(Cs) ->
636
 
            {value, Val, _Bs} =
637
 
                fnk_clauses(Cs, Mod, Name, As0, erl_eval:new_bindings(),
638
 
                            Ieval#ieval{level=Le+1}),
639
 
            pop(),
640
 
            trace(return, {Le,Val}),
641
 
            {value, Val, Bs0};
 
465
        [{clause,FcLine,_,_,_}|_]=Cs ->
 
466
            fnk_clauses(Cs, As0, erl_eval:new_bindings(),
 
467
                        Ieval#ieval{line=FcLine});
642
468
 
643
 
        not_interpreted when Lc -> % We are leaving interpreted code
 
469
        not_interpreted when Top -> % We are leaving interpreted code
644
470
            {value, {dbg_apply,Mod,Name,As0}, Bs0};
645
471
        not_interpreted ->
646
 
            {value, Val, _Bs} =
647
 
                debugged_cmd({apply,Mod,Name,As0}, Bs0,
648
 
                             Ieval#ieval{level=Le+1}),
649
 
            pop(),
650
 
            trace(return, {Le,Val}),
651
 
            {value, Val, Bs0};
 
472
            debugged_cmd({apply,Mod,Name,As0}, Bs0, Ieval);
652
473
 
653
474
        undef ->
654
 
            exception(error, undef, Bs0, Ieval)
 
475
            exception(error, undef, Bs0, Ieval, true)
655
476
    end.
656
477
 
657
478
lambda(eval_fun, [Cs,As,Bs,{Mod,Name}=F]) ->
752
573
 
753
574
%% Try to find a matching function clause
754
575
%% #ieval.level is set, the other fields must be set in this function
755
 
fnk_clauses([{clause,Line,Pars,Gs,Body}|Cs], M, F, As, Bs0, Ieval) ->
 
576
fnk_clauses([{clause,Line,Pars,Gs,Body}|Cs], As, Bs0, Ieval) ->
756
577
    case head_match(Pars, As, [], Bs0) of
757
578
        {match,Bs1} ->
758
579
            Bs = add_bindings(Bs1, Bs0),
759
580
            case guard(Gs, Bs) of
760
581
                true ->
761
 
                    seq(Body, Bs,
762
 
                        Ieval#ieval{line=Line,
763
 
                                    module=M,function=F,arguments=As});
 
582
                    seq(Body, Bs, Ieval#ieval{line=Line});
764
583
                false ->
765
 
                    fnk_clauses(Cs, M, F, As, Bs0, Ieval)
 
584
                    fnk_clauses(Cs, As, Bs0, Ieval)
766
585
            end;
767
586
        nomatch ->
768
 
            fnk_clauses(Cs, M, F, As, Bs0, Ieval)
 
587
            fnk_clauses(Cs, As, Bs0, Ieval)
769
588
    end;
770
 
fnk_clauses([], _M, _F, _As, Bs, Ieval) ->
771
 
    exception(error, function_clause, Bs, Ieval).
 
589
fnk_clauses([], _As, Bs, Ieval) ->
 
590
    exception(error, function_clause, Bs, Ieval, true).
772
591
 
773
592
seq([E], Bs0, Ieval) ->
774
593
    case dbg_icmd:cmd(E, Bs0, Ieval) of
782
601
        {skip,Bs} ->
783
602
            seq(Es, Bs, Ieval);
784
603
        Bs1 ->
785
 
            {value,_,Bs} = expr(E, Bs1, Ieval#ieval{last_call=false}),
 
604
            {value,_,Bs} = expr(E, Bs1, Ieval#ieval{top=false}),
786
605
            seq(Es, Bs, Ieval)
787
606
    end;
788
607
seq([], Bs, _) ->
804
623
 
805
624
%% List
806
625
expr({cons,Line,H0,T0}, Bs0, Ieval0) ->
807
 
    Ieval = Ieval0#ieval{line=Line},
808
 
    Ieval1 = Ieval#ieval{last_call=false},
809
 
    {value,H,Bs1} = expr(H0,Bs0,Ieval1),
810
 
    {value,T,Bs2} = expr(T0,Bs0,Ieval1),
 
626
    Ieval = Ieval0#ieval{line=Line,top=false},
 
627
    {value,H,Bs1} = expr(H0, Bs0, Ieval),
 
628
    {value,T,Bs2} = expr(T0, Bs0, Ieval),
811
629
    {value,[H|T],merge_bindings(Bs2, Bs1, Ieval)};
812
630
 
813
631
%% Tuple
821
639
 
822
640
%% Catch statement
823
641
expr({'catch',Line,Expr}, Bs0, Ieval) ->
824
 
    try expr(Expr, Bs0, Ieval#ieval{line=Line, last_call=false})
 
642
    try expr(Expr, Bs0, Ieval#ieval{line=Line, top=false})
825
643
    catch
826
644
        Class:Reason ->
827
645
            %% Exception caught, reset exit info
828
646
            put(exit_info, undefined),
829
 
            pop(Ieval#ieval.level),
 
647
            dbg_istk:pop(Ieval#ieval.level),
830
648
            Value = catch_value(Class, Reason),
831
649
            trace(return, {Ieval#ieval.level,Value}),
832
650
            {value, Value, Bs0}
835
653
%% Try-catch statement
836
654
expr({'try',Line,Es,CaseCs,CatchCs,[]}, Bs0, Ieval0) ->
837
655
    Ieval = Ieval0#ieval{line=Line},
838
 
    try seq(Es, Bs0, Ieval#ieval{last_call=false}) of
 
656
    try seq(Es, Bs0, Ieval#ieval{top=false}) of
839
657
        {value,Val,Bs} = Value ->
840
658
            case CaseCs of
841
659
                [] -> Value;
848
666
    end;
849
667
expr({'try',Line,Es,CaseCs,CatchCs,As}, Bs0, Ieval0) ->
850
668
    Ieval = Ieval0#ieval{line=Line},
851
 
    try seq(Es, Bs0, Ieval#ieval{last_call=false}) of
 
669
    try seq(Es, Bs0, Ieval#ieval{top=false}) of
852
670
        {value,Val,Bs} = Value ->
853
671
            case CaseCs of
854
672
                [] -> Value;
859
677
        Class:Reason when CatchCs =/= [] ->
860
678
            catch_clauses({Class,Reason,[]}, CatchCs, Bs0, Ieval)
861
679
    after
862
 
            seq(As, Bs0, Ieval#ieval{last_call=false})
 
680
            seq(As, Bs0, Ieval#ieval{top=false})
863
681
    end;
864
682
 
865
683
%% Case statement
866
684
expr({'case',Line,E,Cs}, Bs0, Ieval) ->
867
685
    {value,Val,Bs} =
868
 
        expr(E, Bs0, Ieval#ieval{line=Line, last_call=false}),
 
686
        expr(E, Bs0, Ieval#ieval{line=Line, top=false}),
869
687
    case_clauses(Val, Cs, Bs, case_clause, Ieval#ieval{line=Line});
870
688
 
871
689
%% If statement
874
692
 
875
693
%% Andalso/orelse
876
694
expr({'andalso',Line,E1,E2}, Bs, Ieval) ->
877
 
    case expr(E1, Bs, Ieval#ieval{line=Line, last_call=false}) of
 
695
    case expr(E1, Bs, Ieval#ieval{line=Line, top=false}) of
878
696
        {value,false,_}=Res ->
879
697
            Res;
880
698
        {value,true,_} -> 
881
 
            expr(E2, Bs, Ieval#ieval{line=Line, last_call=false});
 
699
            expr(E2, Bs, Ieval#ieval{line=Line, top=false});
882
700
        {value,Val,Bs} ->
883
701
            exception(error, {badarg,Val}, Bs, Ieval)
884
702
    end;
885
703
expr({'orelse',Line,E1,E2}, Bs, Ieval) ->
886
 
    case expr(E1, Bs, Ieval#ieval{line=Line, last_call=false}) of
 
704
    case expr(E1, Bs, Ieval#ieval{line=Line, top=false}) of
887
705
        {value,true,_}=Res ->
888
706
            Res;
889
707
        {value,false,_} ->
890
 
            expr(E2, Bs, Ieval#ieval{line=Line, last_call=false});
 
708
            expr(E2, Bs, Ieval#ieval{line=Line, top=false});
891
709
        {value,Val,_} ->
892
710
            exception(error, {badarg,Val}, Bs, Ieval)
893
711
    end;
895
713
%% Matching expression
896
714
expr({match,Line,Lhs,Rhs0}, Bs0, Ieval0) ->
897
715
    Ieval = Ieval0#ieval{line=Line},
898
 
    {value,Rhs,Bs1} = expr(Rhs0, Bs0, Ieval#ieval{last_call=false}),
 
716
    {value,Rhs,Bs1} = expr(Rhs0, Bs0, Ieval#ieval{top=false}),
899
717
    case match(Lhs, Rhs, Bs1) of
900
718
        {match,Bs} ->
901
719
            {value,Rhs,Bs};
950
768
        end,
951
769
    {value,Fun,Bs};
952
770
 
 
771
%% Construct an external fun.
 
772
expr({make_ext_fun,Line,MFA0}, Bs0, Ieval0) ->
 
773
    {[M,F,A],Bs} = eval_list(MFA0, Bs0, Ieval0),
 
774
    try erlang:make_fun(M, F, A) of
 
775
        Value ->
 
776
            {value,Value,Bs}
 
777
    catch
 
778
        error:badarg ->
 
779
            Ieval1 = Ieval0#ieval{line=Line},
 
780
            Ieval2 = dbg_istk:push(Bs0, Ieval1, false),
 
781
            Ieval = Ieval2#ieval{module=erlang,function=make_fun,
 
782
                                 arguments=[M,F,A],line=-1},
 
783
            exception(error, badarg, Bs, Ieval, true)
 
784
    end;
 
785
 
953
786
%% Common test adaptation
954
 
expr({call_remote,0,ct_line,line,As0}, Bs0, Ieval0) ->
 
787
expr({call_remote,0,ct_line,line,As0,Lc}, Bs0, Ieval0) ->
955
788
    {As,_Bs} = eval_list(As0, Bs0, Ieval0),
956
 
    eval_function(ct_line, line, As, Bs0, extern, Ieval0);
 
789
    eval_function(ct_line, line, As, Bs0, extern, Ieval0, Lc);
957
790
 
958
791
%% Local function call
959
 
expr({local_call,Line,F,As0}, Bs0, #ieval{module=M} = Ieval0) ->
 
792
expr({local_call,Line,F,As0,Lc}, Bs0, #ieval{module=M} = Ieval0) ->
960
793
    Ieval = Ieval0#ieval{line=Line},
961
794
    {As,Bs} = eval_list(As0, Bs0, Ieval),
962
 
    eval_function(M, F, As, Bs, local, Ieval);
 
795
    eval_function(M, F, As, Bs, local, Ieval, Lc);
963
796
 
964
797
%% Remote function call
965
 
expr({call_remote,Line,M,F,As0}, Bs0, Ieval0) ->
 
798
expr({call_remote,Line,M,F,As0,Lc}, Bs0, Ieval0) ->
966
799
    Ieval = Ieval0#ieval{line=Line},
967
800
    {As,Bs} = eval_list(As0, Bs0, Ieval),
968
 
    eval_function(M, F, As, Bs, extern, Ieval);
 
801
    eval_function(M, F, As, Bs, extern, Ieval, Lc);
969
802
 
970
803
%% Emulated semantics of some BIFs
971
804
expr({dbg,Line,self,[]}, Bs, #ieval{level=Le}) ->
975
808
    {value,Self,Bs};
976
809
expr({dbg,Line,get_stacktrace,[]}, Bs, #ieval{level=Le}) ->
977
810
    trace(bif, {Le,Line,erlang,get_stacktrace,[]}),
978
 
    Stacktrace = get(stacktrace),
 
811
    Stacktrace = get_stacktrace(),
979
812
    trace(return, {Le,Stacktrace}),
980
813
    {value,Stacktrace,Bs};
 
814
expr({dbg,Line,raise,As0}, Bs0, #ieval{level=Le}=Ieval0) ->
 
815
    %% Since erlang:get_stacktrace/0 is emulated, we will
 
816
    %% need to emulate erlang:raise/3 too so that we can
 
817
    %% capture the stacktrace.
 
818
    Ieval = Ieval0#ieval{line=Line},
 
819
    {[Class,Reason,Stk0]=As,Bs} = eval_list(As0, Bs0, Ieval),
 
820
    trace(bif, {Le,Line,erlang,raise,As}),
 
821
    try
 
822
        %% Evaluate raise/3 for error checking and
 
823
        %% truncating of the stacktrace to the correct depth.
 
824
        Error = erlang:raise(Class, Reason, Stk0),
 
825
        trace(return, {Le,Error}),
 
826
        {value,Error,Bs}
 
827
    catch
 
828
        _:_ ->
 
829
            Stk = erlang:get_stacktrace(),      %Possibly truncated.
 
830
            StkFun = fun(_) -> Stk end,
 
831
            do_exception(Class, Reason, StkFun, Bs, Ieval)
 
832
    end;
981
833
expr({dbg,Line,throw,As0}, Bs0, #ieval{level=Le}=Ieval0) ->
982
834
    Ieval = Ieval0#ieval{line=Line},
983
835
    {[Term],Bs} = eval_list(As0, Bs0, Ieval),
988
840
    {[Term],Bs} = eval_list(As0, Bs0, Ieval),
989
841
    trace(bif, {Le,Line,erlang,error,[Term]}),
990
842
    exception(error, Term, Bs, Ieval);
991
 
expr({dbg,Line,fault,As0}, Bs0, #ieval{level=Le}=Ieval0) ->
992
 
    Ieval = Ieval0#ieval{line=Line},
993
 
    {[Term],Bs} = eval_list(As0, Bs0, Ieval),
994
 
    trace(bif, {Le,Line,erlang,fault,[Term]}),
995
 
    exception(fault, Term, Bs, Ieval);
996
843
expr({dbg,Line,exit,As0}, Bs0, #ieval{level=Le}=Ieval0) ->
997
844
    Ieval = Ieval0#ieval{line=Line},
998
845
    {[Term],Bs} = eval_list(As0, Bs0, Ieval),
1001
848
 
1002
849
%% Call to "safe" BIF, ie a BIF that can be executed in Meta process
1003
850
expr({safe_bif,Line,M,F,As0}, Bs0, #ieval{level=Le}=Ieval0) ->
1004
 
    Ieval = Ieval0#ieval{line=Line},
1005
 
    {As,Bs} = eval_list(As0, Bs0, Ieval),
 
851
    Ieval1 = Ieval0#ieval{line=Line},
 
852
    {As,Bs} = eval_list(As0, Bs0, Ieval1),
1006
853
    trace(bif, {Le,Line,M,F,As}),
1007
 
    push({M,F,As}, Bs0, Ieval),
 
854
    Ieval2 = dbg_istk:push(Bs0, Ieval1, false),
 
855
    Ieval = Ieval2#ieval{module=M,function=F,arguments=As,line=-1},
1008
856
    {_,Value,_} = Res = safe_bif(M, F, As, Bs, Ieval),
1009
857
    trace(return, {Le,Value}),
1010
 
    pop(),
 
858
    dbg_istk:pop(),
1011
859
    Res;
1012
860
 
1013
861
%% Call to a BIF that must be evaluated in the correct process
1014
862
expr({bif,Line,M,F,As0}, Bs0, #ieval{level=Le}=Ieval0) ->
1015
 
    Ieval = Ieval0#ieval{line=Line},
1016
 
    {As,Bs} = eval_list(As0, Bs0, Ieval),
 
863
    Ieval1 = Ieval0#ieval{line=Line},
 
864
    {As,Bs} = eval_list(As0, Bs0, Ieval1),
1017
865
    trace(bif, {Le,Line,M,F,As}),
1018
 
    push({M,F,As}, Bs0, Ieval),
1019
 
    {_,Value,_} =
1020
 
        Res = debugged_cmd({apply,M,F,As}, Bs, Ieval#ieval{level=Le+1}),
 
866
    Ieval2 = dbg_istk:push(Bs0, Ieval1, false),
 
867
    Ieval = Ieval2#ieval{module=M,function=F,arguments=As,line=-1},
 
868
    {_,Value,_} = Res = debugged_cmd({apply,M,F,As}, Bs, Ieval),
1021
869
    trace(return, {Le,Value}),
1022
 
    pop(),
1023
 
    Res;
1024
 
 
1025
 
%% Call to a BIF that spawns a new process
1026
 
expr({spawn_bif,Line,M,F,As0}, Bs0, #ieval{level=Le}=Ieval0) ->
1027
 
    Ieval = Ieval0#ieval{line=Line},
1028
 
    {As,Bs} = eval_list(As0, Bs0, Ieval),
1029
 
    trace(bif, {Le,Line,M,F,As}),
1030
 
    push({M,F,As}, Bs0, Ieval),
1031
 
    Res = debugged_cmd({apply,M,F,As}, Bs,Ieval#ieval{level=Le+1}),
1032
 
    trace(return, {Le,Res}),
1033
 
    pop(),
 
870
    dbg_istk:pop(),
1034
871
    Res;
1035
872
 
1036
873
%% Call to an operation
1046
883
    end;
1047
884
 
1048
885
%% apply/2 (fun)
1049
 
expr({apply_fun,Line,Fun0,As0}, Bs0, #ieval{level=Le}=Ieval0) ->
 
886
expr({apply_fun,Line,Fun0,As0,Lc}, Bs0, #ieval{level=Le}=Ieval0) ->
1050
887
    Ieval = Ieval0#ieval{line=Line},
1051
888
    FunValue = case expr(Fun0, Bs0, Ieval) of
1052
889
                   {value,{dbg_apply,Mx,Fx,Asx},Bsx} ->
1058
895
    case FunValue of
1059
896
        {value,Fun,Bs1} when is_function(Fun) ->
1060
897
            {As,Bs} = eval_list(As0, Bs1, Ieval),
1061
 
            eval_function(undefined, Fun, As, Bs, extern, Ieval);
 
898
            eval_function(undefined, Fun, As, Bs, extern, Ieval, Lc);
1062
899
        {value,{M,F},Bs1} when is_atom(M), is_atom(F) ->
1063
900
            {As,Bs} = eval_list(As0, Bs1, Ieval),
1064
 
            eval_function(M, F, As, Bs, extern, Ieval);
 
901
            eval_function(M, F, As, Bs, extern, Ieval, Lc);
1065
902
        {value,BadFun,Bs1} ->
1066
903
            exception(error, {badfun,BadFun}, Bs1, Ieval)
1067
904
    end;
1068
905
 
1069
906
%% apply/3
1070
 
expr({apply,Line,As0}, Bs0, Ieval0) ->
 
907
expr({apply,Line,As0,Lc}, Bs0, Ieval0) ->
1071
908
    Ieval = Ieval0#ieval{line=Line},
1072
909
    {[M,F,As],Bs} = eval_list(As0, Bs0, Ieval),
1073
 
    eval_function(M, F, As, Bs, extern, Ieval);
 
910
    eval_function(M, F, As, Bs, extern, Ieval, Lc);
1074
911
    
1075
 
%% Mod:module_info/0,1
1076
 
expr({module_info_0,_,Mod}, Bs, _Ieval) ->
1077
 
    {value,[{compile,module_info(Mod,compile)},
1078
 
            {attributes,module_info(Mod,attributes)},
1079
 
            {imports,module_info(Mod,imports)},
1080
 
            {exports,module_info(Mod,exports)}],Bs};
1081
 
expr({module_info_1,Line,Mod,[As0]}, Bs0, Ieval0) ->
1082
 
    Ieval = Ieval0#ieval{line=Line},
1083
 
    {value,What,Bs} = expr(As0, Bs0, Ieval),
1084
 
    {value,module_info(Mod, What),Bs};
1085
 
 
1086
912
%% Receive statement
1087
913
expr({'receive',Line,Cs}, Bs0, #ieval{level=Le}=Ieval) ->
1088
914
    trace(receivex, {Le,false}),
1091
917
%% Receive..after statement
1092
918
expr({'receive',Line,Cs,To,ToExprs}, Bs0, #ieval{level=Le}=Ieval0) ->
1093
919
    Ieval = Ieval0#ieval{line=Line},
1094
 
    {value,ToVal,ToBs} = expr(To, Bs0, Ieval#ieval{last_call=false}),
 
920
    {value,ToVal,ToBs} = expr(To, Bs0, Ieval#ieval{top=false}),
1095
921
    trace(receivex, {Le,true}),
1096
922
    check_timeoutvalue(ToVal, ToBs, To, Ieval),
1097
923
    {Stamp,_} = statistics(wall_clock),
1101
927
%% Send (!)
1102
928
expr({send,Line,To0,Msg0}, Bs0, Ieval0) ->
1103
929
    Ieval = Ieval0#ieval{line=Line},
1104
 
    Ieval1 = Ieval#ieval{last_call=false},
 
930
    Ieval1 = Ieval#ieval{top=false},
1105
931
    {value,To,Bs1} = expr(To0, Bs0, Ieval1),
1106
932
    {value,Msg,Bs2} = expr(Msg0, Bs0, Ieval1),
1107
933
    Bs = merge_bindings(Bs2, Bs1, Ieval),
1110
936
%% Binary
1111
937
expr({bin,Line,Fs}, Bs0, Ieval0) ->
1112
938
    Ieval = Ieval0#ieval{line=Line},
1113
 
    eval_bits:expr_grp(Fs, Bs0,
1114
 
                       fun (E, B) -> expr(E, B, Ieval) end,
1115
 
                       [],
1116
 
                       false);
 
939
    try
 
940
        eval_bits:expr_grp(Fs, Bs0,
 
941
                           fun (E, B) -> expr(E, B, Ieval) end,
 
942
                           [],
 
943
                           false)
 
944
    catch
 
945
        Class:Reason ->
 
946
            exception(Class, Reason, Bs0, Ieval)
 
947
    end;
1117
948
 
1118
949
%% List comprehension
1119
950
expr({lc,_Line,E,Qs}, Bs, Ieval) ->
1138
969
 
1139
970
eval_lc1(E, [{generate,Line,P,L0}|Qs], Bs0, Ieval0) ->
1140
971
    Ieval = Ieval0#ieval{line=Line},
1141
 
    {value,L1,Bs1} = expr(L0, Bs0, Ieval#ieval{last_call=false}),
 
972
    {value,L1,Bs1} = expr(L0, Bs0, Ieval#ieval{top=false}),
1142
973
    CompFun = fun(NewBs) -> eval_lc1(E, Qs, NewBs, Ieval) end,
1143
974
    eval_generate(L1, P, Bs1, CompFun, Ieval);
1144
975
eval_lc1(E, [{b_generate,Line,P,L0}|Qs], Bs0, Ieval0) ->
1145
976
    Ieval = Ieval0#ieval{line=Line},
1146
 
    {value,Bin,_} = expr(L0, Bs0, Ieval#ieval{last_call=false}),
 
977
    {value,Bin,_} = expr(L0, Bs0, Ieval#ieval{top=false}),
1147
978
    CompFun = fun(NewBs) -> eval_lc1(E, Qs, NewBs, Ieval) end,
1148
979
    eval_b_generate(Bin, P, Bs0, CompFun, Ieval);
1149
980
eval_lc1(E, [{guard,Q}|Qs], Bs0, Ieval) ->
1152
983
        false -> []
1153
984
    end;
1154
985
eval_lc1(E, [Q|Qs], Bs0, Ieval) ->
1155
 
    case expr(Q, Bs0, Ieval#ieval{last_call=false}) of
 
986
    case expr(Q, Bs0, Ieval#ieval{top=false}) of
1156
987
        {value,true,Bs} -> eval_lc1(E, Qs, Bs, Ieval);
1157
988
        {value,false,_Bs} -> [];
1158
989
        {value,V,Bs} -> exception(error, {bad_filter,V}, Bs, Ieval)
1159
990
    end;
1160
991
eval_lc1(E, [], Bs, Ieval) ->
1161
 
    {value,V,_} = expr(E, Bs, Ieval#ieval{last_call=false}),
 
992
    {value,V,_} = expr(E, Bs, Ieval#ieval{top=false}),
1162
993
    [V].
1163
994
 
1164
995
%% eval_bc(Expr,[Qualifier],Bindings,IevalState) ->
1171
1002
 
1172
1003
eval_bc1(E, [{generate,Line,P,L0}|Qs], Bs0, Ieval0) ->
1173
1004
    Ieval = Ieval0#ieval{line=Line},
1174
 
    {value,L1,Bs1} = expr(L0, Bs0, Ieval#ieval{last_call=false}),
 
1005
    {value,L1,Bs1} = expr(L0, Bs0, Ieval#ieval{top=false}),
1175
1006
    CompFun = fun(NewBs) -> eval_bc1(E, Qs, NewBs, Ieval) end,
1176
1007
    eval_generate(L1, P, Bs1, CompFun, Ieval);
1177
1008
eval_bc1(E, [{b_generate,Line,P,L0}|Qs], Bs0, Ieval0) ->
1178
1009
    Ieval = Ieval0#ieval{line=Line},
1179
 
    {value,Bin,_} = expr(L0, Bs0, Ieval#ieval{last_call=false}),
 
1010
    {value,Bin,_} = expr(L0, Bs0, Ieval#ieval{top=false}),
1180
1011
    CompFun = fun(NewBs) -> eval_bc1(E, Qs, NewBs, Ieval) end,
1181
1012
    eval_b_generate(Bin, P, Bs0, CompFun, Ieval);
1182
1013
eval_bc1(E, [{guard,Q}|Qs], Bs0, Ieval) ->
1185
1016
        false -> []
1186
1017
    end;
1187
1018
eval_bc1(E, [Q|Qs], Bs0, Ieval) ->
1188
 
    case expr(Q, Bs0, Ieval#ieval{last_call=false}) of
 
1019
    case expr(Q, Bs0, Ieval#ieval{top=false}) of
1189
1020
        {value,true,Bs} -> eval_bc1(E, Qs, Bs, Ieval);
1190
1021
        {value,false,_Bs} -> [];
1191
1022
        {value,V,Bs} -> exception(error, {bad_filter,V}, Bs, Ieval)
1192
1023
    end;
1193
1024
eval_bc1(E, [], Bs, Ieval) ->
1194
 
    {value,V,_} = expr(E, Bs, Ieval#ieval{last_call=false}),
 
1025
    {value,V,_} = expr(E, Bs, Ieval#ieval{top=false}),
1195
1026
    [V].
1196
1027
 
1197
1028
eval_generate([V|Rest], P, Bs0, CompFun, Ieval) ->
1208
1039
    exception(error, {bad_generator,Term}, Bs, Ieval).
1209
1040
 
1210
1041
eval_b_generate(<<_/bitstring>>=Bin, P, Bs0, CompFun, Ieval) ->
1211
 
    Mfun = fun(L, R, Bs) -> match1(L, R, Bs, Bs0) end,
 
1042
    Mfun = match_fun(Bs0),
1212
1043
    Efun = fun(Exp, Bs) -> expr(Exp, Bs, #ieval{}) end,
1213
1044
    case eval_bits:bin_gen(P, Bin, erl_eval:new_bindings(), Bs0, Mfun, Efun) of
1214
1045
        {match,Rest,Bs1} ->
1222
1053
eval_b_generate(Term, _P, Bs, _CompFun, Ieval) ->
1223
1054
    exception(error, {bad_generator,Term}, Bs, Ieval).
1224
1055
 
1225
 
module_info(Mod, module) -> Mod;
1226
 
module_info(_Mod, compile) -> [];
1227
 
module_info(Mod, attributes) ->
1228
 
    {ok, Attr} = dbg_iserver:call(get(int), {lookup, Mod, attributes}),
1229
 
    Attr;
1230
 
module_info(_Mod, imports) -> [];
1231
 
module_info(Mod, exports) ->
1232
 
    {ok, Exp} = dbg_iserver:call(get(int), {lookup, Mod, exports}),
1233
 
    Exp;
1234
 
module_info(_Mod, functions) -> [].
1235
 
 
1236
1056
safe_bif(M, F, As, Bs, Ieval) ->
1237
1057
    try apply(M, F, As) of
1238
1058
        Value ->
1239
1059
            {value,Value,Bs}
1240
1060
    catch
1241
1061
        Class:Reason ->
1242
 
            exception(Class, Reason, Bs, Ieval)
 
1062
            exception(Class, Reason, Bs, Ieval, true)
1243
1063
    end.
1244
1064
 
1245
1065
eval_send(To, Msg, Bs, Ieval) ->
1408
1228
%% eval_list(ExpressionList, Bindings, Ieval)
1409
1229
%%  Evaluate a list of expressions "in parallel" at the same level.
1410
1230
eval_list(Es, Bs, Ieval) ->
1411
 
    eval_list(Es, [], Bs, Bs, Ieval).
 
1231
    eval_list_1(Es, [], Bs, Bs, Ieval#ieval{top=false}).
1412
1232
 
1413
 
eval_list([E|Es], Vs, BsOrig, Bs0, Ieval) ->
1414
 
    {value,V,Bs1} = expr(E, BsOrig, Ieval#ieval{last_call=false}),
1415
 
    eval_list(Es, [V|Vs], BsOrig, merge_bindings(Bs1,Bs0,Ieval), Ieval);
1416
 
eval_list([], Vs, _, Bs, _Ieval) ->
 
1233
eval_list_1([E|Es], Vs, BsOrig, Bs0, Ieval) ->
 
1234
    {value,V,Bs1} = expr(E, BsOrig, Ieval),
 
1235
    eval_list_1(Es, [V|Vs], BsOrig, merge_bindings(Bs1, Bs0, Ieval), Ieval);
 
1236
eval_list_1([], Vs, _, Bs, _Ieval) ->
1417
1237
    {lists:reverse(Vs,[]),Bs}.
1418
1238
 
1419
1239
%% if_clauses(Clauses, Bindings, Ieval)
1453
1273
                true ->
1454
1274
                    %% Exception caught, reset exit info
1455
1275
                    put(exit_info, undefined),
1456
 
                    pop(Ieval#ieval.level),
 
1276
                    dbg_istk:pop(Ieval#ieval.level),
1457
1277
                    seq(B, Bs, Ieval);
1458
1278
                false ->
1459
1279
                    catch_clauses(Exception, CatchCs, Bs0, Ieval)
1588
1408
match1({tuple,_,Elts}, Tuple, Bs, BBs) 
1589
1409
  when length(Elts) =:= tuple_size(Tuple) ->
1590
1410
    match_tuple(Elts, Tuple, 1, Bs, BBs);
1591
 
match1({bin,_,Fs}, B, Bs0, BBs0) when is_bitstring(B) ->
1592
 
    Bs1 = lists:sort(Bs0),  %Kludge.
1593
 
    BBs = lists:sort(BBs0),
1594
 
    try eval_bits:match_bits(Fs, B, Bs1, BBs,
1595
 
                             fun(L, R, Bs) -> match1(L, R, Bs, BBs) end,
 
1411
match1({bin,_,Fs}, B, Bs0, BBs) when is_bitstring(B) ->
 
1412
    try eval_bits:match_bits(Fs, B, Bs0, BBs,
 
1413
                             match_fun(BBs),
1596
1414
                             fun(E, Bs) -> expr(E, Bs, #ieval{}) end,
1597
1415
                             false)
1598
1416
    catch
1601
1419
match1(_,_,_,_) ->
1602
1420
    throw(nomatch).
1603
1421
 
 
1422
match_fun(BBs) ->
 
1423
    fun(match, {L,R,Bs}) -> match1(L, R, Bs, BBs);
 
1424
       (binding, {Name,Bs}) -> binding(Name, Bs);
 
1425
       (add_binding, {Name,Val,Bs}) -> add_binding(Name, Val, Bs)
 
1426
    end.
 
1427
 
1604
1428
match_tuple([E|Es], Tuple, I, Bs0, BBs) ->
1605
1429
    {match,Bs} = match1(E, element(I, Tuple), Bs0, BBs),
1606
1430
    match_tuple(Es, Tuple, I+1, Bs, BBs);
1731
1555
    [B1|add_binding(N,Val,Bs)];
1732
1556
add_binding(N,Val,[]) ->
1733
1557
    [{N,Val}].
 
1558
 
 
1559
%% get_stacktrace() -> Stacktrace
 
1560
%%  Return the latest stacktrace for the process.
 
1561
get_stacktrace() ->
 
1562
    case get(stacktrace) of
 
1563
        MakeStk when is_function(MakeStk, 1) ->
 
1564
            %% The stacktrace has not been constructed before.
 
1565
            %% Construct it and remember the result.
 
1566
            Depth = erlang:system_flag(backtrace_depth, 8),
 
1567
            erlang:system_flag(backtrace_depth, Depth),
 
1568
            Stk = MakeStk(Depth),
 
1569
            put(stacktrace, Stk),
 
1570
            Stk;
 
1571
        Stk when is_list(Stk) ->
 
1572
            Stk
 
1573
    end.