1 /*
2  * %CopyrightBegin%
3  *
4  * Copyright Ericsson AB 2007-2018. All Rights Reserved.
5  *
6  * Licensed under the Apache License, Version 2.0 (the "License");
7  * you may not use this file except in compliance with the License.
8  * You may obtain a copy of the License at
9  *
10  *     http://www.apache.org/licenses/LICENSE-2.0
11  *
12  * Unless required by applicable law or agreed to in writing, software
13  * distributed under the License is distributed on an "AS IS" BASIS,
14  * WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
15  * See the License for the specific language governing permissions and
16  * limitations under the License.
17  *
18  * %CopyrightEnd%
19  */
20 
21 
22 /*
23  * Description:	Implementation of Erlang process locks.
24  *
25  * Author: 	Rickard Green
26  */
27 
28 #ifndef ERTS_PROC_LOCK_TYPE__
29 #define ERTS_PROC_LOCK_TYPE__
30 
31 #ifdef ERTS_ENABLE_LOCK_CHECK
32 #define ERTS_PROC_LOCK_DEBUG
33 #endif
34 
35 #ifdef ERTS_ENABLE_LOCK_COUNT
36 #include "erl_lock_count.h"
37 #endif
38 
39 #include "erl_threads.h"
40 
41 #if defined(VALGRIND) || defined(ETHR_DISABLE_NATIVE_IMPLS)
42 #  define ERTS_PROC_LOCK_OWN_IMPL 0
43 #else
44 #  define ERTS_PROC_LOCK_OWN_IMPL 1
45 #endif
46 
47 #define ERTS_PROC_LOCK_ATOMIC_IMPL 0
48 #define ERTS_PROC_LOCK_SPINLOCK_IMPL 0
49 #define ERTS_PROC_LOCK_MUTEX_IMPL 0
50 
51 #if !ERTS_PROC_LOCK_OWN_IMPL
52 #define ERTS_PROC_LOCK_RAW_MUTEX_IMPL 1
53 #else
54 #define ERTS_PROC_LOCK_RAW_MUTEX_IMPL 0
55 
56 #if defined(ETHR_HAVE_32BIT_NATIVE_ATOMIC_OPS)
57 #  undef ERTS_PROC_LOCK_ATOMIC_IMPL
58 #  define ERTS_PROC_LOCK_ATOMIC_IMPL 1
59 #elif defined(ETHR_HAVE_NATIVE_SPINLOCKS)
60 #  undef ERTS_PROC_LOCK_SPINLOCK_IMPL
61 #  define ERTS_PROC_LOCK_SPINLOCK_IMPL 1
62 #else
63 #  undef ERTS_PROC_LOCK_MUTEX_IMPL
64 #  define ERTS_PROC_LOCK_MUTEX_IMPL 1
65 #endif
66 
67 #endif
68 
69 #define ERTS_PROC_LOCK_MAX_BIT 4
70 
71 typedef erts_aint32_t ErtsProcLocks;
72 
73 typedef struct erts_proc_lock_t_ {
74 #if ERTS_PROC_LOCK_OWN_IMPL
75 #if ERTS_PROC_LOCK_ATOMIC_IMPL
76     erts_atomic32_t flags;
77 #else
78     ErtsProcLocks flags;
79 #endif
80     erts_tse_t *queue[ERTS_PROC_LOCK_MAX_BIT+1];
81 #if defined(ERTS_ENABLE_LOCK_COUNT) && !ERTS_PROC_LOCK_RAW_MUTEX_IMPL
82     /* Each erts_mtx_t has its own lock counter ^ */
83 
84     #define ERTS_LCNT_PROCLOCK_IDX_MAIN 0
85     #define ERTS_LCNT_PROCLOCK_IDX_MSGQ 1
86     #define ERTS_LCNT_PROCLOCK_IDX_BTM 2
87     #define ERTS_LCNT_PROCLOCK_IDX_STATUS 3
88     #define ERTS_LCNT_PROCLOCK_IDX_TRACE 4
89 
90     #define ERTS_LCNT_PROCLOCK_COUNT 5
91 
92     erts_lcnt_ref_t lcnt_carrier;
93 #endif
94 #elif ERTS_PROC_LOCK_RAW_MUTEX_IMPL
95     erts_mtx_t main;
96     erts_mtx_t msgq;
97     erts_mtx_t btm;
98     erts_mtx_t status;
99     erts_mtx_t trace;
100 #else
101 #  error "no implementation"
102 #endif
103 #ifdef ERTS_PROC_LOCK_DEBUG
104     erts_atomic32_t locked[ERTS_PROC_LOCK_MAX_BIT+1];
105 #endif
106 } erts_proc_lock_t;
107 
108 /* Process lock flags */
109 
110 /*
111  * Main lock:
112  *   The main lock is held by the scheduler running a process. It
113  *   is used to protect all fields in the process structure except
114  *   for those fields protected by other process locks (follows).
115  */
116 #define ERTS_PROC_LOCK_MAIN		(((ErtsProcLocks) 1) << 0)
117 
118 /*
119  * Message queue lock:
120  *   Protects the following fields in the process structure:
121  *   * msg_inq
122  */
123 #define ERTS_PROC_LOCK_MSGQ		(((ErtsProcLocks) 1) << 1)
124 
125 /*
126  * Bif timer lock:
127  *   Protects the following fields in the process structure:
128  *   * bif_timers
129  */
130 #define ERTS_PROC_LOCK_BTM		(((ErtsProcLocks) 1) << 2)
131 
132 /*
133  * Status lock:
134  *   Protects the following fields in the process structure:
135  *   * pending_suspenders
136  *   * suspendee
137  *   * sys_tasks
138  *   * ...
139  */
140 #define ERTS_PROC_LOCK_STATUS		(((ErtsProcLocks) 1) << 3)
141 
142 /*
143  * Trace message lock:
144  *   Protects the order in which messages are sent
145  *   from trace nifs. This lock is taken inside enif_send.
146  *
147  */
148 #define ERTS_PROC_LOCK_TRACE            (((ErtsProcLocks) 1) << ERTS_PROC_LOCK_MAX_BIT)
149 
150 /*
151  * Special fields:
152  *
153  *   The following fields are read only and can be read if at
154  *   least one process lock (whichever one doesn't matter)
155  *   is held, or if the process structure is guaranteed not to
156  *   disappear by other means (e.g. pix lock is held):
157  *     * id
158  *
159  *   The following fields are only allowed to be written if
160  *   all process locks are held, and are allowed to be read if
161  *   at least one process lock (whichever one doesn't matter)
162  *   is held:
163  *     * common.tracer
164  *     * common.trace_flags
165  *
166  *   The following fields are only allowed to be accessed if
167  *   both the schedule queue lock and at least one process lock
168  *   (whichever one doesn't matter) are held:
169  *     * prio
170  *     * next
171  *     * scheduler_flags
172  */
173 
174 /*
175  * Other rules regarding process locking:
176  *
177  * Exiting processes:
178  *   When changing state to exiting (ERTS_PSFLG_EXITING) on a process,
179  *   you are required to take all process locks (ERTS_PROC_LOCKS_ALL).
180  *   Thus, by holding at least one process lock (whichever one doesn't
181  *   matter) you are guaranteed that the process won't exit until the
182  *   lock you are holding has been released.
183  *
184  * Lock order:
185  *   Process locks with low numeric values has to be locked before
186  *   process locks with high numeric values. E.g., main locks has
187  *   to be locked before message queue locks.
188  *
189  *   When process locks with the same numeric value are to be locked
190  *   on multiple processes, locks on processes with low process ids
191  *   have to be locked before locks on processes with high process
192  *   ids. E.g., if the main and the message queue locks are to be
193  *   locked on processes p1 and p2 and p1->common.id < p2->common.id,
194  *   then locks should be locked in the following order:
195  *     1. main lock on p1
196  *     2. main lock on p2
197  *     3. message queue lock on p1
198  *     4. message queue lock on p2
199  */
200 
201 /* Other lock flags */
202 #define ERTS_PROC_LOCK_WAITER_SHIFT (ERTS_PROC_LOCK_MAX_BIT + 1)
203 
204 
205 /* ERTS_PROC_LOCKS_* are combinations of process locks */
206 
207 #define ERTS_PROC_LOCKS_MSG_RECEIVE	ERTS_PROC_LOCK_MSGQ
208 #define ERTS_PROC_LOCKS_MSG_SEND	ERTS_PROC_LOCK_MSGQ
209 #define ERTS_PROC_LOCKS_XSIG_SEND	ERTS_PROC_LOCK_STATUS
210 
211 #define ERTS_PROC_LOCKS_ALL \
212   ((((ErtsProcLocks) 1) << (ERTS_PROC_LOCK_MAX_BIT + 1)) - 1)
213 
214 #define ERTS_PROC_LOCKS_ALL_MINOR	(ERTS_PROC_LOCKS_ALL \
215                                          & ~ERTS_PROC_LOCK_MAIN)
216 
217 /* All locks we first must unlock to lock L */
218 #define ERTS_PROC_LOCKS_HIGHER_THAN(L) \
219   (ERTS_PROC_LOCKS_ALL & (~(L) & ~((L)-1)))
220 
221 
222 #define ERTS_PIX_LOCKS_BITS		10
223 #define ERTS_NO_OF_PIX_LOCKS		(1 << ERTS_PIX_LOCKS_BITS)
224 
225 
226 #endif /* #ifndef ERTS_PROC_LOCK_TYPE__ */
227 
228 #ifndef ERTS_PROCESS_LOCK_ONLY_PROC_LOCK_TYPE__
229 #ifndef ERTS_PROC_LOCK_LOCK_CHECK__
230 #define  ERTS_PROC_LOCK_LOCK_CHECK__
231 
232 /* Lock counter implemetation */
233 
234 #ifdef ERTS_ENABLE_LOCK_POSITION
235 #define erts_proc_lock__(P,I,L) erts_proc_lock_x__(P,I,L,__FILE__,__LINE__)
236 #define erts_proc_lock(P,L) erts_proc_lock_x(P,L,__FILE__,__LINE__)
237 #endif
238 
239 #if defined (ERTS_ENABLE_LOCK_COUNT)
240 
241 void erts_lcnt_proc_lock_init(Process *p);
242 void erts_lcnt_proc_lock_destroy(Process *p);
243 
244 ERTS_GLB_INLINE
245 void erts_lcnt_proc_lock(erts_proc_lock_t *lock, ErtsProcLocks locks);
246 ERTS_GLB_INLINE
247 void erts_lcnt_proc_lock_post_x(erts_proc_lock_t *lock, ErtsProcLocks locks,
248                                 const char *file, unsigned int line);
249 ERTS_GLB_INLINE
250 void erts_lcnt_proc_lock_unacquire(erts_proc_lock_t *lock, ErtsProcLocks locks);
251 ERTS_GLB_INLINE
252 void erts_lcnt_proc_unlock(erts_proc_lock_t *lock, ErtsProcLocks locks);
253 ERTS_GLB_INLINE
254 void erts_lcnt_proc_trylock(erts_proc_lock_t *lock, ErtsProcLocks locks, int res);
255 
256 void erts_lcnt_enable_proc_lock_count(Process *proc, int enable);
257 void erts_lcnt_update_process_locks(int enable);
258 
259 #if ERTS_GLB_INLINE_INCL_FUNC_DEF
260 
261 ERTS_GLB_INLINE
erts_lcnt_proc_lock(erts_proc_lock_t * lock,ErtsProcLocks locks)262 void erts_lcnt_proc_lock(erts_proc_lock_t *lock, ErtsProcLocks locks) {
263     erts_lcnt_lock_info_carrier_t *carrier;
264     int handle;
265 
266     if(erts_lcnt_open_ref(&lock->lcnt_carrier, &handle, &carrier)) {
267         if (locks & ERTS_PROC_LOCK_MAIN) {
268             erts_lcnt_lock_idx(carrier, ERTS_LCNT_PROCLOCK_IDX_MAIN);
269         }
270         if (locks & ERTS_PROC_LOCK_MSGQ) {
271             erts_lcnt_lock_idx(carrier, ERTS_LCNT_PROCLOCK_IDX_MSGQ);
272         }
273         if (locks & ERTS_PROC_LOCK_BTM) {
274             erts_lcnt_lock_idx(carrier, ERTS_LCNT_PROCLOCK_IDX_BTM);
275         }
276         if (locks & ERTS_PROC_LOCK_STATUS) {
277             erts_lcnt_lock_idx(carrier, ERTS_LCNT_PROCLOCK_IDX_STATUS);
278         }
279         if (locks & ERTS_PROC_LOCK_TRACE) {
280             erts_lcnt_lock_idx(carrier, ERTS_LCNT_PROCLOCK_IDX_TRACE);
281         }
282 
283         erts_lcnt_close_ref(handle, carrier);
284     }
285 }
286 
287 ERTS_GLB_INLINE
erts_lcnt_proc_lock_post_x(erts_proc_lock_t * lock,ErtsProcLocks locks,const char * file,unsigned int line)288 void erts_lcnt_proc_lock_post_x(erts_proc_lock_t *lock, ErtsProcLocks locks,
289                                 const char *file, unsigned int line) {
290     erts_lcnt_lock_info_carrier_t *carrier;
291     int handle;
292 
293     if(erts_lcnt_open_ref(&lock->lcnt_carrier, &handle, &carrier)) {
294         if (locks & ERTS_PROC_LOCK_MAIN) {
295             erts_lcnt_lock_post_x_idx(carrier, ERTS_LCNT_PROCLOCK_IDX_MAIN, file, line);
296         }
297         if (locks & ERTS_PROC_LOCK_MSGQ) {
298             erts_lcnt_lock_post_x_idx(carrier, ERTS_LCNT_PROCLOCK_IDX_MSGQ, file, line);
299         }
300         if (locks & ERTS_PROC_LOCK_BTM) {
301             erts_lcnt_lock_post_x_idx(carrier, ERTS_LCNT_PROCLOCK_IDX_BTM, file, line);
302         }
303         if (locks & ERTS_PROC_LOCK_STATUS) {
304             erts_lcnt_lock_post_x_idx(carrier, ERTS_LCNT_PROCLOCK_IDX_STATUS, file, line);
305         }
306         if (locks & ERTS_PROC_LOCK_TRACE) {
307             erts_lcnt_lock_post_x_idx(carrier, ERTS_LCNT_PROCLOCK_IDX_TRACE, file, line);
308         }
309 
310         erts_lcnt_close_ref(handle, carrier);
311     }
312 }
313 
314 ERTS_GLB_INLINE
erts_lcnt_proc_lock_unacquire(erts_proc_lock_t * lock,ErtsProcLocks locks)315 void erts_lcnt_proc_lock_unacquire(erts_proc_lock_t *lock, ErtsProcLocks locks) {
316     erts_lcnt_lock_info_carrier_t *carrier;
317     int handle;
318 
319     if(erts_lcnt_open_ref(&lock->lcnt_carrier, &handle, &carrier)) {
320         if (locks & ERTS_PROC_LOCK_MAIN) {
321             erts_lcnt_lock_unacquire_idx(carrier, ERTS_LCNT_PROCLOCK_IDX_MAIN);
322         }
323         if (locks & ERTS_PROC_LOCK_MSGQ) {
324             erts_lcnt_lock_unacquire_idx(carrier, ERTS_LCNT_PROCLOCK_IDX_MSGQ);
325         }
326         if (locks & ERTS_PROC_LOCK_BTM) {
327             erts_lcnt_lock_unacquire_idx(carrier, ERTS_LCNT_PROCLOCK_IDX_BTM);
328         }
329         if (locks & ERTS_PROC_LOCK_STATUS) {
330             erts_lcnt_lock_unacquire_idx(carrier, ERTS_LCNT_PROCLOCK_IDX_STATUS);
331         }
332         if (locks & ERTS_PROC_LOCK_TRACE) {
333             erts_lcnt_lock_unacquire_idx(carrier, ERTS_LCNT_PROCLOCK_IDX_TRACE);
334         }
335 
336         erts_lcnt_close_ref(handle, carrier);
337     }
338 }
339 
340 ERTS_GLB_INLINE
erts_lcnt_proc_unlock(erts_proc_lock_t * lock,ErtsProcLocks locks)341 void erts_lcnt_proc_unlock(erts_proc_lock_t *lock, ErtsProcLocks locks) {
342     erts_lcnt_lock_info_carrier_t *carrier;
343     int handle;
344 
345     if(erts_lcnt_open_ref(&lock->lcnt_carrier, &handle, &carrier)) {
346         if (locks & ERTS_PROC_LOCK_MAIN) {
347             erts_lcnt_unlock_idx(carrier, ERTS_LCNT_PROCLOCK_IDX_MAIN);
348         }
349         if (locks & ERTS_PROC_LOCK_MSGQ) {
350             erts_lcnt_unlock_idx(carrier, ERTS_LCNT_PROCLOCK_IDX_MSGQ);
351         }
352         if (locks & ERTS_PROC_LOCK_BTM) {
353             erts_lcnt_unlock_idx(carrier, ERTS_LCNT_PROCLOCK_IDX_BTM);
354         }
355         if (locks & ERTS_PROC_LOCK_STATUS) {
356             erts_lcnt_unlock_idx(carrier, ERTS_LCNT_PROCLOCK_IDX_STATUS);
357         }
358         if (locks & ERTS_PROC_LOCK_TRACE) {
359             erts_lcnt_unlock_idx(carrier, ERTS_LCNT_PROCLOCK_IDX_TRACE);
360         }
361 
362         erts_lcnt_close_ref(handle, carrier);
363     }
364 }
365 
366 ERTS_GLB_INLINE
erts_lcnt_proc_trylock(erts_proc_lock_t * lock,ErtsProcLocks locks,int res)367 void erts_lcnt_proc_trylock(erts_proc_lock_t *lock, ErtsProcLocks locks, int res) {
368     erts_lcnt_lock_info_carrier_t *carrier;
369     int handle;
370 
371     if(erts_lcnt_open_ref(&lock->lcnt_carrier, &handle, &carrier)) {
372         if (locks & ERTS_PROC_LOCK_MAIN) {
373             erts_lcnt_trylock_idx(carrier, ERTS_LCNT_PROCLOCK_IDX_MAIN, res);
374         }
375         if (locks & ERTS_PROC_LOCK_MSGQ) {
376             erts_lcnt_trylock_idx(carrier, ERTS_LCNT_PROCLOCK_IDX_MSGQ, res);
377         }
378         if (locks & ERTS_PROC_LOCK_BTM) {
379             erts_lcnt_trylock_idx(carrier, ERTS_LCNT_PROCLOCK_IDX_BTM, res);
380         }
381         if (locks & ERTS_PROC_LOCK_STATUS) {
382             erts_lcnt_trylock_idx(carrier, ERTS_LCNT_PROCLOCK_IDX_STATUS, res);
383         }
384         if (locks & ERTS_PROC_LOCK_TRACE) {
385             erts_lcnt_trylock_idx(carrier, ERTS_LCNT_PROCLOCK_IDX_TRACE, res);
386         }
387 
388         erts_lcnt_close_ref(handle, carrier);
389     }
390 } /* reversed logic */
391 
392 #endif /* ERTS_GLB_INLINE_INCL_FUNC_DEF */
393 #endif /* ERTS_ENABLE_LOCK_COUNT*/
394 
395 
396 
397 /* --- Process lock checking ----------------------------------------------- */
398 
399 #if defined(ERTS_ENABLE_LOCK_CHECK)
400 #define ERTS_CHK_NO_PROC_LOCKS \
401   erts_proc_lc_chk_no_proc_locks(__FILE__, __LINE__)
402 #define ERTS_CHK_HAVE_ONLY_MAIN_PROC_LOCK(P) \
403   erts_proc_lc_chk_only_proc_main((P))
404 void erts_proc_lc_lock(Process *p, ErtsProcLocks locks,
405 		       const char *file, unsigned int line);
406 void erts_proc_lc_trylock(Process *p, ErtsProcLocks locks, int locked,
407 			  const char *file, unsigned int line);
408 void erts_proc_lc_unlock(Process *p, ErtsProcLocks locks);
409 void erts_proc_lc_might_unlock(Process *p, ErtsProcLocks locks);
410 void erts_proc_lc_chk_have_proc_locks(Process *p, ErtsProcLocks locks);
411 void erts_proc_lc_chk_proc_locks(Process *p, ErtsProcLocks locks);
412 void erts_proc_lc_chk_only_proc_main(Process *p);
413 void erts_proc_lc_chk_only_proc(Process *p, ErtsProcLocks locks);
414 void erts_proc_lc_chk_no_proc_locks(const char *file, int line);
415 ErtsProcLocks erts_proc_lc_my_proc_locks(Process *p);
416 int erts_proc_lc_trylock_force_busy(Process *p, ErtsProcLocks locks);
417 void erts_proc_lc_require_lock(Process *p, ErtsProcLocks locks,
418 			       const char* file, unsigned int line);
419 void erts_proc_lc_unrequire_lock(Process *p, ErtsProcLocks locks);
420 #else
421 #define ERTS_CHK_NO_PROC_LOCKS
422 #define ERTS_CHK_HAVE_ONLY_MAIN_PROC_LOCK(P)
423 #endif
424 
425 #endif /* #ifndef ERTS_PROC_LOCK_LOCK_CHECK__ */
426 #endif /* #ifndef ERTS_PROCESS_LOCK_ONLY_PROC_LOCK_TYPE__ */
427 
428 #if !defined(ERTS_PROCESS_LOCK_ONLY_PROC_LOCK_TYPE__) \
429     && !defined(ERTS_PROCESS_LOCK_ONLY_LOCK_CHECK_PROTO__)
430 #ifndef ERTS_PROCESS_LOCK_H__
431 #define ERTS_PROCESS_LOCK_H__
432 
433 
434 typedef struct {
435     union {
436 	erts_mtx_t mtx;
437 	char buf[ERTS_ALC_CACHE_LINE_ALIGN_SIZE(sizeof(erts_mtx_t))];
438     } u;
439 } erts_pix_lock_t;
440 
441 #define ERTS_PID2PIXLOCK(PID) \
442     (&erts_pix_locks[(internal_pid_data((PID)) & ((1 << ERTS_PIX_LOCKS_BITS) - 1))])
443 
444 #if ERTS_PROC_LOCK_OWN_IMPL
445 
446 #if ERTS_PROC_LOCK_ATOMIC_IMPL
447 
448 #define ERTS_PROC_LOCK_FLGS_BAND_(L, MSK) \
449   ((ErtsProcLocks) erts_atomic32_read_band_nob(&(L)->flags, \
450 						   (erts_aint32_t) (MSK)))
451 #define ERTS_PROC_LOCK_FLGS_BOR_ACQB_(L, MSK) \
452   ((ErtsProcLocks) erts_atomic32_read_bor_acqb(&(L)->flags, \
453 						   (erts_aint32_t) (MSK)))
454 #define ERTS_PROC_LOCK_FLGS_CMPXCHG_ACQB_(L, NEW, EXPECTED) \
455   ((ErtsProcLocks) erts_atomic32_cmpxchg_acqb(&(L)->flags, \
456 						  (erts_aint32_t) (NEW), \
457 						  (erts_aint32_t) (EXPECTED)))
458 #define ERTS_PROC_LOCK_FLGS_CMPXCHG_RELB_(L, NEW, EXPECTED) \
459   ((ErtsProcLocks) erts_atomic32_cmpxchg_relb(&(L)->flags, \
460 						  (erts_aint32_t) (NEW), \
461 						  (erts_aint32_t) (EXPECTED)))
462 #define ERTS_PROC_LOCK_FLGS_READ_(L) \
463   ((ErtsProcLocks) erts_atomic32_read_nob(&(L)->flags))
464 
465 #else /* no opt atomic ops */
466 
467 ERTS_GLB_INLINE ErtsProcLocks erts_proc_lock_flags_band(erts_proc_lock_t *,
468 							ErtsProcLocks);
469 ERTS_GLB_INLINE ErtsProcLocks erts_proc_lock_flags_bor(erts_proc_lock_t *,
470 						       ErtsProcLocks);
471 ERTS_GLB_INLINE ErtsProcLocks erts_proc_lock_flags_cmpxchg(erts_proc_lock_t *,
472 							   ErtsProcLocks,
473 							   ErtsProcLocks);
474 
475 #if ERTS_GLB_INLINE_INCL_FUNC_DEF
476 
477 ERTS_GLB_INLINE ErtsProcLocks
erts_proc_lock_flags_band(erts_proc_lock_t * lck,ErtsProcLocks mask)478 erts_proc_lock_flags_band(erts_proc_lock_t *lck, ErtsProcLocks mask)
479 {
480     ErtsProcLocks res = lck->flags;
481     lck->flags &= mask;
482     return res;
483 }
484 
485 ERTS_GLB_INLINE ErtsProcLocks
erts_proc_lock_flags_bor(erts_proc_lock_t * lck,ErtsProcLocks mask)486 erts_proc_lock_flags_bor(erts_proc_lock_t *lck, ErtsProcLocks mask)
487 {
488     ErtsProcLocks res = lck->flags;
489     lck->flags |= mask;
490     return res;
491 }
492 
493 ERTS_GLB_INLINE ErtsProcLocks
erts_proc_lock_flags_cmpxchg(erts_proc_lock_t * lck,ErtsProcLocks new,ErtsProcLocks expected)494 erts_proc_lock_flags_cmpxchg(erts_proc_lock_t *lck, ErtsProcLocks new,
495                              ErtsProcLocks expected)
496 {
497     ErtsProcLocks res = lck->flags;
498     if (res == expected)
499         lck->flags = new;
500     return res;
501 }
502 
503 #endif
504 
505 #define ERTS_PROC_LOCK_FLGS_BAND_(L, MSK) erts_proc_lock_flags_band((L), (MSK))
506 #define ERTS_PROC_LOCK_FLGS_BOR_ACQB_(L, MSK) erts_proc_lock_flags_bor((L), (MSK))
507 #define ERTS_PROC_LOCK_FLGS_CMPXCHG_ACQB_(L, NEW, EXPECTED) \
508   erts_proc_lock_flags_cmpxchg((L), (NEW), (EXPECTED))
509 #define ERTS_PROC_LOCK_FLGS_CMPXCHG_RELB_(L, NEW, EXPECTED) \
510   erts_proc_lock_flags_cmpxchg((L), (NEW), (EXPECTED))
511 #define ERTS_PROC_LOCK_FLGS_READ_(L) ((L)->flags)
512 
513 #endif /* end no opt atomic ops */
514 #endif /* ERTS_PROC_LOCK_OWN_IMPL */
515 
516 extern erts_pix_lock_t erts_pix_locks[ERTS_NO_OF_PIX_LOCKS];
517 
518 void erts_init_proc_lock(int cpus);
519 void erts_proc_lock_prepare_proc_lock_waiter(void);
520 #if ERTS_PROC_LOCK_OWN_IMPL
521 void erts_proc_lock_failed(Process *,
522 			   erts_pix_lock_t *,
523 			   ErtsProcLocks,
524 			   ErtsProcLocks);
525 void erts_proc_unlock_failed(Process *,
526 			     erts_pix_lock_t *,
527 			     ErtsProcLocks);
528 #endif
529 
530 ERTS_GLB_INLINE void erts_pix_lock(erts_pix_lock_t *);
531 ERTS_GLB_INLINE void erts_pix_unlock(erts_pix_lock_t *);
532 ERTS_GLB_INLINE int erts_lc_pix_lock_is_locked(erts_pix_lock_t *);
533 
534 ERTS_GLB_INLINE ErtsProcLocks erts_proc_raw_trylock__(Process *p,
535 							  ErtsProcLocks locks);
536 #ifdef ERTS_ENABLE_LOCK_POSITION
537 ERTS_GLB_INLINE void erts_proc_lock_x__(Process *,
538 					    erts_pix_lock_t *,
539 					    ErtsProcLocks,
540 					    const char *file, unsigned int line);
541 #else
542 ERTS_GLB_INLINE void erts_proc_lock__(Process *,
543 					  erts_pix_lock_t *,
544 					  ErtsProcLocks);
545 #endif
546 ERTS_GLB_INLINE void erts_proc_unlock__(Process *,
547 					    erts_pix_lock_t *,
548 					    ErtsProcLocks);
549 ERTS_GLB_INLINE int erts_proc_trylock__(Process *,
550 					    erts_pix_lock_t *,
551 					    ErtsProcLocks);
552 
553 #ifdef ERTS_PROC_LOCK_DEBUG
554 ERTS_GLB_INLINE void erts_proc_lock_op_debug(Process *, ErtsProcLocks, int);
555 #endif
556 
557 #if ERTS_GLB_INLINE_INCL_FUNC_DEF
558 
erts_pix_lock(erts_pix_lock_t * pixlck)559 ERTS_GLB_INLINE void erts_pix_lock(erts_pix_lock_t *pixlck)
560 {
561     ASSERT(pixlck);
562     erts_mtx_lock(&pixlck->u.mtx);
563 }
564 
erts_pix_unlock(erts_pix_lock_t * pixlck)565 ERTS_GLB_INLINE void erts_pix_unlock(erts_pix_lock_t *pixlck)
566 {
567     ASSERT(pixlck);
568     erts_mtx_unlock(&pixlck->u.mtx);
569 }
570 
erts_lc_pix_lock_is_locked(erts_pix_lock_t * pixlck)571 ERTS_GLB_INLINE int erts_lc_pix_lock_is_locked(erts_pix_lock_t *pixlck)
572 {
573     return erts_lc_mtx_is_locked(&pixlck->u.mtx);
574 }
575 
576 /*
577  * Helper function for erts_proc_lock__ and erts_proc_trylock__.
578  *
579  * Attempts to grab all of 'locks' simultaneously.
580  *
581  * On success, returns zero.
582  *
583  * On failure, returns the p->locks at the moment it tried to grab them,
584  * at least some of which will intersect with 'locks', so it is nonzero.
585  *
586  * This assumes p's pix lock is held on entry if !ERTS_PROC_LOCK_ATOMIC_IMPL.
587  * Does not release the pix lock.
588  */
589 ERTS_GLB_INLINE ErtsProcLocks
erts_proc_raw_trylock__(Process * p,ErtsProcLocks locks)590 erts_proc_raw_trylock__(Process *p, ErtsProcLocks locks)
591 {
592 #if ERTS_PROC_LOCK_OWN_IMPL
593     ErtsProcLocks expct_lflgs = 0;
594 
595     while (1) {
596         ErtsProcLocks lflgs = ERTS_PROC_LOCK_FLGS_CMPXCHG_ACQB_(&p->lock,
597 								expct_lflgs | locks,
598 								expct_lflgs);
599         if (ERTS_LIKELY(lflgs == expct_lflgs)) {
600             /* We successfully grabbed all locks. */
601             return 0;
602         }
603 
604         if (lflgs & locks) {
605             /* Some locks we need are locked, give up. */
606             return lflgs;
607         }
608 
609         /* cmpxchg failed, try again (should be rare). */
610         expct_lflgs = lflgs;
611     }
612 
613 #elif ERTS_PROC_LOCK_RAW_MUTEX_IMPL
614 
615     if (locks & ERTS_PROC_LOCK_MAIN)
616 	if (erts_mtx_trylock(&p->lock.main) == EBUSY)
617 	    goto busy_main;
618     if (locks & ERTS_PROC_LOCK_MSGQ)
619 	if (erts_mtx_trylock(&p->lock.msgq) == EBUSY)
620 	    goto busy_msgq;
621     if (locks & ERTS_PROC_LOCK_BTM)
622 	if (erts_mtx_trylock(&p->lock.btm) == EBUSY)
623 	    goto busy_btm;
624     if (locks & ERTS_PROC_LOCK_STATUS)
625 	if (erts_mtx_trylock(&p->lock.status) == EBUSY)
626 	    goto busy_status;
627     if (locks & ERTS_PROC_LOCK_TRACE)
628 	if (erts_mtx_trylock(&p->lock.trace) == EBUSY)
629 	    goto busy_trace;
630 
631     return 0;
632 
633 busy_trace:
634     if (locks & ERTS_PROC_LOCK_TRACE)
635 	erts_mtx_unlock(&p->lock.trace);
636 busy_status:
637     if (locks & ERTS_PROC_LOCK_BTM)
638 	erts_mtx_unlock(&p->lock.btm);
639 busy_btm:
640     if (locks & ERTS_PROC_LOCK_MSGQ)
641 	erts_mtx_unlock(&p->lock.msgq);
642 busy_msgq:
643     if (locks & ERTS_PROC_LOCK_MAIN)
644 	erts_mtx_unlock(&p->lock.main);
645 busy_main:
646 
647     return EBUSY;
648 #endif
649 }
650 
651 ERTS_GLB_INLINE void
652 #ifdef ERTS_ENABLE_LOCK_POSITION
erts_proc_lock_x__(Process * p,erts_pix_lock_t * pix_lck,ErtsProcLocks locks,const char * file,unsigned int line)653 erts_proc_lock_x__(Process *p,
654 		     erts_pix_lock_t *pix_lck,
655 		     ErtsProcLocks locks,
656 		     const char *file, unsigned int line)
657 #else
658 erts_proc_lock__(Process *p,
659 		     erts_pix_lock_t *pix_lck,
660 		     ErtsProcLocks locks)
661 #endif
662 {
663 #if ERTS_PROC_LOCK_OWN_IMPL
664 
665     ErtsProcLocks old_lflgs;
666 #if !ERTS_PROC_LOCK_ATOMIC_IMPL
667     erts_pix_lock(pix_lck);
668 #endif
669 
670 #ifdef ERTS_ENABLE_LOCK_COUNT
671     erts_lcnt_proc_lock(&(p->lock), locks);
672 #endif
673 
674     ASSERT((locks & ~ERTS_PROC_LOCKS_ALL) == 0);
675 
676 #ifdef ERTS_ENABLE_LOCK_CHECK
677     erts_proc_lc_lock(p, locks, file, line);
678 #endif
679 
680     old_lflgs = erts_proc_raw_trylock__(p, locks);
681 
682     if (old_lflgs != 0) {
683 	/*
684          * There is lock contention, so let erts_proc_lock_failed() deal
685          * with it. Note that erts_proc_lock_failed() returns with
686          * pix_lck unlocked.
687          */
688 	erts_proc_lock_failed(p, pix_lck, locks, old_lflgs);
689     }
690 
691 #if !ERTS_PROC_LOCK_ATOMIC_IMPL
692     else {
693 	ASSERT(locks == (ERTS_PROC_LOCK_FLGS_READ_(&p->lock) & locks));
694 	erts_pix_unlock(pix_lck);
695     }
696 #endif
697 
698 #ifdef ERTS_ENABLE_LOCK_COUNT
699     erts_lcnt_proc_lock_post_x(&(p->lock), locks, file, line);
700 #endif
701 
702 #ifdef ERTS_PROC_LOCK_DEBUG
703     erts_proc_lock_op_debug(p, locks, 1);
704 #endif
705 
706 #if ERTS_PROC_LOCK_ATOMIC_IMPL
707     ETHR_COMPILER_BARRIER;
708 #endif
709 
710 #elif ERTS_PROC_LOCK_RAW_MUTEX_IMPL
711     if (locks & ERTS_PROC_LOCK_MAIN)
712 	erts_mtx_lock(&p->lock.main);
713     if (locks & ERTS_PROC_LOCK_MSGQ)
714 	erts_mtx_lock(&p->lock.msgq);
715     if (locks & ERTS_PROC_LOCK_BTM)
716 	erts_mtx_lock(&p->lock.btm);
717     if (locks & ERTS_PROC_LOCK_STATUS)
718 	erts_mtx_lock(&p->lock.status);
719     if (locks & ERTS_PROC_LOCK_TRACE)
720 	erts_mtx_lock(&p->lock.trace);
721 
722 #ifdef ERTS_PROC_LOCK_DEBUG
723     erts_proc_lock_op_debug(p, locks, 1);
724 #endif
725 
726 #endif
727 }
728 
729 ERTS_GLB_INLINE void
erts_proc_unlock__(Process * p,erts_pix_lock_t * pix_lck,ErtsProcLocks locks)730 erts_proc_unlock__(Process *p,
731 		       erts_pix_lock_t *pix_lck,
732 		       ErtsProcLocks locks)
733 {
734 #if ERTS_PROC_LOCK_OWN_IMPL
735     ErtsProcLocks old_lflgs;
736 
737 #if ERTS_PROC_LOCK_ATOMIC_IMPL
738     ETHR_COMPILER_BARRIER;
739 #endif
740 
741 #ifdef ERTS_ENABLE_LOCK_COUNT
742     erts_lcnt_proc_unlock(&(p->lock), locks);
743 #endif
744 
745 #ifdef ERTS_ENABLE_LOCK_CHECK
746     erts_proc_lc_unlock(p, locks);
747 #endif
748 #ifdef ERTS_PROC_LOCK_DEBUG
749     erts_proc_lock_op_debug(p, locks, 0);
750 #endif
751 
752 #if !ERTS_PROC_LOCK_ATOMIC_IMPL
753     erts_pix_lock(pix_lck);
754 #endif
755 
756     old_lflgs = ERTS_PROC_LOCK_FLGS_READ_(&p->lock);
757 
758     ASSERT((locks & ~ERTS_PROC_LOCKS_ALL) == 0);
759     ASSERT(locks == (old_lflgs & locks));
760 
761     while (1) {
762         /*
763          * We'll atomically unlock every lock that has no waiter.
764          * If any locks with waiters remain we'll let
765          * erts_proc_unlock_failed() deal with them.
766          */
767         ErtsProcLocks wait_locks =
768             (old_lflgs >> ERTS_PROC_LOCK_WAITER_SHIFT) & locks;
769 
770         /* What p->lock will look like with all non-waited locks released. */
771         ErtsProcLocks want_lflgs = old_lflgs & (wait_locks | ~locks);
772 
773         if (want_lflgs != old_lflgs) {
774             ErtsProcLocks new_lflgs =
775                 ERTS_PROC_LOCK_FLGS_CMPXCHG_RELB_(&p->lock, want_lflgs, old_lflgs);
776 
777             if (new_lflgs != old_lflgs) {
778                 /* cmpxchg failed, try again. */
779                 old_lflgs = new_lflgs;
780                 continue;
781             }
782         }
783 
784         /* We have successfully unlocked every lock with no waiter. */
785 
786         if (want_lflgs & locks) {
787             /* Locks with waiters remain. */
788             /* erts_proc_unlock_failed() returns with pix_lck unlocked. */
789             erts_proc_unlock_failed(p, pix_lck, want_lflgs & locks);
790         }
791         else {
792 #if !ERTS_PROC_LOCK_ATOMIC_IMPL
793             erts_pix_unlock(pix_lck);
794 #endif
795         }
796 
797         break;
798     }
799 
800 #elif ERTS_PROC_LOCK_RAW_MUTEX_IMPL
801 
802 #ifdef ERTS_PROC_LOCK_DEBUG
803     erts_proc_lock_op_debug(p, locks, 0);
804 #endif
805 
806     if (locks & ERTS_PROC_LOCK_TRACE)
807 	erts_mtx_unlock(&p->lock.trace);
808     if (locks & ERTS_PROC_LOCK_STATUS)
809 	erts_mtx_unlock(&p->lock.status);
810     if (locks & ERTS_PROC_LOCK_BTM)
811 	erts_mtx_unlock(&p->lock.btm);
812     if (locks & ERTS_PROC_LOCK_MSGQ)
813 	erts_mtx_unlock(&p->lock.msgq);
814     if (locks & ERTS_PROC_LOCK_MAIN)
815 	erts_mtx_unlock(&p->lock.main);
816 #endif
817 
818 }
819 
820 ERTS_GLB_INLINE int
erts_proc_trylock__(Process * p,erts_pix_lock_t * pix_lck,ErtsProcLocks locks)821 erts_proc_trylock__(Process *p,
822 			erts_pix_lock_t *pix_lck,
823 			ErtsProcLocks locks)
824 {
825 #if ERTS_PROC_LOCK_OWN_IMPL
826     int res;
827 
828 #ifdef ERTS_ENABLE_LOCK_CHECK
829     ASSERT((locks & ~ERTS_PROC_LOCKS_ALL) == 0);
830     if (erts_proc_lc_trylock_force_busy(p, locks)) {
831 	res = EBUSY; /* Make sure caller can handle the situation without
832 			causing a lock order violation to occur */
833     }
834     else
835 #endif
836     {
837 
838 #if !ERTS_PROC_LOCK_ATOMIC_IMPL
839 	erts_pix_lock(pix_lck);
840 #endif
841 
842 	if (erts_proc_raw_trylock__(p, locks) != 0) {
843 	    /* Didn't get all locks... */
844 	    res = EBUSY;
845 
846 #if !ERTS_PROC_LOCK_ATOMIC_IMPL
847 	    erts_pix_unlock(pix_lck);
848 #endif
849 	}
850 	else {
851 	    res = 0;
852 
853 	    ASSERT(locks == (ERTS_PROC_LOCK_FLGS_READ_(&p->lock) & locks));
854 
855 #if !ERTS_PROC_LOCK_ATOMIC_IMPL
856 	    erts_pix_unlock(pix_lck);
857 #endif
858 
859 #ifdef ERTS_PROC_LOCK_DEBUG
860 	    erts_proc_lock_op_debug(p, locks, 1);
861 #endif
862 	}
863     }
864 #ifdef ERTS_ENABLE_LOCK_COUNT
865     erts_lcnt_proc_trylock(&(p->lock), locks, res);
866 #endif
867 
868 #ifdef ERTS_ENABLE_LOCK_CHECK
869     erts_proc_lc_trylock(p, locks, res == 0, __FILE__, __LINE__);
870 #endif
871 
872 #if ERTS_PROC_LOCK_ATOMIC_IMPL
873     ETHR_COMPILER_BARRIER;
874 #endif
875     return res;
876 
877 #elif ERTS_PROC_LOCK_RAW_MUTEX_IMPL
878     if (erts_proc_raw_trylock__(p, locks) != 0)
879 	return EBUSY;
880     else {
881 #ifdef ERTS_PROC_LOCK_DEBUG
882 	erts_proc_lock_op_debug(p, locks, 1);
883 #endif
884 	return 0;
885     }
886 #endif
887 }
888 
889 #ifdef ERTS_PROC_LOCK_DEBUG
890 ERTS_GLB_INLINE void
erts_proc_lock_op_debug(Process * p,ErtsProcLocks locks,int locked)891 erts_proc_lock_op_debug(Process *p, ErtsProcLocks locks, int locked)
892 {
893     int i;
894     for (i = 0; i <= ERTS_PROC_LOCK_MAX_BIT; i++) {
895 	ErtsProcLocks lock = ((ErtsProcLocks) 1) << i;
896 	if (locks & lock) {
897 	    erts_aint32_t lock_count;
898 	    if (locked) {
899 		lock_count = erts_atomic32_inc_read_nob(&p->lock.locked[i]);
900 		ASSERT(lock_count == 1);
901 	    }
902 	    else {
903 		lock_count = erts_atomic32_dec_read_nob(&p->lock.locked[i]);
904 		ASSERT(lock_count == 0);
905 	    }
906 	}
907     }
908 }
909 #endif
910 
911 #endif /* #if ERTS_GLB_INLINE_INCL_FUNC_DEF */
912 
913 
914 #ifdef ERTS_ENABLE_LOCK_POSITION
915 ERTS_GLB_INLINE void erts_proc_lock_x(Process *, ErtsProcLocks, const char *file, unsigned int line);
916 #else
917 ERTS_GLB_INLINE void erts_proc_lock(Process *, ErtsProcLocks);
918 #endif
919 ERTS_GLB_INLINE void erts_proc_unlock(Process *, ErtsProcLocks);
920 ERTS_GLB_INLINE int erts_proc_trylock(Process *, ErtsProcLocks);
921 
922 ERTS_GLB_INLINE void erts_proc_inc_refc(Process *);
923 ERTS_GLB_INLINE void erts_proc_dec_refc(Process *);
924 ERTS_GLB_INLINE void erts_proc_dec_refc_free_func(Process *p,
925                                                   void (*func)(int, void *),
926                                                   void *arg);
927 ERTS_GLB_INLINE void erts_proc_add_refc(Process *, Sint);
928 ERTS_GLB_INLINE Sint erts_proc_read_refc(Process *);
929 
930 #if ERTS_GLB_INLINE_INCL_FUNC_DEF
931 
932 ERTS_GLB_INLINE void
933 #ifdef ERTS_ENABLE_LOCK_POSITION
erts_proc_lock_x(Process * p,ErtsProcLocks locks,const char * file,unsigned int line)934 erts_proc_lock_x(Process *p, ErtsProcLocks locks, const char *file, unsigned int line)
935 #else
936 erts_proc_lock(Process *p, ErtsProcLocks locks)
937 #endif
938 {
939 #if defined(ERTS_ENABLE_LOCK_POSITION)
940     erts_proc_lock_x__(p,
941 #if ERTS_PROC_LOCK_ATOMIC_IMPL
942 			 NULL,
943 #else
944 			 ERTS_PID2PIXLOCK(p->common.id),
945 #endif /*ERTS_PROC_LOCK_ATOMIC_IMPL*/
946 			 locks, file, line);
947 #else
948     erts_proc_lock__(p,
949 #if ERTS_PROC_LOCK_ATOMIC_IMPL
950 			 NULL,
951 #else
952 			 ERTS_PID2PIXLOCK(p->common.id),
953 #endif /*ERTS_PROC_LOCK_ATOMIC_IMPL*/
954 			 locks);
955 #endif /*ERTS_ENABLE_LOCK_POSITION*/
956 }
957 
958 ERTS_GLB_INLINE void
erts_proc_unlock(Process * p,ErtsProcLocks locks)959 erts_proc_unlock(Process *p, ErtsProcLocks locks)
960 {
961     erts_proc_unlock__(p,
962 #if ERTS_PROC_LOCK_ATOMIC_IMPL
963 			   NULL,
964 #else
965 			   ERTS_PID2PIXLOCK(p->common.id),
966 #endif
967 			   locks);
968 }
969 
970 ERTS_GLB_INLINE int
erts_proc_trylock(Process * p,ErtsProcLocks locks)971 erts_proc_trylock(Process *p, ErtsProcLocks locks)
972 {
973     return erts_proc_trylock__(p,
974 #if ERTS_PROC_LOCK_ATOMIC_IMPL
975 				   NULL,
976 #else
977 				   ERTS_PID2PIXLOCK(p->common.id),
978 #endif
979 				   locks);
980 }
981 
erts_proc_inc_refc(Process * p)982 ERTS_GLB_INLINE void erts_proc_inc_refc(Process *p)
983 {
984     ASSERT(!(erts_atomic32_read_nob(&p->state) & ERTS_PSFLG_PROXY));
985     erts_ptab_atmc_inc_refc(&p->common);
986 }
987 
erts_proc_dec_refc(Process * p)988 ERTS_GLB_INLINE void erts_proc_dec_refc(Process *p)
989 {
990     Sint referred;
991     ASSERT(!(erts_atomic32_read_nob(&p->state) & ERTS_PSFLG_PROXY));
992     referred = erts_ptab_atmc_dec_test_refc(&p->common);
993     if (!referred) {
994 	ASSERT(ERTS_PROC_IS_EXITING(p));
995 	erts_free_proc(p);
996     }
997 }
998 
erts_proc_dec_refc_free_func(Process * p,void (* func)(int,void *),void * arg)999 ERTS_GLB_INLINE void erts_proc_dec_refc_free_func(Process *p,
1000                                                   void (*func)(int, void *),
1001                                                   void *arg)
1002 {
1003     Sint referred;
1004     ASSERT(!(erts_atomic32_read_nob(&p->state) & ERTS_PSFLG_PROXY));
1005     referred = erts_ptab_atmc_dec_test_refc(&p->common);
1006     if (!referred) {
1007 	ASSERT(ERTS_PROC_IS_EXITING(p));
1008         (*func)(!0, arg);
1009 	erts_free_proc(p);
1010         (*func)(0, arg);
1011     }
1012 }
1013 
erts_proc_add_refc(Process * p,Sint add_refc)1014 ERTS_GLB_INLINE void erts_proc_add_refc(Process *p, Sint add_refc)
1015 {
1016     Sint referred;
1017     ASSERT(!(erts_atomic32_read_nob(&p->state) & ERTS_PSFLG_PROXY));
1018     referred = erts_ptab_atmc_add_test_refc(&p->common, add_refc);
1019     if (!referred) {
1020 	ASSERT(ERTS_PROC_IS_EXITING(p));
1021 	erts_free_proc(p);
1022     }
1023 }
1024 
erts_proc_read_refc(Process * p)1025 ERTS_GLB_INLINE Sint erts_proc_read_refc(Process *p)
1026 {
1027     ASSERT(!(erts_atomic32_read_nob(&p->state) & ERTS_PSFLG_PROXY));
1028     return erts_ptab_atmc_read_refc(&p->common);
1029 }
1030 
1031 #endif /* #if ERTS_GLB_INLINE_INCL_FUNC_DEF */
1032 
1033 void erts_proc_lock_init(Process *);
1034 void erts_proc_lock_fin(Process *);
1035 void erts_proc_safelock(Process *a_proc,
1036 			ErtsProcLocks a_have_locks,
1037 			ErtsProcLocks a_need_locks,
1038 			Process *b_proc,
1039 			ErtsProcLocks b_have_locks,
1040 			ErtsProcLocks b_need_locks);
1041 
1042 /*
1043  * --- Process table lookup ------------------------------------------------
1044  *
1045  * erts_pid2proc() and friends looks up the process structure of a pid
1046  * and at the same time acquires process locks in the smp case. Locks
1047  * on currently executing process and looked up process are taken according
1048  * to the lock order, i.e., locks on currently executing process may have
1049  * been released and reacquired.
1050  *
1051  * erts_pid2proc_opt() currently accepts the following flags:
1052  *   ERTS_P2P_FLG_ALLOW_OTHER_X    Lookup process even if it currently
1053  *                                 is exiting.
1054  */
1055 
1056 #define ERTS_P2P_FLG_ALLOW_OTHER_X	(1 <<  0)
1057 #define ERTS_P2P_FLG_TRY_LOCK		(1 <<  1)
1058 #define ERTS_P2P_FLG_INC_REFC		(1 <<  2)
1059 
1060 #define ERTS_PROC_LOCK_BUSY ((Process *) &erts_invalid_process)
1061 
1062 #define erts_pid2proc(PROC, HL, PID, NL) \
1063   erts_pid2proc_opt((PROC), (HL), (PID), (NL), 0)
1064 
1065 Process *erts_proc_lookup_inc_refc(Eterm pid);
1066 Process *erts_proc_lookup_raw_inc_refc(Eterm pid);
1067 
1068 ERTS_GLB_INLINE Process *erts_pix2proc(int ix);
1069 ERTS_GLB_INLINE Process *erts_proc_lookup_raw(Eterm pid);
1070 ERTS_GLB_INLINE Process *erts_proc_lookup(Eterm pid);
1071 
1072 Process *erts_pid2proc_opt(Process *, ErtsProcLocks, Eterm, ErtsProcLocks, int);
1073 
1074 #if ERTS_GLB_INLINE_INCL_FUNC_DEF
1075 
erts_pix2proc(int ix)1076 ERTS_GLB_INLINE Process *erts_pix2proc(int ix)
1077 {
1078     Process *proc;
1079     ASSERT(0 <= ix && ix < erts_ptab_max(&erts_proc));
1080     proc = (Process *) erts_ptab_pix2intptr_nob(&erts_proc, ix);
1081     return proc == ERTS_PROC_LOCK_BUSY ? NULL : proc;
1082 }
1083 
erts_proc_lookup_raw(Eterm pid)1084 ERTS_GLB_INLINE Process *erts_proc_lookup_raw(Eterm pid)
1085 {
1086     Process *proc;
1087 
1088     ERTS_LC_ASSERT(erts_thr_progress_lc_is_delaying());
1089 
1090     if (is_not_internal_pid(pid))
1091 	return NULL;
1092 
1093     proc = (Process *) erts_ptab_pix2intptr_ddrb(&erts_proc,
1094 						 internal_pid_index(pid));
1095     if (proc && proc->common.id != pid)
1096 	return NULL;
1097     return proc;
1098 }
1099 
erts_proc_lookup(Eterm pid)1100 ERTS_GLB_INLINE Process *erts_proc_lookup(Eterm pid)
1101 {
1102     Process *proc = erts_proc_lookup_raw(pid);
1103     if (proc && ERTS_PROC_IS_EXITING(proc))
1104 	return NULL;
1105     return proc;
1106 }
1107 
1108 
1109 #endif /* #if ERTS_GLB_INLINE_INCL_FUNC_DEF */
1110 
1111 #endif /* #ifndef ERTS_PROCESS_LOCK_H__ */
1112 #endif /* #if !defined(ERTS_PROCESS_LOCK_ONLY_PROC_LOCK_TYPE__)
1113 	  && !defined(ERTS_PROCESS_LOCK_ONLY_LOCK_CHECK_PROTO__) */
1114