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

« back to all changes in this revision

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

  • Committer: Bazaar Package Importer
  • Author(s): Erlang Packagers, Sergei Golovan
  • Date: 2006-12-03 17:07:44 UTC
  • mfrom: (2.1.11 feisty)
  • Revision ID: james.westby@ubuntu.com-20061203170744-rghjwupacqlzs6kv
Tags: 1:11.b.2-4
[ Sergei Golovan ]
Fixed erlang-base and erlang-base-hipe prerm scripts.

Show diffs side-by-side

added added

removed removed

Lines of Context:
20
20
#  include "config.h"
21
21
#endif
22
22
 
 
23
#define ERL_PROCESS_C__
23
24
#include "sys.h"
24
25
#include "erl_vm.h"
25
26
#include "global.h"
26
27
#include "erl_process.h"
 
28
#include "erl_nmgc.h"
27
29
#include "error.h"
28
30
#include "bif.h"
29
31
#include "erl_db.h"
30
32
#include "dist.h"
31
 
#include "error.h"
32
33
#include "beam_catches.h"
33
34
#include "erl_instrument.h"
 
35
#include "erl_threads.h"
34
36
 
35
37
#ifdef HIPE
36
38
#include "hipe_mode_switch.h"   /* for hipe_init_process() */
 
39
#include "hipe_signal.h"        /* for hipe_thread_signal_init() */
37
40
#endif
38
41
 
39
 
#define MAX_BIT          (1 << PRIORITY_MAX)
40
 
#define HIGH_BIT         (1 << PRIORITY_HIGH)
41
 
#define NORMAL_BIT       (1 << PRIORITY_NORMAL)
42
 
#define LOW_BIT          (1 << PRIORITY_LOW)
 
42
#define MAX_BIT       (1 << PRIORITY_MAX)
 
43
#define HIGH_BIT      (1 << PRIORITY_HIGH)
 
44
#define NORMAL_BIT    (1 << PRIORITY_NORMAL)
 
45
#define LOW_BIT       (1 << PRIORITY_LOW)
 
46
 
 
47
#define DECR_PROC_COUNT(prio)               \
 
48
    if ((prio) == PRIORITY_LOW) {           \
 
49
        if (--queued_low < 1) {             \
 
50
           ASSERT(queued_low == 0);         \
 
51
           qmask &= ~(1 << PRIORITY_LOW);   \
 
52
        }                                   \
 
53
    } else if ((prio) == PRIORITY_NORMAL) { \
 
54
        if (--queued_normal < 1) {          \
 
55
           ASSERT(queued_normal == 0);      \
 
56
           qmask &= ~(1 << PRIORITY_NORMAL);\
 
57
        }                                   \
 
58
    }                                       
 
59
 
 
60
#define ASSERT_NORMAL_Q_EMPTY()                       \
 
61
    ASSERT((((qmask >> PRIORITY_LOW) & 1) == 0) &&    \
 
62
           (((qmask >> PRIORITY_NORMAL) & 1) == 0) && \
 
63
           (queued_low == 0) &&                       \
 
64
           (queued_normal == 0))
43
65
 
44
66
extern Eterm beam_apply[];
45
67
extern Eterm beam_exit[];
46
68
 
 
69
static Sint p_last;
47
70
static Sint p_next;
48
71
static Sint p_serial;
49
72
static Uint p_serial_mask;
52
75
Uint erts_max_processes = ERTS_DEFAULT_MAX_PROCESSES;
53
76
Uint erts_process_tab_index_mask;
54
77
 
55
 
Uint erts_tot_proc_mem; /* in bytes */
 
78
erts_smp_atomic_t erts_tot_proc_mem; /* in bytes */
 
79
 
 
80
#ifdef USE_THREADS
 
81
static erts_tsd_key_t sched_data_key;
 
82
#endif
 
83
 
 
84
static erts_smp_mtx_t schdlq_mtx;
 
85
static erts_smp_cnd_t schdlq_cnd;
 
86
static erts_smp_mtx_t proc_tab_mtx;
 
87
 
 
88
#ifdef ERTS_SMP
 
89
erts_proc_lock_t erts_proc_locks[ERTS_PROC_LOCKS_NO_OF];
 
90
 
 
91
static ErtsSchedulerData *schedulers;
 
92
static Uint last_scheduler_no;
 
93
static Uint no_schedulers;
 
94
static erts_smp_atomic_t atomic_no_schedulers;
 
95
static Uint schedulers_waiting_on_runq;
 
96
static Uint use_no_schedulers;
 
97
static int changing_no_schedulers;
 
98
static ProcessList *pending_exiters;
 
99
 
 
100
#ifdef ERTS_ENABLE_LOCK_CHECK
 
101
static struct {
 
102
    Sint16 proc_lock_main;
 
103
    Sint16 proc_lock_link;
 
104
    Sint16 proc_lock_msgq;
 
105
    Sint16 proc_lock_status;
 
106
} lc_id;
 
107
#endif
 
108
#else /* !ERTS_SMP */
 
109
ErtsSchedulerData erts_scheduler_data;
 
110
#endif
 
111
 
 
112
static void init_sched_thr_data(ErtsSchedulerData *esdp);
56
113
 
57
114
typedef struct schedule_q {
58
115
    Process* first;
59
116
    Process* last;
60
117
} ScheduleQ;
61
118
 
62
 
static ScheduleQ queue[NPRIORITY_LEVELS];
63
 
static int bg_count;
 
119
/* we use the same queue for low and normal prio processes */
 
120
static ScheduleQ queue[NPRIORITY_LEVELS-1];
64
121
static unsigned qmask;
 
122
 
 
123
static Uint queued_low;
 
124
static Uint queued_normal;
 
125
static Sint runq_len;
 
126
 
65
127
#ifndef BM_COUNTERS
66
128
static int processes_busy;
67
129
#endif
68
130
 
69
131
 
70
132
Process**  process_tab;
71
 
Uint context_switches;          /* no of context switches */
72
 
Uint reductions;                /* total number of reductions */
73
 
Uint last_reds;                 /* used in process info */
 
133
static Uint context_switches;           /* no of context switches */
 
134
static Uint reductions;         /* total number of reductions */
 
135
static Uint last_reds;
 
136
static Uint last_exact_reds;
74
137
Uint erts_default_process_flags;
75
 
Eterm erts_default_tracer;
76
138
Eterm erts_system_monitor;
77
139
Eterm erts_system_monitor_long_gc;
78
140
Eterm erts_system_monitor_large_heap;
79
141
struct erts_system_monitor_flags_t erts_system_monitor_flags;
80
142
 
81
 
const struct trace_pattern_flags erts_trace_pattern_flags_off = {0, 0, 0, 0};
82
 
 
83
 
int                         erts_default_trace_pattern_is_on;
84
 
Binary                     *erts_default_match_spec;
85
 
Binary                     *erts_default_meta_match_spec;
86
 
struct trace_pattern_flags  erts_default_trace_pattern_flags;
87
 
Eterm                       erts_default_meta_tracer_pid;
88
 
 
89
 
#ifdef SHARED_HEAP
 
143
#ifdef HYBRID
90
144
Uint erts_num_active_procs;
91
145
Process** erts_active_procs;
92
146
#endif
93
147
 
 
148
static erts_smp_atomic_t process_count;
 
149
 
94
150
/*
95
151
 * Local functions.
96
152
 */
97
 
static void delete_process(Process* p);
98
 
static void print_function_from_pc(Eterm* x, CIO fd);
99
 
static int stack_element_dump(Process* p, Eterm* sp, int yreg, CIO fd);
 
153
static void print_function_from_pc(int to, void *to_arg, Eterm* x);
 
154
static int stack_element_dump(int to, void *to_arg, Process* p, Eterm* sp,
 
155
                              int yreg);
 
156
#ifdef ERTS_SMP
 
157
static void handle_pending_exiters(ProcessList *);
 
158
#endif
 
159
 
 
160
#if defined(ERTS_SMP) && defined(ERTS_ENABLE_LOCK_CHECK)
 
161
 
 
162
void
 
163
erts_proc_lc_lock(Process *p, Uint32 locks)
 
164
{
 
165
    erts_lc_lock_t lck = ERTS_LC_LOCK_INIT(-1,
 
166
                                           p->id,
 
167
                                           ERTS_LC_FLG_LT_PROCLOCK);
 
168
    if (locks & ERTS_PROC_LOCK_MAIN) {
 
169
        lck.id = lc_id.proc_lock_main;
 
170
        erts_lc_lock(&lck);
 
171
    }
 
172
    if (locks & ERTS_PROC_LOCK_LINK) {
 
173
        lck.id = lc_id.proc_lock_link;
 
174
        erts_lc_lock(&lck);
 
175
    }
 
176
    if (locks & ERTS_PROC_LOCK_MSGQ) {
 
177
        lck.id = lc_id.proc_lock_msgq;
 
178
        erts_lc_lock(&lck);
 
179
    }
 
180
    if (locks & ERTS_PROC_LOCK_STATUS) {
 
181
        lck.id = lc_id.proc_lock_status;
 
182
        erts_lc_lock(&lck);
 
183
    }
 
184
}
 
185
 
 
186
void
 
187
erts_proc_lc_trylock(Process *p, Uint32 locks, int locked)
 
188
{
 
189
    erts_lc_lock_t lck = ERTS_LC_LOCK_INIT(-1,
 
190
                                           p->id,
 
191
                                           ERTS_LC_FLG_LT_PROCLOCK);
 
192
    if (locks & ERTS_PROC_LOCK_MAIN) {
 
193
        lck.id = lc_id.proc_lock_main;
 
194
        erts_lc_trylock(locked, &lck);
 
195
    }
 
196
    if (locks & ERTS_PROC_LOCK_LINK) {
 
197
        lck.id = lc_id.proc_lock_link;
 
198
        erts_lc_trylock(locked, &lck);
 
199
    }
 
200
    if (locks & ERTS_PROC_LOCK_MSGQ) {
 
201
        lck.id = lc_id.proc_lock_msgq;
 
202
        erts_lc_trylock(locked, &lck);
 
203
    }
 
204
    if (locks & ERTS_PROC_LOCK_STATUS) {
 
205
        lck.id = lc_id.proc_lock_status;
 
206
        erts_lc_trylock(locked, &lck);
 
207
    }
 
208
}
 
209
 
 
210
void
 
211
erts_proc_lc_unlock(Process *p, Uint32 locks)
 
212
{
 
213
    erts_lc_lock_t lck = ERTS_LC_LOCK_INIT(-1,
 
214
                                           p->id,
 
215
                                           ERTS_LC_FLG_LT_PROCLOCK);
 
216
    if (locks & ERTS_PROC_LOCK_STATUS) {
 
217
        lck.id = lc_id.proc_lock_status;
 
218
        erts_lc_unlock(&lck);
 
219
    }
 
220
    if (locks & ERTS_PROC_LOCK_MSGQ) {
 
221
        lck.id = lc_id.proc_lock_msgq;
 
222
        erts_lc_unlock(&lck);
 
223
    }
 
224
    if (locks & ERTS_PROC_LOCK_LINK) {
 
225
        lck.id = lc_id.proc_lock_link;
 
226
        erts_lc_unlock(&lck);
 
227
    }
 
228
    if (locks & ERTS_PROC_LOCK_MAIN) {
 
229
        lck.id = lc_id.proc_lock_main;
 
230
        erts_lc_unlock(&lck);
 
231
    }
 
232
}
 
233
 
 
234
int
 
235
erts_proc_lc_trylock_force_busy(Process *p, Uint32 locks)
 
236
{
 
237
    if (locks & ERTS_PROC_LOCKS_ALL) {
 
238
        erts_lc_lock_t lck = ERTS_LC_LOCK_INIT(-1,
 
239
                                               p->id,
 
240
                                               ERTS_LC_FLG_LT_PROCLOCK);
 
241
 
 
242
        if (locks & ERTS_PROC_LOCK_MAIN)
 
243
            lck.id = lc_id.proc_lock_main;
 
244
        else if (locks & ERTS_PROC_LOCK_LINK)
 
245
            lck.id = lc_id.proc_lock_link;
 
246
        else if (locks & ERTS_PROC_LOCK_MSGQ)
 
247
            lck.id = lc_id.proc_lock_msgq;
 
248
        else if (locks & ERTS_PROC_LOCK_STATUS)
 
249
            lck.id = lc_id.proc_lock_status;
 
250
        else
 
251
            erts_lc_fail("Unknown proc lock found");
 
252
 
 
253
        return erts_lc_trylock_force_busy(&lck);
 
254
    }
 
255
    return 0;
 
256
}
 
257
 
 
258
void erts_proc_lc_chk_only_proc_main(Process *p)
 
259
{
 
260
    erts_lc_lock_t proc_main = ERTS_LC_LOCK_INIT(lc_id.proc_lock_main,
 
261
                                                 p->id,
 
262
                                                 ERTS_LC_FLG_LT_PROCLOCK);
 
263
    erts_lc_check_exact(&proc_main, 1);
 
264
}
 
265
 
 
266
#define ERTS_PROC_LC_EMPTY_LOCK_INIT \
 
267
  ERTS_LC_LOCK_INIT(-1, THE_NON_VALUE, ERTS_LC_FLG_LT_PROCLOCK)
 
268
 
 
269
void
 
270
erts_proc_lc_chk_have_proc_locks(Process *p, Uint32 locks)
 
271
{
 
272
    int have_locks_len = 0;
 
273
    erts_lc_lock_t have_locks[4] = {ERTS_PROC_LC_EMPTY_LOCK_INIT,
 
274
                                    ERTS_PROC_LC_EMPTY_LOCK_INIT,
 
275
                                    ERTS_PROC_LC_EMPTY_LOCK_INIT,
 
276
                                    ERTS_PROC_LC_EMPTY_LOCK_INIT};
 
277
    if (locks & ERTS_PROC_LOCK_MAIN) {
 
278
        have_locks[have_locks_len].id = lc_id.proc_lock_main;
 
279
        have_locks[have_locks_len++].extra = p->id;
 
280
    }
 
281
    if (locks & ERTS_PROC_LOCK_LINK) {
 
282
        have_locks[have_locks_len].id = lc_id.proc_lock_link;
 
283
        have_locks[have_locks_len++].extra = p->id;
 
284
    }
 
285
    if (locks & ERTS_PROC_LOCK_MSGQ) {
 
286
        have_locks[have_locks_len].id = lc_id.proc_lock_msgq;
 
287
        have_locks[have_locks_len++].extra = p->id;
 
288
    }
 
289
    if (locks & ERTS_PROC_LOCK_STATUS) {
 
290
        have_locks[have_locks_len].id = lc_id.proc_lock_status;
 
291
        have_locks[have_locks_len++].extra = p->id;
 
292
    }
 
293
 
 
294
    erts_lc_check(have_locks, have_locks_len, NULL, 0);
 
295
}
 
296
 
 
297
void
 
298
erts_proc_lc_chk_proc_locks(Process *p, Uint32 locks)
 
299
{
 
300
    int have_locks_len = 0;
 
301
    int have_not_locks_len = 0;
 
302
    erts_lc_lock_t have_locks[4] = {ERTS_PROC_LC_EMPTY_LOCK_INIT,
 
303
                                    ERTS_PROC_LC_EMPTY_LOCK_INIT,
 
304
                                    ERTS_PROC_LC_EMPTY_LOCK_INIT,
 
305
                                    ERTS_PROC_LC_EMPTY_LOCK_INIT};
 
306
    erts_lc_lock_t have_not_locks[4] = {ERTS_PROC_LC_EMPTY_LOCK_INIT,
 
307
                                        ERTS_PROC_LC_EMPTY_LOCK_INIT,
 
308
                                        ERTS_PROC_LC_EMPTY_LOCK_INIT,
 
309
                                        ERTS_PROC_LC_EMPTY_LOCK_INIT};
 
310
 
 
311
    if (locks & ERTS_PROC_LOCK_MAIN) {
 
312
        have_locks[have_locks_len].id = lc_id.proc_lock_main;
 
313
        have_locks[have_locks_len++].extra = p->id;
 
314
    }
 
315
    else {
 
316
        have_not_locks[have_not_locks_len].id = lc_id.proc_lock_main;
 
317
        have_not_locks[have_not_locks_len++].extra = p->id;
 
318
    }
 
319
    if (locks & ERTS_PROC_LOCK_LINK) {
 
320
        have_locks[have_locks_len].id = lc_id.proc_lock_link;
 
321
        have_locks[have_locks_len++].extra = p->id;
 
322
    }
 
323
    else {
 
324
        have_not_locks[have_not_locks_len].id = lc_id.proc_lock_link;
 
325
        have_not_locks[have_not_locks_len++].extra = p->id;
 
326
    }
 
327
    if (locks & ERTS_PROC_LOCK_MSGQ) {
 
328
        have_locks[have_locks_len].id = lc_id.proc_lock_msgq;
 
329
        have_locks[have_locks_len++].extra = p->id;
 
330
    }
 
331
    else {
 
332
        have_not_locks[have_not_locks_len].id = lc_id.proc_lock_msgq;
 
333
        have_not_locks[have_not_locks_len++].extra = p->id;
 
334
    }
 
335
    if (locks & ERTS_PROC_LOCK_STATUS) {
 
336
        have_locks[have_locks_len].id = lc_id.proc_lock_status;
 
337
        have_locks[have_locks_len++].extra = p->id;
 
338
    }
 
339
    else {
 
340
        have_not_locks[have_not_locks_len].id = lc_id.proc_lock_status;
 
341
        have_not_locks[have_not_locks_len++].extra = p->id;
 
342
    }
 
343
 
 
344
    erts_lc_check(have_locks, have_locks_len,
 
345
                  have_not_locks, have_not_locks_len);
 
346
}
 
347
 
 
348
Uint32
 
349
erts_proc_lc_my_proc_locks(Process *p)
 
350
{
 
351
    int resv[4];
 
352
    erts_lc_lock_t locks[4] = {ERTS_LC_LOCK_INIT(lc_id.proc_lock_main,
 
353
                                                 p->id,
 
354
                                                 ERTS_LC_FLG_LT_PROCLOCK),
 
355
                               ERTS_LC_LOCK_INIT(lc_id.proc_lock_link,
 
356
                                                 p->id,
 
357
                                                 ERTS_LC_FLG_LT_PROCLOCK),
 
358
                               ERTS_LC_LOCK_INIT(lc_id.proc_lock_msgq,
 
359
                                                 p->id,
 
360
                                                 ERTS_LC_FLG_LT_PROCLOCK),
 
361
                               ERTS_LC_LOCK_INIT(lc_id.proc_lock_status,
 
362
                                                 p->id,
 
363
                                                 ERTS_LC_FLG_LT_PROCLOCK)};
 
364
 
 
365
    Uint32 res = 0;
 
366
 
 
367
    erts_lc_have_locks(resv, locks, 4);
 
368
    if (resv[0])
 
369
        res |= ERTS_PROC_LOCK_MAIN;
 
370
    if (resv[1])
 
371
        res |= ERTS_PROC_LOCK_LINK;
 
372
    if (resv[2])
 
373
        res |= ERTS_PROC_LOCK_MSGQ;
 
374
    if (resv[3])
 
375
        res |= ERTS_PROC_LOCK_STATUS;
 
376
 
 
377
    return res;
 
378
}
 
379
 
 
380
void
 
381
erts_proc_lc_chk_no_proc_locks(char *file, int line)
 
382
{
 
383
    int resv[4];
 
384
    int ids[4] = {lc_id.proc_lock_main,
 
385
                  lc_id.proc_lock_link,
 
386
                  lc_id.proc_lock_msgq,
 
387
                  lc_id.proc_lock_status};
 
388
    erts_lc_have_lock_ids(resv, ids, 4);
 
389
    if (resv[0] || resv[1] || resv[2] || resv[3]) {
 
390
        erts_lc_fail("%s:%d: Thread has process locks locked when expected "
 
391
                     "not to have any process locks locked",
 
392
                     file, line);
 
393
    }
 
394
}
 
395
 
 
396
#endif
 
397
 
 
398
void
 
399
erts_pre_init_process(void)
 
400
{
 
401
#ifdef USE_THREADS
 
402
    erts_tsd_key_create(&sched_data_key);
 
403
#endif    
 
404
#ifdef ERTS_SMP
 
405
    pending_exiters = NULL;
 
406
#endif
 
407
#if defined(ERTS_ENABLE_LOCK_CHECK) && defined(ERTS_SMP)
 
408
    lc_id.proc_lock_main        = erts_lc_get_lock_order_id("proc_main");
 
409
    lc_id.proc_lock_link        = erts_lc_get_lock_order_id("proc_link");
 
410
    lc_id.proc_lock_msgq        = erts_lc_get_lock_order_id("proc_msgq");
 
411
    lc_id.proc_lock_status      = erts_lc_get_lock_order_id("proc_status");
 
412
#endif
 
413
 
 
414
}
100
415
 
101
416
/* initialize the scheduler */
102
417
void
103
 
init_scheduler(void)
 
418
erts_init_process(void)
104
419
{
105
420
    int i;
106
 
 
107
 
    erts_tot_proc_mem = 0;
 
421
    Uint proc_bits = ERTS_PROC_BITS;
 
422
#ifndef ERTS_SMP
 
423
    ErtsSchedulerData *esdp;
 
424
#endif
 
425
 
 
426
    erts_smp_atomic_init(&process_count, 0);
 
427
 
 
428
    if (erts_use_r9_pids_ports) {
 
429
        proc_bits = ERTS_R9_PROC_BITS;
 
430
        ASSERT(erts_max_processes <= (1 << ERTS_R9_PROC_BITS));
 
431
    }
 
432
 
 
433
    erts_smp_atomic_init(&erts_tot_proc_mem, 0L);
108
434
 
109
435
    process_tab = (Process**) erts_alloc(ERTS_ALC_T_PROC_TABLE,
110
436
                                         erts_max_processes*sizeof(Process*));
111
437
    ERTS_PROC_MORE_MEM(erts_max_processes * sizeof(Process*));
112
438
    sys_memzero(process_tab, erts_max_processes * sizeof(Process*));
113
 
#ifdef SHARED_HEAP
 
439
#ifdef HYBRID
114
440
    erts_active_procs = (Process**)
115
 
        erts_alloc(ERTS_ALC_T_ACTIVE_PROCS, erts_max_processes*sizeof(Process*));
 
441
        erts_alloc(ERTS_ALC_T_ACTIVE_PROCS,
 
442
                   erts_max_processes * sizeof(Process*));
116
443
    ERTS_PROC_MORE_MEM(erts_max_processes * sizeof(Process*));
117
444
    erts_num_active_procs = 0;
118
445
#endif
119
446
 
 
447
#ifdef ERTS_SMP
 
448
    erts_smp_mtx_init(&schdlq_mtx, "schdlq");
 
449
    erts_smp_cnd_init(&schdlq_cnd);
 
450
 
 
451
    use_no_schedulers = 1;
 
452
    changing_no_schedulers = 0;
 
453
    no_schedulers = 0;
 
454
    erts_smp_atomic_init(&atomic_no_schedulers, 0L);
 
455
    last_scheduler_no = 0;
 
456
    schedulers_waiting_on_runq = 0;
 
457
 
 
458
    schedulers = NULL;
 
459
 
 
460
    for (i = 0; i < ERTS_PROC_LOCKS_NO_OF; i++) {
 
461
        erts_smp_mtx_init(&erts_proc_locks[i].mtx,
 
462
                          "proc_main" /* Con the lock checker */);
 
463
#ifdef ERTS_ENABLE_LOCK_CHECK
 
464
        erts_proc_locks[i].mtx.lc.id = -1; /* Dont want lock checking on
 
465
                                              these mutexes */
 
466
#endif
 
467
        erts_smp_cnd_init(&erts_proc_locks[i].cnd);
 
468
    }
 
469
 
 
470
#else /* !ERTS_SMP */
 
471
 
 
472
    esdp = &erts_scheduler_data;
 
473
 
 
474
#ifdef USE_THREADS
 
475
    erts_tsd_set(sched_data_key, (void *) esdp);
 
476
#endif
 
477
 
 
478
    init_sched_thr_data(esdp);
 
479
 
 
480
#endif
 
481
 
 
482
    erts_smp_mtx_init(&proc_tab_mtx, "proc_tab");
 
483
    p_last = -1;
120
484
    p_next = 0;
121
485
    p_serial = 0;
122
486
 
123
487
    p_serial_shift = erts_fit_in_bits(erts_max_processes - 1);
124
 
    p_serial_mask = ((~(~((Uint) 0) << ERTS_PROCESSES_BITS)) >> p_serial_shift);
 
488
    p_serial_mask = ((~(~((Uint) 0) << proc_bits)) >> p_serial_shift);
125
489
    erts_process_tab_index_mask = ~(~((Uint) 0) << p_serial_shift);
126
490
 
127
491
    /* mark the schedule queue as empty */
128
 
    for(i = 0; i < NPRIORITY_LEVELS; i++)
 
492
    for(i = 0; i < NPRIORITY_LEVELS - 1; i++)
129
493
        queue[i].first = queue[i].last = (Process*) 0;
130
494
    qmask = 0;
 
495
    queued_low = 0;
 
496
    queued_normal = 0;
 
497
    runq_len = 0;
131
498
#ifndef BM_COUNTERS
132
499
    processes_busy = 0;
133
500
#endif
134
 
    bg_count = 0;
135
501
    context_switches = 0;
136
502
    reductions = 0;
137
503
    last_reds = 0;
 
504
    last_exact_reds = 0;
138
505
    erts_default_process_flags = 0;
139
 
    erts_default_tracer = NIL;
140
 
    erts_system_monitor_clear();
 
506
}
 
