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

« back to all changes in this revision

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

  • Committer: Bazaar Package Importer
  • Author(s): Sergei Golovan
  • Date: 2009-06-11 12:18:07 UTC
  • mfrom: (1.2.2 upstream)
  • Revision ID: james.westby@ubuntu.com-20090611121807-ks7eb4xrt7dsysgx
Tags: 1:13.b.1-dfsg-1
* New upstream release.
* Removed unnecessary dependency of erlang-os-mon on erlang-observer and
  erlang-tools and added missing dependency of erlang-nox on erlang-os-mon
  (closes: #529512).
* Removed a patch to eunit application because the bug was fixed upstream.

Show diffs side-by-side

added added

removed removed

Lines of Context:
43
43
#include "erl_process.h"
44
44
#include "erl_monitors.h"
45
45
#include "erl_smp.h"
46
 
 
 
46
#define ERTS_PORT_TASK_ONLY_BASIC_TYPES__
 
47
#include "erl_port_task.h"
 
48
#undef ERTS_PORT_TASK_ONLY_BASIC_TYPES__
 
49
 
47
50
#define ERST_INTERNAL_CHANNEL_NO 0
48
51
 
49
 
#define ERTS_DE_SFLG_INITIALIZING                       (((Uint32) 1) <<  0)
50
 
#define ERTS_DE_SFLG_CONNECTED                          (((Uint32) 1) <<  1)
51
 
#define ERTS_DE_SFLG_EXITING                            (((Uint32) 1) <<  2)
 
52
#define ERTS_DE_SFLG_CONNECTED                  (((Uint32) 1) <<  0)
 
53
#define ERTS_DE_SFLG_EXITING                    (((Uint32) 1) <<  1)
 
54
 
 
55
#define ERTS_DE_SFLGS_ALL                       (ERTS_DE_SFLG_CONNECTED \
 
56
                                                 | ERTS_DE_SFLG_EXITING)
 
57
 
 
58
#define ERTS_DE_QFLG_BUSY                       (((Uint32) 1) <<  0)
 
59
#define ERTS_DE_QFLG_EXIT                       (((Uint32) 1) <<  1)
 
60
 
 
61
#define ERTS_DE_QFLGS_ALL                       (ERTS_DE_QFLG_BUSY \
 
62
                                                 | ERTS_DE_QFLG_EXIT)
 
63
 
 
64
#ifdef ARCH_64
 
65
#define ERTS_DIST_OUTPUT_BUF_DBG_PATTERN ((Uint) 0xf713f713f713f713UL)
 
66
#else
 
67
#define ERTS_DIST_OUTPUT_BUF_DBG_PATTERN ((Uint) 0xf713f713)
 
68
#endif
 
69
 
 
70
typedef struct ErtsDistOutputBuf_ ErtsDistOutputBuf;
 
71
struct ErtsDistOutputBuf_ {
 
72
#ifdef DEBUG
 
73
    Uint dbg_pattern;
 
74
#endif
 
75
    ErtsDistOutputBuf *next;
 
76
    byte *extp;
 
77
    byte *ext_endp;
 
78
    byte data[1];
 
79
};
 
80
 
 
81
typedef struct {
 
82
    ErtsDistOutputBuf *first;
 
83
    ErtsDistOutputBuf *last;
 
84
} ErtsDistOutputQueue;
 
85
 
 
86
struct ErtsProcList_;
 
87
typedef struct {
 
88
    struct ErtsProcList_ *first;
 
89
    struct ErtsProcList_ *last;
 
90
} ErtsDistSuspended;
52
91
 
53
92
/*
54
93
 * Lock order:
55
 
 *   1. dist_entry->mtxp
56
 
 *   2. erts_node_table_mtx
57
 
 *   3. erts_dist_table_mtx
 
94
 *   1. dist_entry->rwmtx
 
95
 *   2. erts_node_table_rwmtx
 
96
 *   3. erts_dist_table_rwmtx
58
97
 *
59
98
 *   Lock mutexes with lower numbers before mutexes with higher numbers and
60
99
 *   unlock mutexes with higher numbers before mutexes with higher numbers.
61
100
 */
