~ubuntu-branches/ubuntu/trusty/erlang/trusty

« back to all changes in this revision

Viewing changes to erts/emulator/beam/beam_bp.c

  • Committer: Bazaar Package Importer
  • Author(s): Clint Byrum
  • Date: 2011-05-05 15:48:43 UTC
  • mfrom: (3.5.13 sid)
  • Revision ID: james.westby@ubuntu.com-20110505154843-0om6ekzg6m7ugj27
Tags: 1:14.b.2-dfsg-3ubuntu1
* Merge from debian unstable.  Remaining changes:
  - Drop libwxgtk2.8-dev build dependency. Wx isn't in main, and not
    supposed to.
  - Drop erlang-wx binary.
  - Drop erlang-wx dependency from -megaco, -common-test, and -reltool, they
    do not really need wx. Also drop it from -debugger; the GUI needs wx,
    but it apparently has CLI bits as well, and is also needed by -megaco,
    so let's keep the package for now.
  - debian/patches/series: Do what I meant, and enable build-options.patch
    instead.
* Additional changes:
  - Drop erlang-wx from -et
* Dropped Changes:
  - patches/pcre-crash.patch: CVE-2008-2371: outer level option with
    alternatives caused crash. (Applied Upstream)
  - fix for ssl certificate verification in newSSL: 
    ssl_cacertfile_fix.patch (Applied Upstream)
  - debian/patches/series: Enable native.patch again, to get stripped beam
    files and reduce the package size again. (build-options is what
    actually accomplished this)
  - Remove build-options.patch on advice from upstream and because it caused
    odd build failures.

Show diffs side-by-side

added added

removed removed

Lines of Context:
1
1
/*
2
2
 * %CopyrightBegin%
3
 
 * 
4
 
 * Copyright Ericsson AB 2000-2009. All Rights Reserved.
5
 
 * 
 
3
 *
 
4
 * Copyright Ericsson AB 2000-2010. All Rights Reserved.
 
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
8
8
 * compliance with the License. You should have received a copy of the
9
9
 * Erlang Public License along with this software. If not, it can be
10
10
 * retrieved online at http://www.erlang.org/.
11
 
 * 
 
11
 *
12
12
 * Software distributed under the License is distributed on an "AS IS"
13
13
 * basis, WITHOUT WARRANTY OF ANY KIND, either express or implied. See
14
14
 * the License for the specific language governing rights and limitations
15
15
 * under the License.
16
 
 * 
 
16
 *
17
17
 * %CopyrightEnd%
18
18
 */
19
19
 
30
30
#include "error.h"
31
31
#include "erl_binary.h"
32
32
#include "beam_bp.h"
 
33
#include "erl_term.h"
33
34
 
34
35
/* *************************************************************************
35
36
** Macros
100
101
    (b)->prev = (a);               \
101
102
} while (0)
102
103
 
 
104
 
 
105
#define BREAK_IS_BIF (1)
 
106
#define BREAK_IS_ERL (0)
 
107
 
 
108
 
103
109
/* *************************************************************************
104
110
** Local prototypes
105
111
*/
109
115
*/
110
116
 
111
117
static int set_break(Eterm mfa[3], int specified,
112
 
                     Binary *match_spec, Uint break_op, 
 
118
                     Binary *match_spec, BeamInstr break_op,
113
119
                     enum erts_break_op count_op, Eterm tracer_pid);
114
120
static int set_module_break(Module *modp, Eterm mfa[3], int specified,
115
 
                            Binary *match_spec, Uint break_op,
 
121
                            Binary *match_spec, BeamInstr break_op,
116
122
                            enum erts_break_op count_op, Eterm tracer_pid);
117
 
static int set_function_break(Module *modp, Uint *pc,
118
 
                              Binary *match_spec, Uint break_op,
 
123
static int set_function_break(Module *modp, BeamInstr *pc, int bif,
 
124
                              Binary *match_spec, BeamInstr break_op,
119
125
                              enum erts_break_op count_op, Eterm tracer_pid); 
120
126
 
121
127
static int clear_break(Eterm mfa[3], int specified, 
122
 
                       Uint break_op);
 
128
                       BeamInstr break_op);
123
129
static int clear_module_break(Module *modp, Eterm mfa[3], int specified, 
124
 
                              Uint break_op);
125
 
static int clear_function_break(Module *modp, Uint *pc, 
126
 
                                Uint break_op);
127
 
 
128
 
static BpData *is_break(Uint *pc, Uint break_op);
129
 
 
 
130
                              BeamInstr break_op);
 
131
static int clear_function_break(Module *modp, BeamInstr *pc, int bif,
 
132
                                BeamInstr break_op);
 
133
 
 
134
static BpData *is_break(BeamInstr *pc, BeamInstr break_op);
 
135
static BpData *get_break(Process *p, BeamInstr *pc, BeamInstr break_op);
 
136
 
 
137
/* bp_hash */
 
138
#define BP_TIME_ADD(pi0, pi1)                       \
 
139
    do {                                            \
 
140
        Uint r;                                     \
 
141
        (pi0)->count   += (pi1)->count;             \
 
142
        (pi0)->s_time  += (pi1)->s_time;            \
 
143
        (pi0)->us_time += (pi1)->us_time;           \
 
144
        r = (pi0)->us_time / 1000000;               \
 
145
        (pi0)->s_time  += r;                        \
 
146
        (pi0)->us_time  = (pi0)->us_time % 1000000; \
 
147
    } while(0)
 
148
 
 
149
static void bp_hash_init(bp_time_hash_t *hash, Uint n);
 
150
static void bp_hash_rehash(bp_time_hash_t *hash, Uint n);
 
151
static ERTS_INLINE bp_data_time_item_t * bp_hash_get(bp_time_hash_t *hash, bp_data_time_item_t *sitem);
 
152
static ERTS_INLINE bp_data_time_item_t * bp_hash_put(bp_time_hash_t *hash, bp_data_time_item_t *sitem);
 
153
static void bp_hash_delete(bp_time_hash_t *hash);
130
154
 
131
155
 
132
156
/* *************************************************************************
145
169
                     Eterm tracer_pid) {
146
170
    ERTS_SMP_LC_ASSERT(erts_smp_is_system_blocked(0));
147
171
    return set_break(mfa, specified, match_spec,
148
 
                     (Uint) BeamOp(op_i_trace_breakpoint), 0, tracer_pid);
 
172
                     (BeamInstr) BeamOp(op_i_trace_breakpoint), 0, tracer_pid);
149
173
}
150
174
 
151
175
int 
153
177
                      Eterm tracer_pid) {
154
178
    ERTS_SMP_LC_ASSERT(erts_smp_is_system_blocked(0));
155
179
    return set_break(mfa, specified, match_spec,
156
 
                     (Uint) BeamOp(op_i_mtrace_breakpoint), 0, tracer_pid);
 
180
                     (BeamInstr) BeamOp(op_i_mtrace_breakpoint), 0, tracer_pid);
157
181
}
158
182
 
 
183
/* set breakpoint data for on exported bif entry */
 
184
 
159
185
void
160
 
erts_set_mtrace_bif(Uint *pc, Binary *match_spec, Eterm tracer_pid) {
161
 
    BpDataTrace *bdt;
 
186
erts_set_mtrace_bif(BeamInstr *pc, Binary *match_spec, Eterm tracer_pid) {
162
187
    ERTS_SMP_LC_ASSERT(erts_smp_is_system_blocked(0));
163
 
 
164
 
    bdt = (BpDataTrace *) pc[-4];
165
 
    if (bdt) {
166
 
        MatchSetUnref(bdt->match_spec);
167
 
        MatchSetRef(match_spec);
168
 
        bdt->match_spec = match_spec;
169
 
        bdt->tracer_pid = tracer_pid;
170
 
    } else {
171
 
        bdt = Alloc(sizeof(BpDataTrace));
172
 
        BpInit((BpData *) bdt, 0);
173
 
        MatchSetRef(match_spec);
174
 
        bdt->match_spec = match_spec;
175
 
        bdt->tracer_pid = tracer_pid;
176
 
        pc[-4] = (Uint) bdt;
177
 
    }
 
188
    set_function_break(NULL, pc, BREAK_IS_BIF, match_spec, (BeamInstr) BeamOp(op_i_mtrace_breakpoint), 0, tracer_pid);
 
189
}
 
190
 
 
191
void erts_set_time_trace_bif(BeamInstr *pc, enum erts_break_op count_op) {
 
192
    set_function_break(NULL, pc, BREAK_IS_BIF, NULL, (BeamInstr) BeamOp(op_i_time_breakpoint), count_op, NIL);
 
193
}
 
194
 
 
195
void erts_clear_time_trace_bif(BeamInstr *pc) {
 
196
    clear_function_break(NULL, pc, BREAK_IS_BIF, (BeamInstr) BeamOp(op_i_time_breakpoint));
178
197
}
179
198
 
180
199
int 
181
200
erts_set_debug_break(Eterm mfa[3], int specified) {
182
201
    ERTS_SMP_LC_ASSERT(erts_smp_is_system_blocked(0));
183
202
    return set_break(mfa, specified, NULL, 
184
 
                     (Uint) BeamOp(op_i_debug_breakpoint), 0, NIL);
 
203
                     (BeamInstr) BeamOp(op_i_debug_breakpoint), 0, NIL);
185
204
}
186
205
 
