~rdoering/ubuntu/karmic/erlang/fix-535090

« back to all changes in this revision

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

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-02-15 16:42:52 UTC
  • mfrom: (1.1.13 upstream)
  • mto: (3.3.1 squeeze)
  • mto: This revision was merged to the branch mainline in revision 17.
  • Revision ID: james.westby@ubuntu.com-20090215164252-dxpjjuq108nz4noa
Upload to unstable after lenny is released.

Show diffs side-by-side

added added

removed removed

Lines of Context:
56
56
 
57
57
#define ERTS_DEFAULT_MAX_PROCESSES (1 << 15)
58
58
 
59
 
Uint erts_get_tot_proc_mem(void);
60
 
 
61
 
#define ERTS_PROC_MORE_MEM(Size) \
62
 
  (erts_smp_atomic_add(&erts_tot_proc_mem, (long) (Size)))
63
 
 
64
 
#define ERTS_PROC_LESS_MEM(Size) \
65
 
  (ASSERT_EXPR(erts_smp_atomic_read(&erts_tot_proc_mem) >= (long) (Size)), \
66
 
   erts_smp_atomic_add(&erts_tot_proc_mem, -((long) (Size))))
67
 
 
68
59
#define ERTS_HEAP_ALLOC(Type, Size)                                     \
69
 
    (ERTS_PROC_MORE_MEM((Size)),                                        \
70
 
     erts_alloc((Type), (Size)))
 
60
     erts_alloc((Type), (Size))
71
61
 
72
62
#define ERTS_HEAP_REALLOC(Type, Ptr, OldSize, NewSize)                  \
73
 
    (ERTS_PROC_LESS_MEM((OldSize)),                                     \
74
 
     ERTS_PROC_MORE_MEM((NewSize)),                                     \
75
 
     erts_realloc((Type), (Ptr), (NewSize)))
 
63
     erts_realloc((Type), (Ptr), (NewSize))
76
64
 
77
65
#define ERTS_HEAP_FREE(Type, Ptr, Size)                                 \
78
 
    (ERTS_PROC_LESS_MEM((Size)),                                        \
79
 
     erts_free((Type), (Ptr)))
 
66
     erts_free((Type), (Ptr))
80
67
 
81
68
#define INITIAL_MOD 0
82
69
#define INITIAL_FUN 1
92
79
};
93
80
 
94
81
extern Export exp_send, exp_receive, exp_timeout;
95
 
extern Uint erts_no_of_schedulers;
 
82
extern Uint erts_no_schedulers;
96
83
 
97
84
#ifdef ERTS_SMP
98
85
#include "erl_bits.h"
115
102
 
116
103
    Process *current_process;
117
104
 
 
105
    struct port *current_port;
 
106
 
 
107
    Sint yield_reduction_bump;
 
108
 
118
109
#ifdef ERTS_SMP_SCHEDULERS_NEED_TO_CHECK_CHILDREN
119
110
    /* NOTE: These fields are modified under held mutexes by other threads */
120
111
    int check_children; /* schdlq mutex */
285
276
    ErlHeapFragment* mbuf;      /* Pointer to message buffer list */
286
277
    Uint mbuf_sz;               /* Size of all message buffers */
287
278
 
 
279
    union {
288
280
#ifdef ERTS_SMP
289
 
    ErtsSmpPTimer *ptimer;
 
281
        ErtsSmpPTimer *ptimer;
290
282
#else
291
 
    ErlTimer tm;                /* Timer entry */
 
283
        ErlTimer tm;            /* Timer entry */
292
284
#endif
 
285
        void *exit_data;        /* Misc data referred during termination */
 
286
    } u;
293
287
 
294
288
#ifdef ERTS_SMP
295
289
    erts_proc_lock_t lock;
471
465
};
472
466
extern struct erts_system_profile_flags_t erts_system_profile_flags;
473
467
 
474
 
extern erts_smp_atomic_t erts_tot_proc_mem;
475
 
 
476
468
#define INVALID_PID(p, pid)     ((p) == NULL                            \
477
469
                                 || (p)->id != (pid)                    \
478
470
                                 || (p)->status == P_EXITING)
531
523
#define F_TRACE_SCHED_PROCS  (1 << 19) /* With virtual scheduling */
532
524
#define F_TRACE_PORTS        (1 << 20) /* Ports equivalent to F_TRACE_PROCS */
533
525
#define F_TRACE_SCHED_NO     (1 << 21) /* Trace with scheduler id */
 
526
#define F_TRACE_SCHED_EXIT   (1 << 22)
534
527
 
535
 
#define F_NUM_FLAGS          22
 
528
#define F_NUM_FLAGS          23
536
529
#ifdef DEBUG
537
530
#  define F_INITIAL_TRACE_FLAGS (5 << F_NUM_FLAGS)
538
531
#else
541
534
 