62
101
 
63
102
struct erl_link;
64
 
struct process;
65
103
struct port;
66
104
 
67
105
typedef struct dist_entry_ {
69
107
    struct dist_entry_ *next;   /* Next entry in dist_table (not sorted) */
70
108
    struct dist_entry_ *prev;   /* Previous entry in dist_table (not sorted) */
71
109
    erts_refc_t refc;           /* Reference count */
 
110
 
 
111
    erts_smp_rwmtx_t rwmtx;     /* Protects all fields below until lck_mtx. */
72
112
    Eterm sysname;              /* name@host atom for efficiency */
73
113
    Uint32 creation;            /* creation of connected node */
74
114
    Eterm cid;                  /* connection handler (pid or port), NIL == free */
 
115
    Uint32 connection_id;       /* Connection id incremented on connect */
 
116
    Uint32 status;              /* Slot status, like exiting reserved etc */
 
117
    Uint32 flags;               /* Distribution flags, like hidden, 
 
118
                                   atom cache etc. */
 
119
    unsigned long version;      /* Protocol version */
 
120
 
 
121
 
 
122
    erts_smp_mtx_t lnk_mtx;     /* Protects node_links, nlinks, and
 
123
                                   monitors. */
75
124
    ErtsLink *node_links;       /* In a dist entry, node links are kept 
76
125
                                   in a separate tree, while they are 
77
126
                                   colocted with the ordinary link tree
81
130
                                */
82
131
    ErtsLink *nlinks;           /* Link tree with subtrees */
83
132
    ErtsMonitor *monitors;      /* Monitor tree */
84
 
    Uint32 status;              /* Slot status, like exiting reserved etc */
85
 
    Uint32 flags;               /* Distribution flags, like hidden, 
86
 
                                   atom cache etc. */
 
133
 
 
134
    erts_smp_spinlock_t qlock;  /* Protects qflgs and out_queue */
 
135
    Uint32 qflgs;
 
136
    Sint qsize;
 
137
    ErtsDistOutputQueue out_queue;
 
138
    ErtsDistSuspended suspended;
 
139
 
 
140
    ErtsDistOutputQueue finalized_out_queue;
 
141
    erts_smp_atomic_t dist_cmd_scheduled;
 
142
    ErtsPortTaskHandle dist_cmd;
 
143
 
 
144
    Uint (*send)(struct port *prt, ErtsDistOutputBuf *obuf);
 
145
 
87
146
    struct cache* cache;        /* The atom cache */
88
 
    unsigned long version;      /* Protocol version */
89
 
#ifdef ERTS_SMP
90
 
    erts_smp_mtx_t *mtxp;
91
 
#endif
92
 
 
93
147
} DistEntry;
94
148
 