507
 
 
508
#ifdef ERTS_SMP
 
509
 
 
510
static void
 
511
prepare_for_block(void *c_p)
 
512
{
 
513
    erts_smp_mtx_unlock(&schdlq_mtx);
 
514
    if (c_p)
 
515
        erts_smp_proc_unlock((Process *) c_p, ERTS_PROC_LOCK_MAIN);
 
516
}
 
517
 
 
518
static void
 
519
resume_after_block(void *c_p)
 
520
{
 
521
    if (c_p)
 
522
        erts_smp_proc_lock((Process *) c_p, ERTS_PROC_LOCK_MAIN);
 
523
    erts_smp_mtx_lock(&schdlq_mtx);
 
524
}
 
525
 
 
526
void
 
527
erts_start_schedulers(Uint wanted)
 
528
{
 
529
    int res;
 
530
    int want_reschedule;
 
531
    Uint actual;
 
532
    if (wanted < 1)
 
533
        wanted = 1;
 
534
    res = erts_set_no_schedulers(NULL, NULL, &actual, wanted, 
 
535
                                 &want_reschedule);
 
536
    if (actual < 1)
 
537
        erl_exit(1,
 
538
                 "Failed to create any scheduler-threads: %s (%d)\n",
 
539
                 erl_errno_id(res),
 
540
                 res);
 
541
    if (want_reschedule)
 
542
        erl_exit(1, "%s:%d: Internal error\n", __FILE__, __LINE__);
 
543
    if (res != 0) {
 
544
        erts_dsprintf_buf_t *dsbufp = erts_create_logger_dsbuf();
 
545
        ASSERT(actual != wanted);
 
546
        erts_dsprintf(dsbufp,
 
547
                      "Failed to create %bpu scheduler-threads (%s:%d); "
 
548
                      "only %bpu scheduler-thread%s created.\n",
 
549
                      wanted, erl_errno_id(res), res,
 
550
                      actual, actual == 1 ? " was" : "s were");
 
551
        erts_send_error_to_logger_nogl(dsbufp);
 
552
    }
 
553
}
 
554
 
 
555
#endif /* #ifdef ERTS_SMP */
 
556
 
 
557
static void
 
558
init_sched_thr_data(ErtsSchedulerData *esdp)
 
559
{
 
560
#ifdef ERTS_SMP
 
561
    erts_bits_init_state(&esdp->erl_bits_state);
 
562
    esdp->match_pseudo_process = NULL;
 
563
    esdp->no = last_scheduler_no;
 
564
    esdp->free_process = NULL;
 
565
#endif
 
566
 
 
567
    esdp->current_process = NULL;
 
568
 
 
569
}
 
570
 
 
571
#ifdef USE_THREADS
 
572
 
 
573
ErtsSchedulerData *
 
574
erts_get_scheduler_data(void)
 
575
{
 
576
    return (ErtsSchedulerData *) erts_tsd_get(sched_data_key);
 
577
}
 
578
 
 
579
#endif
 
580
 
 
581
static int remove_proc_from_sched_q(Process *p);
 
582
 
 
583
static ERTS_INLINE void
 
584
suspend_process(Process *p)
 
585
{
 
586
    ERTS_SMP_LC_ASSERT(ERTS_PROC_LOCK_STATUS & erts_proc_lc_my_proc_locks(p));
 
587
    ERTS_SMP_LC_ASSERT(erts_smp_lc_mtx_is_locked(&schdlq_mtx));
 
588
 
 
589
    p->rcount++;  /* count number of suspend */
 
590
#ifdef ERTS_SMP
 
591
    ASSERT(!(p->scheduler_flags & ERTS_PROC_SCHED_FLG_SCHEDULED)
 
592
           || p == erts_get_current_process());
 
593
    ASSERT(p->status != P_RUNNING
 
594
           || p->scheduler_flags & ERTS_PROC_SCHED_FLG_SCHEDULED);
 
595
    if (p->status_flags & ERTS_PROC_SFLG_PENDADD2SCHEDQ)
 
596
        goto runable;
 
597
#endif
 
598
    switch(p->status) {
 
599
    case P_SUSPENDED:
 
600
        break;
 
601
    case P_RUNABLE:
 
602
#ifdef ERTS_SMP
 
603
    runable:
 
604
        if (!ERTS_PROC_PENDING_EXIT(p)) 
 
605
#endif
 
606
            remove_proc_from_sched_q(p);
 
607
        /* else:
 
608
         * leave process in schedq so it will discover the pending exit
 
609
         */
 
610
        p->rstatus = P_RUNABLE; /* wakeup as runnable */
 
611
        break;
 
612
    case P_RUNNING:
 
613
        p->rstatus = P_RUNABLE; /* wakeup as runnable */
 
614
        break;
 
615
    case P_WAITING:
 
616
        p->rstatus = P_WAITING; /* wakeup as waiting */
 
617
        break;
 
618
    case P_EXITING:
 
619
        return; /* ignore this */
 
620
    case P_GARBING:
 
621
    case P_FREE:
 
622
        erl_exit(1, "bad state in suspend_process()\n");
 
623
    }
 
624
    p->status = P_SUSPENDED;
 
625
}
 
626
 
 
627
static ERTS_INLINE void
 
628
resume_process(Process *p)
 
629
{
 
630
    ERTS_SMP_LC_ASSERT(ERTS_PROC_LOCK_STATUS & erts_proc_lc_my_proc_locks(p));
 
631
    /* We may get called from trace([suspend], false) */
 
632
    if (p->status != P_SUSPENDED)
 
633
        return;
 
634
    ASSERT(p->rcount > 0);
 
635
 
 
636
    if (--p->rcount > 0)  /* multiple suspend i.e trace and busy port */
 
637
        return;
 
638
    switch(p->rstatus) {
 
639
    case P_RUNABLE:
 
640
        p->status = P_WAITING;  /* make add_to_schedule_q work */
 
641
        add_to_schedule_q(p);
 
642
        break;
 
643
    case P_WAITING:
 
644
        p->status = P_WAITING;
 
645
        break;
 
646
    default:
 
647
        erl_exit(1, "bad state in resume_process()\n");
 
648
    }
 
649
    p->rstatus = P_FREE;    
 
650
}
 
651
 
 
652
#ifdef ERTS_SMP
 
653
 
 
654
static void
 
655
exit_sched_thr(ErtsSchedulerData *esdp, int schdlq_mtx_locked)
 
656
{
 
657
    ASSERT(esdp);
 
658
    if (!schdlq_mtx_locked)
 
659
        erts_smp_mtx_lock(&schdlq_mtx);
 
660
    if (esdp->prev)
 
661
        esdp->prev->next = esdp->next;
 
662
    else
 
663
        schedulers = esdp->next;
 
664
    if (esdp->next)
 
665
        esdp->next->prev = esdp->prev;
 
666
    no_schedulers--;
 
667
    erts_smp_atomic_dec(&atomic_no_schedulers);
 
668
    erts_bits_destroy_state(&esdp->erl_bits_state);
 
669
    erts_free(ERTS_ALC_T_SCHDLR_DATA, (void *) esdp);
 
670
    erts_smp_cnd_broadcast(&schdlq_cnd);
 
671
    erts_smp_mtx_unlock(&schdlq_mtx);
 
672
    erts_thr_exit(NULL);
 
673
}
 
674
 
 
675
static void *
 
676
sched_thread_func(void *vesdp)
 
677
{
 
678
#ifdef ERTS_ENABLE_LOCK_CHECK
 
679
    {
 
680
        char buf[31];
 
681
        Uint no = ((ErtsSchedulerData *) vesdp)->no;
 
682
        erts_snprintf(&buf[0], 31, "scheduler %bpu", no);
 
683
        erts_lc_set_thread_name(&buf[0]);
 
684
    }
 
685
#endif
 
686
    erts_tsd_set(sched_data_key, vesdp);
 
687
    erts_register_blockable_thread();
 
688
#ifdef HIPE
 
689
    hipe_thread_signal_init();
 
690
#endif
 
691
    erts_thread_init_float();
 
692
    process_main();
 
693
    exit_sched_thr((ErtsSchedulerData *) vesdp, 0);
 
694
    return NULL;
 
695
}
 
696
 
 
697
static void
 
698
add_to_proc_list(ProcessList** plpp, Eterm pid)
 
699
{
 
700
    ProcessList* plp;
 
701
 
 
702
    /* Add at the end of the list */
 
703
    for (; *plpp; plpp = &(*plpp)->next) {
 
704
        ASSERT((*plpp)->pid != pid);
 
705
    }
 
706
 
 
707
    plp = (ProcessList *) erts_alloc(ERTS_ALC_T_PROC_LIST, sizeof(ProcessList));
 
708
    plp->pid = pid;
 
709
    plp->next = NULL;
 
710
 
 
711
    *plpp = plp;
 
712
}
 
713
 
 
714
#if 0
 
715
static void
 
716
remove_from_proc_list(ProcessList** plpp, Eterm pid)
 
717
{
 
718
    for (; *plpp; plpp = &(*plpp)->next) {
 
719
        if ((*plpp)->pid == pid) {
 
720
            ProcessList* plp = *plpp;
 
721
            *plpp = plp->next;
 
722
            erts_free(ERTS_ALC_T_PROC_LIST, (void *) plp);
 
723
#ifdef DEBUG
 
724
            for (plp = *plpp; plp; plp = plp->next) {
 
725
                ASSERT(plp->pid != pid);
 
726
            }
 
727
#endif
 
728
            return;
 
729
        }
 
730
    }
 
731
    ASSERT(0);
 
732
}
 
733
#endif
 
734
 
 
735
static void
 
736
handle_pending_suspend(Process *p, Uint32 p_locks)
 
737
{
 
738
    ProcessList *plp;
 
739
    int do_suspend;
 
740
    Eterm suspendee;
 
741
 
 
742
    ASSERT(p->pending_suspenders);
 
743
 
 
744
    if (ERTS_PROC_IS_EXITING(p)) {
 
745
        do_suspend = 0;
 
746
        suspendee = NIL;
 
747
    }
 
748
    else {
 
749
        do_suspend = 1;
 
750
        suspendee = p->id;
 
751
    }
 
752
 
 
753
    plp = p->pending_suspenders; 
 
754
    while (plp) {
 
755
        ProcessList *free_plp;
 
756
        Process *rp = erts_pid2proc(p, p_locks,
 
757
                                    plp->pid, ERTS_PROC_LOCK_STATUS);
 
758
        if (rp) {
 
759
            ASSERT(is_nil(rp->suspendee));
 
760
            rp->suspendee = suspendee;
 
761
            if (do_suspend) {
 
762
                erts_smp_mtx_lock(&schdlq_mtx);
 
763
                suspend_process(p);
 
764
                erts_smp_mtx_unlock(&schdlq_mtx);
 
765
                do_suspend = 0;
 
766
            }
 
767
            /* rp is suspended waiting for p to suspend: resume rp */
 
768
            resume_process(rp);
 
769
            erts_smp_proc_unlock(rp, ERTS_PROC_LOCK_STATUS);
 
770
        }
 
771
        free_plp = plp;
 
772
        plp = plp->next;
 
773
        erts_free(ERTS_ALC_T_PROC_LIST, (void *) free_plp);
 
774
    }
 
775
    p->pending_suspenders = NULL;
 
776
}
 
777
 
 
778
static ERTS_INLINE void
 
779
cancel_suspend_of_suspendee(Process *p, Uint32 p_locks)
 
780
{
 
781
    if (is_not_nil(p->suspendee)) {
 
782
        Process *rp;
 
783
        if (!(p_locks & ERTS_PROC_LOCK_STATUS))
 
784
            erts_smp_proc_lock(p, ERTS_PROC_LOCK_STATUS);
 
785
        rp = erts_pid2proc(p, p_locks|ERTS_PROC_LOCK_STATUS,
 
786
                           p->suspendee, ERTS_PROC_LOCK_STATUS);
 
787
        if (rp)
 
788
            erts_resume(rp, ERTS_PROC_LOCK_STATUS);
 
789
        if (!(p_locks & ERTS_PROC_LOCK_STATUS))
 
790
            erts_smp_proc_unlock(p, ERTS_PROC_LOCK_STATUS);
 
791
        p->suspendee = NIL;
 
792
    }
 
793
}
 
794
 
 
795
Process *
 
796
erts_suspend_another_process(Process *c_p, Uint32 c_p_locks,
 
797
                             Eterm suspendee, Uint32 suspendee_locks)
 
798
{
 
799
    Process *rp;
 
800
    int unlock_c_p_status;
 
801
 
 
802
    ASSERT(c_p->id != suspendee);
 
803
 
 
804
    ERTS_SMP_LC_ASSERT(c_p_locks == erts_proc_lc_my_proc_locks(c_p));
 
805
 
 
806
    c_p->freason = EXC_NULL;
 
807
 
 
808
    if (c_p_locks & ERTS_PROC_LOCK_STATUS)
 
809
        unlock_c_p_status = 0;
 
810
    else {
 
811
        unlock_c_p_status = 1;
 
812
        erts_smp_proc_lock(c_p, ERTS_PROC_LOCK_STATUS);
 
813
    }
 
814
 
 
815
    if (c_p->suspendee == suspendee) {
 
816
    suspended:
 
817
        if (unlock_c_p_status)
 
818
            erts_smp_proc_unlock(c_p, ERTS_PROC_LOCK_STATUS);
 
819
        return erts_pid2proc(c_p, c_p_locks, suspendee, suspendee_locks);
 
820
    }
141
821
    
142
 
    erts_default_trace_pattern_is_on = 0;
143
 
    erts_default_match_spec = NULL;
144
 
    erts_default_meta_match_spec = NULL;
145
 
    erts_default_trace_pattern_flags = erts_trace_pattern_flags_off;
146
 
    erts_default_meta_tracer_pid = NIL;
 
822
    rp = erts_pid2proc(c_p, c_p_locks|ERTS_PROC_LOCK_STATUS,
 
823
                       suspendee, ERTS_PROC_LOCK_STATUS);
 
824
 
 
825
    if (rp) {
 
826
        erts_smp_mtx_lock(&schdlq_mtx);
 
827
        if (!(rp->scheduler_flags & ERTS_PROC_SCHED_FLG_SCHEDULED)) {
 
828
            Uint32 need_locks = suspendee_locks & ~ERTS_PROC_LOCK_STATUS;
 
829
            suspend_process(rp);
 
830
            erts_smp_mtx_unlock(&schdlq_mtx);
 
831
            c_p->suspendee = suspendee;
 
832
            if (need_locks && erts_smp_proc_trylock(rp, need_locks) == EBUSY) {
 
833
                erts_smp_proc_unlock(rp, ERTS_PROC_LOCK_STATUS);
 
834
                goto suspended;
 
835
            }
 
836
        }
 
837
        else {
 
838
            /* Mark rp pending for suspend by c_p */
 
839
            add_to_proc_list(&rp->pending_suspenders, c_p->id);
 
840
            ASSERT(is_nil(c_p->suspendee));
 
841
 
 
842
            /* Suspend c_p (caller is assumed to return to process_main
 
843
               immediately). When rp is suspended c_p will be resumed. */
 
844
            suspend_process(c_p);
 
845
            erts_smp_mtx_unlock(&schdlq_mtx);
 
846
            c_p->freason = RESCHEDULE;
 
847
            erts_smp_proc_unlock(rp, ERTS_PROC_LOCK_STATUS);
 
848
            rp = NULL;
 
849
        }
 
850
    }
 
851
 
 
852
    if (rp && !(suspendee_locks & ERTS_PROC_LOCK_STATUS))
 
853
        erts_smp_proc_unlock(rp, ERTS_PROC_LOCK_STATUS);
 
854
    if (unlock_c_p_status)
 
855
        erts_smp_proc_unlock(c_p, ERTS_PROC_LOCK_STATUS);
 
856
 
 
857
    return rp;
 
858
}
 
859
 
 
860
/*
 
861
 * Like erts_pid2proc() but:
 
862
 *
 
863
 * * At least ERTS_PROC_LOCK_MAIN have to be held on c_p.
 
864
 * * At least ERTS_PROC_LOCK_MAIN have to be taken on pid.
 
865
 * * It also waits for proc to be in a state != running and garbing.
 
866
 * * If NULL is returned, process might have to be rescheduled.
 
867
 *   Use ERTS_SMP_BIF_CHK_RESCHEDULE(P) to check this.
 
868
 */
 
869
 
 
870
 
 
871
Process *
 
872
erts_pid2proc_not_running(Process *c_p, Uint32 c_p_locks,
 
873
                          Eterm pid, Uint32 pid_locks)
 
874
{
 
875
    Process *rp;
 
876
    int unlock_c_p_status;
 
877
 
 
878
    ERTS_SMP_LC_ASSERT(c_p_locks == erts_proc_lc_my_proc_locks(c_p));
 
879
 
 
880
    ASSERT(pid_locks & (ERTS_PROC_LOCK_MAIN|ERTS_PROC_LOCK_STATUS));
 
881
 
 
882
    c_p->freason = EXC_NULL;
 
883
 
 
884
    if (c_p->id == pid)
 
885
        return erts_pid2proc(c_p, c_p_locks, pid, pid_locks);
 
886
 
 
887
    if (c_p_locks & ERTS_PROC_LOCK_STATUS)
 
888
        unlock_c_p_status = 0;
 
889
    else {
 
890
        unlock_c_p_status = 1;
 
891
        erts_smp_proc_lock(c_p, ERTS_PROC_LOCK_STATUS);
 
892
    }
 
893
 
 
894
    if (c_p->suspendee == pid) {
 
895
        /* Process previously suspended by c_p (below)... */
 
896
        Uint32 rp_locks = pid_locks|ERTS_PROC_LOCK_STATUS;
 
897
        rp = erts_pid2proc(c_p, c_p_locks|ERTS_PROC_LOCK_STATUS, pid, rp_locks);
 
898
        c_p->suspendee = NIL;
 
899
        if (rp)
 
900
            resume_process(rp);
 
901
    }
 
902
    else {
 
903
 
 
904
        rp = erts_pid2proc(c_p, c_p_locks|ERTS_PROC_LOCK_STATUS,
 
905
                           pid, ERTS_PROC_LOCK_STATUS);
 
906
 
 
907
        if (!rp)
 
908
            goto done;
 
909
 
 
910
        erts_smp_mtx_lock(&schdlq_mtx);
 
911
        if (rp->scheduler_flags & ERTS_PROC_SCHED_FLG_SCHEDULED) {
 
912
        scheduled:
 
913
            /* Phiu... */
 
914
 
 
915
            /* Mark rp pending for suspend by c_p */
 
916
            add_to_proc_list(&rp->pending_suspenders, c_p->id);
 
917
            ASSERT(is_nil(c_p->suspendee));
 
918
 
 
919
            /* Suspend c_p (caller is assumed to return to process_main
 
920
               immediately). When rp is suspended c_p will be resumed. */
 
921
            suspend_process(c_p);
 
922
            c_p->freason = RESCHEDULE;
 
923
            erts_smp_proc_unlock(rp, ERTS_PROC_LOCK_STATUS);
 
924
            rp = NULL;
 
925
        }
 
926
        else {
 
927
            Uint32 need_locks = pid_locks & ~ERTS_PROC_LOCK_STATUS;
 
928
            if (need_locks && erts_smp_proc_trylock(rp, need_locks) == EBUSY) {
 
929
                erts_smp_mtx_unlock(&schdlq_mtx);
 
930
                erts_smp_proc_unlock(rp, ERTS_PROC_LOCK_STATUS);
 
931
                rp = erts_pid2proc(c_p, c_p_locks|ERTS_PROC_LOCK_STATUS,
 
932
                                   pid, pid_locks|ERTS_PROC_LOCK_STATUS);
 
933
                if (!rp)
 
934
                    goto done;
 
935
                erts_smp_mtx_lock(&schdlq_mtx);
 
936
                if (rp->scheduler_flags & ERTS_PROC_SCHED_FLG_SCHEDULED) {
 
937
                    /* Ahh... */
 
938
                    erts_smp_proc_unlock(rp,
 
939
                                         pid_locks & ~ERTS_PROC_LOCK_STATUS);
 
940
                    goto scheduled;
 
941
                }
 
942
            }
 
943
 
 
944
            /* rp is not scheduled and we got the locks we want... */
 
945
        }
 
946
        erts_smp_mtx_unlock(&schdlq_mtx);
 
947
    }
 
948
 
 
949
 done:
 
950
    if (rp && !(pid_locks & ERTS_PROC_LOCK_STATUS))
 
951
        erts_smp_proc_unlock(rp, ERTS_PROC_LOCK_STATUS);
 
952
    if (unlock_c_p_status)
 
953
        erts_smp_proc_unlock(c_p, ERTS_PROC_LOCK_STATUS);
 
954
    return rp;
 
955
}
 
956
 
 
957
/*
 
958
 * erts_proc_get_locks() assumes that lckp->mtx is locked by calling
 
959
 * thread and that one or more locks have been taken by other threads.
 
960
 * erts_proc_get_locks() returns when all locks in lock_flags
 
961
 * have been acquired if wait_for_locks != 0; otherwise, when
 
962
 * as many locks as possible have been acquired.
 
963
 */
 
964
 
 
965
Uint32
 
966
erts_proc_get_locks(Process *p,
 
967
                    erts_proc_lock_t *lckp,
 
968
                    Uint32 lock_flags,
 
969
                    int wait_for_locks)
 
970
{
 
971
    int i;
 
972
    Uint32 got_locks = 0;
 
973
    Uint32 need_locks = lock_flags & ERTS_PROC_LOCKS_ALL;
 
974
    ASSERT(need_locks & (p->lock_flags & ERTS_PROC_LOCKS_ALL));
 
975
 
 
976
#ifdef ERTS_ENABLE_LOCK_CHECK
 
977
    if (wait_for_locks)
 
978
        erts_proc_lc_lock(p, need_locks);
 
979
#endif
 
980
 
 
981
    /*
 
982
     * Need to lock as many locks as possible (according to lock order)
 
983
     * in order to avoid starvation.
 
984
     */
 
985
    i = 0;
 
986
    while (1) {
 
987
        Uint32 lock = (1 << i);
 
988
        if (lock & need_locks) {
 
989
        check_lock_again:
 
990
            if (lock & p->lock_flags) {
 
991
                if (wait_for_locks) {
 
992
                    p->lock_flags |= ERTS_PROC_LOCK_FLAG_WAITERS;
 
993
                    erts_smp_cnd_wait(&lckp->cnd, &lckp->mtx);
 
994
                }
 
995
                else
 
996
                    return got_locks;
 
997
                if (!(need_locks & p->lock_flags)) {
 
998
                    p->lock_flags |= need_locks; /* Got them all at once... */
 
999
#ifdef ERTS_ENABLE_LOCK_CHECK
 
1000
                    if (!wait_for_locks)
 
1001
                        erts_proc_lc_lock(p, need_locks);
 
1002
#endif
 
1003
                    got_locks |= need_locks;
 
1004
                    ASSERT(got_locks == (lock_flags & ERTS_PROC_LOCKS_ALL));
 
1005
                    return got_locks;
 
1006
                }
 
1007
                goto check_lock_again;
 
1008
            }
 
1009
            else {
 
1010
                p->lock_flags |= lock;
 
1011
#ifdef ERTS_ENABLE_LOCK_CHECK
 
1012
                if (!wait_for_locks)
 
1013
                    erts_proc_lc_lock(p, lock);
 
1014
#endif
 
1015
                got_locks |= lock;
 
1016
                need_locks &= ~lock;
 
1017
                if (!need_locks) {
 
1018
                    ASSERT(got_locks == (lock_flags & ERTS_PROC_LOCKS_ALL));
 
1019
                    return got_locks;
 
1020
                }
 
1021
            }
 
1022
        }
 
1023
        i++;
 
1024
    }
 
1025
}
 
1026
 
 
1027
/*
 
1028
 * proc_safelock_aux() is a helper function for erts_proc_safelock().
 
1029
 *
 
1030
 * If no locks are held, process might have become exiting since the
 
1031
 * last time we looked at it; therefore, we must check that process
 
1032
 * is not exiting each time we acquires the lckp->mtx if no locks
 
1033
 * were held.
 
1034
 */
 
1035
static int
 
1036
proc_safelock_aux(Process *p, Uint pid, erts_proc_lock_t *lckp,
 
1037
                  Uint32 *have_locks, Uint32 *need_locks,
 
1038
                  Uint32 get_locks, Uint32 allow_exiting)
 