187
206
int 
188
207
erts_set_count_break(Eterm mfa[3], int specified, enum erts_break_op count_op) {
189
208
    ERTS_SMP_LC_ASSERT(erts_smp_is_system_blocked(0));
190
209
    return set_break(mfa, specified, NULL, 
191
 
                     (Uint) BeamOp(op_i_count_breakpoint), count_op, NIL);
192
 
}
193
 
 
194
 
 
 
210
                     (BeamInstr) BeamOp(op_i_count_breakpoint), count_op, NIL);
 
211
}
 
212
 
 
213
int
 
214
erts_set_time_break(Eterm mfa[3], int specified, enum erts_break_op count_op) {
 
215
    ERTS_SMP_LC_ASSERT(erts_smp_is_system_blocked(0));
 
216
    return set_break(mfa, specified, NULL,
 
217
                     (BeamInstr) BeamOp(op_i_time_breakpoint), count_op, NIL);
 
218
}
195
219
 
196
220
int
197
221
erts_clear_trace_break(Eterm mfa[3], int specified) {
198
222
    ERTS_SMP_LC_ASSERT(erts_smp_is_system_blocked(0));
199
223
    return clear_break(mfa, specified, 
200
 
                       (Uint) BeamOp(op_i_trace_breakpoint));
 
224
                       (BeamInstr) BeamOp(op_i_trace_breakpoint));
201
225
}
202
226
 
203
227
int
204
228
erts_clear_mtrace_break(Eterm mfa[3], int specified) {
205
229
    ERTS_SMP_LC_ASSERT(erts_smp_is_system_blocked(0));
206
230
    return clear_break(mfa, specified, 
207
 
                       (Uint) BeamOp(op_i_mtrace_breakpoint));
 
231
                       (BeamInstr) BeamOp(op_i_mtrace_breakpoint));
208
232
}
209
233
 
210
234
void
211
 
erts_clear_mtrace_bif(Uint *pc) {
212
 
    BpDataTrace *bdt;
213
 
    ERTS_SMP_LC_ASSERT(erts_smp_is_system_blocked(0));
214
 
    
215
 
    bdt = (BpDataTrace *) pc[-4];
216
 
    if (bdt) {
217
 
        if (bdt->match_spec) {
218
 
            MatchSetUnref(bdt->match_spec);
219
 
        }
220
 
        Free(bdt);
221
 
    }
222
 
    pc[-4] = (Uint) NULL;
 
235
erts_clear_mtrace_bif(BeamInstr *pc) {
 
236
    clear_function_break(NULL, pc, BREAK_IS_BIF, (BeamInstr) BeamOp(op_i_mtrace_breakpoint));
223
237
}
224
238
 
225
239
int
226
240
erts_clear_debug_break(Eterm mfa[3], int specified) {
227
241
    ERTS_SMP_LC_ASSERT(erts_smp_is_system_blocked(0));
228
242
    return clear_break(mfa, specified, 
229
 
                       (Uint) BeamOp(op_i_debug_breakpoint));
 
243
                       (BeamInstr) BeamOp(op_i_debug_breakpoint));
230
244
}
231
245
 
232
246
int
233
247
erts_clear_count_break(Eterm mfa[3], int specified) {
234
248
    ERTS_SMP_LC_ASSERT(erts_smp_is_system_blocked(0));
235
249
    return clear_break(mfa, specified, 
236
 
                       (Uint) BeamOp(op_i_count_breakpoint));
 
250
                       (BeamInstr) BeamOp(op_i_count_breakpoint));
 
251
}
 
252
 
 
253
int
 
254
erts_clear_time_break(Eterm mfa[3], int specified) {
 
255
    ERTS_SMP_LC_ASSERT(erts_smp_is_system_blocked(0));
 
256
    return clear_break(mfa, specified,
 
257
                       (BeamInstr) BeamOp(op_i_time_breakpoint));
237
258
}
238
259
 
239
260
int
250
271
}
251
272
 
252
273
int
253
 