95
149
typedef struct erl_node_ {
103
157
 
104
158
extern Hash erts_dist_table;
105
159
extern Hash erts_node_table;
106
 
extern erts_smp_mtx_t erts_dist_table_mtx;
107
 
extern erts_smp_mtx_t erts_node_table_mtx;
 
160
extern erts_smp_rwmtx_t erts_dist_table_rwmtx;
 
161
extern erts_smp_rwmtx_t erts_node_table_rwmtx;
108
162
 
109
163
extern DistEntry *erts_hidden_dist_entries;
110
164
extern DistEntry *erts_visible_dist_entries;
116
170
extern DistEntry *erts_this_dist_entry;
117
171
extern ErlNode *erts_this_node;
118
172
 
119
 
#ifdef ERTS_SMP
120
 
#define ERTS_SMP_LOCK_NODE_TABLES_AND_ENTRIES \
121
 
  erts_lock_node_tables_and_entries()
122
 
#define ERTS_SMP_UNLOCK_NODE_TABLES_AND_ENTRIES \
123
 
  erts_unlock_node_tables_and_entries()
124
 
void erts_lock_node_tables_and_entries(void);
125
 
void erts_unlock_node_tables_and_entries(void);
126
 
#else
127
 
#define ERTS_SMP_LOCK_NODE_TABLES_AND_ENTRIES
128
 
#define ERTS_SMP_UNLOCK_NODE_TABLES_AND_ENTRIES
129
 
#endif
130
 
 
131
173
DistEntry *erts_channel_no_to_dist_entry(Uint);
132
174
DistEntry *erts_sysname_to_connected_dist_entry(Eterm);
133
175
DistEntry *erts_find_or_insert_dist_entry(Eterm);
146
188
void erts_print_node_info(int, void *, Eterm, int*, int*);
147
189
Eterm erts_get_node_and_dist_references(struct process *);
148
190
#if defined(ERTS_SMP) && defined(ERTS_ENABLE_LOCK_CHECK)
149
 
int erts_lc_is_dist_entry_locked(DistEntry *);
 
191
int erts_lc_is_de_rwlocked(DistEntry *);
 
192
int erts_lc_is_de_rlocked(DistEntry *);
150
193
#endif
151
194
 
152
195
ERTS_GLB_INLINE void erts_deref_dist_entry(DistEntry *dep);
153
196
ERTS_GLB_INLINE void erts_deref_node_entry(ErlNode *np);
154
 
ERTS_GLB_INLINE void erts_smp_dist_entry_lock(DistEntry *dep);
155
 
ERTS_GLB_INLINE void erts_smp_dist_entry_unlock(DistEntry *dep);
 
197
ERTS_GLB_INLINE void erts_smp_de_rlock(DistEntry *dep);
 
198
ERTS_GLB_INLINE void erts_smp_de_runlock(DistEntry *dep);
 
199
ERTS_GLB_INLINE void erts_smp_de_rwlock(DistEntry *dep);
 
200
ERTS_GLB_INLINE void erts_smp_de_rwunlock(DistEntry *dep);
 
201
ERTS_GLB_INLINE void erts_smp_de_links_lock(DistEntry *dep);
 
202
ERTS_GLB_INLINE void erts_smp_de_links_unlock(DistEntry *dep);
156
203
 
157
204
#if ERTS_GLB_INLINE_INCL_FUNC_DEF
158
205
 
173
220
}
174
221
 
175
222
ERTS_GLB_INLINE void
176
 
erts_smp_dist_entry_lock(DistEntry *dep)
177
 
{
178
 
#ifdef ERTS_SMP
179
 
    erts_smp_mtx_lock(dep->mtxp);
180
 
#endif
181
 
}
182
 
 
183
 
ERTS_GLB_INLINE void
184
 
erts_smp_dist_entry_unlock(DistEntry *dep)
185
 
{
186
 
#ifdef ERTS_SMP
187
 
    erts_smp_mtx_unlock(dep->mtxp);
188
 
#endif
 
223
erts_smp_de_rlock(DistEntry *dep)
 
224
{
 
225
    erts_smp_rwmtx_rlock(&dep->rwmtx);
 
226
}
 
227
 
 
228
ERTS_GLB_INLINE void
 
229
erts_smp_de_runlock(DistEntry *dep)
 
230
{
 
231
    erts_smp_rwmtx_runlock(&dep->rwmtx);
 
232
}
 
233
 
 
234
ERTS_GLB_INLINE void
 
235
erts_smp_de_rwlock(DistEntry *dep)
 
236
{
 
237
    erts_smp_rwmtx_rwlock(&dep->rwmtx);
 
238
}
 
239
 
 
240
ERTS_GLB_INLINE void
 
241
erts_smp_de_rwunlock(DistEntry *dep)
 
242
{
 
243
    erts_smp_rwmtx_rwunlock(&dep->rwmtx);
 
244
}
 
245
 
 
246
ERTS_GLB_INLINE void
 
247
erts_smp_de_links_lock(DistEntry *dep)
 
248
{
 
249
    erts_smp_mtx_lock(&dep->lnk_mtx);
 
250
}
 
251
 
 
252
ERTS_GLB_INLINE void
 
253
erts_smp_de_links_unlock(DistEntry *dep)
 
254
{
 
255
    erts_smp_mtx_unlock(&dep->lnk_mtx);
189
256
}
190
257
 
191
258
#endif /* #if ERTS_GLB_INLINE_INCL_FUNC_DEF */