1039
{
 
1040
#define SAME_PROC(PID, PIX, PROC) \
 
1041
  ((PROC) == process_tab[(PIX)] && (PROC)->id == (PID))
 
1042
#define EXITING_PROC(PROC) \
 
1043
  ((PROC)->lock_flags & ERTS_PROC_LOCK_FLAG_EXITING)
 
1044
    int res = 0;
 
1045
    Uint pix = internal_pid_index(pid);
 
1046
    int check_same_proc = !*have_locks && pid != ERTS_INVALID_PID;
 
1047
    int check_exiting_proc = (!allow_exiting && !*have_locks);
 
1048
    Uint32 got_locks = 0;
 
1049
 
 
1050
    ASSERT((*have_locks & get_locks) == 0);
 
1051
    ASSERT((*have_locks & *need_locks) == 0);
 
1052
    ASSERT((*need_locks & get_locks) != 0);
 
1053
 
 
1054
    erts_smp_mtx_lock(&lckp->mtx);
 
1055
    if (check_same_proc && (!SAME_PROC(pid, pix, p)
 
1056
                            || (check_exiting_proc && EXITING_PROC(p))))
 
1057
        goto done;
 
1058
 
 
1059
 do_get_locks:
 
1060
    if (p->lock_flags & get_locks) {
 
1061
        Uint32 locks = erts_proc_get_locks(p, lckp, get_locks, 0);
 
1062
        get_locks &= ~locks;
 
1063
        got_locks |= locks;
 
1064
        if (get_locks) {
 
1065
            p->lock_flags |= ERTS_PROC_LOCK_FLAG_WAITERS;
 
1066
            erts_smp_cnd_wait(&lckp->cnd, &lckp->mtx);
 
1067
            if (check_same_proc
 
1068
                && (check_same_proc = !got_locks)
 
1069
                && (!SAME_PROC(pid, pix, p)
 
1070
                    || (check_exiting_proc
 
1071
                        && (check_exiting_proc = !got_locks)
 
1072
                        && EXITING_PROC(p))))
 
1073
                goto done;
 
1074
            goto do_get_locks;
 
1075
        }
 
1076
    }
 
1077
    else {
 
1078
        p->lock_flags |= get_locks; /* Got them all at once... */
 
1079
#ifdef ERTS_ENABLE_LOCK_CHECK
 
1080
        erts_proc_lc_lock(p, get_locks);
 
1081
#endif
 
1082
        got_locks |= get_locks;
 
1083
        /* get_locks = 0; */
 
1084
    }
 
1085
    res = 1;
 
1086
 
 
1087
 done:
 
1088
    erts_smp_mtx_unlock(&lckp->mtx);
 
1089
    *have_locks |= got_locks;
 
1090
    *need_locks &= ~got_locks;
 
1091
    return res;
 
1092
#undef SAME_PROC
 
1093
#undef EXITING_PROC
 
1094
}
 
1095
 
 
1096
/*
 
1097
 * erts_proc_safelock() locks process locks on two processes. this_proc
 
1098
 * should be the currently running process. In order to avoid a deadlock,
 
1099
 * erts_proc_safelock() unlocks those locks that needs to be unlocked,
 
1100
 * and then acquires locks in lock order (including the previously unlocked
 
1101
 * ones).
 
1102
 *
 
1103
 * If other_proc becomes invalid during the locking NULL is returned,
 
1104
 * this_proc's lock state is restored, and all locks on other_proc are
 
1105
 * left unlocked.
 
1106
 *
 
1107
 * If allow_this_exiting is true this_proc is allowed to become invalid
 
1108
 * (exiting); otherwise if this_proc becomes invalid, NULL is returned
 
1109
 * and both processes lock states are restored.
 
1110
 */
 
1111
 
 
1112
int
 
1113
erts_proc_safelock(Process * this_proc,
 
1114
                   Uint32 this_have_locks,
 
1115
                   Uint32 this_need_locks,
 
1116
                   int allow_this_exiting,
 
1117
                   Uint32 other_pid,
 
1118
                   Process *other_proc,
 
1119
                   Uint32 other_have_locks,
 
1120
                   Uint32 other_need_locks,
 
1121
                   int allow_other_exiting)
 
1122
{
 
1123
    Process *p1, *p2, *exiting_p;
 
1124
    Eterm pid1, pid2;
 
1125
    Uint32 need_locks1, have_locks1, need_locks2, have_locks2;
 
1126
    Uint32 unlock_mask, ax1, ax2;
 
1127
    erts_proc_lock_t *lckp1, *lckp2;
 
1128
    int lock_no, res;
 
1129
 
 
1130
    ASSERT(other_proc);
 
1131
 
 
1132
 
 
1133
    /* Determine inter process lock order...
 
1134
     * Locks with the same lock order should be locked on p1 before p2.
 
1135
     */
 
1136
    if (this_proc) {
 
1137
        if (this_proc->id < other_pid) {
 
1138
            p1 = this_proc;
 
1139
            pid1 = this_proc->id;
 
1140
            need_locks1 = this_need_locks;
 
1141
            have_locks1 = this_have_locks;
 
1142
            lckp1 = &erts_proc_locks[ERTS_PID2LOCKIX(pid1)];
 
1143
            ax1 = allow_this_exiting;
 
1144
            p2 = other_proc;
 
1145
            pid2 = other_pid;
 
1146
            need_locks2 = other_need_locks;
 
1147
            have_locks2 = other_have_locks;
 
1148
            lckp2 = &erts_proc_locks[ERTS_PID2LOCKIX(pid2)];
 
1149
            ax2 = allow_other_exiting;
 
1150
        }
 
1151
        else if (this_proc->id > other_pid) {
 
1152
            p1 = other_proc;
 
1153
            pid1 = other_pid;
 
1154
            need_locks1 = other_need_locks;
 
1155
            have_locks1 = other_have_locks;
 
1156
            lckp1 = &erts_proc_locks[ERTS_PID2LOCKIX(pid1)];
 
1157
            ax1 = allow_other_exiting;
 
1158
            p2 = this_proc;
 
1159
            pid2 = this_proc->id;
 
1160
            need_locks2 = this_need_locks;
 
1161
            have_locks2 = this_have_locks;
 
1162
            lckp2 = &erts_proc_locks[ERTS_PID2LOCKIX(pid2)];
 
1163
            ax2 = allow_this_exiting;
 
1164
        }
 
1165
        else {
 
1166
            ASSERT(this_proc == other_proc);
 
1167
            ASSERT(this_proc->id == other_pid);
 
1168
            p1 = this_proc;
 
1169
            pid1 = this_proc->id;
 
1170
            need_locks1 = this_need_locks | other_need_locks;
 
1171
            have_locks1 = this_have_locks | other_have_locks;
 
1172
            lckp1 = &erts_proc_locks[ERTS_PID2LOCKIX(pid1)];
 
1173
            ax1 = allow_this_exiting || allow_other_exiting;
 
1174
            p2 = NULL;
 
1175
            pid2 = 0;
 
1176
            need_locks2 = 0;
 
1177
            have_locks2 = 0;
 
1178
            lckp2 = NULL;
 
1179
            ax2 = 0;
 
1180
        }
 
1181
    }
 
1182
    else {
 
1183
        p1 = other_proc;
 
1184
        pid1 = other_pid;
 
1185
        need_locks1 = other_need_locks;
 
1186
        have_locks1 = other_have_locks;
 
1187
        lckp1 = &erts_proc_locks[ERTS_PID2LOCKIX(pid1)];
 
1188
        ax1 = allow_other_exiting;
 
1189
        p2 = NULL;
 
1190
        pid2 = 0;
 
1191
        need_locks2 = 0;
 
1192
        have_locks2 = 0;
 
1193
        lckp2 = NULL;
 
1194
        ax2 = 0;
 
1195
#ifdef ERTS_ENABLE_LOCK_CHECK
 
1196
        this_need_locks = 0;
 
1197
        this_have_locks = 0;
 
1198
#endif
 
1199
    }
 
1200
 
 
1201
    res = 1; /* Prepare for success... */
 
1202
 
 
1203
 start_restore:
 
1204
 
 
1205
 
 
1206
#ifdef ERTS_ENABLE_LOCK_CHECK
 
1207
    if (p1)
 
1208
        erts_proc_lc_chk_proc_locks(p1, have_locks1);
 
1209
    if (p2)
 
1210
        erts_proc_lc_chk_proc_locks(p2, have_locks2);
 
1211
 
 
1212
    if ((need_locks1 & have_locks1) != have_locks1)
 
1213
        erts_lc_fail("Thread tries to release process lock(s) "
 
1214
                     "on %T via erts_proc_safelock().", pid1);
 
1215
    if ((need_locks2 & have_locks2) != have_locks2)
 
1216
        erts_lc_fail("Thread tries to release process lock(s) "
 
1217
                     "on %T via erts_proc_safelock().",
 
1218
                     pid2);
 
1219
#endif
 
1220
 
 
1221
 
 
1222
    need_locks1 &= ~have_locks1;
 
1223
    need_locks2 &= ~have_locks2;
 
1224
 
 
1225
    /* Figure out the range of locks that needs to be unlocked... */
 
1226
    unlock_mask = ERTS_PROC_LOCKS_ALL;
 
1227
    for (lock_no = 0;
 
1228
         lock_no <= ERTS_PROC_LOCK_MAX_BIT;
 
1229
         lock_no++) {
 
1230
        Uint32 lock = (1 << lock_no);
 
1231
        if (lock & need_locks1)
 
1232
            break;
 
1233
        unlock_mask &= ~lock;
 
1234
        if (lock & need_locks2)
 
1235
            break;
 
1236
    }
 
1237
 
 
1238
    /* ... and unlock locks in that range... */
 
1239
    if (have_locks1 || have_locks2) {
 
1240
        Uint32 unlock_locks;
 
1241
        unlock_locks = unlock_mask & have_locks1;
 
1242
        if (unlock_locks) {
 
1243
            have_locks1 &= ~unlock_locks;
 
1244
            need_locks1 |= unlock_locks;
 
1245
            erts_proc_unlock(p1, unlock_locks);
 
1246
        }
 
1247
        unlock_locks = unlock_mask & have_locks2;
 
1248
        if (unlock_locks) {
 
1249
            have_locks2 &= ~unlock_locks;
 
1250
            need_locks2 |= unlock_locks;
 
1251
            erts_proc_unlock(p2, unlock_locks);
 
1252
        }
 
1253
    }
 
1254
 
 
1255
    /*
 
1256
     * lock_no equals the number of the first lock to lock on
 
1257
     * either p1 *or* p2.
 
1258
     */
 
1259
 
 
1260
 
 
1261
#ifdef ERTS_ENABLE_LOCK_CHECK
 
1262
    if (p1)
 
1263
        erts_proc_lc_chk_proc_locks(p1, have_locks1);
 
1264
    if (p2)
 
1265
        erts_proc_lc_chk_proc_locks(p2, have_locks2);
 
1266
#endif
 
1267
 
 
1268
    /* Lock locks in lock order... */
 
1269
    while (lock_no <= ERTS_PROC_LOCK_MAX_BIT) {
 
1270
        Uint32 locks;
 
1271
        Uint32 lock = (1 << lock_no);
 
1272
        Uint32 lock_mask = 0;
 
1273
        if (need_locks1 & lock) {
 
1274
            do {
 
1275
                lock = (1 << lock_no++);
 
1276
                lock_mask |= lock;
 
1277
            } while (lock_no <= ERTS_PROC_LOCK_MAX_BIT
 
1278
                     && !(need_locks2 & lock));
 
1279
            if (need_locks2 & lock)
 
1280
                lock_no--;
 
1281
            locks = need_locks1 & lock_mask;
 
1282
            if (!proc_safelock_aux(p1, pid1, lckp1,
 
1283
                                   &have_locks1, &need_locks1,
 
1284
                                   locks, ax1)) {
 
1285
                exiting_p = p1;
 
1286
                goto exiting_proc;
 
1287
            }
 
1288
        }
 
1289
        else if (need_locks2 & lock) {
 
1290
            while (lock_no <= ERTS_PROC_LOCK_MAX_BIT
 
1291
                   && !(need_locks1 & lock)) {
 
1292
                lock_mask |= lock;
 
1293
                lock = (1 << ++lock_no);
 
1294
            }
 
1295
            locks = need_locks2 & lock_mask;
 
1296
            if (!proc_safelock_aux(p2, pid2, lckp2,
 
1297
                                   &have_locks2, &need_locks2,
 
1298
                                   locks, ax2)) {
 
1299
                exiting_p = p2;
 
1300
                goto exiting_proc;
 
1301
            }
 
1302
        }
 
1303
        else
 
1304
            lock_no++;
 
1305
    }
 
1306
 
 
1307
 done:
 
1308
 
 
1309
 
 
1310
#ifdef ERTS_ENABLE_LOCK_CHECK
 
1311
    if (p1)
 
1312
        erts_proc_lc_chk_proc_locks(p1, have_locks1);
 
1313
    if (p2)
 
1314
        erts_proc_lc_chk_proc_locks(p2, have_locks2);
 
1315
 
 
1316
    if (p1 && p2) {
 
1317
        if (p1 == this_proc) {
 
1318
            ERTS_SMP_LC_ASSERT(this_need_locks == have_locks1);
 
1319
            ERTS_SMP_LC_ASSERT(other_need_locks == have_locks2);
 
1320
        }
 
1321
        else {
 
1322
            ERTS_SMP_LC_ASSERT(this_need_locks == have_locks2);
 
1323
            ERTS_SMP_LC_ASSERT(other_need_locks == have_locks1);
 
1324
        }
 
1325
    }
 
1326
    else {
 
1327
        ERTS_SMP_LC_ASSERT(p1);
 
1328
        if (this_proc) {
 
1329
            ERTS_SMP_LC_ASSERT(have_locks1
 
1330
                               == (this_need_locks
 
1331
                                   | other_need_locks));
 
1332
        }
 
1333
        else {
 
1334
            ERTS_SMP_LC_ASSERT(have_locks1 == other_need_locks);
 
1335
        }
 
1336
    }
 
1337
#endif
 
1338
 
 
1339
 
 
1340
    return res;
 
1341
 
 
1342
 exiting_proc:
 
1343
    res = 0;
 
1344
    /*
 
1345
     * Note: We may end up here two times if this_proc gets exiting
 
1346
     *       the first time we try to lock, and other_proc gets exiting
 
1347
     *       when we try to restore the lock states. This is no problem
 
1348
     *       and will work out fine.
 
1349
     */
 
1350
 
 
1351
    /*
 
1352
     * We have no locks on the proc that got exiting.
 
1353
     */
 
1354
    if (this_proc) {
 
1355
        /* Piuhhhh!!! Fix the mess... */
 
1356
        Uint32 restore_locks1, restore_locks2;
 
1357
        Uint32 unlock_locks;
 
1358
        if (this_proc == exiting_p) {
 
1359
            /* Restore locks on both procs */
 
1360
            if (this_proc == p1) {
 
1361
                ASSERT(!have_locks1);
 
1362
                restore_locks1 = this_have_locks;
 
1363
                restore_locks2 = other_have_locks;
 
1364
                ax1 = 1;
 
1365
            }
 
1366
            else {
 
1367
                ASSERT(this_proc == p2);
 
1368
                ASSERT(!have_locks2);
 
1369
                restore_locks1 = other_have_locks;
 
1370
                restore_locks2 = this_have_locks;
 
1371
                ax2 = 1;
 
1372
            }
 
1373
#ifdef ERTS_ENABLE_LOCK_CHECK
 
1374
            this_need_locks = this_have_locks;
 
1375
            other_need_locks = other_have_locks;
 
1376
#endif
 
1377
        }
 
1378
        else {
 
1379
            /* Restore locks on this_proc */
 
1380
            if (this_proc == p1) {
 
1381
                ASSERT(!have_locks2);
 
1382
                restore_locks1 = this_have_locks;
 
1383
                restore_locks2 = 0;
 
1384
                ax1 = 1;
 
1385
            }
 
1386
            else {
 
1387
                ASSERT(this_proc == p2);
 
1388
                ASSERT(!have_locks1);
 
1389
                restore_locks1 = 0;
 
1390
                restore_locks2 = this_have_locks;
 
1391
                ax2 = 1;
 
1392
            }
 
1393
#ifdef ERTS_ENABLE_LOCK_CHECK
 
1394
            this_need_locks = this_have_locks;
 
1395
            other_need_locks = 0;
 
1396
#endif
 
1397
        }
 
1398
 
 
1399
        unlock_locks = have_locks1 & ~restore_locks1;
 
1400
        if (unlock_locks) {
 
1401
            erts_proc_unlock(p1, unlock_locks);
 
1402
            have_locks1 &= ~unlock_locks;
 
1403
        }
 
1404
        need_locks1 = restore_locks1;
 
1405
 
 
1406
        unlock_locks = have_locks2 & ~restore_locks2;
 
1407
        if (unlock_locks) {
 
1408
            erts_proc_unlock(p2, unlock_locks);
 
1409
            have_locks2 &= ~unlock_locks;
 
1410
        }
 
1411
        need_locks2 = restore_locks2;
 
1412
 
 
1413
        if (need_locks1 != have_locks1 || need_locks2 != have_locks1)
 
1414
            goto start_restore;
 
1415
    }
 
1416
    else {
 
1417
        ASSERT(exiting_p == other_proc);
 
1418
        /* No this_proc and other_proc exiting == we are done */
 
1419
#ifdef ERTS_ENABLE_LOCK_CHECK
 
1420
        need_locks1 = have_locks1 = need_locks2 = have_locks2
 
1421
            = this_need_locks = other_need_locks = 0;
 
1422
#endif
 
1423
    }
 
1424
 
 
1425
    goto done;
 
1426
}
 
1427
 
 
1428
#endif /* ERTS_SMP */
 
1429
 
 
1430
Uint erts_get_no_schedulers(void)
 
1431
{
 
1432
#ifndef ERTS_SMP
 
1433
    return 1;
 
1434
#else
 
1435
    return (Uint) erts_smp_atomic_read(&atomic_no_schedulers);
 
1436
#endif
 
1437
}
 
1438
 
 
1439
int
 
1440
erts_set_no_schedulers(Process *c_p, Uint *oldp, Uint *actualp, Uint wanted, int *reschedule)
 
1441
{
 
1442
#ifndef ERTS_SMP
 
1443
    *reschedule = 0;
 
1444
    if (oldp)
 
1445
        *oldp = 1;
 
1446
    if (actualp)
 
1447
        *actualp = 1;
 
1448
    if (wanted < 1)
 
1449
        return EINVAL;
 
1450
    if (wanted != 1)
 
1451
        return ENOTSUP;
 
1452
    return 0;
 
1453
#else
 
1454
    int res = 0;
 
1455
    ErtsSchedulerData *esdp;
 
1456
 
 
1457
    *reschedule = 0;
 
1458
    erts_smp_mtx_lock(&schdlq_mtx);
 
1459
 
 
1460
    if (oldp)
 
1461
        *oldp = no_schedulers;
 
1462
 
 
1463
    if (wanted < 1) {
 
1464
        res = EINVAL;
 
1465
        goto done;
 
1466
    }
 
1467
 
 
1468
    if (changing_no_schedulers) {
 
1469
        /*
 
1470
         * Only one scheduler at a time is allowed to change the
 
1471
         * number of schedulers. Currently, someone else is doing
 
1472
         * this, i.e. we need to rescheduler c_p ...
 
1473
         */
 
1474
        *reschedule = 1;
 
1475
        goto done;
 
1476
    }
 
1477
 
 
1478
    changing_no_schedulers = 1;
 
1479
 
 
1480
    use_no_schedulers = wanted;
 
1481
 
 
1482
    if (use_no_schedulers > ERTS_MAX_NO_OF_SCHEDULERS) {
 
1483
        use_no_schedulers = ERTS_MAX_NO_OF_SCHEDULERS;
 
1484
        res = EAGAIN;
 
1485
    }
 
1486
 
 
1487
    while (no_schedulers > use_no_schedulers) {
 
1488
        erts_smp_cnd_broadcast(&schdlq_cnd);
 
1489
 
 
1490
        /* Wait for another scheduler to terminate ... */
 
1491
        erts_smp_activity_begin(ERTS_ACTIVITY_WAIT,
 
1492
                                prepare_for_block,
 
1493
                                resume_after_block,
 
1494
                                (void *) c_p);
 
1495
        erts_smp_cnd_wait(&schdlq_cnd, &schdlq_mtx);
 
1496
        erts_smp_activity_end(ERTS_ACTIVITY_WAIT,
 
1497
                              prepare_for_block,
 
1498
                              resume_after_block,
 
1499
                              (void *) c_p);
 
1500
    }
 
1501
 
 
1502
 
 
1503
    while (no_schedulers < use_no_schedulers) {
 
1504
        int cres;
 
1505
        erts_smp_chk_system_block(prepare_for_block,
 
1506
                                  resume_after_block,
 
1507
                                  (void *) c_p);
 
1508
        esdp = erts_alloc_fnf(ERTS_ALC_T_SCHDLR_DATA, sizeof(ErtsSchedulerData));
 
1509
        if (!esdp) {
 
1510
            res = ENOMEM;
 
1511
            use_no_schedulers = no_schedulers;
 
1512
            break;
 
1513
        }
 
1514
        last_scheduler_no++;
 
1515
        init_sched_thr_data(esdp);
 
1516
        cres = ethr_thr_create(&esdp->tid,sched_thread_func,(void*)esdp,1);
 
1517
        if (cres != 0) {
 
1518
            res = cres;
 
1519
            erts_free(ERTS_ALC_T_SCHDLR_DATA, (void *) esdp);
 
1520
            last_scheduler_no--;
 
1521
            use_no_schedulers = no_schedulers;
 
1522
            break;
 
1523
        }
 
1524
 
 
1525
        no_schedulers++;
 
1526
        erts_smp_atomic_inc(&atomic_no_schedulers);
 
1527
 
 
1528
        if (schedulers)
 
1529
            schedulers->prev = esdp;
 
1530
        esdp->next = schedulers;
 
1531
        esdp->prev = NULL;
 
1532
        schedulers = esdp;
 
1533
    }
 
1534
 
 
1535
    changing_no_schedulers = 0;
 
1536
 
 
1537
 done:
 
1538
    if (actualp)
 
1539
        *actualp = no_schedulers;
 
1540
 
 
1541
    erts_smp_mtx_unlock(&schdlq_mtx);
 
1542
 
 
1543
    return res;
 
1544
#endif /* ERTS_SMP */
147
1545
}
148
1546
 
149
1547
int
150
1548
sched_q_len(void)
151
1549
{
 
1550
#ifdef DEBUG
152
1551
    int i;
153
 
    int len = 0;
154
 
 
155
 
    for (i = 0; i < NPRIORITY_LEVELS; i++) {
 
1552
#endif
 
1553
    Sint len = 0;
 
1554
 
 
1555
    erts_smp_mtx_lock(&schdlq_mtx);
 
1556
 
 
1557
#ifdef DEBUG
 
1558
    for (i = 0; i < NPRIORITY_LEVELS - 1; i++) {
156
1559
        Process* p;
157
1560
 
158
1561
        for (p = queue[i].first; p != NULL; p = p->next) {
159
1562
            len++;
160
1563
        }
161
1564
    }
162
 
    return len;
163
 
}
 
1565
    ASSERT(len == runq_len);
 
1566
#endif
 
1567
 
 
1568
    len = runq_len;
 
1569
 
 
1570
    erts_smp_mtx_unlock(&schdlq_mtx);
 
1571
 
 
1572
    return (int) len;
 
1573
}
 
1574
 
 
1575
#ifdef HARDDEBUG
 
1576
static int
 
1577
is_proc_in_schdl_q(Process *p)
 
1578
{
 
1579
    int i;
 
1580
    for (i = 0; i < NPRIORITY_LEVELS - 1; i++) {
 
1581
        Process* rp;
 
1582
        for (rp = queue[i].first; rp; rp = rp->next) {
 
1583
            if (rp == p)
 
1584
                return 1;
 
1585
        }
 
1586
    }
 
1587
    return 0;
 
1588
}
 
1589
#endif
164
1590
 
165
1591
/* schedule a process */
166
 
void
167
 
add_to_schedule_q(Process *p)
 
1592
static ERTS_INLINE void
 
1593
internal_add_to_schedule_q(Process *p)
168
1594
{
169
 
    ScheduleQ* sq = &queue[p->prio];
170
 
 
171
 
    /* Never schedule a suspended process */
 
1595
    /*
 
1596
     * ERTS_SMP: internal_add_to_schuduleq should only be used from:
 
1597
     *           - add_to_scheduleq()
 
1598
     *           - schedule() when schdlq_mtx and scheduler is about
 
1599
     *             to schedule a new process.
 
1600
     */
 
1601
    ScheduleQ* sq;
 
1602
 
 
1603
#ifdef ERTS_SMP
 
1604
 
 
1605
    ERTS_SMP_LC_ASSERT(ERTS_PROC_LOCK_STATUS & erts_proc_lc_my_proc_locks(p));
 
1606
    ERTS_SMP_LC_ASSERT(erts_smp_lc_mtx_is_locked(&schdlq_mtx));
 
1607
 
 
1608
    if (p->status_flags & ERTS_PROC_SFLG_INRUNQ)
 
1609
        return;
 
1610
    else if (p->scheduler_flags & ERTS_PROC_SCHED_FLG_SCHEDULED) {
 
1611
        ASSERT(p->status != P_SUSPENDED);
 
1612
#ifdef HARDDEBUG
 
1613
        ASSERT(!is_proc_in_schdl_q(p));
 
1614
#endif
 
1615
        p->status_flags |= ERTS_PROC_SFLG_PENDADD2SCHEDQ;
 
1616
        return;
 
1617
    }
 
1618
    ASSERT(!p->scheduler_data);
 
1619
#endif
 
1620
 
 
1621
#ifdef HARDDEBUG
 
1622
    ASSERT(!is_proc_in_schdl_q(p));
 
1623
#endif
 
1624
 
 
1625
    switch (p->prio) {
 
1626
    case PRIORITY_LOW:
 
1627
      queued_low++;
 
1628
      sq = &queue[PRIORITY_NORMAL];
 
1629
      break;
 
1630
    case PRIORITY_NORMAL:
 
1631
      queued_normal++;
 
1632
    default:
 
1633
      sq = &queue[p->prio];      
 
1634
    }
 
1635
 
 
1636
#ifndef ERTS_SMP
 
1637
    /* Never schedule a suspended process (ok in smp case) */
172
1638
    ASSERT(p->status != P_SUSPENDED);
 
1639
#endif
173
1640
 
174
1641
    qmask |= (1 << p->prio);
 
1642
 
175
1643
    p->next = NULL;
176
1644
    if (sq->first == (Process *) 0)
177
1645
        sq->first = p;
181
1649
    if (p->status != P_EXITING) {
182
1650
        p->status = P_RUNABLE;
183
1651
    }
 
1652
 
 
1653
    runq_len++;
 
1654
#ifdef ERTS_SMP
 
1655
    p->status_flags |= ERTS_PROC_SFLG_INRUNQ;
 
1656
#endif
 
1657
 
 
1658
}
 