erts_clear_function_break(Module *modp, Uint *pc) {
 
274
erts_clear_function_break(Module *modp, BeamInstr *pc) {
254
275
    ERTS_SMP_LC_ASSERT(erts_smp_is_system_blocked(0));
255
276
    ASSERT(modp);
256
 
    return clear_function_break(modp, pc, 0);
 
277
    return clear_function_break(modp, pc, BREAK_IS_ERL, 0);
257
278
}
258
279
 
259
280
 
261
282
/*
262
283
 * SMP NOTE: Process p may have become exiting on return!
263
284
 */
264
 
Uint 
265
 
erts_trace_break(Process *p, Uint *pc, Eterm *args, 
 
285
BeamInstr
 
286
erts_trace_break(Process *p, BeamInstr *pc, Eterm *args,
266
287
                 Uint32 *ret_flags, Eterm *tracer_pid) {
267
288
    Eterm tpid1, tpid2;
268
 
    BpDataTrace *bdt = (BpDataTrace *) pc[-4];
269
 
    
270
 
    ASSERT(pc[-5] == (Uint) BeamOp(op_i_func_info_IaaI));
 
289
    BpData **bds = (BpData **) (pc)[-4];
 
290
    BpDataTrace *bdt = NULL;
 
291
 
 
292
    ASSERT(bds);
 
293
    ASSERT(pc[-5] == (BeamInstr) BeamOp(op_i_func_info_IaaI));
 
294
    bdt = (BpDataTrace *) bds[bp_sched2ix_proc(p)];
271
295
    ASSERT(bdt);
272
296
    bdt = (BpDataTrace *) bdt->next;
273
297
    ASSERT(bdt);
286
310
        bdt->tracer_pid = tpid2;
287
311
        ErtsSmpBPUnlock(bdt);
288
312
    }
289
 
    pc[-4] = (Uint) bdt;
 
313
    bds[bp_sched2ix_proc(p)] = (BpData *) bdt;
290
314
    return bdt->orig_instr;
291
315
}
292
316
 
296
320
 * SMP NOTE: Process p may have become exiting on return!
297
321
 */
298
322
Uint32
299
 
erts_bif_mtrace(Process *p, Uint *pc, Eterm *args, int local, 
 
323
erts_bif_mtrace(Process *p, BeamInstr *pc, Eterm *args, int local,
300
324
                Eterm *tracer_pid) {
301
 
    BpDataTrace *bdt = (BpDataTrace *) pc[-4];
302
 
    
 
325
    BpData **bds = (BpData **) (pc)[-4];
 
326
    BpDataTrace *bdt = NULL;
 
327
 
 
328
 
303
329
    ASSERT(tracer_pid);
304
 
    if (bdt) {
 
330
    if (bds) {
305
331
        Eterm tpid1, tpid2;
306
332
        Uint32 flags;
 
333
        bdt = (BpDataTrace *)bds[bp_sched2ix_proc(p)];
307
334
 
308
335
        ErtsSmpBPLock(bdt);
309
336
        tpid1 = tpid2 = bdt->tracer_pid;
326
353
 
327
354
 
328
355
int 
329
 
erts_is_trace_break(Uint *pc, Binary **match_spec_ret, Eterm *tracer_pid_ret) {
 
356
erts_is_trace_break(BeamInstr *pc, Binary **match_spec_ret, Eterm *tracer_pid_ret) {
330
357
    BpDataTrace *bdt = 
331
 
        (BpDataTrace *) is_break(pc, (Uint) BeamOp(op_i_trace_breakpoint));
 
358
        (BpDataTrace *) is_break(pc, (BeamInstr) BeamOp(op_i_trace_breakpoint));
332
359
    
333
360
    if (bdt) {
334
361
        if (match_spec_ret) {
345
372
}
346
373
 
347
374
int 
348
 
erts_is_mtrace_break(Uint *pc, Binary **match_spec_ret, Eterm *tracer_pid_ret) {
 
375
erts_is_mtrace_break(BeamInstr *pc, Binary **match_spec_ret, Eterm *tracer_pid_ret) {
349
376
    BpDataTrace *bdt = 
350
 
        (BpDataTrace *) is_break(pc, (Uint) BeamOp(op_i_mtrace_breakpoint));
351
 
    
352
 
    if (bdt) {
353
 
        if (match_spec_ret) {
354
 
            *match_spec_ret = bdt->match_spec;
355
 
        }
356
 
        if (tracer_pid_ret) {
357
 
            ErtsSmpBPLock(bdt);
358
 
            *tracer_pid_ret = bdt->tracer_pid;
359
 
            ErtsSmpBPUnlock(bdt);
360
 
        }
361
 
        return !0;
362
 
    }
363
 
    return 0;
364
 
}
365
 
 
366
 
int
367
 
erts_is_mtrace_bif(Uint *pc, Binary **match_spec_ret, Eterm *tracer_pid_ret) {
368
 
    BpDataTrace *bdt = (BpDataTrace *) pc[-4];
369
 
    
370
 
    if (bdt) {
371
 
        if (match_spec_ret) {
372
 
            *match_spec_ret = bdt->match_spec;
373
 
        }
374
 
        if (tracer_pid_ret) {
375
 
            ErtsSmpBPLock(bdt);
376
 
            *tracer_pid_ret = bdt->tracer_pid;
377
 
            ErtsSmpBPUnlock(bdt);
378
 
        }
379
 
        return !0;
380
 
    }
381
 
    return 0;
382
 
}
383
 
 
384
 
int
385
 
erts_is_native_break(Uint *pc) {
 
377
        (BpDataTrace *) is_break(pc, (BeamInstr) BeamOp(op_i_mtrace_breakpoint));
 
378
    
 
379
    if (bdt) {
 
380
        if (match_spec_ret) {
 
381
            *match_spec_ret = bdt->match_spec;
 
382
        }
 
383
        if (tracer_pid_ret) {
 
384
            ErtsSmpBPLock(bdt);
 
385
            *tracer_pid_ret = bdt->tracer_pid;
 
386
            ErtsSmpBPUnlock(bdt);
 
387
        }
 
388
        return !0;
 
389
    }
 
390
    return 0;
 
391
}
 
392
 
 
393
int
 
394
erts_is_native_break(BeamInstr *pc) {
386
395
#ifdef HIPE
387
 
    ASSERT(pc[-5] == (Uint) BeamOp(op_i_func_info_IaaI));
388
 
    return pc[0]  == (Uint) BeamOp(op_hipe_trap_call) 
389
 
        || pc[0]  == (Uint) BeamOp(op_hipe_trap_call_closure);
 
396
    ASSERT(pc[-5] == (BeamInstr) BeamOp(op_i_func_info_IaaI));
 
397
    return pc[0]  == (BeamInstr) BeamOp(op_hipe_trap_call)
 
398
        || pc[0]  == (BeamInstr) BeamOp(op_hipe_trap_call_closure);
390
399
#else
391
400
    return 0;
392
401
#endif
393
402
}
394
403
 
395
404
int 
396
 
erts_is_count_break(Uint *pc, Sint *count_ret) {
 
405
erts_is_count_break(BeamInstr *pc, Sint *count_ret) {
397
406
    BpDataCount *bdc = 
398
 
        (BpDataCount *) is_break(pc, (Uint) BeamOp(op_i_count_breakpoint));
 
407
        (BpDataCount *) is_break(pc, (BeamInstr) BeamOp(op_i_count_breakpoint));
399
408
    
400
409
    if (bdc) {
401
410
        if (count_ret) {
402
 
            ErtsSmpBPLock(bdc);
403
 
            *count_ret = bdc->count;
404
 
            ErtsSmpBPUnlock(bdc);
405
 
        }
406
 
        return !0;
407
 
    }
408
 
    return 0;
409
 
}
410
 
 
411
 
Uint *
 
411
            *count_ret = (Sint) erts_smp_atomic_read(&bdc->acount);
 
412
        }
 
413
        return !0;
 
414
    }
 
415
    return 0;
 
416
}
 
417
 
 
418
int erts_is_time_break(Process *p, BeamInstr *pc, Eterm *retval) {
 
419
    Uint i, ix;
 
420
    bp_time_hash_t hash;
 
421
    Uint size;
 
422
    Eterm *hp, t;
 
423
    bp_data_time_item_t *item = NULL;
 
424
    BpDataTime *bdt = (BpDataTime *) is_break(pc, (BeamInstr) BeamOp(op_i_time_breakpoint));
 
425
 
 
426
    if (bdt) {
 
427
        if (retval) {
 
428
            /* collect all hashes to one hash */
 
429
            bp_hash_init(&hash, 64);
 
430
            /* foreach threadspecific hash */
 
431
            for (i = 0; i < bdt->n; i++) {
 
432
                bp_data_time_item_t *sitem;
 
433
 
 
434
                /* foreach hash bucket not NIL*/
 
435
                for(ix = 0; ix < bdt->hash[i].n; ix++) {
 
436
                    item = &(bdt->hash[i].item[ix]);
 
437
                    if (item->pid != NIL) {
 
438
                        sitem = bp_hash_get(&hash, item);
 
439
                        if (sitem) {
 
440
                            BP_TIME_ADD(sitem, item);
 
441
                        } else {
 
442
                            bp_hash_put(&hash, item);
 
443
                        }
 
444
                    }
 
445
                }
 
446
            }
 
447
            /* *retval should be NIL or term from previous bif in export entry */
 
448
 
 
449
            if (hash.used > 0) {
 
450
                size = (5 + 2)*hash.used;
 
451
                hp   = HAlloc(p, size);
 
452
 
 
453
                for(ix = 0; ix < hash.n; ix++) {
 
454
                    item = &(hash.item[ix]);
 
455
                    if (item->pid != NIL) {
 
456
                        t = TUPLE4(hp, item->pid,
 
457
                                make_small(item->count),
 
458
                                make_small(item->s_time),
 
459
                                make_small(item->us_time));
 
460
                        hp += 5;
 
461
                        *retval = CONS(hp, t, *retval); hp += 2;
 
462
                    }
 
463
                }
 
464
            }
 
465
            bp_hash_delete(&hash);
 
466
        }
 
467
        return !0;
 
468
    }
 
469
 
 
470
    return 0;
 
471
}
 
472
 
 
473
 
 
474
BeamInstr *
412
475
erts_find_local_func(Eterm mfa[3]) {
413
476
    Module *modp;
414
 
    Uint** code_base;
415
 
    Uint* code_ptr;
 
477
    BeamInstr** code_base;
 
478
    BeamInstr* code_ptr;
416
479
    Uint i,n;
417
480
 
418
481
    if ((modp = erts_get_module(mfa[0])) == NULL)
419
482
        return NULL;
420
 
    if ((code_base = (Uint **) modp->code) == NULL)
 
483
    if ((code_base = (BeamInstr **) modp->code) == NULL)
421
484
        return NULL;
422
 
    n = (Uint) code_base[MI_NUM_FUNCTIONS];
 
485
    n = (BeamInstr) code_base[MI_NUM_FUNCTIONS];
423
486
    for (i = 0; i < n; ++i) {
424
487
        code_ptr = code_base[MI_FUNCTIONS+i];
425
 
        ASSERT(((Uint) BeamOp(op_i_func_info_IaaI)) == code_ptr[0]);
 
488
        ASSERT(((BeamInstr) BeamOp(op_i_func_info_IaaI)) == code_ptr[0]);
426
489
        ASSERT(mfa[0] == ((Eterm) code_ptr[2]));
427
490
        if (mfa[1] == ((Eterm) code_ptr[3]) &&
428
 
            ((Uint) mfa[2]) == code_ptr[4]) {
 
491
            ((BeamInstr) mfa[2]) == code_ptr[4]) {
429
492
            return code_ptr + 5;
430
493
        }
431
494
    }
432
495
    return NULL;
433
496
}
434
497
 
 
498
/* bp_hash */
 
499
ERTS_INLINE Uint bp_sched2ix() {
 
500
#ifdef ERTS_SMP
 
501
    ErtsSchedulerData *esdp;
 
502
    esdp = erts_get_scheduler_data();
 
503
    return esdp->no - 1;
 
504
#else
 
505
    return 0;
 
506
#endif
 
507
}
 
508
static void bp_hash_init(bp_time_hash_t *hash, Uint n) {
 
509
    Uint size = sizeof(bp_data_time_item_t)*n;
 
510
    Uint i;
 
511
 
 
512
    hash->n    = n;
 
513
    hash->used = 0;
 
514
 
 
515
    hash->item = (bp_data_time_item_t *)Alloc(size);
 
516
    sys_memzero(hash->item, size);
 
517
 
 
518
    for(i = 0; i < n; ++i) {
 
519
        hash->item[i].pid = NIL;
 
520
    }
 
521
}
 
522
 
 
523
static void bp_hash_rehash(bp_time_hash_t *hash, Uint n) {
 
524
    bp_data_time_item_t *item = NULL;
 
525
    Uint size = sizeof(bp_data_time_item_t)*n;
 
526
    Uint ix;
 
527
    Uint hval;
 
528
 
 
529
    item = (bp_data_time_item_t *)Alloc(size);
 
530
    sys_memzero(item, size);
 
531
 
 
532
    for( ix = 0; ix < n; ++ix) {
 
533
        item[ix].pid = NIL;
 
534
    }
 
535
 
 
536
    /* rehash, old hash -> new hash */
 
537
 
 
538
    for( ix = 0; ix < hash->n; ix++) {
 
539
        if (hash->item[ix].pid != NIL) {
 
540
 
 
541
            hval = ((hash->item[ix].pid) >> 4) % n; /* new n */
 
542
 
 
543
            while (item[hval].pid != NIL) {
 
544
                hval = (hval + 1) % n;
 
545
            }
 
546
            item[hval].pid     = hash->item[ix].pid;
 
547
            item[hval].count   = hash->item[ix].count;
 
548
            item[hval].s_time  = hash->item[ix].s_time;
 
549
            item[hval].us_time = hash->item[ix].us_time;
 
550
        }
 
551
    }
 
552
 
 
553
    Free(hash->item);
 
554
    hash->n = n;
 
555
    hash->item = item;
 
556
}
 
557
static ERTS_INLINE bp_data_time_item_t * bp_hash_get(bp_time_hash_t *hash, bp_data_time_item_t *sitem) {
 
558
    Eterm pid = sitem->pid;
 
559
    Uint hval = (pid >> 4) % hash->n;
 
560
    bp_data_time_item_t *item = NULL;
 
561
 
 
562
    item = hash->item;
 
563
 
 
564
    while (item[hval].pid != pid) {
 
565
        if (item[hval].pid == NIL) return NULL;
 
566
        hval = (hval + 1) % hash->n;
 
567
    }
 
568
 
 
569
    return &(item[hval]);
 
570
}
 
571
 
 
572
static ERTS_INLINE bp_data_time_item_t * bp_hash_put(bp_time_hash_t *hash, bp_data_time_item_t* sitem) {
 
573
    Uint hval;
 
574
    float r = 0.0;
 
575
    bp_data_time_item_t *item;
 
576
 
 
577
    /* make sure that the hash is not saturated */
 
578
    /* if saturated, rehash it */
 
579
 
 
580
    r = hash->used / (float) hash->n;
 
581
 
 
582
    if (r > 0.7f) {
 
583
        bp_hash_rehash(hash, hash->n * 2);
 
584
    }
 
585
    /* Do hval after rehash */
 
586
    hval = (sitem->pid >> 4) % hash->n;
 
587
 
 
588
    /* find free slot */
 
589
    item = hash->item;
 
590
 
 
591
    while (item[hval].pid != NIL) {
 
592
        hval = (hval + 1) % hash->n;
 
593
    }
 
594
    item = &(hash->item[hval]);
 
595
 
 
596
    item->pid     = sitem->pid;
 
597
    item->s_time  = sitem->s_time;
 
598
    item->us_time = sitem->us_time;
 
599
    item->count   = sitem->count;
 
600
    hash->used++;
 
601
 
 
602
    return item;
 
603
}
 
604
 
 
605
static void bp_hash_delete(bp_time_hash_t *hash) {
 
606
    hash->n = 0;
 
607
    hash->used = 0;
 
608
    Free(hash->item);
 
609
    hash->item = NULL;
 
610
}
 
611
 
 
612
static void bp_time_diff(bp_data_time_item_t *item, /* out */
 
613
        process_breakpoint_time_t *pbt,             /* in  */
 
614
        Uint ms, Uint s, Uint us) {
 
615
    int dms,ds,dus;
 
616
 
 
617
    dms = ms - pbt->ms;
 
618
    ds  = s  - pbt->s;
 
619
    dus = us - pbt->us;
 
620
 
 
621
    /* get_sys_now may return zero difftime,
 
622
     * this is ok.
 
623
     */
 
624
 
 
625
    ASSERT(dms >= 0 || ds >= 0 || dus >= 0);
 
626
 
 
627
    if (dus < 0) {
 
628
        dus += 1000000;
 
629
        ds  -= 1;
 
630
    }
 
631
    if (ds < 0) {
 
632
        ds += 1000000;
 
633
    }
 
634
 
 
635
    item->s_time  = ds;
 
636
    item->us_time = dus;
 
637
}
 
638
 
 
639
void erts_schedule_time_break(Process *p, Uint schedule) {
 
640
    Uint ms, s, us;
 
641
    process_breakpoint_time_t *pbt = NULL;
 
642
    bp_data_time_item_t sitem, *item = NULL;
 
643
    bp_time_hash_t *h = NULL;
 
644
    BpDataTime *pbdt = NULL;
 
645
 
 
646
    ASSERT(p);
 
647
 
 
648
    pbt = ERTS_PROC_GET_CALL_TIME(p);
 
649
 
 
650
    if (pbt) {
 
651
 
 
652
        switch(schedule) {
 
653
        case ERTS_BP_CALL_TIME_SCHEDULE_EXITING :
 
654
            break;
 
655
        case ERTS_BP_CALL_TIME_SCHEDULE_OUT :
 
656
            /* When a process is scheduled _out_,
 
657
             * timestamp it and add its delta to
 
658
             * the previous breakpoint.
 
659
             */
 
660
 
 
661
            pbdt = (BpDataTime *) get_break(p, pbt->pc, (BeamInstr) BeamOp(op_i_time_breakpoint));
 
662
            if (pbdt) {
 
663
                get_sys_now(&ms,&s,&us);
 
664
                bp_time_diff(&sitem, pbt, ms, s, us);
 
665
                sitem.pid   = p->id;
 
666
                sitem.count = 0;
 
667
 
 
668
                h = &(pbdt->hash[bp_sched2ix_proc(p)]);
 
669
 
 
670
                ASSERT(h);
 
671
                ASSERT(h->item);
 
672
 
 
673
                item = bp_hash_get(h, &sitem);
 
674
                if (!item) {
 
675
                    item = bp_hash_put(h, &sitem);
 
676
                } else {
 
677
                    BP_TIME_ADD(item, &sitem);
 
678
                }
 
679
            }
 
680
            break;
 
681
        case ERTS_BP_CALL_TIME_SCHEDULE_IN :
 
682
            /* When a process is scheduled _in_,
 
683
             * timestamp it and remove the previous
 
684
             * timestamp in the psd.
 
685
             */
 
686
            get_sys_now(&ms,&s,&us);
 
687
            pbt->ms = ms;
 
688
            pbt->s  = s;
 
689
            pbt->us = us;
 
690
            break;
 
691
        default :
 
692
            ASSERT(0);
 
693
                /* will never happen */
 
694
            break;
 
695
        }
 
696
    } /* pbt */
 
697
}
 
698
 
 
699
/* call_time breakpoint
 
700
 * Accumulated times are added to the previous bp,
 
701
 * not the current one. The current one is saved
 
702
 * for future reference.
 
703
 * The previous breakpoint is stored in the process it self, the psd.
 
704
 * We do not need to store in a stack frame.
 
705
 * There is no need for locking, each thread has its own
 
706
 * area in each bp to save data.
 
707
 * Since we need to diffrentiate between processes for each bp,
 
708
 * every bp has a hash (per thread) to process-bp statistics.
 
709
 * - egil
 
710
 */
 
711
 
 
712
void erts_trace_time_break(Process *p, BeamInstr *pc, BpDataTime *bdt, Uint type) {
 
713
    Uint ms,s,us;
 
714
    process_breakpoint_time_t *pbt = NULL;
 
715
    bp_data_time_item_t sitem, *item = NULL;
 
716
    bp_time_hash_t *h = NULL;
 
717
    BpDataTime *pbdt = NULL;
 
718
 
 
719
    ASSERT(p);
 
720
    ASSERT(p->status == P_RUNNING);
 
721
 
 
722
    /* get previous timestamp and breakpoint
 
723
     * from the process psd  */
 
724
 
 
725
    pbt = ERTS_PROC_GET_CALL_TIME(p);
 
726
    get_sys_now(&ms,&s,&us);
 
727
 
 
728
    switch(type) {
 
729
            /* get pbt
 
730
             * timestamp = t0
 
731
             * lookup bdt from code
 
732
             * set ts0 to pbt
 
733
             * add call count here?
 
734
             */
 
735
        case ERTS_BP_CALL_TIME_CALL:
 
736
        case ERTS_BP_CALL_TIME_TAIL_CALL:
 
737
 
 
738
            if (pbt) {
 
739
                ASSERT(pbt->pc);
 
740
                /* add time to previous code */
 
741
                bp_time_diff(&sitem, pbt, ms, s, us);
 
742
                sitem.pid   = p->id;
 
743
                sitem.count = 0;
 
744
 
 
745
                /* previous breakpoint */
 
746
                pbdt = (BpDataTime *) get_break(p, pbt->pc, (BeamInstr) BeamOp(op_i_time_breakpoint));
 
747
 
 
748
                /* if null then the breakpoint was removed */
 
749
                if (pbdt) {
 
750
                    h = &(pbdt->hash[bp_sched2ix_proc(p)]);
 
751
 
 
752
                    ASSERT(h);
 
753
                    ASSERT(h->item);
 
754
 
 
755
                    item = bp_hash_get(h, &sitem);
 
756
                    if (!item) {
 
757
                        item = bp_hash_put(h, &sitem);
 
758
                    } else {
 
759
                        BP_TIME_ADD(item, &sitem);
 
760
                    }
 
761
                }
 
762
 
 
763
            } else {
 
764
                /* first call of process to instrumented function */
 
765
                pbt = Alloc(sizeof(process_breakpoint_time_t));
 
766
                (void *) ERTS_PROC_SET_CALL_TIME(p, ERTS_PROC_LOCK_MAIN, pbt);
 
767
            }
 
768
            /* add count to this code */
 
769
            sitem.pid     = p->id;
 
770
            sitem.count   = 1;
 
771
            sitem.s_time  = 0;
 
772
            sitem.us_time = 0;
 
773
 
 
774
            /* this breakpoint */
 
775
            ASSERT(bdt);
 
776
            h = &(bdt->hash[bp_sched2ix_proc(p)]);
 
777
 
 
778
            ASSERT(h);
 
779
            ASSERT(h->item);
 
780
 
 
781
            item = bp_hash_get(h, &sitem);
 
782
            if (!item) {
 
783
                item = bp_hash_put(h, &sitem);
 
784
            } else {
 
785
                BP_TIME_ADD(item, &sitem);
 
786
            }
 
787
 
 
788
            pbt->pc = pc;
 
789
            pbt->ms = ms;
 
790
            pbt->s  = s;
 
791
            pbt->us = us;
 
792
            break;
 
793
 
 
794
        case ERTS_BP_CALL_TIME_RETURN:
 
795
            /* get pbt
 
796
             * lookup bdt from code
 
797
             * timestamp = t1
 
798
             * get ts0 from pbt
 
799
             * get item from bdt->hash[bp_hash(p->id)]
 
800
             * ack diff (t1, t0) to item
 
801
             */
 
802
 
 
803
            if(pbt) {
 
804
                /* might have been removed due to
 
805
                 * trace_pattern(false)
 
806
                 */
 
807
                ASSERT(pbt->pc);
 
808
 
 
809
                bp_time_diff(&sitem, pbt, ms, s, us);
 
810
                sitem.pid   = p->id;
 
811
                sitem.count = 0;
 
812
 
 
813
                /* previous breakpoint */
 
814
                pbdt = (BpDataTime *) get_break(p, pbt->pc, (BeamInstr) BeamOp(op_i_time_breakpoint));
 
815
 
 
816
                /* beware, the trace_pattern might have been removed */
 
817
                if (pbdt) {
 
818
                    h = &(pbdt->hash[bp_sched2ix_proc(p)]);
 
819
 
 
820
                    ASSERT(h);
 
821
                    ASSERT(h->item);
 
822
 
 
823
                    item = bp_hash_get(h, &sitem);
 
824
                    if (!item) {
 
825
                        item = bp_hash_put(h, &sitem);
 
826
                    } else {
 
827
                        BP_TIME_ADD(item, &sitem);
 
828
                    }
 
829
                }
 
830
 
 
831
                pbt->pc = pc;
 
832
                pbt->ms = ms;
 
833
                pbt->s  = s;
 
834
                pbt->us = us;
 
835
            }
 
836
            break;
 
837
        default :
 
838
            ASSERT(0);
 
839
                /* will never happen */
 
840
            break;
 
841
    }
 
842
}
435
843
 
436
844
 
437
845
/* *************************************************************************
440
848
 
441
849
 
442
850
static int set_break(Eterm mfa[3], int specified, 
443
 
                     Binary *match_spec, Eterm break_op, 
 
851
                     Binary *match_spec, BeamInstr break_op,
444
852
                     enum erts_break_op count_op, Eterm tracer_pid)
445
853
{
446
854
    Module *modp;
470
878
}
471
879
 
472
880
static int set_module_break(Module *modp, Eterm mfa[3], int specified,
473
 
                            Binary *match_spec, Uint break_op, 
 
881
                            Binary *match_spec, BeamInstr break_op,
474
882
                            enum erts_break_op count_op, Eterm tracer_pid) {
475
 
    Uint** code_base;
476
 
    Uint* code_ptr;
 
883
    BeamInstr** code_base;
 
884
    BeamInstr* code_ptr;
477
885
    int num_processed = 0;
478
886
    Uint i,n;
479
887
 
480
888
    ASSERT(break_op);
481
889
    ASSERT(modp);
482
 
    code_base = (Uint **) modp->code;
 
890
    code_base = (BeamInstr **) modp->code;
483
891
    if (code_base == NULL) {
484
892
        return 0;
485
893
    }
486
 
    n = (Uint) code_base[MI_NUM_FUNCTIONS];
 
894
    n = (BeamInstr) code_base[MI_NUM_FUNCTIONS];
487
895
    for (i = 0; i < n; ++i) {
488
896
        code_ptr = code_base[MI_FUNCTIONS+i];
489
 
        ASSERT(code_ptr[0] == (Uint) BeamOp(op_i_func_info_IaaI));
 
897
        ASSERT(code_ptr[0] == (BeamInstr) BeamOp(op_i_func_info_IaaI));
490
898
        if ((specified < 2 || mfa[1] == ((Eterm) code_ptr[3])) &&
491
899
            (specified < 3 || ((int) mfa[2]) == ((int) code_ptr[4]))) {
492
 
            Uint   *pc = code_ptr+5;
 
900
            BeamInstr *pc = code_ptr+5;
493
901
            
494
902
            num_processed +=
495
 
                set_function_break(modp, pc, match_spec, 
 
903
                set_function_break(modp, pc, BREAK_IS_ERL, match_spec,
496
904
                                   break_op, count_op, tracer_pid);
497
905
        }
498
906
    }
499
907
    return num_processed;
500
908
}
501
909
 
502
 
static int set_function_break(Module *modp, Uint *pc, 
503
 
                              Binary *match_spec, Uint break_op, 
 
910
static int set_function_break(Module *modp, BeamInstr *pc, int bif,
 
911
                              Binary *match_spec, BeamInstr break_op,
504
912
                              enum erts_break_op count_op, Eterm tracer_pid) {
505
 
    BpData *bd, **r;
 
913
 
 
914
    BeamInstr **code_base = NULL;
 
915
    BpData *bd, **r, ***rs;
506
916
    size_t size;
507
 
    Uint **code_base = (Uint **)modp->code;
 
917
    Uint ix = 0;
508
918
    
509
 
    ASSERT(code_base);
510
 
    ASSERT(code_base <= (Uint **)pc);
511
 
    ASSERT((Uint **)pc < code_base + (modp->code_length/sizeof(Uint *)));
 
919
    if (bif == BREAK_IS_ERL) {
 
920
        code_base = (BeamInstr **)modp->code;
 
921
        ASSERT(code_base);
 
922
        ASSERT(code_base <= (BeamInstr **)pc);
 
923
        ASSERT((BeamInstr **)pc < code_base + (modp->code_length/sizeof(BeamInstr *)));
 
924
    } else {
 
925
        ASSERT(*pc == (BeamInstr) em_apply_bif);
 
926
        ASSERT(modp == NULL);
 
927
    }
 
928
 
512
929
    /*
513
930
     * Currently no trace support for native code.
514
931
     */
517
934
    }
518
935
    /* Do not allow two breakpoints of the same kind */
519
936
    if ( (bd = is_break(pc, break_op))) {
520
 
        if (break_op == (Uint) BeamOp(op_i_trace_breakpoint) 
521
 
            || break_op == (Uint) BeamOp(op_i_mtrace_breakpoint)) {
 
937
        if (break_op == (BeamInstr) BeamOp(op_i_trace_breakpoint)
 
938
            || break_op == (BeamInstr) BeamOp(op_i_mtrace_breakpoint)) {
 
939
 
522
940
            BpDataTrace *bdt = (BpDataTrace *) bd;
523
941
            Binary *old_match_spec;
524
942
            
531
949
            ErtsSmpBPUnlock(bdt);
532
950
            MatchSetUnref(old_match_spec);
533
951
        } else {
 
952
            BpDataCount *bdc = (BpDataCount *) bd;
 
953
            erts_aint_t count = 0;
 
954
            erts_aint_t res   = 0;
 
955
 
534
956
            ASSERT(! match_spec);
535
957
            ASSERT(is_nil(tracer_pid));
536
 
            if (break_op == (Uint) BeamOp(op_i_count_breakpoint)) {
537
 
                BpDataCount *bdc = (BpDataCount *) bd;
538
958
                
539
 
                ErtsSmpBPLock(bdc);
540
 
                if (count_op == erts_break_stop) {
541
 
                    if (bdc->count >= 0) {
542
 
                        bdc->count = -bdc->count-1; /* Stop call counter */
543
 
                    }
544
 
                } else {
545
 
                    bdc->count = 0; /* Reset call counter */
546
 
                }
547
 
                ErtsSmpBPUnlock(bdc);
 
959
            if (break_op == (BeamInstr) BeamOp(op_i_count_breakpoint)) {
 
960
                if (count_op == erts_break_stop) {
 
961
                    count = erts_smp_atomic_read(&bdc->acount);
 
962
                    if (count >= 0) {
 
963
                        while(1) {
 
964
                            res = erts_smp_atomic_cmpxchg(&bdc->acount, -count - 1, count);
 
965
                            if ((res == count) || count < 0) break;
 
966
                            count = res;
 
967
                        }
 
968
                    }
 
969
                } else {
 
970
                    /* Reset call counter */
 
971
                    erts_smp_atomic_set(&bdc->acount, 0);
 
972
                }
 
973
 
 
974
            } else if (break_op == (BeamInstr) BeamOp(op_i_time_breakpoint)) {
 
975
                BpDataTime *bdt = (BpDataTime *) bd;
 
976
                Uint i = 0;
 
977
 
 
978
                ERTS_SMP_LC_ASSERT(erts_smp_is_system_blocked(0));
 
979
 
 
980
                if (count_op == erts_break_stop) {
 
981
                    bdt->pause = 1;
 
982
                } else {
 
983
                    bdt->pause = 0;
 
984
                    for (i = 0; i < bdt->n; i++) {
 
985
                        bp_hash_delete(&(bdt->hash[i]));
 
986
                        bp_hash_init(&(bdt->hash[i]), 32);
 
987
                    }
 
988
                }
 
989
 
548
990
            } else {
549
991
                ASSERT (! count_op);
550
992
            }
551
993
        }
552
994
        return 1;
553
995
    }
554
 
    if (break_op == (Uint) BeamOp(op_i_trace_breakpoint) ||
555
 
        break_op == (Uint) BeamOp(op_i_mtrace_breakpoint)) {
 
996
    if (break_op == (BeamInstr) BeamOp(op_i_trace_breakpoint) ||
 
997
        break_op == (BeamInstr) BeamOp(op_i_mtrace_breakpoint)) {
556
998
        size = sizeof(BpDataTrace);
557
999
    } else {
558
1000
        ASSERT(! match_spec);
559
1001
        ASSERT(is_nil(tracer_pid));
560
 
        if (break_op == (Uint) BeamOp(op_i_count_breakpoint)) {
561
 
            if (count_op == erts_break_reset
562
 
                || count_op == erts_break_stop) {
 
1002
        if (break_op == (BeamInstr) BeamOp(op_i_count_breakpoint)) {
 
1003
            if (count_op == erts_break_reset || count_op == erts_break_stop) {
563
1004
                /* Do not insert a new breakpoint */
564
1005
                return 1;
565
1006
            }
566
1007
            size = sizeof(BpDataCount);
 
1008
        } else if (break_op == (BeamInstr) BeamOp(op_i_time_breakpoint))  {
 
1009
            if (count_op == erts_break_reset || count_op == erts_break_stop) {
 
1010
                /* Do not insert a new breakpoint */
 
1011
                return 1;
 
1012
            }
 
1013
            size = sizeof(BpDataTime);
567
1014
        } else {
568
1015
            ASSERT(! count_op);
569
 
            ASSERT(break_op == (Uint) BeamOp(op_i_debug_breakpoint));
 
1016
            ASSERT(break_op == (BeamInstr) BeamOp(op_i_debug_breakpoint));
570
1017
            size = sizeof(BpDataDebug);
571
1018
        }
572
1019
    }
573
 
    r = (BpData **) (pc-4);
 
1020
    rs = (BpData ***) (pc-4);
 
1021
    if (! *rs) {
 
1022
        size_t ssize = sizeof(BeamInstr) * erts_no_schedulers;
 
1023
        *rs = (BpData **) Alloc(ssize);
 
1024
        sys_memzero(*rs, ssize);
 
1025
    }
 
1026
 
 
1027
    r = &((*rs)[0]);
 
1028
 
574
1029
    if (! *r) {
575
 
        ASSERT(*pc != (Uint) BeamOp(op_i_trace_breakpoint));
576
 
        ASSERT(*pc != (Uint) BeamOp(op_i_mtrace_breakpoint));
577
 
        ASSERT(*pc != (Uint) BeamOp(op_i_debug_breakpoint));
578
 
        ASSERT(*pc != (Uint) BeamOp(op_i_count_breakpoint));
 
1030
        ASSERT(*pc != (BeamInstr) BeamOp(op_i_trace_breakpoint));
 
1031
        ASSERT(*pc != (BeamInstr) BeamOp(op_i_mtrace_breakpoint));
 
1032
        ASSERT(*pc != (BeamInstr) BeamOp(op_i_debug_breakpoint));
 
1033
        ASSERT(*pc != (BeamInstr) BeamOp(op_i_count_breakpoint));
 
1034
        ASSERT(*pc != (BeamInstr) BeamOp(op_i_time_breakpoint));
579
1035
        /* First breakpoint; create singleton ring */
580
1036
        bd = Alloc(size);
581
1037
        BpInit(bd, *pc);
582
 
        *pc = break_op;
583
1038
        *r = bd;
 
1039
        if (bif == BREAK_IS_ERL) {
 
1040
            *pc = break_op;
 
1041
        }
584
1042
    } else {
585
 
        ASSERT(*pc == (Uint) BeamOp(op_i_trace_breakpoint) ||
586
 
               *pc == (Uint) BeamOp(op_i_mtrace_breakpoint) ||
587
 
               *pc == (Uint) BeamOp(op_i_debug_breakpoint) ||
588
 
               *pc == (Uint) BeamOp(op_i_count_breakpoint));
589
 
        if (*pc == (Uint) BeamOp(op_i_debug_breakpoint)) {
 
1043
        ASSERT(*pc == (BeamInstr) BeamOp(op_i_trace_breakpoint) ||
 
1044
               *pc == (BeamInstr) BeamOp(op_i_mtrace_breakpoint) ||
 
1045
               *pc == (BeamInstr) BeamOp(op_i_debug_breakpoint) ||
 
1046
               *pc == (BeamInstr) BeamOp(op_i_time_breakpoint) ||
 
1047
               *pc == (BeamInstr) BeamOp(op_i_count_breakpoint) ||
 
1048
               *pc == (BeamInstr) em_apply_bif);
 
1049
        if (*pc == (BeamInstr) BeamOp(op_i_debug_breakpoint)) {
590
1050
            /* Debug bp must be last, so if it is also first; 
591
1051
             * it must be singleton. */
592
 
            ASSERT(BpSingleton(*r)); 
 
1052
            ASSERT(BpSingleton(*r));
593
1053
            /* Insert new bp first in the ring, i.e second to last. */
594
1054
            bd = Alloc(size);
595
1055
            BpInitAndSpliceNext(bd, *pc, *r);
596
 
            *pc = break_op;
597
 
        } else if ((*r)->prev->orig_instr 
598
 
                   == (Uint) BeamOp(op_i_debug_breakpoint)) {
 
1056
            if (bif == BREAK_IS_ERL) {
 
1057
                *pc = break_op;
 
1058
            }
 
1059
        } else if ((*r)->prev->orig_instr
 
1060
                   == (BeamInstr) BeamOp(op_i_debug_breakpoint)) {
599
1061
            /* Debug bp last in the ring; insert new second to last. */
600
1062
            bd = Alloc(size);
601
1063
            BpInitAndSplicePrev(bd, (*r)->prev->orig_instr, *r);
608
1070
            *r = bd;
609
1071
        }
610
1072
    }
 
1073
    for (ix = 1; ix < erts_no_schedulers; ++ix) {
 
1074
        (*rs)[ix] = (*rs)[0];
 
1075
    }
 
1076
 
 
1077
    bd->this_instr = break_op;
611
1078
    /* Init the bp type specific data */
612
 
    if (break_op == (Uint) BeamOp(op_i_trace_breakpoint) ||
613
 
        break_op == (Uint) BeamOp(op_i_mtrace_breakpoint)) {
 
1079
    if (break_op == (BeamInstr) BeamOp(op_i_trace_breakpoint) ||
 
1080
        break_op == (BeamInstr) BeamOp(op_i_mtrace_breakpoint)) {
614
1081
                
615
1082
        BpDataTrace *bdt = (BpDataTrace *) bd;
616
1083
                
617
1084
        MatchSetRef(match_spec);
618
1085
        bdt->match_spec = match_spec;
619
1086
        bdt->tracer_pid = tracer_pid;
620
 
    } else if (break_op == (Uint) BeamOp(op_i_count_breakpoint)) {
 
1087
    } else if (break_op == (BeamInstr) BeamOp(op_i_time_breakpoint)) {
 
1088
        BpDataTime *bdt = (BpDataTime *) bd;
 
1089
        Uint i = 0;
 
1090
 
 
1091
        bdt->pause = 0;
 
1092
        bdt->n     = erts_no_schedulers;
 
1093
        bdt->hash  = Alloc(sizeof(bp_time_hash_t)*(bdt->n));
 
1094
 
 
1095
        for (i = 0; i < bdt->n; i++) {
 
1096
            bp_hash_init(&(bdt->hash[i]), 32);
 
1097
        }
 
1098
    } else if (break_op == (BeamInstr) BeamOp(op_i_count_breakpoint)) {
621
1099
        BpDataCount *bdc = (BpDataCount *) bd;
 
1100
        erts_smp_atomic_init(&bdc->acount, 0);
 
1101
    }
622
1102
 
623
 
        bdc->count = 0;
 
1103
    if (bif == BREAK_IS_ERL) {
 
1104
        ++(*(BeamInstr*)&code_base[MI_NUM_BREAKPOINTS]);
624
1105
    }
625
 
    ++(*(Uint*)&code_base[MI_NUM_BREAKPOINTS]);
626
1106
    return 1;
627
1107
}
628
1108
 
629
 
static int clear_break(Eterm mfa[3], int specified, Uint break_op)
 
1109
static int clear_break(Eterm mfa[3], int specified, BeamInstr break_op)
630
1110
{
631
1111
    int num_processed = 0;
632
1112
    Module *modp;
652
1132
}
653
1133
 
654
1134
static int clear_module_break(Module *m, Eterm mfa[3], int specified, 
655
 
                              Uint break_op) {
656
 
    Uint** code_base;
657
 
    Uint* code_ptr;
 
1135
                              BeamInstr break_op) {
 
1136
    BeamInstr** code_base;
 
1137
    BeamInstr* code_ptr;
658
1138
    int num_processed = 0;
659
 
    Uint i,n;
 
1139
    Uint i;
 
1140
    BeamInstr n;
660
1141
    
661
1142
    ASSERT(m);
662
 
    code_base = (Uint **) m->code;
 
1143
    code_base = (BeamInstr **) m->code;
663
1144
    if (code_base == NULL) {
664
1145
        return 0;
665
1146
    }
666
 
    n = (Uint) code_base[MI_NUM_FUNCTIONS];
 
1147
    n = (BeamInstr) code_base[MI_NUM_FUNCTIONS];
667
1148
    for (i = 0; i < n; ++i) {
668
1149
        code_ptr = code_base[MI_FUNCTIONS+i];
669
1150
        if ((specified < 2 || mfa[1] == ((Eterm) code_ptr[3])) &&
670
1151
            (specified < 3 || ((int) mfa[2]) == ((int) code_ptr[4]))) {
671
 
            Uint *pc = code_ptr + 5;
 
1152
            BeamInstr *pc = code_ptr + 5;
672
1153
            
673
1154
            num_processed += 
674
 
                clear_function_break(m, pc, break_op);
 
1155
                clear_function_break(m, pc, BREAK_IS_ERL, break_op);
675
1156
        }
676
1157
    }
677
1158
    return num_processed;
678
1159
}
679
1160
 
680
 
static int clear_function_break(Module *m, Uint *pc, Uint break_op) {
 
1161
static int clear_function_break(Module *m, BeamInstr *pc, int bif, BeamInstr break_op) {
681
1162
    BpData *bd;
682
 
    Uint **code_base = (Uint **)m->code;
683
 
    
684
 
    ASSERT(code_base);
685
 
    ASSERT(code_base <= (Uint **)pc);
686
 
    ASSERT((Uint **)pc < code_base + (m->code_length/sizeof(Uint *)));
 
1163
    Uint ix = 0;
 
1164
    BeamInstr **code_base = NULL;
 
1165
 
 
1166
    if (bif == BREAK_IS_ERL) {
 
1167
        code_base = (BeamInstr **)m->code;
 
1168
        ASSERT(code_base);
 
1169
        ASSERT(code_base <= (BeamInstr **)pc);
 
1170
        ASSERT((BeamInstr **)pc < code_base + (m->code_length/sizeof(BeamInstr *)));
 
1171
    } else {
 
1172
        ASSERT(*pc == (BeamInstr) em_apply_bif);
 
1173
        ASSERT(m == NULL);
 
1174
    }
 
1175
 
687
1176
    /*
688
1177
     * Currently no trace support for native code.
689
1178
     */
690
1179
    if (erts_is_native_break(pc)) {
691
1180
        return 0;
692
1181
    }
 
1182
 
693
1183
    while ( (bd = is_break(pc, break_op))) {
694
1184
        /* Remove all breakpoints of this type.
695
1185
         * There should be only one of each type, 
696
1186
         * but break_op may be 0 which matches any type. 
697
1187
         */
698
 
        Uint op;
699
 
        BpData **r = (BpData **) (pc-4);
 
1188
        BeamInstr op;
 
1189
        BpData ***rs = (BpData ***) (pc - 4);
 
1190
        BpData   **r = NULL;
 
1191
 
 
1192
#ifdef DEBUG
 
1193
        for (ix = 1; ix < erts_no_schedulers; ++ix) {
 
1194
            ASSERT((*rs)[ix] == (*rs)[0]);
 
1195
        }
 
1196
#endif
700
1197
        
 
1198
        r = &((*rs)[0]);
 
1199
 
701
1200
        ASSERT(*r);
702
1201
        /* Find opcode for this breakpoint */
703
1202
        if (break_op) {
713
1212
        if (BpSingleton(bd)) {
714
1213
            ASSERT(*r == bd);
715
1214
            /* Only one breakpoint to remove */
716
 
            *r  = NULL;
717
 
            *pc = bd->orig_instr;
 
1215
            if (bif == BREAK_IS_ERL) {
 
1216
                *pc = bd->orig_instr;
 
1217
            }
 
1218
            Free(*rs);
 
1219
            *rs = NULL;
718
1220
        } else {
719
1221
            BpData *bd_prev = bd->prev;
720
1222
            
726
1228
                bd_prev->orig_instr = bd->orig_instr;
727
1229
            } else if (bd_prev == *r) {
728
1230
                /* We removed the first breakpoint in the ring */
729
 
                *pc = bd->orig_instr;
 
1231
                if (bif == BREAK_IS_ERL) {
 
1232
                    *pc = bd->orig_instr;
 
1233
                }
730
1234
            } else {
731
1235
                bd_prev->orig_instr = bd->orig_instr;
732
1236
            }
733
1237
        }
734
 
        if (op == (Uint) BeamOp(op_i_trace_breakpoint) ||
735
 
            op == (Uint) BeamOp(op_i_mtrace_breakpoint)) {
 
1238
        if (op == (BeamInstr) BeamOp(op_i_trace_breakpoint) ||
 
1239
            op == (BeamInstr) BeamOp(op_i_mtrace_breakpoint)) {
736
1240
            
737
1241
            BpDataTrace *bdt = (BpDataTrace *) bd;
738
 
            
739
1242
            MatchSetUnref(bdt->match_spec);
740
1243
        }
 
1244
        if (op == (BeamInstr) BeamOp(op_i_time_breakpoint)) {
 
1245
            BpDataTime *bdt = (BpDataTime *) bd;
 
1246
            Uint i = 0;
 
1247
            Uint j = 0;
 
1248
            Process *h_p = NULL;
 
1249
            bp_data_time_item_t *item = NULL;
 
1250
            process_breakpoint_time_t *pbt = NULL;
 
1251
 
 
1252
            /* remove all psd associated with the hash
 
1253
             * and then delete the hash.
 
1254
             * ... sigh ...
 
1255
             */
 
1256
 
 
1257
            for( i = 0; i < bdt->n; ++i) {
 
1258
                if (bdt->hash[i].used) {
 
1259
                    for (j = 0; j < bdt->hash[i].n; ++j) {
 
1260
                        item = &(bdt->hash[i].item[j]);
 
1261
                        if (item->pid != NIL) {
 
1262
                            h_p = process_tab[internal_pid_index(item->pid)];
 
1263
                            if (h_p) {
 
1264
                                pbt = ERTS_PROC_SET_CALL_TIME(h_p, ERTS_PROC_LOCK_MAIN, NULL);
 
1265
                                if (pbt) {
 
1266
                                    Free(pbt);
 
1267
                                }
 
1268
                            }
 
1269
                        }
 
1270
                    }
 
1271
                }
 
1272
                bp_hash_delete(&(bdt->hash[i]));
 
1273
            }
 
1274
            Free(bdt->hash);
 
1275
            bdt->hash = NULL;
 
1276
            bdt->n = 0;
 
1277
        }
741
1278
        Free(bd);
742
 
        ASSERT(((Uint) code_base[MI_NUM_BREAKPOINTS]) > 0);
743
 
        --(*(Uint*)&code_base[MI_NUM_BREAKPOINTS]);
744
 
    }
 
1279
        if (bif == BREAK_IS_ERL) {
 
1280
            ASSERT(((BeamInstr) code_base[MI_NUM_BREAKPOINTS]) > 0);
 
1281
            --(*(BeamInstr*)&code_base[MI_NUM_BREAKPOINTS]);
 
1282
        }
 
1283
        if (*rs) {
 
1284
            for (ix = 1; ix < erts_no_schedulers; ++ix) {
 
1285
                (*rs)[ix] = (*rs)[0];
 
1286
            }
 
1287
        }
 
1288
    } /* while bd != NULL */
745
1289
    return 1;
746
1290
}
747
1291
 
754
1298
** returned. The program counter must point to the first executable
755
1299
** (breakpoint) instruction of the function.
756
1300
*/
757
 
static BpData *is_break(Uint *pc, Uint break_op) {
758
 
    ASSERT(pc[-5] == (Uint) BeamOp(op_i_func_info_IaaI));
 
1301
 
 
1302
BpData *erts_get_time_break(Process *p, BeamInstr *pc) {
 
1303
    return get_break(p, pc, (BeamInstr) BeamOp(op_i_time_breakpoint));
 
1304
}
 
1305
 
 
1306
static BpData *get_break(Process *p, BeamInstr *pc, BeamInstr break_op) {
 
1307
    ASSERT(pc[-5] == (BeamInstr) BeamOp(op_i_func_info_IaaI));
759
1308
    if (! erts_is_native_break(pc)) {
760
 
        BpData *bd = (BpData *) pc[-4];
761
 
        
762
 
        if (break_op == 0) {
763
 
            return bd;
764
 
        }
765
 
        if (*pc == break_op) {
766
 
            ASSERT(bd);
767
 
            return bd->next;
768
 
        }
769
 
        if (! bd){
 
1309
        BpData **rs = (BpData **) pc[-4];
 
1310
        BpData  *bd = NULL, *ebd = NULL;
 
1311
 
 
1312
        if (! rs) {
770
1313
            return NULL;
771
1314
        }
 
1315
 
 
1316
        bd = ebd = rs[bp_sched2ix_proc(p)];
 
1317
        ASSERT(bd);
 
1318
        if (bd->this_instr == break_op) {
 
1319
            return bd;
 
1320
        }
 
1321
 
772
1322
        bd = bd->next;
773
 
        while (bd != (BpData *) pc[-4]) {
 
1323
        while (bd != ebd) {
774
1324
            ASSERT(bd);
775
 
            if (bd->orig_instr == break_op) {
776
 
                bd = bd->next;
 
1325
            if (bd->this_instr == break_op) {
777
1326
                ASSERT(bd);
778
1327
                return bd;
779
 
            } else {
780
 
                bd = bd->next;
781
1328
            }
782
 
        }
 
1329
            bd = bd->next;
 
1330
        }
 
1331
    }
 
1332
    return NULL;
 
1333
}
 
1334
 
 
1335
static BpData *is_break(BeamInstr *pc, BeamInstr break_op) {
 
1336
    BpData **rs = (BpData **) pc[-4];
 
1337
    BpData  *bd = NULL, *ebd = NULL;
 
1338
    ASSERT(pc[-5] == (BeamInstr) BeamOp(op_i_func_info_IaaI));
 
1339
 
 
1340
    if (! rs) {
 
1341
        return NULL;
 
1342
    }
 
1343
 
 
1344
    bd = ebd = rs[bp_sched2ix()];
 
1345
    ASSERT(bd);
 
1346
    if ( (break_op == 0) || (bd->this_instr == break_op)) {
 
1347
        return bd;
 
1348
    }
 
1349
 
 
1350
    bd = bd->next;
 
1351
    while (bd != ebd) {
 
1352
        ASSERT(bd);
 
1353
        if (bd->this_instr == break_op) {
 
1354
            ASSERT(bd);
 
1355
            return bd;
 
1356
        }
 
1357
        bd = bd->next;
783
1358
    }
784
1359
    return NULL;
785
1360
}