542
535
 
543
536
 
544
 
#define TRACEE_FLAGS (  F_TRACE_PROCS | F_TRACE_CALLS \
 
537
#define TRACEE_FLAGS ( F_TRACE_PROCS | F_TRACE_CALLS \
545
538
                     | F_TRACE_SOS |  F_TRACE_SOS1| F_TRACE_RECEIVE  \
546
 
                     | F_TRACE_SOL | F_TRACE_SOL1 | F_TRACE_SEND | \
547
 
                     F_TRACE_SCHED | F_TIMESTAMP | F_TRACE_GC  | \
548
 
                     F_TRACE_ARITY_ONLY | F_TRACE_RETURN_TO | \
549
 
                     F_TRACE_SILENT | F_TRACE_SCHED_PROCS | F_TRACE_PORTS | \
550
 
                     F_TRACE_SCHED_PORTS | F_TRACE_SCHED_NO)
 
539
                     | F_TRACE_SOL | F_TRACE_SOL1 | F_TRACE_SEND \
 
540
                     | F_TRACE_SCHED | F_TIMESTAMP | F_TRACE_GC \
 
541
                     | F_TRACE_ARITY_ONLY | F_TRACE_RETURN_TO \
 
542
                     | F_TRACE_SILENT | F_TRACE_SCHED_PROCS | F_TRACE_PORTS \
 
543
                     | F_TRACE_SCHED_PORTS | F_TRACE_SCHED_NO \
 
544
                     | F_TRACE_SCHED_EXIT)
 
545
 
 
546
#define ERTS_TRACEE_MODIFIER_FLAGS \
 
547
  (F_TRACE_SILENT | F_TIMESTAMP | F_TRACE_SCHED_NO)
 
548
#define ERTS_PORT_TRACEE_FLAGS \
 
549
  (ERTS_TRACEE_MODIFIER_FLAGS | F_TRACE_PORTS | F_TRACE_SCHED_PORTS)
 
550
#define ERTS_PROC_TRACEE_FLAGS \
 
551
  ((TRACEE_FLAGS & ~ERTS_PORT_TRACEE_FLAGS) | ERTS_TRACEE_MODIFIER_FLAGS)
551
552
 
552
553
/* Sequential trace flags */
553
554
#define SEQ_TRACE_SEND     (1 << 0)
629
630
int erts_block_multi_scheduling(Process *, ErtsProcLocks, int, int);
630
631
int erts_is_multi_scheduling_blocked(void);
631
632
Eterm erts_multi_scheduling_blockers(Process *);
632
 
void erts_start_schedulers(Uint);
 
633
void erts_start_schedulers(void);
633
634
void erts_smp_notify_check_children_needed(void);
634
635
#endif
635
636
void erts_init_process(void);
640
641
void erts_schedule_misc_op(void (*)(void *), void *);
641
642
Eterm erl_create_process(Process*, Eterm, Eterm, Eterm, ErlSpawnOpts*);
642
643
void erts_do_exit_process(Process*, Eterm);
 
644
void erts_continue_exit_process(Process *);
643
645
void set_timer(Process*, Uint);
644
646
void cancel_timer(Process*);
645
647
/* Begin System profile */
682
684
#define ERTS_PROC_PENDING_EXIT(P) 0
683
685
#endif
684
686
 
685
 
#ifdef ERTS_SMP
686
 
Process *erts_suspend_another_process(Process *c_p, ErtsProcLocks c_p_locks,
687
 
                                      Eterm suspendee, ErtsProcLocks suspendee_locks);
688
 
#endif
689
687
void erts_deep_process_dump(int, void *);
690
688
 
691
689
Sint erts_test_next_pid(int, Uint);
714
712
 
715
713
ERTS_GLB_INLINE Process *erts_get_current_process(void);
716
714
ERTS_GLB_INLINE Eterm erts_get_current_pid(void);
 
715
ERTS_GLB_INLINE Uint erts_get_scheduler_id(void);
717
716
 
718
717
 
719
718
#if ERTS_GLB_INLINE_INCL_FUNC_DEF
732
731
    return proc ? proc->id : THE_NON_VALUE;
733
732
}
734
733
 
 
734
ERTS_GLB_INLINE
 
735
Uint erts_get_scheduler_id(void)
 
736
{
 
737
#ifdef ERTS_SMP
 
738
    ErtsSchedulerData *esdp = erts_get_scheduler_data();
 
739
    return esdp ? esdp->no : (Uint) 0;
 
740
#else
 
741
    return erts_get_scheduler_data() ? (Uint) 1 : (Uint) 0;
 
742
#endif
 
743
}
 
744
 
735
745
#endif /* #if ERTS_GLB_INLINE_INCL_FUNC_DEF */
736
746
 
737
747
#ifdef ERTS_SMP