1659
 
 
1660
 
 
1661
void
 
1662
add_to_schedule_q(Process *p)
 
1663
{
 
1664
    erts_smp_mtx_lock(&schdlq_mtx);
 
1665
    internal_add_to_schedule_q(p);
 
1666
#ifdef ERTS_SMP
 
1667
    if (no_schedulers == schedulers_waiting_on_runq)
 
1668
        erts_smp_cnd_signal(&schdlq_cnd);
 
1669
#endif
 
1670
    erts_smp_mtx_unlock(&schdlq_mtx);
184
1671
}
185
1672
 
186
1673
/* Possibly remove a scheduled process we need to suspend */
187
1674
 
188
 
int
 
1675
static int
189
1676
remove_proc_from_sched_q(Process *p)
190
1677
{
191
1678
    Process *tmp, *prev;
192
 
    int i;
193
 
 
194
 
    for(i = 0; i < NPRIORITY_LEVELS; i++) {
 
1679
    int res, i;
 
1680
 
 
1681
    ERTS_SMP_LC_ASSERT(ERTS_PROC_LOCK_STATUS & erts_proc_lc_my_proc_locks(p));
 
1682
 
 
1683
#ifdef ERTS_SMP
 
1684
    if (p->status_flags & ERTS_PROC_SFLG_PENDADD2SCHEDQ) {
 
1685
        p->status_flags &= ~ERTS_PROC_SFLG_PENDADD2SCHEDQ;
 
1686
        ASSERT(!remove_proc_from_sched_q(p));
 
1687
        return 1;
 
1688
    }
 
1689
#endif
 
1690
 
 
1691
    res = 0;
 
1692
 
 
1693
    for(i = 0; i < NPRIORITY_LEVELS - 1; i++) {
195
1694
        ScheduleQ *sq = &queue[i];
196
1695
 
197
1696
        if (sq->first == (Process*) NULL)
198
1697
            continue;
199
1698
        if (sq->first == sq->last && sq->first == p) {
200
1699
            sq->first = sq->last = NULL;
201
 
            qmask &= ~(1 << p->prio);
202
 
            return 1;
 
1700
 
 
1701
            if (i == PRIORITY_NORMAL) {
 
1702
               qmask &= ~(1 << PRIORITY_NORMAL) & ~(1 << PRIORITY_LOW);
 
1703
               queued_low = 0;
 
1704
               queued_normal = 0; 
 
1705
            }
 
1706
            else
 
1707
               qmask &= ~(1 << p->prio);
 
1708
 
 
1709
            ASSERT(runq_len > 0);
 
1710
            res = 1;
 
1711
            goto done;
203
1712
        }
204
1713
        if (sq->first == p) {
205
1714
            sq->first = sq->first->next;
206
 
            return 1;
 
1715
            DECR_PROC_COUNT(p->prio);
 
1716
            ASSERT(runq_len > 0);
 
1717
            res = 1;
 
1718
            goto done;
207
1719
        }
208
1720
        tmp = sq->first->next;
209
1721
        prev = sq->first;
210
1722
        while (tmp) {
211
1723
            if (tmp == p) {
212
1724
                prev->next = tmp->next;
 
1725
                DECR_PROC_COUNT(p->prio);
213
1726
                if (p == sq->last)
214
1727
                    sq->last = prev;
215
 
                return 1;
 
1728
                ASSERT(runq_len > 0);
 
1729
                res = 1;
 
1730
                goto done;
216
1731
            }
217
1732
            prev = tmp;
218
1733
            tmp = tmp->next;
219
1734
        }
220
1735
    }
221
 
    return 0;
222
 
}
 
1736
 
 
1737
 done:
 
1738
 
 
1739
    if (res) {
 
1740
#ifdef ERTS_SMP
 
1741
        p->status_flags &= ~ERTS_PROC_SFLG_INRUNQ;
 
1742
#endif
 
1743
        runq_len--;
 
1744
    }
 
1745
#ifdef ERTS_SMP
 
1746
    ASSERT(!(p->status_flags & ERTS_PROC_SFLG_INRUNQ));
 
1747
#endif
 
1748
#ifdef HARDDEBUG
 
1749
    ASSERT(!is_proc_in_schdl_q(p));
 
1750
#endif
 
1751
    return res;
 
1752
}
 
1753
 
 
1754
 
 
1755
Eterm
 
1756
erts_process_status(Process *c_p, Uint32 c_p_locks,
 
1757
                    Process *rp, Eterm rpid)
 
1758
{
 
1759
    Eterm res = am_undefined;
 
1760
    Process *p;
 
1761
 
 
1762
    if (rp) {
 
1763
        ERTS_SMP_LC_ASSERT(ERTS_PROC_LOCK_STATUS
 
1764
                           & erts_proc_lc_my_proc_locks(rp));
 
1765
        p = rp;
 
1766
    }
 
1767
    else {
 
1768
        p = erts_pid2proc_opt(c_p, c_p_locks,
 
1769
                              rpid, ERTS_PROC_LOCK_STATUS,
 
1770
                              ERTS_P2P_FLG_ALLOW_OTHER_X);
 
1771
    }
 
1772
 
 
1773
    if (p) {
 
1774
        switch (p->status) {
 
1775
        case P_RUNABLE:
 
1776
            res = am_runnable;
 
1777
            break;
 
1778
        case P_WAITING:
 
1779
            res = am_waiting;
 
1780
            break;
 
1781
        case P_RUNNING:
 
1782
            res = am_running;
 
1783
            break;
 
1784
        case P_EXITING:
 
1785
            res = am_exiting;
 
1786
            break;
 
1787
        case P_GARBING:
 
1788
            res = am_garbage_collecting;
 
1789
            break;
 
1790
        case P_SUSPENDED:
 
1791
            res = am_suspended;
 
1792
            break;
 
1793
        case P_FREE:    /* We cannot look up a process in P_FREE... */
 
1794
        default:        /* Not a valid status... */
 
1795
            erl_exit(1, "Bad status (%b32u) found for process %T\n",
 
1796
                     p->status, p->id);
 
1797
            break;
 
1798
        }
 
1799
 
 
1800
#ifdef ERTS_SMP
 
1801
        if (!rp && (p != c_p || !(ERTS_PROC_LOCK_STATUS & c_p_locks)))
 
1802
            erts_smp_proc_unlock(p, ERTS_PROC_LOCK_STATUS);
 
1803
    }
 
1804
    else {
 
1805
        ErtsSchedulerData *esdp;
 
1806
        erts_smp_mtx_lock(&schdlq_mtx);
 
1807
        for (esdp = schedulers; esdp; esdp = esdp->next) {
 
1808
            if (esdp->free_process && esdp->free_process->id == rpid) {
 
1809
                res = am_free;
 
1810
                break;
 
1811
            }
 
1812
        }
 
1813
        erts_smp_mtx_unlock(&schdlq_mtx);
 
1814
#endif
 
1815
 
 
1816
    }
 
1817
 
 
1818
    return res;
 
1819
}
 
1820
 
 
1821
/*
 
1822
** Suspend a process 
 
1823
** If we are to suspend on a port the busy_port is the thing
 
1824
** otherwise busy_port is NIL
 
1825
*/
 
1826
 
 
1827
void
 
1828
erts_suspend(Process* process, Uint32 process_locks, Eterm busy_port)
 
1829
{
 
1830
 
 
1831
    ERTS_SMP_LC_ASSERT(process_locks == erts_proc_lc_my_proc_locks(process));
 
1832
    if (!(process_locks & ERTS_PROC_LOCK_STATUS))
 
1833
        erts_smp_proc_lock(process, ERTS_PROC_LOCK_STATUS);
 
1834
 
 
1835
    erts_smp_mtx_lock(&schdlq_mtx);
 
1836
 
 
1837
    suspend_process(process);
 
1838
 
 
1839
    erts_smp_mtx_unlock(&schdlq_mtx);
 
1840
 
 
1841
    if (busy_port != NIL)
 
1842
        wake_process_later(busy_port, process);
 
1843
 
 
1844
    if (!(process_locks & ERTS_PROC_LOCK_STATUS))
 
1845
        erts_smp_proc_unlock(process, ERTS_PROC_LOCK_STATUS);
 
1846
 
 
1847
}
 
1848
 
 
1849
void
 
1850
erts_resume(Process* process, Uint32 process_locks)
 
1851
{
 
1852
    ERTS_SMP_LC_ASSERT(process_locks == erts_proc_lc_my_proc_locks(process));
 
1853
    if (!(process_locks & ERTS_PROC_LOCK_STATUS))
 
1854
        erts_smp_proc_lock(process, ERTS_PROC_LOCK_STATUS);
 
1855
    resume_process(process);
 
1856
    if (!(process_locks & ERTS_PROC_LOCK_STATUS))
 
1857
        erts_smp_proc_unlock(process, ERTS_PROC_LOCK_STATUS);
 
1858
}
 
1859
 
 
1860
Eterm
 
1861
erts_get_process_priority(Process *p)
 
1862
{
 
1863
    Eterm value;
 
1864
    ERTS_SMP_LC_ASSERT(erts_proc_lc_my_proc_locks(p));
 
1865
    erts_smp_mtx_lock(&schdlq_mtx);
 
1866
    switch(p->prio) {
 
1867
    case PRIORITY_MAX:          value = am_max;                 break;
 
1868
    case PRIORITY_HIGH:         value = am_high;                break;
 
1869
    case PRIORITY_NORMAL:       value = am_normal;              break;
 
1870
    case PRIORITY_LOW:          value = am_low;                 break;
 
1871
    default: ASSERT(0);         value = am_undefined;           break;
 
1872
    }
 
1873
    erts_smp_mtx_unlock(&schdlq_mtx);
 
1874
    return value;
 
1875
}
 
1876
 
 
1877
Eterm
 
1878
erts_set_process_priority(Process *p, Eterm new_value)
 
1879
{
 
1880
    Eterm old_value;
 
1881
    ERTS_SMP_LC_ASSERT(erts_proc_lc_my_proc_locks(p));
 
1882
    erts_smp_mtx_lock(&schdlq_mtx);
 
1883
    switch(p->prio) {
 
1884
    case PRIORITY_MAX:          old_value = am_max;             break;
 
1885
    case PRIORITY_HIGH:         old_value = am_high;            break;
 
1886
    case PRIORITY_NORMAL:       old_value = am_normal;          break;
 
1887
    case PRIORITY_LOW:          old_value = am_low;             break;
 
1888
    default: ASSERT(0);         old_value = am_undefined;       break;
 
1889
    }
 
1890
    switch (new_value) {
 
1891
    case am_max:                p->prio = PRIORITY_MAX;         break;
 
1892
    case am_high:               p->prio = PRIORITY_HIGH;        break;
 
1893
    case am_normal:             p->prio = PRIORITY_NORMAL;      break;
 
1894
    case am_low:                p->prio = PRIORITY_LOW;         break;
 
1895
    default:                    old_value = THE_NON_VALUE;      break;
 
1896
    }
 
1897
    erts_smp_mtx_unlock(&schdlq_mtx);
 
1898
    return old_value;
 
1899
}
 
1900
 
 
1901
 
223
1902
 
224
1903
/* note that P_RUNNING is only set so that we don't try to remove
225
1904
** running processes from the schedule queue if they exit - a running
240
1919
 * When no process is runnable, or when sufficiently many reduction
241
1920
 * steps have been made, schedule() calls erl_sys_schedule() to
242
1921
 * schedule system-level activities.
 
1922
 *
 
1923
 * We use the same queue for normal and low prio processes.
 
1924
 * We reschedule low prio processes a certain number of times 
 
1925
 * so that normal processes get to run more frequently. 
243
1926
 */
 
1927
 
244
1928
Process *schedule(Process *p, int calls)
245
1929
{
246
1930
    ScheduleQ *sq;
 
1931
#ifndef ERTS_SMP
247
1932
    static int function_calls;
248
 
 
 
1933
#endif
 
1934
    long dt;
 
1935
    ErtsSchedulerData *esdp;
 
1936
    
249
1937
    /*
250
1938
     * Clean up after the process being suspended.
251
1939
     */
252
 
    if (p) {    /* NULL in the very first schedule() call */
 
1940
    if (!p) {   /* NULL in the very first schedule() call */
 
1941
        esdp = erts_get_scheduler_data();
 
1942
        ASSERT(esdp);
 
1943
        erts_smp_mtx_lock(&schdlq_mtx);
 
1944
    } else {
 
1945
#ifdef ERTS_SMP
 
1946
        esdp = p->scheduler_data;
 
1947
        ASSERT(esdp->current_process == p
 
1948
               || esdp->free_process == p);
 
1949
#else
 
1950
        esdp = &erts_scheduler_data;
 
1951
        ASSERT(esdp->current_process == p);
253
1952
        function_calls += calls;
 
1953
#endif
254
1954
        reductions += calls;
255
 
 
256
 
#ifdef SHARED_HEAP
257
 
        ASSERT(p->heap && p->htop && p->hend && p->heap_sz);
258
 
        ASSERT(!(global_heap || global_htop || global_hend || global_heap_sz));
259
 
        global_htop = p->htop;
260
 
        global_heap = p->heap;
261
 
        global_hend = p->hend;
262
 
        global_heap_sz = p->heap_sz;
263
 
        p->htop = NULL;
264
 
        p->heap = NULL;
265
 
        p->hend = NULL;
266
 
        p->heap_sz = 0;
267
 
#endif
268
 
 
269
 
        ERTS_INSTR_RESET_CURR_PROC();
 
1955
        ASSERT(esdp && esdp == erts_get_scheduler_data());
270
1956
 
271
1957
        p->reds += calls;
 
1958
 
 
1959
        erts_smp_proc_lock(p, ERTS_PROC_LOCK_STATUS);
 
1960
 
 
1961
#ifdef ERTS_SMP
 
1962
        if (ERTS_PROC_PENDING_EXIT(p)) {
 
1963
            erts_handle_pending_exit(p,
 
1964
                                     ERTS_PROC_LOCK_MAIN|ERTS_PROC_LOCK_STATUS);
 
1965
            p->status_flags |= ERTS_PROC_SFLG_PENDADD2SCHEDQ;
 
1966
        }
 
1967
 
 
1968
        if (p->pending_suspenders) {
 
1969
            handle_pending_suspend(p,
 
1970
                                   ERTS_PROC_LOCK_MAIN|ERTS_PROC_LOCK_STATUS);
 
1971
            ASSERT(!(p->status_flags & ERTS_PROC_SFLG_PENDADD2SCHEDQ)
 
1972
                   || p->status != P_SUSPENDED);
 
1973
        }
 
1974
#endif
 
1975
        erts_smp_mtx_lock(&schdlq_mtx);
 
1976
 
 
1977
        /* Rule of thumb, only trace when we have a valid current_process */
 
1978
        if (p->status != P_FREE && IS_TRACED_FL(p, F_TRACE_SCHED)) {
 
1979
            trace_sched(p, am_out);
 
1980
        }
 
1981
 
 
1982
        esdp->current_process = NULL;
 
1983
#ifdef ERTS_SMP
 
1984
        p->scheduler_data = NULL;
 
1985
        p->scheduler_flags &= ~ERTS_PROC_SCHED_FLG_SCHEDULED;
 
1986
        p->status_flags &= ~ERTS_PROC_SFLG_SCHEDULED;
 
1987
 
 
1988
        if (p->status_flags & ERTS_PROC_SFLG_PENDADD2SCHEDQ) {
 
1989
            p->status_flags &= ~ERTS_PROC_SFLG_PENDADD2SCHEDQ;
 
1990
            internal_add_to_schedule_q(p);
 
1991
        }
 
1992
#endif
 
1993
 
 
1994
 
272
1995
        if (p->status == P_FREE) {
273
1996
            ERTS_PROC_LESS_MEM(sizeof(Process));
 
1997
#ifdef ERTS_SMP
 
1998
            ASSERT(esdp->free_process == p);
 
1999
            esdp->free_process = NULL;
 
2000
#endif
 
2001
#ifdef ERTS_ENABLE_LOCK_CHECK
 
2002
            /* No need to unlock unless we are checking locks */
 
2003
            erts_smp_proc_unlock(p, ERTS_PROC_LOCK_MAIN|ERTS_PROC_LOCK_STATUS);
 
2004
#endif
274
2005
            erts_free(ERTS_ALC_T_PROC, (void *) p);
275
 
        } else if (IS_TRACED_FL(p, F_TRACE_SCHED)) {
276
 
            trace_sched(p, am_out);
277
 
        }
278
 
 
279
 
        if (do_time) {
280
 
            bump_timer();
281
 
        }
282
 
        BM_STOP_TIMER(system);
 
2006
        } else {
 
2007
            erts_smp_proc_unlock(p, ERTS_PROC_LOCK_MAIN|ERTS_PROC_LOCK_STATUS);
 
2008
        }
 
2009
 
 
2010
#ifdef ERTS_SMP
 
2011
        ASSERT(!esdp->free_process);
 
2012
#endif
 
2013
        ASSERT(!esdp->current_process);
 
2014
 
 
2015
        ERTS_SMP_CHK_NO_PROC_LOCKS;
 
2016
 
 
2017
        dt = do_time_read_and_reset();
 
2018
        if (dt) {
 
2019
            erts_smp_mtx_unlock(&schdlq_mtx);
 
2020
            bump_timer(dt);
 
2021
            erts_smp_mtx_lock(&schdlq_mtx);
 
2022
        }
 
2023
        BM_STOP_TIMER(system);
 
2024
 
283
2025
    }
284
2026
 
285
2027
    /*
286
2028
     * Find a new process to run.
287
2029
     */
288
2030
 pick_next_process:
289
 
    if (function_calls <= INPUT_REDUCTIONS) {
290
 
        switch (qmask) {
 
2031
#ifdef ERTS_SMP
 
2032
    erts_smp_chk_system_block(prepare_for_block, resume_after_block, NULL);
 
2033
    if (no_schedulers > use_no_schedulers)
 
2034
        exit_sched_thr(esdp, 1);
 
2035
 
 
2036
#else
 
2037
    if (function_calls <= INPUT_REDUCTIONS)
 
2038
#endif
 
2039
    {
 
2040
      switch (qmask) {
291
2041
        case MAX_BIT:
292
2042
        case MAX_BIT|HIGH_BIT:
293
2043
        case MAX_BIT|NORMAL_BIT:
304
2054
        case HIGH_BIT|NORMAL_BIT|LOW_BIT:
305
2055
            sq = &queue[PRIORITY_HIGH];
306
2056
            break;
307
 
        case NORMAL_BIT:
308
 
            sq = &queue[PRIORITY_NORMAL];
309
 
            break;
310
 
        case NORMAL_BIT|LOW_BIT:
311
 
            bg_count++;
312
 
            if ((bg_count % BG_PROPORTION) == 0)
313
 
                sq = &queue[PRIORITY_LOW];
314
 
            else
315
 
                sq = &queue[PRIORITY_NORMAL];
316
 
            break;
317
 
        case LOW_BIT:
318
 
            bg_count++;
319
 
            sq = &queue[PRIORITY_LOW];
320
 
            break;
321
 
        case 0:                 /* No process at all */
 
2057
        case NORMAL_BIT:
 
2058
            sq = &queue[PRIORITY_NORMAL];
 
2059
            break;
 
2060
        case LOW_BIT:
 
2061
            sq = &queue[PRIORITY_NORMAL];
 
2062
            break;
 
2063
        case NORMAL_BIT|LOW_BIT:          
 
2064
            sq = &queue[PRIORITY_NORMAL];
 
2065
            ASSERT(sq->first != NULL);
 
2066
            p = sq->first;
 
2067
            if (p->prio == PRIORITY_LOW) {
 
2068
              if ((p != sq->last) && (p->skipped < RESCHEDULE_LOW-1)) { /* reschedule */
 
2069
                p->skipped++;
 
2070
                /* put last in queue */
 
2071
                sq->first = p->next;
 
2072
                p->next = NULL;
 
2073
                (sq->last)->next = p;
 
2074
                sq->last = p;
 
2075
                goto pick_next_process;
 
2076
              } else {
 
2077
                p->skipped = 0;
 
2078
              }
 
2079
            }
 
2080
            break;
 
2081
        case 0:                 /* No process at all */
 
2082
            ASSERT(runq_len == 0);
322
2083
            goto do_sys_schedule;
323
2084
#ifdef DEBUG
324
2085
        default:
337
2098
        ASSERT(sq->first != NULL); /* Wrong bitmask in qmask? */
338
2099
        p = sq->first;
339
2100
        sq->first = p->next;
340
 
        if (sq->first == NULL) {
 
2101
        
 
2102
        if (p->prio == PRIORITY_LOW) {
 
2103
          if (--queued_low == 0) {
 
2104
            qmask &= ~(1 << PRIORITY_LOW);
 
2105
            if (sq->first == NULL) {
 
2106
              sq->last = NULL;
 
2107
              ASSERT_NORMAL_Q_EMPTY();
 
2108
            } else
 
2109
              ASSERT((queued_normal > 0) && ((qmask >> PRIORITY_NORMAL) & 1));
 
2110
          }
 
2111
        } else if (p->prio == PRIORITY_NORMAL) {
 
2112
          if (--queued_normal == 0) {
 
2113
            qmask &= ~(1 << PRIORITY_NORMAL);
 
2114
            if (sq->first == NULL) {
 
2115
              sq->last = NULL;
 
2116
              ASSERT_NORMAL_Q_EMPTY();
 
2117
            } else
 
2118
              ASSERT((queued_low > 0) && ((qmask >> PRIORITY_LOW) & 1));
 
2119
          }
 
2120
        } else {
 
2121
          if (sq->first == NULL) {
341
2122
            sq->last = NULL;
342
2123
            qmask &= ~(1 << p->prio);
343
 
        }
344
 
 
 
2124
          }
 
2125
        }
 
2126
 
 
2127
        ASSERT(runq_len > 0);
 
2128
        runq_len--;
 
2129
 
 
2130
        context_switches++;
 
2131
 
 
2132
#ifdef ERTS_SMP
 
2133
        p->scheduler_flags |= ERTS_PROC_SCHED_FLG_SCHEDULED;
 
2134
        if (runq_len && schedulers_waiting_on_runq)
 
2135
            erts_smp_cnd_signal(&schdlq_cnd);
 
2136
#endif
 
2137
        
 
2138
#ifdef HARDDEBUG
 
2139
        ASSERT(!is_proc_in_schdl_q(p));
 
2140
#endif
 
2141
 
 
2142
        esdp->current_process = p;
 
2143
 
 
2144
#ifdef ERTS_SMP
 
2145
        {
 
2146
            ProcessList *pnd_xtrs = pending_exiters;
 
2147
            pending_exiters = NULL;
 
2148
            erts_smp_mtx_unlock(&schdlq_mtx);
 
2149
 
 
2150
            if (pnd_xtrs)
 
2151
                handle_pending_exiters(pnd_xtrs);
 
2152
        }
 
2153
 
 
2154
        ERTS_SMP_CHK_NO_PROC_LOCKS;
 
2155
 
 
2156
        erts_smp_proc_lock(p, ERTS_PROC_LOCK_MAIN|ERTS_PROC_LOCK_STATUS);
 
2157
 
 
2158
        p->status_flags |= ERTS_PROC_SFLG_SCHEDULED;
 
2159
        p->status_flags &= ~ERTS_PROC_SFLG_INRUNQ;
 
2160
        if (ERTS_PROC_PENDING_EXIT(p)) {
 
2161
            erts_handle_pending_exit(p,
 
2162
                                     ERTS_PROC_LOCK_MAIN|ERTS_PROC_LOCK_STATUS);
 
2163
        }
 
2164
        ASSERT(!p->scheduler_data);
 
2165
        p->scheduler_data = esdp;
 
2166
 
 
2167
#endif
345
2168
        ASSERT(p->status != P_SUSPENDED); /* Never run a suspended process */
346
 
#ifdef SHARED_HEAP
347
 
        p->active = 1;
348
 
        ASSERT(!p->heap && !p->htop && !p->hend && !p->heap_sz);
349
 
        p->htop = global_htop;
350
 
        p->heap = global_heap;
351
 
        p->hend = global_hend;
352
 
        p->heap_sz = global_heap_sz;
353
 
        global_htop = NULL;
354
 
        global_heap = NULL;
355
 
        global_hend = NULL;
356
 
        global_heap_sz = 0;
357
 
#endif
358
 
        context_switches++;
 
2169
 
 
2170
        ACTIVATE(p);
359
2171
        calls = CONTEXT_REDS;
360
2172
        if (p->status != P_EXITING) {
361
2173
            if (IS_TRACED_FL(p, F_TRACE_SCHED)) {
364
2176
            p->status = P_RUNNING;
365
2177
        }
366
2178
 
 
2179
        erts_smp_proc_unlock(p, ERTS_PROC_LOCK_STATUS);
 
2180
 
 
2181
#ifdef ERTS_SMP
 
2182
        if (is_not_nil(p->tracer_proc))
 
2183
            erts_check_my_tracer_proc(p);
 
2184
#endif
 
2185
 
367
2186
        if (((MBUF_SIZE(p) + MSO(p).overhead) * MBUF_GC_FACTOR) >= HEAP_SIZE(p)) {
368
2187
            calls -= erts_garbage_collect(p, 0, p->arg_reg, p->arity);
369
2188
            if (calls < 0) {
371
2190
            }
372
2191
        }
373
2192
 
374
 
        ERTS_INSTR_SET_CURR_PROC(p->id);
375
 
 
376
2193
        p->fcalls = calls;
377
 
#ifdef SHARED_HEAP
378
 
        ASSERT(p->active);
379
 
#endif
 
2194
        ASSERT(IS_ACTIVE(p));
 
2195
 
380
2196
        return p;
381
2197
    }
382
2198
 
384
2200
     * Schedule system-level activities.
385
2201
     */
386
2202
 do_sys_schedule:
 
2203
 
 
2204
#ifdef ERTS_SMP
 
2205
    schedulers_waiting_on_runq++;
 
2206
    erts_smp_activity_begin(ERTS_ACTIVITY_WAIT,
 
2207
                            prepare_for_block,
 
2208
                            resume_after_block,
 
2209
                            NULL);
 
2210
    erts_smp_cnd_wait(&schdlq_cnd, &schdlq_mtx);
 
2211
    ASSERT(schedulers_waiting_on_runq > 0);
 
2212
    erts_smp_activity_end(ERTS_ACTIVITY_WAIT,
 
2213
                          prepare_for_block,
 
2214
                          resume_after_block,
 
2215
                          NULL);
 
2216
    schedulers_waiting_on_runq--;
 
2217
#else
387
2218
    erl_sys_schedule(qmask);
 
2219
 
388
2220
    function_calls = 0;
389
 
    if (do_time) {
390
 
        bump_timer();
391
 
    }
 
2221
    dt = do_time_read_and_reset();
 
2222
    if (dt) bump_timer(dt);
 
2223
#endif
 
2224
 
392
2225
    goto pick_next_process;
393
2226
}
394
2227
 
395
 
/*
396
 
** Fix allocate a process
 
2228
 
 
2229
Uint erts_get_tot_proc_mem(void)
 
2230
{
 
2231
    return (Uint) erts_smp_atomic_read(&erts_tot_proc_mem);
 
2232
}
 
2233
 
 
2234
Uint
 
2235
erts_get_total_context_switches(void)
 
2236
{
 
2237
    Uint res;
 
2238
    erts_smp_mtx_lock(&schdlq_mtx);
 
2239
    res = context_switches;
 
2240
    erts_smp_mtx_unlock(&schdlq_mtx);
 
2241
    return res;
 
2242
}
 
2243
 
 
2244
void
 
2245
erts_get_total_reductions(Uint *redsp, Uint *diffp)
 
2246
{
 
2247
    Uint reds;
 
2248
    erts_smp_mtx_lock(&schdlq_mtx);
 
2249
    reds = reductions;
 
2250
    if (redsp)
 
2251
        *redsp = reds;
 
2252
    if (diffp)
 
2253
        *diffp = reds - last_reds;
 
2254
    last_reds = reds;
 
2255
    erts_smp_mtx_unlock(&schdlq_mtx);
 
2256
}
 
2257
 
 
2258
/*
 
2259
 * Current process might be exiting after call to
 
2260
 * erts_get_total_reductions().
 
2261
 */
 
2262
void
 
2263
erts_get_exact_total_reductions(Process *c_p, Uint *redsp, Uint *diffp)
 
2264
{
 
2265
    Uint reds = erts_current_reductions(c_p, c_p);
 
2266
    erts_smp_proc_unlock(c_p, ERTS_PROC_LOCK_MAIN);
 
2267
    /*
 
2268
     * Wait for other schedulers to schedule out their processes
 
2269
     * and update 'reductions'.
 
2270
     */
 
2271
    erts_smp_block_system(ERTS_ACTIVITY_IO); /*erts_smp_mtx_lock(&schdlq_mtx);*/
 
2272
    reds += reductions;
 
2273
    if (redsp)
 
2274
        *redsp = reds;
 
2275
    if (diffp)
 
2276
        *diffp = reds - last_exact_reds;
 
2277
    last_exact_reds = reds;
 
2278
    erts_smp_release_system(); /*erts_smp_mtx_unlock(&schdlq_mtx);*/
 
2279
    erts_smp_proc_lock(c_p, ERTS_PROC_LOCK_MAIN);
 
2280
}
 
2281
 
 
2282
/*
 
2283
 * erts_test_next_pid() is only used for testing.
 
2284
 */
 
2285
Sint
 
2286
erts_test_next_pid(int set, Uint next)
 
2287
{
 
2288
    Sint res;
 
2289
    Sint p_prev;
 
2290
 
 
2291
    erts_smp_mtx_lock(&proc_tab_mtx);
 
2292
 
 
2293
    if (!set) {
 
2294
        res = p_next < 0 ? -1 : (p_serial << p_serial_shift | p_next);
 
2295
    }
 
2296
    else {
 
2297
        erts_smp_proc_tab_lock();
 
2298
 
 
2299
        p_serial = (Sint) ((next >> p_serial_shift) & p_serial_mask);
 
2300
        p_next = (Sint) (erts_process_tab_index_mask & next);
 
2301
 
 
2302
        if (p_next >= erts_max_processes) {
 
2303
            p_next = 0;
 
2304
            p_serial++;
 
2305
            p_serial &= p_serial_mask;
 
2306
        }
 
2307
 
 
2308
        p_prev = p_next;
 
2309
 
 
2310
        do {
 
2311
            if (!process_tab[p_next])
 
2312
                break;
 
2313
            p_next++;
 
2314
            if(p_next >= erts_max_processes) {
 
2315
                p_next = 0;
 
2316
                p_serial++;
 
2317
                p_serial &= p_serial_mask;
 
2318
            }
 
2319
        } while (p_prev != p_next);
 
2320
 
 
2321
        res = process_tab[p_next] ? -1 : (p_serial << p_serial_shift | p_next);
 
2322
 
 
2323
        erts_smp_proc_tab_unlock();
 
2324
    }
 
2325
 
 
2326
    erts_smp_mtx_unlock(&proc_tab_mtx);
 
2327
 
 
2328
    return res;
 
2329
 
 
2330
}
 
2331
 
 
2332
Uint erts_process_count(void)
 
2333
{
 
2334
    long res = erts_smp_atomic_read(&process_count);
 
2335
    ASSERT(res >= 0);
 
2336
    return (Uint) res;
 
2337
}
 
2338
 
 
2339
/*
 
2340
** Allocate process and find out where to place next process.
397
2341
*/
398
2342
static Process*
399
2343
alloc_process(void)
400
2344
{
 
2345
    erts_smp_mtx_t *ptabix_mtxp;
401
2346
    Process* p;
402
2347
    int p_prev;
403
2348
 
404
 
    if (p_next == -1)
405
 
        return NULL;
 
2349
    erts_smp_mtx_lock(&proc_tab_mtx);
 
2350
 
 
2351
    if (p_next == -1) {
 
2352
        p = NULL;
 
2353
        goto error; /* Process table full! */
 
2354
    }
406
2355
 
407
2356
    p = (Process*) erts_alloc_fnf(ERTS_ALC_T_PROC, sizeof(Process));
408
2357
    if (!p)
409
 
        return NULL;
 
2358
        goto error; /* ENOMEM */ 
 
2359
 
 
2360
    p_last = p_next;
 
2361
 
 
2362
#ifdef ERTS_SMP
 
2363
    ptabix_mtxp = &erts_proc_locks[ERTS_PIX2LOCKIX(p_next)].mtx;
 
2364
#else
 
2365
    ptabix_mtxp = NULL;
 
2366
#endif
 
2367
 
 
2368
    erts_smp_mtx_lock(ptabix_mtxp);
 
2369
 
 
2370
    process_tab[p_next] = p;
 
2371
    erts_smp_atomic_inc(&process_count);
410
2372
    ERTS_PROC_MORE_MEM(sizeof(Process));
411
2373
    p->id = make_internal_pid(p_serial << p_serial_shift | p_next);
 
2374
    if (p->id == ERTS_INVALID_PID) {
 
2375
        /* Do not use the invalid pid; change serial */
 
2376
        p_serial++;
 
2377
        p_serial &= p_serial_mask;
 
2378
        p->id = make_internal_pid(p_serial << p_serial_shift | p_next);
 
2379
        ASSERT(p->id != ERTS_INVALID_PID);
 
2380
    }
 
2381
    ASSERT(internal_pid_serial(p->id) <= (erts_use_r9_pids_ports
 
2382
                                          ? ERTS_MAX_PID_R9_SERIAL
 
2383
                                          : ERTS_MAX_PID_SERIAL));
 
2384
 
 
2385
#ifdef ERTS_SMP
 
2386
    p->lock_flags = ERTS_PROC_LOCKS_ALL;
 
2387
#ifdef ERTS_ENABLE_LOCK_CHECK
 
2388
    erts_proc_lc_trylock(p, ERTS_PROC_LOCKS_ALL, 1);
 
2389
#endif
 
2390
#endif
 
2391
 
412
2392
    p->rstatus = P_FREE;
413
2393
    p->rcount = 0;
414
2394
 
415
 
    /* set p_next to the next available slot */
 
2395
 
 
2396
    erts_smp_mtx_unlock(ptabix_mtxp);
 
2397
 
 
2398
    /*
 
2399
     * set p_next to the next available slot
 
2400
     */
 
2401
 
416
2402
    p_prev = p_next;
417
2403
 
418
 
    p_next++;
419
 
    if(p_next >= erts_max_processes)
420
 
        p_next = 0;
421
 
 
422
 
    while(p_prev != p_next) {
423
 
        if (p_next == 0)
424
 
            p_serial = (p_serial+1) & p_serial_mask;
425
 
        if (process_tab[p_next] == NULL)
426
 
            /* found a free slot */
427
 
            return p;
 
2404
    while (1) {
428
2405
        p_next++;
429
 
        if(p_next >= erts_max_processes)
 
2406
        if(p_next >= erts_max_processes) {
 
2407
            p_serial++;
 
2408
            p_serial &= p_serial_mask;
430
2409
            p_next = 0;
 
2410
        }
 
2411
 
 
2412
        if (p_prev == p_next) {
 
2413
            p_next = -1;
 
2414
            break; /* Table full! */
 
2415
        }
 
2416
 
 
2417
        if (!process_tab[p_next])
 
2418
            break; /* found a free slot */
431
2419
    }
432
2420
 
433
 
    p_next = -1;
 
2421
 error:
 
2422
 
 
2423
    erts_smp_mtx_unlock(&proc_tab_mtx);
 
2424
 
434
2425
    return p;
 
2426
 
435
2427
}
436
2428
 
437
2429
Eterm
443
2435
{
444
2436
    Process *p;
445
2437
    Sint arity;                 /* Number of arguments. */
446
 
#ifndef SHARED_HEAP
 
2438
#ifndef HYBRID
447
2439
    Uint arg_size;              /* Size of arguments. */
 
2440
#endif
448
2441
    Uint sz;                    /* Needed words on heap. */
449
2442
    Uint heap_need;             /* Size needed on heap. */
 
2443
    ScheduleQ* sq;
 
2444
    Eterm res = THE_NON_VALUE;
 
2445
 
 
2446
#ifdef ERTS_SMP
 
2447
    erts_smp_proc_lock(parent, ERTS_PROC_LOCKS_ALL_MINOR);
450
2448
#endif
451
 
    ScheduleQ* sq;
452
2449
 
 
2450
#ifdef HYBRID
 
2451
    /*
 
2452
     * Copy the arguments to the global heap
 
2453
     * Since global GC might occur we want to do this before adding the
 
2454
     * new process to the process_tab.
 
2455
     */
 
2456
    BM_SWAP_TIMER(system,copy);
 
2457
    LAZY_COPY(parent,args);
 
2458
    BM_SWAP_TIMER(copy,system);
 
2459
    heap_need = 0;
 
2460
#endif /* HYBRID */
453
2461
    /*
454
2462
     * Check for errors.
455
2463
     */
456
2464
 
457
2465
    if (is_not_atom(mod) || is_not_atom(func) || ((arity = list_length(args)) < 0)) {
458
2466
        so->error_code = BADARG;
459
 
        return THE_NON_VALUE;
 
2467
        goto error;
460
2468
    }
461
 
    if ((p = alloc_process()) == NULL) {
462
 
        cerr_pos = 0;
463
 
        erl_printf(CBUF, "Too many processes\n");
464
 
        send_error_to_logger(parent->group_leader);
 
2469
    p = alloc_process(); /* All proc locks are locked by this thread
 
2470
                            on success */
 
2471
    if (!p) {
 
2472
        erts_send_error_to_logger_str(parent->group_leader,
 
2473
                                      "Too many processes\n");
465
2474
        so->error_code = SYSTEM_LIMIT;
466
 
        return THE_NON_VALUE;
 
2475
        goto error;
467
2476
    }
468
2477
 
469
2478
    processes_busy++;
470
2479
    BM_COUNT(processes_spawned);
471
2480
 
472
 
#ifndef SHARED_HEAP
 
2481
#ifndef HYBRID
473
2482
    BM_SWAP_TIMER(system,size);
474
2483
    arg_size = size_object(args);
475
2484
    BM_SWAP_TIMER(size,system);
478
2487
 
479
2488
    p->flags = erts_default_process_flags;
480
2489
 
 
2490
    /* Scheduler queue mutex should be locked when changeing
 
2491
     * prio. In this case we don't have to lock it, since
 
2492
     * noone except us has access to the process.
 
2493
     */
481
2494
    if (so->flags & SPO_USE_ARGS) {
482
2495
        p->min_heap_size = so->min_heap_size;
483
2496
        p->prio = so->priority;
484
 
#ifndef SHARED_HEAP
485
2497
        p->max_gen_gcs = so->max_gen_gcs;
486
 
#endif
487
2498
    } else {
488
2499
        p->min_heap_size = H_MIN_SIZE;
489
2500
        p->prio = PRIORITY_NORMAL;
490
 
#ifndef SHARED_HEAP
491
 
        p->max_gen_gcs = erts_max_gen_gcs;
492
 
#endif
 
2501
        p->max_gen_gcs = (Uint16) erts_smp_atomic_read(&erts_max_gen_gcs);
493
2502
    }
 
2503
    p->skipped = 0;
494
2504
    ASSERT(p->min_heap_size == erts_next_heap_size(p->min_heap_size, 0));
495
2505
    
496
2506
    p->initial[INITIAL_MOD] = mod;
497
2507
    p->initial[INITIAL_FUN] = func;
498
2508
    p->initial[INITIAL_ARI] = (Uint) arity;
499
2509
 
500
 
#ifndef SHARED_HEAP
501
2510
    /*
502
2511
     * Must initialize binary lists here before copying binaries to process.
503
2512
     */
504
2513
    p->off_heap.mso = NULL;
 
2514
#ifndef HYBRID /* FIND ME! */
505
2515
    p->off_heap.funs = NULL;
 
2516
#endif
506
2517
    p->off_heap.externals = NULL;
507
2518
    p->off_heap.overhead = 0;
508
2519
 
514
2525
    } else {
515
2526
        sz = erts_next_heap_size(heap_need, 0);
516
2527
    }
517
 
    p->arith_lowest_htop = (Eterm *) 0;
518
 
#endif
519
 
 
520
2528
 
521
2529
#ifdef HIPE
522
2530
    hipe_init_process(&p->hipe);
 
2531
#ifdef ERTS_SMP
 
2532
    hipe_init_process_smp(&p->hipe_smp);
 
2533
#endif
523
2534
#endif
524
2535
 
525
 
#ifdef SHARED_HEAP
526
 
    p->send = (Eterm *) ERTS_STACK_ALLOC(sizeof(Eterm) * S_DEFAULT_SIZE);
527
 
    p->stop = p->stack = p->send + S_DEFAULT_SIZE;
528
 
    p->stack_sz = S_DEFAULT_SIZE;
529
 
    p->htop = NULL;
530
 
    p->hend = NULL;
531
 
    p->heap = NULL;
532
 
    p->heap_sz = 0;
533
 
#else
534
2536
    p->heap = (Eterm *) ERTS_HEAP_ALLOC(ERTS_ALC_T_HEAP, sizeof(Eterm)*sz);
535
2537
    p->old_hend = p->old_htop = p->old_heap = NULL;
536
2538
    p->high_water = p->heap;
 
2539
#ifdef INCREMENTAL
 
2540
    p->scan_top = p->high_water;
 
2541
#endif
537
2542
    p->gen_gcs = 0;
538
2543
    p->stop = p->hend = p->heap + sz;
539
2544
    p->htop = p->heap;
540
2545
    p->heap_sz = sz;
 
2546
#if !defined(HEAP_FRAG_ELIM_TEST)
541
2547
    p->arith_avail = 0;         /* No arithmetic heap. */
542
2548
    p->arith_heap = NULL;
543
2549
#ifdef DEBUG
544
2550
    p->arith_check_me = NULL;
545
2551
#endif
546
2552
#endif
547
 
    p->saved_htop = NULL;
548
 
    p->fvalue = NIL;
549
2553
    p->catches = 0;
550
2554
 
551
2555
    /* No need to initialize p->fcalls. */
562
2566
    BM_STOP_TIMER(system);
563
2567
    BM_MESSAGE(args,p,parent);
564
2568
    BM_START_TIMER(system);
565
 
#ifdef SHARED_HEAP
 
2569
#ifdef HYBRID
566
2570
    p->arg_reg[2] = args;
 
2571
#ifdef INCREMENTAL
 
2572
    p->active = 0;
 
2573
    if (ptr_val(args) >= inc_fromspc && ptr_val(args) < inc_fromend)
 
2574
        INC_ACTIVATE(p);
 
2575
#endif
567
2576
#else
568
2577
    BM_SWAP_TIMER(system,copy);
569
2578
    p->arg_reg[2] = copy_struct(args, arg_size, &p->htop, &p->off_heap);
572
2581
#endif
573
2582
    p->arity = 3;
574
2583
 
575
 
    p->freason = 0;
 
2584
    p->fvalue = NIL;
 
2585
    p->freason = EXC_NULL;
 
2586
    p->ftrace = NIL;
576
2587
    p->reds = 0;
 
2588
 
 
2589
#ifdef ERTS_SMP
 
2590
    p->ptimer = NULL;
 
2591
#else
577
2592
    sys_memset(&p->tm, 0, sizeof(ErlTimer));
 
2593
#endif
578
2594
 
579
2595
    p->reg = NULL;
580
2596
    p->dist_entry = NULL;
581
2597
    p->error_handler = am_error_handler;    /* default */
582
 
    p->links = NULL;
 
2598
    p->nlinks = NULL;
 
2599
    p->monitors = NULL;
583
2600
    p->ct = NULL;
584
2601
 
585
 
#ifdef SHARED_HEAP
586
 
    p->group_leader = parent->group_leader;
587
 
#else
588
 
    /* Needs to be done after the heap has been set up */
589
 
    p->group_leader =
590
 
        IS_CONST(parent->group_leader)
591
 
        ? parent->group_leader
592
 
        : STORE_NC(&p->htop, &p->off_heap.externals, parent->group_leader);
593
 
#endif
594
 
    ASSERT(IS_CONST(erts_default_tracer));
595
 
    p->tracer_proc = erts_default_tracer;
 
2602
    ASSERT(is_pid(parent->group_leader));
 
2603
 
 
2604
    if (parent->group_leader == ERTS_INVALID_PID)
 
2605
        p->group_leader = p->id;
 
2606
    else {
 
2607
        /* Needs to be done after the heap has been set up */
 
2608
        p->group_leader =
 
2609
            IS_CONST(parent->group_leader)
 
2610
            ? parent->group_leader
 
2611
            : STORE_NC(&p->htop, &p->off_heap.externals, parent->group_leader);
 
2612
    }
 
2613
 
 
2614
    erts_get_default_tracing(&p->trace_flags, &p->tracer_proc);
596
2615
 
597
2616
    p->msg.first = NULL;
598
2617
    p->msg.last = &p->msg.first;
599
2618
    p->msg.save = &p->msg.first;
600
2619
    p->msg.len = 0;
601
 
#ifndef SHARED_HEAP
 
2620
#ifdef ERTS_SMP
 
2621
    p->msg_inq.first = NULL;
 
2622
    p->msg_inq.last = &p->msg_inq.first;
 
2623
    p->msg_inq.len = 0;
 
2624
#endif
 
2625
    p->bif_timers = NULL;
602
2626
    p->mbuf = NULL;
603
 
    p->halloc_mbuf = NULL;
604
2627
    p->mbuf_sz = 0;
605
 
#endif
606
2628
    p->dictionary = NULL;
607
2629
    p->debug_dictionary = NULL;
608
2630
    p->seq_trace_lastcnt = 0;
609
2631
    p->seq_trace_clock = 0;
610
2632
    SEQ_TRACE_TOKEN(p) = NIL;
611
 
#ifdef HEAP_FRAG_ELIM_TEST
612
 
    p->ssb = NULL;
613
 
#endif
614
 
    p->parent = parent->id;
 
2633
    p->parent = parent->id == ERTS_INVALID_PID ? NIL : parent->id;
615
2634
    p->started = erts_get_time();
616
2635
 
617
 
    process_tab[internal_pid_index(p->id)] = p;
 
2636
#ifdef HYBRID
 
2637
    p->rrma  = NULL;
 
2638
    p->rrsrc = NULL;
 
2639
    p->nrr   = 0;
 
2640
    p->rrsz  = 0;
 
2641
#endif
 
2642
 
 
2643
    INIT_HOLE_CHECK(p);
618
2644
 
619
2645
    if (IS_TRACED(parent)) {
620
 
        if (parent->flags & F_TRACE_SOS) {
621
 
            p->flags |= (parent->flags & TRACE_FLAGS);
 
2646
        if (parent->trace_flags & F_TRACE_SOS) {
 
2647
            p->trace_flags |= (parent->trace_flags & TRACEE_FLAGS);
622
2648
            p->tracer_proc = parent->tracer_proc;
623
2649
        }
624
 
        if (parent->flags & F_TRACE_PROCS) 
 
2650
        if (parent->trace_flags & F_TRACE_PROCS) 
625
2651
            trace_proc_spawn(parent, p->id, mod, func, args);
626
 
        if (parent->flags & F_TRACE_SOS1) { /* Overrides TRACE_CHILDREN */
627
 
            p->flags |= (parent->flags & TRACE_FLAGS);
 
2652
        if (parent->trace_flags & F_TRACE_SOS1) { /* Overrides TRACE_CHILDREN */
 
2653
            p->trace_flags |= (parent->trace_flags & TRACEE_FLAGS);
628
2654
            p->tracer_proc = parent->tracer_proc;
629
 
            p->flags &= ~(F_TRACE_SOS1 | F_TRACE_SOS);
630
 
            parent->flags &= ~(F_TRACE_SOS1 | F_TRACE_SOS);
 
2655
            p->trace_flags &= ~(F_TRACE_SOS1 | F_TRACE_SOS);
 
2656
            parent->trace_flags &= ~(F_TRACE_SOS1 | F_TRACE_SOS);
631
2657
        }
632
2658
    }
633
2659
 
636
2662
     */
637
2663
 
638
2664
    if (so->flags & SPO_LINK) {
639
 
        if (IS_TRACED(parent) && (parent->flags & F_TRACE_PROCS) != 0) {
 
2665
#ifdef DEBUG
 
2666
        int ret;
 
2667
#endif
 
2668
        if (IS_TRACED(parent) && (parent->trace_flags & F_TRACE_PROCS) != 0) {
640
2669
            trace_proc(parent, parent, am_link, p->id);
641
2670
        }
642
 
        parent->links = new_link(parent->links, LNK_LINK, p->id, NIL);
643
 
        p->links = new_link(p->links, LNK_LINK, parent->id, NIL);
 
2671
 
 
2672
#ifdef DEBUG
 
2673
        ret = erts_add_link(&(parent->nlinks),  LINK_PID, p->id);
 
2674
        ASSERT(ret == 0);
 
2675
        ret = erts_add_link(&(p->nlinks), LINK_PID, parent->id);
 
2676
        ASSERT(ret == 0);
 
2677
#else   
 
2678
        erts_add_link(&(parent->nlinks), LINK_PID, p->id);
 
2679
        erts_add_link(&(p->nlinks), LINK_PID, parent->id);
 
2680
#endif
 
2681
 
644
2682
        if (IS_TRACED(parent)) {
645
 
            if (parent->flags & F_TRACE_SOL)  {
646
 
                p->flags |= (parent->flags & TRACE_FLAGS);
 
2683
            if (parent->trace_flags & (F_TRACE_SOL|F_TRACE_SOL1))  {
 
2684
                p->trace_flags |= (parent->trace_flags & TRACEE_FLAGS);
647
2685
                p->tracer_proc = parent->tracer_proc;    /* maybe steal */
648
 
            }
649
 
            if (parent->flags & F_TRACE_SOL1)  { /* maybe override */
650
 
                p->flags |= (parent->flags & TRACE_FLAGS);
651
 
                p->tracer_proc = parent->tracer_proc;   
652
 
                p ->flags &= ~(F_TRACE_SOL1 | F_TRACE_SOL);
653
 
                parent->flags &= ~(F_TRACE_SOL1 | F_TRACE_SOL);
 
2686
 
 
2687
                if (parent->trace_flags & F_TRACE_SOL1)  { /* maybe override */
 
2688
                    p ->trace_flags &= ~(F_TRACE_SOL1 | F_TRACE_SOL);
 
2689
                    parent->trace_flags &= ~(F_TRACE_SOL1 | F_TRACE_SOL);
 
2690
                }
654
2691
            }
655
2692
        }
656
2693
    }
657
2694
 
658
 
#ifdef SHARED_HEAP
 
2695
    /*
 
2696
     * Test whether this process should be initially monitored by its parent.
 
2697
     */
 
2698
    if (so->flags & SPO_MONITOR) {
 
2699
        Eterm mref;
 
2700
 
 
2701
        mref = erts_make_ref(parent);
 
2702
        erts_add_monitor(&(parent->monitors), MON_ORIGIN, mref, p->id, NIL);
 
2703
        erts_add_monitor(&(p->monitors), MON_TARGET, mref, parent->id, NIL);
 
2704
        so->mref = mref;
 
2705
    }
 
2706
 
 
2707
#ifdef HYBRID
659
2708
    /*
660
2709
     * Add process to the array of active processes.
661
2710
     */
662
 
    p->active = 1;
663
 
    erts_active_procs[erts_num_active_procs++] = p;
 
2711
    ACTIVATE(p);
 
2712
    p->active_index = erts_num_active_procs++;
 
2713
    erts_active_procs[p->active_index] = p;
664
2714
#endif
665
2715
 
666
2716
    /*
667
2717
     * Schedule process for execution.
668
2718
     */
669
 
    sq = &queue[p->prio];
 
2719
 
 
2720
    erts_smp_mtx_lock(&schdlq_mtx);
 
2721
 
670
2722
    qmask |= (1 << p->prio);
 
2723
 
 
2724
    switch (p->prio) {
 
2725
    case PRIORITY_LOW:
 
2726
      queued_low++;
 
2727
      sq = &queue[PRIORITY_NORMAL];
 
2728
      break;
 
2729
    case PRIORITY_NORMAL:
 
2730
      queued_normal++;
 
2731
    default:
 
2732
      sq = &queue[p->prio];      
 
2733
    }
 
2734
 
 
2735
    runq_len++;
 
2736
 
671
2737
    p->next = NULL;
672
 
    if (sq->first == (Process *) 0)
 
2738
    if (!sq->first)
673
2739
        sq->first = p;
674
2740
    else
675
2741
        sq->last->next = p;
676
2742
    sq->last = p;
 
2743
 
677
2744
    p->status = P_RUNABLE;
678
 
    return p->id;
 
2745
 
 
2746
#ifdef ERTS_SMP
 
2747
    p->scheduler_data = NULL;
 
2748
    p->is_exiting = 0;
 
2749
    p->status_flags = ERTS_PROC_SFLG_INRUNQ;
 
2750
    p->scheduler_flags = 0;
 
2751
    p->suspendee = NIL;
 
2752
    p->pending_suspenders = NULL;
 
2753
    p->pending_exit.reason = THE_NON_VALUE;
 
2754
    p->pending_exit.bp = NULL;
 
2755
#endif
 
2756
 
 
2757
#if !defined(NO_FPE_SIGNALS)
 
2758
    p->fp_exception = 0;
 
2759
#endif
 
2760
 
 
2761
    erts_smp_cnd_signal(&schdlq_cnd);
 
2762
    erts_smp_mtx_unlock(&schdlq_mtx);
 
2763
 
 
2764
    res = p->id;
 
2765
    erts_smp_proc_unlock(p, ERTS_PROC_LOCKS_ALL);
 
2766
 
 
2767
    VERBOSE(DEBUG_PROCESSES, ("Created a new process: %T\n",p->id));
 
2768
 
 
2769
 error:
 
2770
 
 
2771
    erts_smp_proc_unlock(parent, ERTS_PROC_LOCKS_ALL_MINOR);
 
2772
 
 
2773
    return res;
679
2774
}
680
2775
 
681
2776
/*
689
2784
    p->stop = NULL;
690
2785
    p->hend = NULL;
691
2786
    p->heap = NULL;
692
 
#ifdef SHARED_HEAP
693
 
    p->stack = NULL;
694
 
    p->send  = NULL;
695
 
    p->stack_sz = 0;
696
 
#else
697
 
    p->arith_lowest_htop = (Eterm *) 0;
698
2787
    p->gen_gcs = 0;
699
2788
    p->max_gen_gcs = 0;
700
 
    p->saved_htop = NULL;
701
 
#endif
702
2789
    p->min_heap_size = 0;
703
2790
    p->status = P_RUNABLE;
704
2791
    p->rstatus = P_RUNABLE;
705
2792
    p->rcount = 0;
706
 
    p->id = NIL;
 
2793
    p->id = ERTS_INVALID_PID;
707
2794
    p->prio = PRIORITY_NORMAL;
708
2795
    p->reds = 0;
709
2796
    p->error_handler = am_error_handler;
710
2797
    p->tracer_proc = NIL;
711
 
    p->group_leader = NIL;
 
2798
    p->trace_flags = 0;
 
2799
    p->group_leader = ERTS_INVALID_PID;
712
2800
    p->flags = 0;
713
2801
    p->fvalue = NIL;
714
 
    p->freason = 0;
 
2802
    p->freason = EXC_NULL;
 
2803
    p->ftrace = NIL;
715
2804
    p->fcalls = 0;
716
2805
    p->dist_entry = NULL;
 
2806
#ifdef ERTS_SMP
 
2807
    p->ptimer = NULL;
 
2808
#else
717
2809
    memset(&(p->tm), 0, sizeof(ErlTimer));
 
2810
#endif
718
2811
    p->next = NULL;
719
 
#ifndef SHARED_HEAP
720
2812
    p->off_heap.mso = NULL;
 
2813
#ifndef HYBRID /* FIND ME! */
721
2814
    p->off_heap.funs = NULL;
 
2815
#endif
722
2816
    p->off_heap.externals = NULL;
723
2817
    p->off_heap.overhead = 0;
724
 
#endif
725
2818
    p->reg = NULL;
726
2819
    p->heap_sz = 0;
727
 
#ifndef SHARED_HEAP
728
2820
    p->high_water = NULL;
 
2821
#ifdef INCREMENTAL
 
2822
    p->scan_top = NULL;
 
2823
#endif
729
2824
    p->old_hend = NULL;
730
2825
    p->old_htop = NULL;
731
2826
    p->old_heap = NULL;
732
2827
    p->mbuf = NULL;
733
 
    p->halloc_mbuf = NULL;
734
2828
    p->mbuf_sz = 0;
735
 
#endif
736
 
    p->links = NULL;         /* List of links */
 
2829
    p->monitors = NULL;
 
2830
    p->nlinks = NULL;         /* List of links */
737
2831
    p->msg.first = NULL;
738
2832
    p->msg.last = &p->msg.first;
739
2833
    p->msg.save = &p->msg.first;
740
2834
    p->msg.len = 0;
 
2835
    p->bif_timers = NULL;
741
2836
    p->dictionary = NULL;
742
2837
    p->debug_dictionary = NULL;
743
2838
    p->ct = NULL;
755
2850
    /*
756
2851
     * Secondary heap for arithmetic operations.
757
2852
     */
758
 
#ifndef SHARED_HEAP
 
2853
#if !defined(HEAP_FRAG_ELIM_TEST)
759
2854
    p->arith_heap = NULL;
760
2855
    p->arith_avail = 0;
761
2856
#ifdef DEBUG
775
2870
    p->def_arg_reg[3] = 0;
776
2871
    p->def_arg_reg[4] = 0;
777
2872
    p->def_arg_reg[5] = 0;
778
 
#ifdef HEAP_FRAG_ELIM_TEST
779
 
    p->ssb = NULL;
780
 
#endif
781
2873
 
782
2874
    p->parent = NIL;
783
2875
    p->started = 0;
784
2876
 
785
2877
#ifdef HIPE
786
2878
    hipe_init_process(&p->hipe);
787
 
#endif
 
2879
#ifdef ERTS_SMP
 
2880
    hipe_init_process_smp(&p->hipe_smp);
 
2881
#endif
 
2882
#endif
 
2883
 
 
2884
    ACTIVATE(p);
 
2885
 
 
2886
#ifdef HYBRID
 
2887
    p->rrma  = NULL;
 
2888
    p->rrsrc = NULL;
 
2889
    p->nrr   = 0;
 
2890
    p->rrsz  = 0;
 
2891
#endif
 
2892
    INIT_HOLE_CHECK(p);
 
2893
 
 
2894
#ifdef ERTS_SMP
 
2895
    p->scheduler_data = NULL;
 
2896
    p->is_exiting = 0;
 
2897
    p->status_flags = 0;
 
2898
    p->scheduler_flags = 0;
 
2899
    p->lock_flags = 0;
 
2900
    p->msg_inq.first = NULL;
 
2901
    p->msg_inq.last = &p->msg_inq.first;
 
2902
    p->msg_inq.len = 0;
 
2903
    p->suspendee = NIL;
 
2904
    p->pending_suspenders = NULL;
 
2905
    p->pending_exit.reason = THE_NON_VALUE;
 
2906
    p->pending_exit.bp = NULL;
 
2907
#endif
 
2908
 
 
2909
#if !defined(NO_FPE_SIGNALS)
 
2910
    p->fp_exception = 0;
 
2911
#endif
 
2912
 
788
2913
}    
789
2914
 
 
2915
#ifdef DEBUG
 
2916
 
 
2917
void
 
2918
erts_debug_verify_clean_empty_process(Process* p)
 
2919
{
 
2920
    /* Things that erts_cleanup_empty_process() will *not* cleanup... */
 
2921
    ASSERT(p->htop == NULL);
 
2922
    ASSERT(p->stop == NULL);
 
2923
    ASSERT(p->hend == NULL);
 
2924
    ASSERT(p->heap == NULL);
 
2925
    ASSERT(p->id == ERTS_INVALID_PID);
 
2926
    ASSERT(p->tracer_proc == NIL);
 
2927
    ASSERT(p->trace_flags == 0);
 
2928
    ASSERT(p->group_leader == ERTS_INVALID_PID);
 
2929
    ASSERT(p->dist_entry == NULL);
 
2930
    ASSERT(p->next == NULL);
 
2931
    ASSERT(p->reg == NULL);
 
2932
    ASSERT(p->heap_sz == 0);
 
2933
    ASSERT(p->high_water == NULL);
 
2934
#ifdef INCREMENTAL
 
2935
    ASSERT(p->scan_top == NULL);
 
2936
#endif
 
2937
    ASSERT(p->old_hend == NULL);
 
2938
    ASSERT(p->old_htop == NULL);
 
2939
    ASSERT(p->old_heap == NULL);
 
2940
 
 
2941
    ASSERT(p->monitors == NULL);
 
2942
    ASSERT(p->nlinks == NULL);
 
2943
    ASSERT(p->msg.first == NULL);
 
2944
    ASSERT(p->msg.len == 0);
 
2945
    ASSERT(p->bif_timers == NULL);
 
2946
    ASSERT(p->dictionary == NULL);
 
2947
    ASSERT(p->debug_dictionary == NULL);
 
2948
    ASSERT(p->ct == NULL);
 
2949
    ASSERT(p->catches == 0);
 
2950
    ASSERT(p->cp == NULL);
 
2951
    ASSERT(p->i == NULL);
 
2952
    ASSERT(p->current == NULL);
 
2953
 
 
2954
    ASSERT(p->parent == NIL);
 
2955
 
 
2956
#ifdef ERTS_SMP
 
2957
    ASSERT(p->msg_inq.first == NULL);
 
2958
    ASSERT(p->msg_inq.len == 0);
 
2959
    ASSERT(p->suspendee == NIL);
 
2960
    ASSERT(p->pending_suspenders == NULL);
 
2961
    ASSERT(p->pending_exit.reason == THE_NON_VALUE);
 
2962
    ASSERT(p->pending_exit.bp == NULL);
 
2963
#endif
 
2964
 
 
2965
    /* Thing that erts_cleanup_empty_process() cleans up */
 
2966
 
 
2967
    ASSERT(p->off_heap.mso == NULL);
 
2968
#ifndef HYBRID /* FIND ME! */
 
2969
    ASSERT(p->off_heap.funs == NULL);
 
2970
#endif
 
2971
    ASSERT(p->off_heap.externals == NULL);
 
2972
    ASSERT(p->off_heap.overhead == 0);
 
2973
 
 
2974
#if !defined(HEAP_FRAG_ELIM_TEST)
 
2975
    ASSERT(p->arith_avail == 0);
 
2976
    ASSERT(p->arith_heap == NULL);
 
2977
#ifdef DEBUG
 
2978
    ASSERT(p->arith_check_me == NULL);
 
2979
#endif
 
2980
#endif
 
2981
    ASSERT(p->mbuf == NULL);
 
2982
}
 
2983
 
 
2984
#endif
 
2985
 
790
2986
void
791
2987
erts_cleanup_empty_process(Process* p)
792
2988
{
793
 
#ifdef SHARED_HEAP
794
 
    ;
795
 
#else
796
 
    ErlHeapFragment* ptr = p->mbuf;
 
2989
    ErlHeapFragment* mbufp;
 
2990
 
 
2991
    /* We only check fields that are known to be used... */
797
2992
 
798
2993
    erts_cleanup_offheap(&p->off_heap);
799
 
    while (ptr) {
800
 
        ErlHeapFragment*next = ptr->next;
801
 
        free_message_buffer(ptr);
802
 
        ptr = next;
 
2994
    p->off_heap.mso = NULL;
 
2995
#ifndef HYBRID /* FIND ME! */
 
2996
    p->off_heap.funs = NULL;
 
2997
#endif
 
2998
    p->off_heap.externals = NULL;
 
2999
    p->off_heap.overhead = 0;
 
3000
 
 
3001
#if !defined(HEAP_FRAG_ELIM_TEST)
 
3002
    p->arith_avail = 0;
 
3003
    p->arith_heap = NULL;
 
3004
#ifdef DEBUG
 
3005
    p->arith_check_me = NULL;
 
3006
#endif
 
3007
#endif
 
3008
 
 
3009
    mbufp = p->mbuf;
 
3010
    while (mbufp) {
 
3011
        ErlHeapFragment *next = mbufp->next;
 
3012
        free_message_buffer(mbufp);
 
3013
        mbufp = next;
803
3014
    }
 
3015
    p->mbuf = NULL;
 
3016
 
 
3017
#ifdef DEBUG
 
3018
    erts_debug_verify_clean_empty_process(p);
804
3019
#endif
805
3020
}
806
3021
 
 
3022
/*
 
3023
 * p must be the currently executing process.
 
3024
 */
807
3025
static void
808
 
delete_process0(Process* p, int do_delete)
 
3026
delete_process(Process* p)
809
3027
{
810
 
    ErlLink* lnk;
811
3028
    ErlMessage* mp;
812
 
#ifndef SHARED_HEAP
813
3029
    ErlHeapFragment* bp;
814
 
#endif
815
 
    int i;
816
 
 
817
 
#ifndef SHARED_HEAP
 
3030
 
 
3031
    VERBOSE(DEBUG_PROCESSES, ("Removing process: %T\n",p->id));
 
3032
 
818
3033
    /* Clean binaries and funs */
819
3034
    erts_cleanup_offheap(&p->off_heap);
820
3035
 
823
3038
     * we'll notice.
824
3039
     */
825
3040
    p->off_heap.mso = (void *) 0x8DEFFACD;
826
 
#endif
827
 
    
 
3041
 
828
3042
    if (p->arg_reg != p->def_arg_reg) {
829
3043
        ERTS_PROC_LESS_MEM(p->max_arg_reg * sizeof(p->arg_reg[0]));
830
3044
        erts_free(ERTS_ALC_T_ARG_REG, p->arg_reg);
834
3048
     * Release heaps. Clobber contents in DEBUG build.
835
3049
     */
836
3050
 
837
 
#ifdef SHARED_HEAP
838
 
#ifdef DEBUG
839
 
    sys_memset(p->send, 0xfb, p->stack_sz*sizeof(Eterm));
840
 
#endif
841
 
#ifdef HIPE
842
 
    hipe_delete_process(&p->hipe);
843
 
#endif
844
 
    ERTS_STACK_FREE((void*) p->send, p->stack_sz * sizeof(Eterm));
845
 
#else /* not SHARED_HEAP */
846
 
#ifdef DEBUG
847
 
    sys_memset(p->heap, 0xfb, p->heap_sz*sizeof(Eterm));
848
 
#endif
849
 
#ifdef HIPE
850
 
    hipe_delete_process(&p->hipe);
851
 
#endif
 
3051
 
 
3052
#ifdef DEBUG
 
3053
    sys_memset(p->heap, DEBUG_BAD_BYTE, p->heap_sz*sizeof(Eterm));
 
3054
#endif
 
3055
 
 
3056
#ifdef HIPE
 
3057
    hipe_delete_process(&p->hipe);
 
3058
#endif
 
3059
 
852
3060
    ERTS_HEAP_FREE(ERTS_ALC_T_HEAP, (void*) p->heap, p->heap_sz*sizeof(Eterm));
853
3061
    if (p->old_heap != NULL) {
 
3062
 
854
3063
#ifdef DEBUG
855
 
        sys_memset(p->old_heap, 0xfb, (p->old_hend-p->old_heap)*sizeof(Eterm));
 
3064
        sys_memset(p->old_heap, DEBUG_BAD_BYTE,
 
3065
                   (p->old_hend-p->old_heap)*sizeof(Eterm));
856
3066
#endif
857
3067
        ERTS_HEAP_FREE(ERTS_ALC_T_OLD_HEAP,
858
3068
                       p->old_heap,
859
3069
                       (p->old_hend-p->old_heap)*sizeof(Eterm));
860
3070
    }
861
3071
 
862
 
#ifdef HEAP_FRAG_ELIM_TEST
863
 
    if (p->ssb) {
864
 
        erts_free(ERTS_ALC_T_SSB, p->ssb);
865
 
    }
866
 
#ifdef DEBUG
867
 
    p->ssb = (void *) 0x7DEFFACD;
868
 
#endif
869
 
#endif
870
 
 
871
3072
    /*
872
3073
     * Free all pending message buffers.
873
3074
     */
877
3078
        free_message_buffer(bp);
878
3079
        bp = next_bp;
879
3080
    }
880
 
#endif /* SHARED_HEAP */
881
3081
 
882
3082
    erts_erase_dicts(p);
883
3083
 
885
3085
    mp = p->msg.first;
886
3086
    while(mp != NULL) {
887
3087
        ErlMessage* next_mp = mp->next;
 
3088
#ifdef ERTS_SMP
 
3089
        if (mp->bp)
 
3090
            free_message_buffer(mp->bp);
 
3091
#endif
888
3092
        free_message(mp);
889
3093
        mp = next_mp;
890
3094
    }
891
3095
 
892
 
    /* free all links */
893
 
    lnk = p->links;
894
 
    while(lnk != NULL) {
895
 
        ErlLink* next_link = lnk->next;
896
 
        del_link(&lnk);
897
 
        lnk = next_link;
898
 
    }
 
3096
    ASSERT(!p->monitors);
 
3097
    ASSERT(!p->nlinks);
899
3098
 
900
3099
    if (p->ct != NULL) {
901
3100
        ERTS_PROC_LESS_MEM((sizeof(struct saved_calls)
903
3102
        erts_free(ERTS_ALC_T_CALLS_BUF, (void *) p->ct);
904
3103
    }
905
3104
 
906
 
    if (p->flags & F_USING_DB)
907
 
        db_proc_dead(p->id);
908
 
 
909
 
    ASSERT(internal_pid_index(p->id) < erts_max_processes);
910
 
    i = internal_pid_index(p->id);
911
 
 
912
 
    process_tab[i] = NULL;
913
 
    if (p_next == -1)
914
 
        p_next = i;
915
 
 
916
3105
    if(p->dist_entry) {
917
 
        DEREF_DIST_ENTRY(p->dist_entry);
 
3106
        erts_deref_dist_entry(p->dist_entry);
918
3107
        p->dist_entry = NULL;
919
3108
    }
920
3109
 
921
3110
    p->fvalue = NIL;
922
3111
    
923
 
#ifdef SHARED_HEAP
924
 
    for (i = 0; i < erts_num_active_procs; i++) {
925
 
        if (erts_active_procs[i] == p) {
926
 
            erts_active_procs[i] = erts_active_procs[--erts_num_active_procs];
927
 
            break;
928
 
        }
929
 
    }
930
 
#endif
931
 
 
932
 
    /*
933
 
     * Don't free it here, just mark it.
934
 
     */
935
 
    if (do_delete) {
936
 
        ERTS_PROC_LESS_MEM(sizeof(Process));
937
 
        erts_free(ERTS_ALC_T_PROC, (void *) p);
938
 
    } else {
939
 
        p->status = P_FREE;
940
 
    }
941
 
    processes_busy--;
942
 
}
943
 
 
944
 
/*
945
 
 * p must be the currently executing process.
946
 
 */
947
 
static void
948
 
delete_process(Process* p)
949
 
{
950
 
   if (p->reg != NULL)
951
 
      unregister_name(p, p->reg->name);
952
 
 
953
 
   cancel_timer(p);             /* Always cancel timer just in case */
954
 
   delete_process0(p, 0);
955
 
}
956
 
 
957
 
void
958
 
schedule_exit(Process *p, Eterm reason)
959
 
{
960
 
    Eterm copy;
961
 
    Uint32 status = p->status;
962
 
 
963
 
    /*
964
 
     * If this is the currently running process, we'll only change its
965
 
     * status to P_EXITING, and do nothing more.  It's the responsibility
966
 
     * of the caller to make the current process exit.
967
 
     */
 
3112
#ifdef HYBRID
 
3113
    erts_active_procs[p->active_index] =
 
3114
        erts_active_procs[--erts_num_active_procs];
 
3115
    erts_active_procs[p->active_index]->active_index = p->active_index;
 
3116
#ifdef INCREMENTAL
 
3117
    if (INC_IS_ACTIVE(p))
 
3118
         INC_DEACTIVATE(p);
 
3119
#endif
 
3120
 
 
3121
    if (p->rrma != NULL) {
 
3122
        erts_free(ERTS_ALC_T_ROOTSET,p->rrma);
 
3123
        erts_free(ERTS_ALC_T_ROOTSET,p->rrsrc);
 
3124
        ERTS_PROC_LESS_MEM(sizeof(Eterm) * p->rrsz * 2);
 
3125
    }
 
3126
#endif
 
3127
 
 
3128
}
 
3129
 
 
3130
static ERTS_INLINE void
 
3131
set_proc_exiting(Process *p, Eterm reason, ErlHeapFragment *bp)
 
3132
{
 
3133
    ERTS_SMP_LC_ASSERT(erts_proc_lc_my_proc_locks(p) == ERTS_PROC_LOCKS_ALL);
 
3134
    /*
 
3135
     * You are required to have all locks when going to status P_EXITING,
 
3136
     * This makes it is enough to take any lock when looking up a process
 
3137
     * (pid2proc()) to prevent the looked up process from exiting until
 
3138
     * the lock has been released.
 
3139
     */
 
3140
 
 
3141
#ifdef ERTS_SMP
 
3142
    erts_smp_proc_lock(p, ERTS_PROC_LOCK_FLAG_EXITING);
 
3143
    p->is_exiting = 1;
 
3144
#endif
968
3145
    p->status = P_EXITING;
969
 
    if (status == P_RUNNING)
970
 
        return;
971
 
 
972
 
    copy = copy_object(reason, p);
973
 
    
974
 
#ifdef SHARED_HEAP
975
 
    p->active = 1;
976
 
#endif
977
 
 
978
 
    p->fvalue = copy;
 
3146
    p->fvalue = reason;
 
3147
    if (bp) {
 
3148
        bp->next = p->mbuf;
 
3149
        p->mbuf = bp;
 
3150
    }
 
3151
    p->freason = EXC_EXIT;
 
3152
    KILL_CATCHES(p);
979
3153
    cancel_timer(p);
980
 
    p->freason = USER_EXIT;
981
 
    KILL_CATCHES(p);
982
3154
    p->i = (Eterm *) beam_exit;
983
 
    if (status != P_RUNABLE) {
984
 
        add_to_schedule_q(p);
985
 
    }
986
 
}
 
3155
}
 
3156
 
 
3157
 
 
3158
#ifdef ERTS_SMP
 
3159
 
 
3160
void
 
3161
erts_handle_pending_exit(Process *c_p, Uint32 locks)
 
3162
{
 
3163
    Uint32 xlocks;
 
3164
    ASSERT(is_value(c_p->pending_exit.reason));
 
3165
    ERTS_SMP_LC_ASSERT(erts_proc_lc_my_proc_locks(c_p) == locks);
 
3166
    ERTS_SMP_LC_ASSERT(locks & ERTS_PROC_LOCK_MAIN);
 
3167
    ERTS_SMP_LC_ASSERT(c_p->status != P_EXITING);
 
3168
    ERTS_SMP_LC_ASSERT(c_p->status != P_FREE);
 
3169
 
 
3170
    /* Ensure that all locks on c_p are locked before proceeding... */
 
3171
    if (locks == ERTS_PROC_LOCKS_ALL)
 
3172
        xlocks = 0;
 
3173
    else {
 
3174
        xlocks = ~locks & ERTS_PROC_LOCKS_ALL;
 
3175
        if (erts_smp_proc_trylock(c_p, xlocks) == EBUSY) {
 
3176
            erts_smp_proc_unlock(c_p, locks & ~ERTS_PROC_LOCK_MAIN);
 
3177
            erts_smp_proc_lock(c_p, ERTS_PROC_LOCKS_ALL_MINOR);
 
3178
        }
 
3179
    }
 
3180
 
 
3181
    set_proc_exiting(c_p, c_p->pending_exit.reason, c_p->pending_exit.bp);
 
3182
    c_p->pending_exit.reason = THE_NON_VALUE;
 
3183
    c_p->pending_exit.bp = NULL;
 
3184
 
 
3185
    if (xlocks)
 
3186
        erts_smp_proc_unlock(c_p, xlocks);
 
3187
}
 
3188
 
 
3189
static void
 
3190
handle_pending_exiters(ProcessList *pnd_xtrs)
 
3191
{
 
3192
    ProcessList *plp = pnd_xtrs;
 
3193
    ProcessList *free_plp;
 
3194
    while (plp) {
 
3195
        Process *p = erts_pid2proc(NULL, 0, plp->pid, ERTS_PROC_LOCKS_ALL);
 
3196
        if (p && !(p->status_flags & ERTS_PROC_SFLG_SCHEDULED)) {
 
3197
            ASSERT(p->status_flags & ERTS_PROC_SFLG_INRUNQ);
 
3198
            ASSERT(ERTS_PROC_PENDING_EXIT(p));
 
3199
            erts_handle_pending_exit(p, ERTS_PROC_LOCKS_ALL);
 
3200
        }
 
3201
        if (p)
 
3202
            erts_smp_proc_unlock(p, ERTS_PROC_LOCKS_ALL);
 
3203
        free_plp = plp;
 
3204
        plp = plp->next;
 
3205
        erts_free(ERTS_ALC_T_PROC_LIST, (void *) free_plp);
 
3206
    }
 
3207
}
 
3208
 
 
3209
static void
 
3210
save_pending_exiter(Eterm pid)
 
3211
{
 
3212
    ProcessList *plp;
 
3213
 
 
3214
    plp = erts_alloc(ERTS_ALC_T_PROC_LIST, sizeof(ProcessList));
 
3215
    plp->pid = pid;
 
3216
    erts_smp_mtx_lock(&schdlq_mtx);
 
3217
    plp->next = pending_exiters;
 
3218
    pending_exiters = plp;
 
3219
    erts_smp_mtx_unlock(&schdlq_mtx);
 
3220
}
 
3221
 
 
3222
#endif
987
3223
 
988
3224
/*
989
3225
 * This function delivers an EXIT message to a process
990
3226
 * which is trapping EXITs.
991
3227
 */
992
3228
 
993
 
static void
994
 
send_exit_message(Process *to, Eterm exit_term, Uint term_size, Eterm token)
 
3229
static ERTS_INLINE void
 
3230
send_exit_message(Process *to, Uint32 *to_locksp,
 
3231
                  Eterm exit_term, Uint term_size, Eterm token)
995
3232
{
996
 
#ifdef SHARED_HEAP
997
 
    if (token != NIL) {
998
 
        ASSERT(token == NIL);
999
 
    } else {
1000
 
        queue_message_tt(to, NULL, exit_term, NIL);
1001
 
    }
1002
 
#else
1003
3233
    if (token == NIL) {
1004
3234
        Eterm* hp;
1005
3235
        Eterm mess;
 
3236
        ErlHeapFragment* bp;
 
3237
        ErlOffHeap *ohp;
1006
3238
 
1007
 
        hp = HAlloc(to, term_size);
1008
 
        mess = copy_struct(exit_term, term_size, &hp, &MSO(to));
1009
 
        queue_message_tt(to, NULL, mess, NIL);
 
3239
        hp = erts_alloc_message_heap(term_size, &bp, &ohp, to, to_locksp);
 
3240
        mess = copy_struct(exit_term, term_size, &hp, ohp);
 
3241
        erts_queue_message(to, *to_locksp, bp, mess, NIL);
1010
3242
    } else {
1011
3243
        ErlHeapFragment* bp;
1012
3244
        Eterm* hp;
1018
3250
        sz_token = size_object(token);
1019
3251
        bp = new_message_buffer(term_size+sz_token);
1020
3252
        hp = bp->mem;
1021
 
        mess = copy_struct(exit_term, term_size, &hp, &MSO(to));
 
3253
        mess = copy_struct(exit_term, term_size, &hp, &bp->off_heap);
1022
3254
        /* the trace token must in this case be updated by the caller */
1023
3255
        seq_trace_output(token, mess, SEQ_TRACE_SEND, to->id, NULL);
1024
 
        temp_token = copy_struct(token, sz_token, &hp, &MSO(to));
1025
 
        queue_message_tt(to, bp, mess, temp_token);
1026
 
    }
1027
 
#endif
1028
 
}
 
3256
        temp_token = copy_struct(token, sz_token, &hp, &bp->off_heap);
 
3257
        erts_queue_message(to, *to_locksp, bp, mess, temp_token);
 
3258
    }
 
3259
}
 
3260
 
 
3261
/*
 
3262
 *
 
3263
 * *** Exit signal behavior ***
 
3264
 *
 
3265
 * Exit signals are asynchronous (truly asynchronous in the
 
3266
 * SMP emulator). When the signal is received the receiver receives an
 
3267
 * 'EXIT' message if it is trapping exits; otherwise, it will either
 
3268
 * ignore the signal if the exit reason is normal, or go into an
 
3269
 * exiting state (status P_EXITING). When a process has gone into the
 
3270
 * exiting state it will not execute any more Erlang code, but it might
 
3271
 * take a while before it actually exits. The exit signal is being
 
3272
 * received when the 'EXIT' message is put in the message queue, the
 
3273
 * signal is dropped, or when it changes state into exiting. The time it
 
3274
 * is in the exiting state before actually exiting is undefined (it
 
3275
 * might take a really long time under certain conditions). The
 
3276
 * receiver of the exit signal does not break links or trigger monitors
 
3277
 * until it actually exits.
 
3278
 *
 
3279
 * Exit signals and other signals, e.g. messages, have to be received
 
3280
 * by a receiver in the same order as sent by a sender.
 
3281
 *
 
3282
 *
 
3283
 *
 
3284
 * Exit signal implementation in the SMP emulator:
 
3285
 *
 
3286
 * If the receiver is trapping exits, the signal is transformed
 
3287
 * into an 'EXIT' message and sent as a normal message, if the
 
3288
 * reason is normal the signal is dropped; otherwise, the process
 
3289
 * is determined to be exited. The interesting case is when the
 
3290
 * process is to be exited and this is what is described below.
 
3291
 *
 
3292
 * If it is possible, the receiver is set in the exiting state straight
 
3293
 * away and we are done; otherwise, the sender places the exit reason
 
3294
 * in the pending_exit field of the process struct and if necessary
 
3295
 * adds the receiver to the run queue. It is typically not possible
 
3296
 * to set a scheduled process or a process which we cannot get all locks
 
3297
 * on without releasing locks on it in an exiting state straight away.
 
3298
 *
 
3299
 * The receiver will poll the pending_exit field when it reach certain
 
3300
 * places during it's execution. When it discovers the pending exit
 
3301
 * it will change state into the exiting state. If the receiver wasn't
 
3302
 * scheduled when the pending exit was set, the first scheduler that
 
3303
 * schedules a new process will set the receiving process in the exiting
 
3304
 * state just before it schedules next process.
 
3305
 * 
 
3306
 * When the exit signal is placed in the pending_exit field, the signal
 
3307
 * is considered as being in transit on the Erlang level. The signal is
 
3308
 * actually in some kind of semi transit state, since we have already
 
3309
 * determined how it should be received. It will exit the process no
 
3310
 * matter what if it is received (the process may exit by itself before
 
3311
 * reception of the exit signal). The signal is received when it is
 
3312
 * discovered in the pending_exit field by the receiver.
 
3313
 *
 
3314
 * The receiver have to poll the pending_exit field at least before:
 
3315
 * - moving messages from the message in queue to the private message
 
3316
 *   queue. This in order to preserve signal order.
 
3317
 * - unlink. Otherwise the process might get exited on a link that
 
3318
 *   have been removed.
 
3319
 * - changing the trap_exit flag to true. This in order to simplify the
 
3320
 *   implementation; otherwise, we would have to transform the signal
 
3321
 *   into an 'EXIT' message when setting the trap_exit flag to true. We
 
3322
 *   would also have to maintain a queue of exit signals in transit.
 
3323
 * - being scheduled in or out.
 
3324
 */
 
3325
 
 
3326
static ERTS_INLINE int
 
3327
send_exit_signal(Process *c_p,          /* current process if and only
 
3328
                                           if reason is stored on it */
 
3329
                 Eterm from,            /* Id of sender of signal */
 
3330
                 Process *rp,           /* receiving process */
 
3331
                 Uint32 *rp_locks,      /* current locks on receiver */
 
3332
                 Eterm reason,          /* exit reason */
 
3333
                 Eterm exit_tuple,      /* Prebuild exit tuple
 
3334
                                           or THE_NON_VALUE */
 
3335
                 Uint exit_tuple_sz,    /* Size of prebuilt exit tuple
 
3336
                                           (if exit_tuple != THE_NON_VALUE) */
 
3337
                 Eterm token,           /* token */
 
3338
                 Process *token_update, /* token updater */
 
3339
                 Uint32 flags           /* flags */
 
3340
    )           
 
3341
{
 
3342
    Eterm rsn = reason == am_kill ? am_killed : reason;
 
3343
 
 
3344
    ERTS_SMP_LC_ASSERT(*rp_locks == erts_proc_lc_my_proc_locks(rp));
 
3345
    ERTS_SMP_LC_ASSERT((*rp_locks & ERTS_PROC_LOCKS_XSIG_SEND)
 
3346
                       == ERTS_PROC_LOCKS_XSIG_SEND);
 
3347
 
 
3348
    ASSERT(reason != THE_NON_VALUE);
 
3349
 
 
3350
    if (ERTS_PROC_IS_TRAPPING_EXITS(rp)
 
3351
        && (reason != am_kill || (flags & ERTS_XSIG_FLG_IGN_KILL))) {
 
3352
        if (is_not_nil(token) && token_update)
 
3353
            seq_trace_update_send(token_update);
 
3354
        if (is_value(exit_tuple))
 
3355
            send_exit_message(rp, rp_locks, exit_tuple, exit_tuple_sz, token);
 
3356
        else
 
3357
            erts_deliver_exit_message(from, rp, rp_locks, rsn, token);
 
3358
        return 1; /* Receiver will get a message */
 
3359
    }
 
3360
    else if (reason != am_normal || (flags & ERTS_XSIG_FLG_NO_IGN_NORMAL)) {
 
3361
#ifdef ERTS_SMP
 
3362
        if (!ERTS_PROC_PENDING_EXIT(rp) && !rp->is_exiting) {
 
3363
            ASSERT(rp->status != P_EXITING);
 
3364
            ASSERT(rp->status != P_FREE);
 
3365
            ASSERT(!rp->pending_exit.bp);
 
3366
 
 
3367
            if (rp == c_p && (*rp_locks & ERTS_PROC_LOCK_MAIN)) {
 
3368
                /* Ensure that all locks on c_p are locked before
 
3369
                   proceeding... */
 
3370
                if (*rp_locks != ERTS_PROC_LOCKS_ALL) {
 
3371
                    Uint32 need_locks = ~(*rp_locks) & ERTS_PROC_LOCKS_ALL;
 
3372
                    if (erts_smp_proc_trylock(c_p, need_locks) == EBUSY) {
 
3373
                        erts_smp_proc_unlock(c_p,
 
3374
                                             *rp_locks & ~ERTS_PROC_LOCK_MAIN);
 
3375
                        erts_smp_proc_lock(c_p, ERTS_PROC_LOCKS_ALL_MINOR);
 
3376
                    }
 
3377
                    *rp_locks = ERTS_PROC_LOCKS_ALL;
 
3378
                }
 
3379
                set_proc_exiting(c_p, rsn, NULL);
 
3380
            }
 
3381
            else if (!(rp->status_flags & ERTS_PROC_SFLG_SCHEDULED)) {
 
3382
                /* Process not scheduled ... */
 
3383
                Uint32 need_locks = ~(*rp_locks) & ERTS_PROC_LOCKS_ALL;
 
3384
                if (need_locks
 
3385
                    && erts_smp_proc_trylock(rp, need_locks) == EBUSY) {
 
3386
                    /* ... but we havn't got all locks on it ... */
 
3387
                    save_pending_exiter(rp->id);
 
3388
                    /*
 
3389
                     * The pending exit will be discovered when next
 
3390
                     * process is scheduled in
 
3391
                     */
 
3392
                    goto set_pending_exit;
 
3393
                }
 
3394
                else {
 
3395
                    /* ...and we have all locks on it... */
 
3396
                    *rp_locks = ERTS_PROC_LOCKS_ALL;
 
3397
                    set_proc_exiting(rp,
 
3398
                                     (is_immed(rsn)
 
3399
                                      ? rsn
 
3400
                                      : copy_object(rsn, rp)),
 
3401
                                     NULL);
 
3402
                }
 
3403
            }
 
3404
            else { /* Process scheduled... */
 
3405
 
 
3406
                /*
 
3407
                 * The pending exit will be discovered when the process
 
3408
                 * is scheduled out if not discovered earlier.
 
3409
                 */
 
3410
 
 
3411
            set_pending_exit:
 
3412
                if (is_immed(rsn)) {
 
3413
                    rp->pending_exit.reason = rsn;
 
3414
                }
 
3415
                else {
 
3416
                    Eterm *hp;
 
3417
                    Uint sz = size_object(rsn);
 
3418
                    ErlHeapFragment *bp = new_message_buffer(sz);
 
3419
 
 
3420
                    hp = &bp->mem[0];
 
3421
                    rp->pending_exit.reason = copy_struct(rsn,
 
3422
                                                          sz,
 
3423
                                                          &hp,
 
3424
                                                          &bp->off_heap);
 
3425
                    rp->pending_exit.bp = bp;
 
3426
                }
 
3427
                ASSERT(ERTS_PROC_PENDING_EXIT(rp));
 
3428
            }
 
3429
            if (!(rp->status_flags
 
3430
                  & (ERTS_PROC_SFLG_INRUNQ|ERTS_PROC_SFLG_SCHEDULED)))
 
3431
                add_to_schedule_q(rp);
 
3432
        }
 
3433
        /* else:
 
3434
         *
 
3435
         *    The receiver already has a pending exit (or is exiting)
 
3436
         *    so we drop this signal.
 
3437
         *
 
3438
         *    NOTE: dropping this exit signal is based on the assumption
 
3439
         *          that the receiver *will* exit; either on the pending
 
3440
         *          exit or by itself before seeing the pending exit.
 
3441
         */
 
3442
#else /* !ERTS_SMP */
 
3443
        if (c_p == rp) {
 
3444
            rp->status = P_EXITING;
 
3445
            c_p->fvalue = rsn;
 
3446
        }
 
3447
        else if (rp->status != P_EXITING) { /* No recursive process exits /PaN */
 
3448
            Eterm old_status = rp->status;
 
3449
            set_proc_exiting(rp,
 
3450
                             is_immed(rsn) ? rsn : copy_object(rsn, rp),
 
3451
                             NULL);
 
3452
            ACTIVATE(rp);
 
3453
            if (old_status != P_RUNABLE && old_status != P_RUNNING)
 
3454
                add_to_schedule_q(rp);
 
3455
        }
 
3456
#endif
 
3457
        return -1; /* Receiver will exit */
 
3458
    }
 
3459
 
 
3460
    return 0; /* Receiver unaffected */
 
3461
}
 
3462
 
 
3463
 
 
3464
int
 
3465
erts_send_exit_signal(Process *c_p,
 
3466
                      Eterm from,
 
3467
                      Process *rp,
 
3468
                      Uint32 *rp_locks,
 
3469
                      Eterm reason,
 
3470
                      Eterm token,
 
3471
                      Process *token_update,
 
3472
                      Uint32 flags)
 
3473
{
 
3474
    return send_exit_signal(c_p,
 
3475
                            from,
 
3476
                            rp,
 
3477
                            rp_locks,
 
3478
                            reason,
 
3479
                            THE_NON_VALUE,
 
3480
                            0,
 
3481
                            token,
 
3482
                            token_update,
 
3483
                            flags);
 
3484
}
 
3485
 
 
3486
typedef struct {
 
3487
    Eterm reason;
 
3488
    Process *p;
 
3489
} ExitMonitorContext;
 
3490
 
 
3491
static void doit_exit_monitor(ErtsMonitor *mon, void *vpcontext)
 
3492
{
 
3493
    ExitMonitorContext *pcontext = vpcontext;
 
3494
    DistEntry *dep;
 
3495
    ErtsMonitor *rmon;
 
3496
    Process *rp;
 
3497
 
 
3498
    if (mon->type == MON_ORIGIN) {
 
3499
        /* We are monitoring someone else, we need to demonitor that one.. */
 
3500
        if (is_atom(mon->pid)) { /* remote by name */
 
3501
            ASSERT(is_node_name_atom(mon->pid));
 
3502
            dep = erts_sysname_to_connected_dist_entry(mon->pid);
 
3503
            if (dep) {
 
3504
                erts_smp_io_lock();
 
3505
                erts_smp_dist_entry_lock(dep);
 
3506
                rmon = erts_remove_monitor(&(dep->monitors), mon->ref);
 
3507
                if (rmon) {
 
3508
                    dist_demonitor(NULL,0,dep,rmon->pid,mon->name,mon->ref,1);
 
3509
                    erts_destroy_monitor(rmon);
 
3510
                }
 
3511
                erts_smp_io_unlock();
 
3512
                erts_smp_dist_entry_unlock(dep);
 
3513
                erts_deref_dist_entry(dep);
 
3514
            }
 
3515
        } else {
 
3516
            ASSERT(is_pid(mon->pid));
 
3517
            if (is_internal_pid(mon->pid)) { /* local by pid or name */
 
3518
                rp = erts_pid2proc(NULL, 0, mon->pid, ERTS_PROC_LOCK_LINK);
 
3519
                if (!rp) {
 
3520
                    goto done;
 
3521
                }
 
3522
                rmon = erts_remove_monitor(&(rp->monitors),mon->ref);
 
3523
                erts_smp_proc_unlock(rp, ERTS_PROC_LOCK_LINK);
 
3524
                if (rmon == NULL) {
 
3525
                    goto done;
 
3526
                }
 
3527
                erts_destroy_monitor(rmon);
 
3528
            } else { /* remote by pid */
 
3529
                ASSERT(is_external_pid(mon->pid));
 
3530
                dep = external_pid_dist_entry(mon->pid);
 
3531
                ASSERT(dep != NULL);
 
3532
                if (dep) {
 
3533
                    erts_smp_io_lock();
 
3534
                    erts_smp_dist_entry_lock(dep);
 
3535
                    rmon = erts_remove_monitor(&(dep->monitors), mon->ref);
 
3536
                    if (rmon) {
 
3537
                        dist_demonitor(NULL,0,dep,rmon->pid,mon->pid,mon->ref,1);
 
3538
                        erts_destroy_monitor(rmon);
 
3539
                    }
 
3540
                    erts_smp_io_unlock();
 
3541
                    erts_smp_dist_entry_unlock(dep);
 
3542
                }
 
3543
            }
 
3544
        }
 
3545
    } else { /* type == MON_TARGET */
 
3546
        ASSERT(mon->type == MON_TARGET && is_pid(mon->pid));
 
3547
        if (is_internal_pid(mon->pid)) {/* local by name or pid */
 
3548
            Eterm watched;
 
3549
            Eterm lhp[3];
 
3550
            Uint32 rp_locks = ERTS_PROC_LOCK_LINK|ERTS_PROC_LOCKS_MSG_SEND;
 
3551
            rp = erts_pid2proc(NULL, 0, mon->pid, rp_locks);
 
3552
            if (rp == NULL) {
 
3553
                goto done;
 
3554
            }
 
3555
            rmon = erts_remove_monitor(&(rp->monitors),mon->ref);
 
3556
            if (rmon) {
 
3557
                erts_destroy_monitor(rmon);
 
3558
                watched = (is_atom(mon->name)
 
3559
                           ? TUPLE2(lhp, mon->name, 
 
3560
                                    erts_this_dist_entry->sysname)
 
3561
                           : pcontext->p->id);
 
3562
                erts_queue_monitor_message(rp, &rp_locks, mon->ref, am_process, 
 
3563
                                           watched, pcontext->reason);
 
3564
            }
 
3565
            /* else: demonitor while we exited, i.e. do nothing... */
 
3566
            erts_smp_proc_unlock(rp, rp_locks);
 
3567
        } else { /* external by pid or name */
 
3568
            ASSERT(is_external_pid(mon->pid));    
 
3569
            erts_smp_io_lock();
 
3570
            dep = external_pid_dist_entry(mon->pid);
 
3571
            ASSERT(dep != NULL);
 
3572
            if (dep) {
 
3573
                erts_smp_dist_entry_lock(dep);
 
3574
                rmon = erts_remove_monitor(&(dep->monitors), mon->ref);
 
3575
                if (rmon) {
 
3576
                    dist_m_exit(NULL, 0,
 
3577
                                dep, mon->pid, (rmon->name != NIL) 
 
3578
                                ? rmon->name : rmon->pid,
 
3579
                                mon->ref, pcontext->reason);
 
3580
                    erts_destroy_monitor(rmon);
 
3581
                }
 
3582
                erts_smp_dist_entry_unlock(dep);
 
3583
            }
 
3584
            erts_smp_io_unlock();
 
3585
        }
 
3586
    }
 
3587
 done:
 
3588
    /* As the monitors are previously removed from the process, 
 
3589
       distribution operations will not cause monitors to disappear,
 
3590
       we can safely delete it. */
 
3591
       
 
3592
    erts_destroy_monitor(mon);
 
3593
}
 
3594
 
 
3595
typedef struct {
 
3596
    Process *p;
 
3597
    Eterm reason;
 
3598
    Eterm exit_tuple;
 
3599
    Uint exit_tuple_sz;
 
3600
} ExitLinkContext;
 
3601
 
 
3602
static void doit_exit_link(ErtsLink *lnk, void *vpcontext)
 
3603
{
 
3604
    ExitLinkContext *pcontext = vpcontext;
 
3605
    /* Unpack context, it's readonly */
 
3606
    Process *p = pcontext->p;
 
3607
    Eterm reason = pcontext->reason;
 
3608
    Eterm exit_tuple = pcontext->exit_tuple;
 
3609
    Uint exit_tuple_sz = pcontext->exit_tuple_sz;
 
3610
    Eterm item = lnk->pid;
 
3611
    int ix;
 
3612
    ErtsLink *rlnk;
 
3613
    DistEntry *dep;
 
3614
    Process *rp;
 
3615
 
 
3616
    switch(lnk->type) {
 
3617
    case LINK_PID:
 
3618
        if(is_internal_port(item)) {
 
3619
            erts_smp_io_lock();
 
3620
            ix = internal_port_index(item);
 
3621
            if (! INVALID_PORT(erts_port+ix, item)) {
 
3622
                rlnk = erts_remove_link(&(erts_port[ix].nlinks),
 
3623
                                        p->id);
 
3624
                if (rlnk != NULL) {
 
3625
                    erts_destroy_link(rlnk);
 
3626
                }
 
3627
                erts_do_exit_port(item, p->id, reason);
 
3628
            }
 
3629
            erts_smp_io_unlock();
 
3630
        }
 
3631
        else if(is_external_port(item)) {
 
3632
            dep = external_port_dist_entry(item);
 
3633
            if(dep != erts_this_dist_entry) {
 
3634
                erts_smp_io_lock();
 
3635
                erts_smp_dist_entry_lock(dep);
 
3636
                dist_exit(NULL, 0, dep, p->id, item, reason);
 
3637
                erts_smp_dist_entry_unlock(dep);
 
3638
                erts_smp_io_unlock();
 
3639
            }
 
3640
        }
 
3641
        else if (is_internal_pid(item)) {
 
3642
            Uint32 rp_locks = ERTS_PROC_LOCK_LINK|ERTS_PROC_LOCKS_XSIG_SEND;
 
3643
            rp = erts_pid2proc(NULL, 0, item, rp_locks);
 
3644
            if (rp) {
 
3645
                rlnk = erts_remove_link(&(rp->nlinks), p->id);
 
3646
                /* If rlnk == NULL, we got unlinked while exiting,
 
3647
                   i.e., do nothing... */
 
3648
                if (rlnk) {
 
3649
                    int xres;
 
3650
                    erts_destroy_link(rlnk);
 
3651
                    xres = send_exit_signal(NULL,
 
3652
                                            p->id,
 
3653
                                            rp,
 
3654
                                            &rp_locks, 
 
3655
                                            reason,
 
3656
                                            exit_tuple,
 
3657
                                            exit_tuple_sz,
 
3658
                                            SEQ_TRACE_TOKEN(p),
 
3659
                                            p,
 
3660
                                            ERTS_XSIG_FLG_IGN_KILL);
 
3661
                    if (xres >= 0 && IS_TRACED_FL(rp, F_TRACE_PROCS)) {
 
3662
                        /* We didn't exit the process and it is traced */
 
3663
                        if (IS_TRACED_FL(rp, F_TRACE_PROCS)) {
 
3664
                            trace_proc(p, rp, am_getting_unlinked, p->id);
 
3665
                        }
 
3666
                    }
 
3667
                }
 
3668
                ASSERT(rp != p);
 
3669
                erts_smp_proc_unlock(rp, rp_locks);
 
3670
            }
 
3671
        }
 
3672
        else if (is_external_pid(item)) {
 
3673
            dep = external_pid_dist_entry(item);
 
3674
            if(dep != erts_this_dist_entry) {
 
3675
                erts_smp_io_lock();
 
3676
                erts_smp_dist_entry_lock(dep);
 
3677
                if (SEQ_TRACE_TOKEN(p) != NIL) {
 
3678
                    seq_trace_update_send(p);
 
3679
                }
 
3680
                dist_exit_tt(NULL,0,dep,p->id,item,reason,SEQ_TRACE_TOKEN(p));
 
3681
                erts_smp_io_unlock();
 
3682
                erts_smp_dist_entry_unlock(dep);
 
3683
            }
 
3684
        }
 
3685
        break;
 
3686
    case LINK_NODE:
 
3687
        ASSERT(is_node_name_atom(item));
 
3688
        dep = erts_sysname_to_connected_dist_entry(item);
 
3689
        if(dep) {
 
3690
            /* dist entries have node links in a separate structure to 
 
3691
               avoid confusion */
 
3692
            erts_smp_dist_entry_lock(dep);
 
3693
            rlnk = erts_remove_link(&(dep->node_links), p->id);
 
3694
            erts_smp_dist_entry_unlock(dep);
 
3695
            if (rlnk != NULL) {
 
3696
                erts_destroy_link(rlnk);
 
3697
            }
 
3698
            erts_deref_dist_entry(dep);
 
3699
        } else {
 
3700
#ifndef ERTS_SMP
 
3701
            /* XXX Is this possible? Shouldn't this link
 
3702
               previously have been removed if the node
 
3703
               had previously been disconnected. */
 
3704
            ASSERT(0);
 
3705
#endif
 
3706
            /* This is possible when smp support has been enabled,
 
3707
               and dist port and process exits simultaneously. */
 
3708
        }
 
3709
        break;
 
3710
        
 
3711
    default:
 
3712
        erl_exit(1, "bad type in link list\n");
 
3713
        break;
 
3714
    }
 
3715
    erts_destroy_link(lnk);
 
3716
}
 
3717
 
1029
3718
 
1030
3719
/* this function fishishes a process and propagates exit messages - called
1031
3720
   by process_main when a process dies */
1032
3721
void 
1033
 
do_exit(Process* p, Eterm reason)
 
3722
erts_do_exit_process(Process* p, Eterm reason)
1034
3723
{
1035
 
    Process *rp;
1036
 
    ErlLink* lnk;
1037
 
    Eterm item;
1038
 
    DistEntry *dep;
1039
 
    int ix;
1040
 
    Eterm ref;
1041
 
    Eterm exit_tuple = NIL;
1042
 
    Uint exit_tuple_sz = 0;
 
3724
    ErtsLink* lnk;
 
3725
    ErtsMonitor *mon;
1043
3726
 
1044
3727
    p->arity = 0;               /* No live registers */
1045
3728
    p->fvalue = reason;
 
3729
    
 
3730
#ifdef ERTS_SMP
 
3731
    ERTS_CHK_HAVE_ONLY_MAIN_PROC_LOCK(p->id);
 
3732
    /* By locking all locks (main lock is already locked) when going
 
3733
       to status P_EXITING, it is enough to take any lock when
 
3734
       looking up a process (erts_pid2proc()) to prevent the looked up
 
3735
       process from exiting until the lock has been released. */
 
3736
    erts_smp_proc_lock(p,
 
3737
                       ERTS_PROC_LOCKS_ALL_MINOR|ERTS_PROC_LOCK_FLAG_EXITING);
 
3738
    p->is_exiting = 1;
 
3739
#endif
 
3740
 
1046
3741
    p->status = P_EXITING;
1047
3742
 
 
3743
#ifdef ERTS_SMP
 
3744
 
 
3745
    if (ERTS_PROC_PENDING_EXIT(p)) {
 
3746
        /* Process exited before pending exit was received... */
 
3747
        p->pending_exit.reason = THE_NON_VALUE;
 
3748
        if (p->pending_exit.bp) {
 
3749
            free_message_buffer(p->pending_exit.bp);
 
3750
            p->pending_exit.bp = NULL;
 
3751
        }
 
3752
    }
 
3753
 
 
3754
    cancel_suspend_of_suspendee(p, ERTS_PROC_LOCKS_ALL); 
 
3755
 
 
3756
    ERTS_SMP_MSGQ_MV_INQ2PRIVQ(p);
 
3757
#endif
 
3758
 
1048
3759
    if (IS_TRACED_FL(p,F_TRACE_PROCS))
1049
3760
        trace_proc(p, p, am_exit, reason);
1050
3761
 
1051
 
    if (p->flags & F_TRACER) {
1052
 
        if (EQ(erts_default_tracer, p->id)) {
1053
 
            erts_default_tracer = NIL;
1054
 
            erts_default_process_flags &= ~TRACE_FLAGS;
1055
 
        }
1056
 
        if (EQ(erts_system_monitor, p->id)) {
1057
 
            erts_system_monitor_clear();
1058
 
        }
1059
 
    }
1060
 
 
1061
 
    lnk = p->links;
1062
 
    p->links = NULL;
1063
 
    
1064
 
    
 
3762
    erts_trace_check_exiting(p->id);
 
3763
 
 
3764
    cancel_timer(p);            /* Always cancel timer just in case */
 
3765
 
 
3766
    if (p->bif_timers)
 
3767
        erts_cancel_bif_timers(p, ERTS_PROC_LOCKS_ALL);
 
3768
 
 
3769
    if (p->flags & F_USING_DB)
 
3770
        db_proc_dead(p->id);
 
3771
 
 
3772
    if (p->flags & F_USING_DDLL) {
 
3773
        erts_ddll_proc_dead(p, ERTS_PROC_LOCKS_ALL);
 
3774
    }
 
3775
 
 
3776
    /*
 
3777
     * The registered name *should* be the last "erlang resource" to
 
3778
     * cleanup.
 
3779
     */
 
3780
    if (p->reg)
 
3781
        (void) erts_unregister_name(p, ERTS_PROC_LOCKS_ALL, 0, p->reg->name);
 
3782
 
 
3783
    {
 
3784
        int pix;
 
3785
        erts_smp_mtx_t *ptabix_mtxp;
 
3786
#ifdef ERTS_SMP
 
3787
        ptabix_mtxp = &(erts_proc_locks[ERTS_PID2LOCKIX(p->id)].mtx);
 
3788
#else
 
3789
        ptabix_mtxp = NULL;
 
3790
#endif
 
3791
        
 
3792
        ASSERT(internal_pid_index(p->id) < erts_max_processes);
 
3793
        pix = internal_pid_index(p->id);
 
3794
 
 
3795
        erts_smp_mtx_lock(&proc_tab_mtx);
 
3796
        erts_smp_mtx_lock(&schdlq_mtx);
 
3797
        erts_smp_mtx_lock(ptabix_mtxp);
 
3798
 
 
3799
#ifdef ERTS_SMP
 
3800
        ASSERT(p->scheduler_data);
 
3801
        ASSERT(p->scheduler_data->current_process == p);
 
3802
        ASSERT(p->scheduler_data->free_process == NULL);
 
3803
 
 
3804
        p->scheduler_data->current_process = NULL;
 
3805
        p->scheduler_data->free_process = p;
 
3806
        p->status_flags = 0;
 
3807
#endif
 
3808
        process_tab[pix] = NULL; /* Time of death! */
 
3809
        ASSERT(erts_smp_atomic_read(&process_count) > 0);
 
3810
        erts_smp_atomic_dec(&process_count);
 
3811
 
 
3812
        erts_smp_mtx_unlock(ptabix_mtxp);
 
3813
        erts_smp_mtx_unlock(&schdlq_mtx);
 
3814
 
 
3815
        if (p_next < 0) {
 
3816
            if (p_last >= p_next) {
 
3817
                p_serial++;
 
3818
                p_serial &= p_serial_mask;
 
3819
            }
 
3820
            p_next = pix;
 
3821
        }
 
3822
 
 
3823
        erts_smp_mtx_unlock(&proc_tab_mtx);
 
3824
    }
 
3825
 
 
3826
    /*
 
3827
     * All "erlang resources" have to be deallocated before this point,
 
3828
     * e.g. registered name, so monitoring and linked processes can
 
3829
     * be sure that all interesting resources have been deallocated
 
3830
     * when the monitors and/or links hit.
 
3831
     */
 
3832
 
 
3833
    mon = p->monitors;
 
3834
    p->monitors = NULL; /* to avoid recursive deletion during traversal */
 
3835
 
 
3836
    lnk = p->nlinks;
 
3837
    p->nlinks = NULL;
 
3838
    p->status = P_FREE;
 
3839
    erts_smp_proc_unlock(p, ERTS_PROC_LOCKS_ALL);
 
3840
    processes_busy--;
 
3841
 
 
3842
    if ((p->flags & F_DISTRIBUTION) && p->dist_entry)
 
3843
        erts_do_net_exits(p->dist_entry);
 
3844
 
1065
3845
    /*
1066
3846
     * Pre-build the EXIT tuple if there are any links.
1067
3847
     */
1068
 
    if (lnk != NULL) {
 
3848
    if (lnk) {
 
3849
        Eterm tmp_heap[4];
 
3850
        Eterm exit_tuple;
 
3851
        Uint exit_tuple_sz;
1069
3852
        Eterm* hp;
1070
 
        if (HEAP_LIMIT(p) - HEAP_TOP(p) <= 4) {
1071
 
            (void) erts_garbage_collect(p, 4, NULL, 0);
1072
 
            reason = p->fvalue;
1073
 
        }
1074
 
        hp = HEAP_TOP(p);
1075
 
        HEAP_TOP(p) += 4;
 
3853
 
 
3854
        hp = &tmp_heap[0];
 
3855
 
1076
3856
        exit_tuple = TUPLE3(hp, am_EXIT, p->id, reason);
1077
 
#ifndef SHARED_HEAP
 
3857
 
1078
3858
        exit_tuple_sz = size_object(exit_tuple);
1079
 
#endif
1080
 
    }
1081
 
 
1082
 
    while (lnk != NULL) {
1083
 
        item = lnk->item;
1084
 
        switch(lnk->type) {
1085
 
        case LNK_LINK:
1086
 
            if(is_internal_port(item)) {
1087
 
                ix = internal_port_index(item);
1088
 
                if (! INVALID_PORT(erts_port+ix, item)) {
1089
 
                    del_link(find_link(&erts_port[ix].links,LNK_LINK,
1090
 
                                       p->id,NIL));
1091
 
                    do_exit_port(item, p->id, reason);
1092
 
                }
1093
 
            }
1094
 
            else if(is_external_port(item)) {
1095
 
                dep = external_port_dist_entry(item);
1096
 
                if(dep != erts_this_dist_entry)
1097
 
                    dist_exit(dep, p->id, item, reason);
1098
 
            }
1099
 
            else if (is_internal_pid(item)) {
1100
 
                if ((rp = pid2proc(item)) != NULL) {
1101
 
                    ErlLink **rlinkpp = 
1102
 
                        find_link(&rp->links, LNK_LINK, p->id, NIL);
1103
 
                    del_link(rlinkpp);
1104
 
                    if (rp->flags & F_TRAPEXIT) {
1105
 
                        if (SEQ_TRACE_TOKEN(p) != NIL ) {
1106
 
                            seq_trace_update_send(p);
1107
 
                        }
1108
 
                        send_exit_message(rp, exit_tuple, exit_tuple_sz,
1109
 
                                          SEQ_TRACE_TOKEN(p));
1110
 
                        if (IS_TRACED_FL(rp, F_TRACE_PROCS) && rlinkpp != NULL) {
1111
 
                            trace_proc(p, rp, am_getting_unlinked, p->id);
1112
 
                        }
1113
 
                    } else if (reason == am_normal) {
1114
 
                        if (IS_TRACED_FL(rp, F_TRACE_PROCS) && rlinkpp != NULL) {
1115
 
                            trace_proc(p, rp, am_getting_unlinked, p->id);
1116
 
                        }
1117
 
                    } else {
1118
 
                        schedule_exit(rp, reason);
1119
 
                    } 
1120
 
                }
1121
 
            }
1122
 
            else if (is_external_pid(item)) {
1123
 
                dep = external_pid_dist_entry(item);
1124
 
                if(dep != erts_this_dist_entry) {
1125
 
                    if (SEQ_TRACE_TOKEN(p) != NIL) {
1126
 
                        seq_trace_update_send(p);
1127
 
                    }
1128
 
                    dist_exit_tt(dep, p->id, item, reason, SEQ_TRACE_TOKEN(p));
1129
 
                }
1130
 
            }
1131
 
            break;
1132
 
        case LNK_LINK1:
1133
 
            ref = lnk->ref;
1134
 
            if (item == p->id) {
1135
 
                /* We are monitoring 'data' */
1136
 
                if (is_atom(lnk->data)) {
1137
 
                    /* Monitoring a name on this node */
1138
 
                    ASSERT(is_node_name_atom(lnk->data));
1139
 
                    dep = erts_sysname_to_connected_dist_entry(lnk->data);
1140
 
                    if(!dep)
1141
 
                        break;
1142
 
                }
1143
 
                else {
1144
 
                    ASSERT(is_pid(lnk->data));
1145
 
                    dep = pid_dist_entry(lnk->data);
1146
 
                }
1147
 
                if (dep != erts_this_dist_entry) {
1148
 
                    ErlLink** lnkp;
1149
 
                    lnkp = find_link_by_ref(&dep->links, ref);
1150
 
                    if (lnkp != NULL) {
1151
 
                        /* Force send, use the atom in dist slot 
1152
 
                         * link list as data for the message.
1153
 
                         */
1154
 
                        dist_demonitor(dep, item, (*lnkp)->data, ref, 1);
1155
 
                        /* dist_demonitor() may have removed the link;
1156
 
                           therefore, look it up again. */
1157
 
                        lnkp = find_link_by_ref(&dep->links, ref);
1158
 
                        del_link(lnkp);
1159
 
                    }
1160
 
                } else {
1161
 
                    if ((rp = pid2proc(lnk->data)) != NULL)
1162
 
                        del_link(find_link_by_ref(&rp->links, ref));
1163
 
                }
1164
 
            } else {
1165
 
                /* 'Item' is monitoring us */
1166
 
                if (is_internal_pid(item)) {
1167
 
                    if ((rp = pid2proc(item)) != NULL) {
1168
 
                        Eterm lhp[3];
1169
 
                        Eterm item = (is_atom(lnk->data)
1170
 
                                      ? TUPLE2(&lhp[0],
1171
 
                                               lnk->data,
1172
 
                                               erts_this_dist_entry->sysname)
1173
 
                                      : lnk->data);
1174
 
                        ASSERT(lnk->data == p->id || is_atom(lnk->data));
1175
 
                        queue_monitor_message(rp, ref, am_process,
1176
 
                                              item, reason);
1177
 
                        del_link(find_link_by_ref(&rp->links, ref));
1178
 
                    }
1179
 
                } else if (is_external_pid(item)) {
1180
 
                    dep = external_pid_dist_entry(item);
1181
 
                    if(dep != erts_this_dist_entry)
1182
 
                        dist_m_exit(dep, item, lnk->data, ref, reason);
1183
 
                }
1184
 
                else {
1185
 
                    ASSERT(0);
1186
 
                }
1187
 
            }
1188
 
 
1189
 
            break;
1190
 
        case LNK_NODE:
1191
 
            ASSERT(is_node_name_atom(item));
1192
 
            dep = erts_sysname_to_connected_dist_entry(item);
1193
 
            if(dep)
1194
 
                del_link(find_link(&dep->links,LNK_NODE,p->id,NIL));
1195
 
            else {
1196
 
                /* XXX Is this possible? Shouldn't this link
1197
 
                   previously have been removed if the node
1198
 
                   had previously been disconnected. */
1199
 
                ASSERT(0);
1200
 
            }
1201
 
            break;
1202
 
 
1203
 
        case LNK_OMON:
1204
 
        case LNK_TMON:
1205
 
        default:
1206
 
            erl_exit(1, "bad type in link list\n");
1207
 
            break;
 
3859
 
 
3860
        {
 
3861
            ExitLinkContext context = {p, reason, exit_tuple, exit_tuple_sz};
 
3862
            erts_sweep_links(lnk, &doit_exit_link, &context);
1208
3863
        }
1209
 
        del_link(&lnk);         /* will set lnk to next as well !! */
1210
3864
    }
1211
3865
 
1212
 
    if ((p->flags & F_DISTRIBUTION) && p->dist_entry)
1213
 
        do_net_exits(p->dist_entry);
 
3866
    {
 
3867
        ExitMonitorContext context = {reason, p};
 
3868
        erts_sweep_monitors(mon,&doit_exit_monitor,&context);
 
3869
    }
1214
3870
 
1215
3871
    delete_process(p);
 
3872
 
 
3873
#ifdef ERTS_ENABLE_LOCK_CHECK
 
3874
    erts_smp_proc_lock(p, ERTS_PROC_LOCK_MAIN); /* Make process_main() happy */
 
3875
#endif
1216
3876
}
1217
3877
 
1218
3878
/* Callback for process timeout */
1233
3893
void
1234
3894
cancel_timer(Process* p)
1235
3895
{
 
3896
    ERTS_SMP_LC_ASSERT(ERTS_PROC_LOCK_MAIN & erts_proc_lc_my_proc_locks(p));
 
3897
    p->flags &= ~(F_INSLPQUEUE|F_TIMO);
 
3898
#ifdef ERTS_SMP
 
3899
    erts_cancel_smp_ptimer(p->ptimer);
 
3900
#else
1236
3901
    erl_cancel_timer(&p->tm);
1237
 
    p->flags &= ~(F_INSLPQUEUE|F_TIMO);
 
3902
#endif
1238
3903
}
1239
3904
 
1240
3905
/*
1243
3908
void
1244
3909
set_timer(Process* p, Uint timeout)
1245
3910
{
 
3911
    ERTS_SMP_LC_ASSERT(ERTS_PROC_LOCK_MAIN & erts_proc_lc_my_proc_locks(p));
 
3912
 
1246
3913
    /* check for special case timeout=0 DONT ADD TO time queue */
1247
3914
    if (timeout == 0) {
1248
3915
        p->flags |= F_TIMO;
1249
3916
        return;
1250
3917
    }
 
3918
    p->flags |= F_INSLPQUEUE;
 
3919
    p->flags &= ~F_TIMO;
 
3920
 
 
3921
#ifdef ERTS_SMP
 
3922
    erts_create_smp_ptimer(&p->ptimer,
 
3923
                           p->id,
 
3924
                           (ErlTimeoutProc) timeout_proc,
 
3925
                           timeout);
 
3926
#else
1251
3927
    erl_set_timer(&p->tm,
1252
3928
                  (ErlTimeoutProc) timeout_proc,
1253
3929
                  NULL,
1254
3930
                  (void*) p,
1255
3931
                  timeout);
1256
 
    p->flags |= F_INSLPQUEUE;
1257
 
    p->flags &= ~F_TIMO;
 
3932
#endif
1258
3933
}
1259
3934
 
1260
3935
/*
1262
3937
 */
1263
3938
 
1264
3939
void
1265
 
erts_stack_dump(Process *p, CIO fd)
 
3940
erts_stack_dump(int to, void *to_arg, Process *p)
1266
3941
{
1267
3942
    Eterm* sp;
1268
3943
    int yreg = -1;
1269
3944
 
1270
 
    erts_program_counter_info(p, fd);
 
3945
    erts_program_counter_info(to, to_arg, p);
1271
3946
    for (sp = p->stop; sp < STACK_START(p); sp++) {
1272
 
        yreg = stack_element_dump(p, sp, yreg, fd);
 
3947
        yreg = stack_element_dump(to, to_arg, p, sp, yreg);
1273
3948
    }
1274
3949
}
1275
3950
 
1276
3951
void
1277
 
erts_program_counter_info(Process *p, CIO fd)
 
3952
erts_program_counter_info(int to, void *to_arg, Process *p)
1278
3953
{
1279
3954
    int i;
1280
3955
 
1281
 
    erl_printf(fd, "Program counter: 0x%x (", p->i);
1282
 
    print_function_from_pc(p->i, fd);
1283
 
    erl_printf(fd, ")\n");
1284
 
    erl_printf(fd, "CP: 0x%x (", p->cp);
1285
 
    print_function_from_pc(p->cp, fd);
1286
 
    erl_printf(fd, ")\n");
 
3956
    erts_print(to, to_arg, "Program counter: %p (", p->i);
 
3957
    print_function_from_pc(to, to_arg, p->i);
 
3958
    erts_print(to, to_arg, ")\n");
 
3959
    erts_print(to, to_arg, "CP: %p (", p->cp);
 
3960
    print_function_from_pc(to, to_arg, p->cp);
 
3961
    erts_print(to, to_arg, ")\n");
1287
3962
    if (!((p->status == P_RUNNING) || (p->status == P_GARBING))) {
1288
 
        erl_printf(fd, "arity = %d\n",p->arity);
1289
 
        for (i = 0; i < p->arity; i++) {
1290
 
            erl_printf(fd, "   ");
1291
 
            display(p->arg_reg[i], fd);
1292
 
            erl_printf(fd, "\n");
1293
 
        }
 
3963
        erts_print(to, to_arg, "arity = %d\n",p->arity);
 
3964
        for (i = 0; i < p->arity; i++)
 
3965
            erts_print(to, to_arg, "   %T\n", p->arg_reg[i]);
1294
3966
    }
1295
3967
}
1296
3968
 
1297
3969
static void
1298
 
print_function_from_pc(Eterm* x, CIO fd)
 
3970
print_function_from_pc(int to, void *to_arg, Eterm* x)
1299
3971
{
1300
3972
    Eterm* addr = find_function_from_pc(x);
1301
3973
    if (addr == NULL) {
1302
3974
        if (x == beam_exit) {
1303
 
            sys_printf(fd, "<terminate process>");
 
3975
            erts_print(to, to_arg, "<terminate process>");
1304
3976
        } else if (x == beam_apply+1) {
1305
 
            sys_printf(fd, "<terminate process normally>");
 
3977
            erts_print(to, to_arg, "<terminate process normally>");
1306
3978
        } else {
1307
 
            sys_printf(fd, "unknown function");
 
3979
            erts_print(to, to_arg, "unknown function");
1308
3980
        }
1309
3981
    } else {
1310
 
        display(addr[0], fd);
1311
 
        sys_printf(fd, ":");
1312
 
        display(addr[1], fd);
1313
 
        sys_printf(fd, "/%d", addr[2]);
1314
 
        sys_printf(fd, " + %d", ((x-addr)-2) * sizeof(Eterm));
 
3982
        erts_print(to, to_arg, "%T:%T/%d + %d",
 
3983
                   addr[0], addr[1], addr[2], ((x-addr)-2) * sizeof(Eterm));
1315
3984
    }
1316
3985
}
1317
3986
 
1318
3987
static int
1319
 
stack_element_dump(Process* p, Eterm* sp, int yreg, CIO fd)
 
3988
stack_element_dump(int to, void *to_arg, Process* p, Eterm* sp, int yreg)
1320
3989
{
1321
3990
    Eterm x = *sp;
1322
3991
 
1323
3992
    if (yreg < 0 || is_CP(x)) {
1324
 
        erl_printf(fd, "\n%-8p ", sp);
 
3993
        erts_print(to, to_arg, "\n%p ", sp);
1325
3994
    } else {
1326
3995
        char sbuf[16];
1327
3996
        sprintf(sbuf, "y(%d)", yreg);
1328
 
        sys_printf(fd, "%-8s ", sbuf);
 
3997
        erts_print(to, to_arg, "%-8s ", sbuf);
1329
3998
        yreg++;
1330
3999
    }
1331
4000
 
1332
4001
    if (is_CP(x)) {
1333
 
        sys_printf(fd, "Return addr 0x%X (", (Eterm *) x);
1334
 
        print_function_from_pc(cp_val(x), fd);
1335
 
        sys_printf(fd, ")\n");
 
4002
        erts_print(to, to_arg, "Return addr %p (", (Eterm *) x);
 
4003
        print_function_from_pc(to, to_arg, cp_val(x));
 
4004
        erts_print(to, to_arg, ")\n");
1336
4005
        yreg = 0;
1337
4006
    } else if is_catch(x) {
1338
 
        sys_printf(fd, "Catch 0x%X (", catch_pc(x));
1339
 
        print_function_from_pc(catch_pc(x), fd);
1340
 
        sys_printf(fd, ")\n");
 
4007
        erts_print(to, to_arg, "Catch %p (", catch_pc(x));
 
4008
        print_function_from_pc(to, to_arg, catch_pc(x));
 
4009
        erts_print(to, to_arg, ")\n");
1341
4010
    } else {
1342
 
        display(x, fd);
1343
 
        erl_putc('\n', fd);
 
4011
        erts_print(to, to_arg, "%T\n", x);
1344
4012
    }
1345
4013
    return yreg;
1346
4014
}
 
4015
 
 
4016