1 /*
2  * %CopyrightBegin%
3  *
4  * Copyright Ericsson AB 2018-2020. 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  * Description:	Monitor and link implementation.
23  *
24  *              === Monitors ==================================================
25  *
26  *              The monitor data structure contains:
27  *              - an 'origin' part that should be inserted in a data structure
28  *                of the origin entity, i.e., the entity monitoring another
29  *                entity
30  *              - a 'target' part that should be inserted in a data structure
31  *                of the target entity, i.e., the entity being monitored by
32  *                another entity
33  *              - a shared part that contains information shared between both
34  *                origin and target entities
35  *
36  *              That is, the two halves of the monitor as well as shared data
37  *              are allocated in one single continuous memory block. The
38  *              origin and target parts can separately each be inserted in
39  *              either a (red-black) tree, a (circular double linked) list, or
40  *              in a process signal queue.
41  *
42  *              Each process and port contains:
43  *              - a monitor list for local target monitors that is accessed
44  *                via the ERTS_P_LT_MONITORS() macro, and
45  *              - a monitor tree for other monitors that is accessed via the
46  *                ERTS_P_MONITORS() macro
47  *
48  *              These fields of processes/ports are protected by the main lock
49  *              of the process/port. These are only intended to be accessed by
50  *              the process/port itself. When setting up or tearing down a
51  *              monitor one should *only* operate on the monitor tree/list of
52  *              the currently executing process/port and send signals to the
53  *              other involved process/port so it can modify its own monitor
54  *              tree/list by itself (see erl_proc_sig_queue.h). One should
55  *              absolutely *not* acquire the lock of the other involved
56  *              process/port and operate on its monitor tree/list directly.
57  *
58  *              Each dist entry contains a monitor/link dist structure that
59  *              contains:
60  *              - a monitor tree for origin named monitors that is accessed via
61  *                the field 'orig_name_monitors', and
62  *              - a monitor list for other monitors that is accessed via the
63  *                'monitors' field.
64  *              Monitors in these fields contain information about all monitors
65  *              over this specific connection.
66  *
67  *              The fields of the dist structure are protected by a mutex in
68  *              the same dist structure. Operations on these fields are
69  *              normally performed by the locally involved process only,
70  *              except when a connection is taken down. However in the case
71  *              of distributed named monitors that originates from another
72  *              node this is not possible. That is this operation is also
73  *              performed from another context that the locally involved
74  *              process.
75  *
76  *              Access to monitor trees are performed using the
77  *              erts_monitor_tree_* functions below. Access to monitor lists
78  *              are performed using the erts_monitor_list_* functions below.
79  *
80  *
81  *              The different monitor types:
82  *
83  *              --- ERTS_MON_TYPE_PROC ----------------------------------------
84  *
85  *              A local process (origin) monitors another local process
86  *              (target).
87  *
88  *              Origin:
89  *                      Other Item:     Target process identifier
90  *              Target:
91  *                      Other Item:     Origin process identifier
92  *              Shared:
93  *                      Key:            Reference
94  *                      Name:           Name (atom) if by name
95  *
96  *              Valid keys are only ordinary internal references.
97  *
98  *              Origin part of the monitor is stored in the monitor tree of
99  *              origin process and target part of the monitor is stored in
100  *              monitor list for local targets on the target process.
101  *
102  *              --- ERTS_MON_TYPE_PORT ----------------------------------------
103  *
104  *              A local process (origin) monitors a local port (target), or a
105  *              local port (origin) monitors a local process (target).
106  *
107  *              Origin:
108  *                      Other Item:     Target process/port identifier
109  *              Target:
110  *                      Other Item:     Origin process/port identifier
111  *              Shared:
112  *                      Key:            Reference
113  *                      Name:           Name (atom) if by name
114  *
115  *              Valid keys are only ordinary internal references.
116  *
117  *              Origin part of the monitor is stored in the monitor tree of
118  *              origin process/port and target part of the monitor is stored
119  *              in monitor list for local targets on the target process/port.
120  *
121  *
122  *              --- ERTS_MON_TYPE_TIME_OFFSET ---------------------------------
123  *
124  *              A local process (origin) monitors time offset (target)
125  *
126  *              Origin:
127  *                      Other Item:     clock_service
128  *              Target:
129  *                      Other Item:     Origin process identifier
130  *              Shared:
131  *                      Key:            Reference
132  *
133  *              Valid keys are only ordinary internal references.
134  *
135  *              Origin part of the monitor is stored in the monitor tree of
136  *              origin process and target part of the monitor is stored in
137  *              monitor list referred by the variable 'time_offset_monitors'
138  *              (see erl_time_sup.c).
139  *
140  *
141  *              --- ERTS_MON_TYPE_DIST_PROC -----------------------------------
142  *
143  *              A local process (origin) monitors a remote process (target).
144  *              Origin node on local process and target node on dist entry.
145  *
146  *              Origin:
147  *                      Other Item:     Remote process identifier/Node name
148  *                                      if by name
149  *              Target:
150  *                      Other Item:     Local process identifier
151  *              Shared:
152  *                      Key:            Reference
153  *                      Name:           Name (atom) if by name
154  *                      Dist:           Pointer to dist structure
155  *
156  *              Valid keys are only ordinary internal references.
157  *
158  *              Origin part of the monitor is stored in the monitor tree of
159  *              origin process and target part of the monitor is stored in
160  *              monitor list referred by 'monitors' field of the dist
161  *              structure.
162  *
163  *
164  *              A remote process (origin) monitors a local process (target).
165  *              Origin node on dist entry and target node on local process.
166  *
167  *              Origin:
168  *                      Other Item:     Local process identifier
169  *              Target:
170  *                      Other Item:     Remote process identifier
171  *              Shared:
172  *                      Key:            Reference
173  *                      Name:           Name (atom) if by name
174  *
175  *              Valid keys are only external references.
176  *
177  *              If monitor by name, the origin part of the monitor is stored
178  *              in the monitor tree referred by 'orig_name_monitors' field in
179  *              dist structure; otherwise in the monitor list referred by
180  *              'monitors' field in dist structure. The target part of the
181  *              monitor is stored in the monitor tree of the local target
182  *              process.
183  *
184  *
185  *              --- ERTS_MON_TYPE_RESOURCE ------------------------------------
186  *
187  *              A NIF resource (origin) monitors a process (target).
188  *
189  *              Origin:
190  *                      Other Item:     Target process identifier
191  *              Target:
192  *                      Other Ptr:      Pointer to resource
193  *              Shared:
194  *                      Key:            Reference
195  *
196  *              Valid keys are only ordinary internal references.
197  *
198  *              Origin part of the monitor is stored in the monitor tree of
199  *              origin resource (see erl_nif.c) and target part of the
200  *              monitor is stored in monitor list for local targets on the
201  *              target process.
202  *
203  *              --- ERTS_MON_TYPE_NODE ----------------------------------------
204  *
205  *              A local process (origin) monitors a distribution connection
206  *              (target) via erlang:monitor_node().
207  *
208  *              Origin:
209  *                      Other Item:     Node name (atom)
210  *                      Key:            Node name
211  *              Target:
212  *                      Other Item:     Origin process identifier
213  *                      Key:            Origin process identifier
214  *              Shared:
215  *                      Refc:           Number of invocations
216  *
217  *              Valid keys are only node-name atoms and internal process
218  *              identifiers.
219  *
220  *              Origin part of the monitor is stored in the monitor tree of
221  *              origin process and target part of the monitor is stored in
222  *              monitor list referred by 'monitors' field of the dist
223  *              structure.
224  *
225  *              --- ERTS_MON_TYPE_NODES ---------------------------------------
226  *
227  *              A local process (origin) monitors all connections (target),
228  *              via net_kernel:monitor_nodes().
229  *
230  *              Origin:
231  *                      Other Item:     Bit mask (small)
232  *                      Key:            Bit mask
233  *              Target:
234  *                      Other Item:     Origin process identifier
235  *                      Key:            Origin process identifier
236  *              Shared:
237  *                      Refc:           Number of invocations
238  *
239  *              Valid keys are only small integers and internal process
240  *              identifiers.
241  *
242  *              Origin part of the monitor is stored in the monitor tree of
243  *              origin process and target part of the monitor is stored in
244  *              monitor list referred by the variable 'nodes_monitors' (see
245  *              dist.c).
246  *
247  *              --- ERTS_MON_TYPE_SUSPEND -------------------------------------
248  *
249  *              Suspend monitor. A local process (origin) suspends another
250  *              local process (target).
251  *
252  *              Origin:
253  *                      Other Item:     Process identifier of suspendee
254  *                                      (target)
255  *                      Key:            Process identifier of suspendee
256  *                                      (target)
257  *              Target:
258  *                      Other Item:     Process identifier of suspender
259  *                                      (origin)
260  *                      Key:            Process identifier of suspender
261  *                                      (origin)
262  *              Shared:
263  *                      Next:           Pointer to another suspend monitor
264  *                      State:          Number of suspends and a flag
265  *                                      indicating if the suspend is
266  *                                      active or not.
267  *
268  *              Origin part of the monitor is stored in the monitor tree of
269  *              origin process and target part of the monitor is stored in
270  *              monitor list for local targets on the target process.
271  *
272  *
273  *
274  *              === Links =====================================================
275  *
276  *              The link data structure contains:
277  *              - an 'a' part that should be inserted in a data structure of
278  *                one entity and contains the identifier of the other involved
279  *                entity (b)
280  *              - a 'b' part that should be inserted in a data structure of
281  *                the other involved entity and contains the identifier of the
282  *                other involved entity (a)
283  *              - shared part that contains information shared between both
284  *                involved entities
285  *
286  *              That is, the two halves of the link as well as shared data
287  *              are allocated in one single continuous memory block. The 'a'
288  *              and the 'b' parts can separately each be inserted in either
289  *              a (red-black) tree, a (circular double linked) list, or in a
290  *              process signal queue.
291  *
292  *              Each process and port contains:
293  *              - a link tree for links that is accessed via the
294  *                ERTS_P_LINKS() macro
295  *
296  *              This field of processes/ports is protected by the main lock of
297  *              the process/port. It is only intended to be accessed by the
298  *              process/port itself. When setting up or tearing down a link
299  *              one should *only* operate on the link tree of the currently
300  *              executing process/port and send signals to the other involved
301  *              process/port so it can modify its own monitor tree by itself
302  *              (see erl_proc_sig_queue.h). One should absolutely *not*
303  *              acquire the lock of the other involved process/port and
304  *              operate on its link tree directly.
305  *
306  *              Each dist entry contains a monitor/link dist structure that
307  *              contains:
308  *              - a link list for links via the 'links' field.
309  *              Links in this field contain information about all links over
310  *              this specific connection.
311  *
312  *              The fields of the dist structure are protected by a mutex in
313  *              the same dist structure. Operation on the 'links' fields are
314  *              normally performed by the locally involved process only,
315  *              except when a connection is taken down.
316  *
317  *              Access to link trees are performed using the erts_link_tree_*
318  *              functions below. Access to link lists are performed using the
319  *              erts_link_list_* functions below.
320  *
321  *              There can only be one link between the same pair of
322  *              processes/ports. Since a link can be simultaneously initiated
323  *              from both ends we always save the link data structure with the
324  *              lowest address if multiple links should appear between the
325  *              same pair of processes/ports.
326  *
327  *
328  *              The different link types:
329  *
330  *              --- ERTS_LNK_TYPE_PROC -----------------------------------------
331  *
332  *              A link between a local process A and a local process B.
333  *
334  *              A:
335  *                      Other Item:     B process identifier
336  *                      Key:            B process identifier
337  *              B:
338  *                      Other Item:     A process identifier
339  *                      Key:            A process identifier
340  *
341  *              Valid keys are only internal process identifiers.
342  *
343  *              'A' part of the link stored in the link tree of process A and
344  *              'B' part of the link is stored in link tree of process B.
345  *
346  *              --- ERTS_LNK_TYPE_PORT -----------------------------------------
347  *
348  *              A link between a local process/port A and a local process/port
349  *              B.
350  *
351  *              A:
352  *                      Other Item:     B process/port identifier
353  *                      Key:            B process/port identifier
354  *              B:
355  *                      Other Item:     A process/port identifier
356  *                      Key:            A process/port identifier
357  *
358  *              Valid keys are internal process identifiers and internal port
359  *              identifiers.
360  *
361  *              'A' part of the link stored in the link tree of process/port
362  *              A and 'B' part of the link is stored in link tree of
363  *              process/port B.
364  *
365  *              --- ERTS_LNK_TYPE_DIST_PROC ------------------------------------
366  *
367  *              A link between a local process and a remote process. Either of
368  *              the processes can be used as A or B.
369  *
370  *              A:
371  *                      Other Item:     B process identifier
372  *                      Key:            B process identifier
373  *              B:
374  *                      Other Item:     A process identifier
375  *                      Key:            A process identifier
376  *              Shared:
377  *                      Dist:           Pointer to dist structure
378  *
379  *              Valid keys are internal and external process identifiers.
380  *
381  *              The part of the link with a remote pid as "other item" is
382  *              stored in the link tree of the local process. The part of
383  *              the link with a local pid as "other item" is stored in the
384  *              links list of the dist structure.
385  *
386  *              ===============================================================
387  *
388  * Author: 	Rickard Green
389  *
390  */
391 
392 #ifndef ERL_MONITOR_LINK_H__
393 #define ERL_MONITOR_LINK_H__
394 
395 #define ERTS_PROC_SIG_QUEUE_TYPE_ONLY
396 #include "erl_proc_sig_queue.h"
397 #undef ERTS_PROC_SIG_QUEUE_TYPE_ONLY
398 
399 #define ERL_THR_PROGRESS_TSD_TYPE_ONLY
400 #include "erl_thr_progress.h"
401 #undef ERL_THR_PROGRESS_TSD_TYPE_ONLY
402 
403 #include "erl_alloc.h"
404 
405 #if defined(DEBUG) || 0
406 #  define ERTS_ML_DEBUG
407 #else
408 #  undef ERTS_ML_DEBUG
409 #endif
410 
411 #ifdef ERTS_ML_DEBUG
412 #  define ERTS_ML_ASSERT ERTS_ASSERT
413 #else
414 #  define ERTS_ML_ASSERT(E) ((void) 1)
415 #endif
416 
417 #define ERTS_ML_STATE_ALIAS_BITS        2
418 #define ERTS_ML_STATE_ALIAS_SHIFT       11
419 #define ERTS_ML_STATE_ALIAS_MASK        \
420     ((((Uint16) 1 << ERTS_ML_STATE_ALIAS_BITS) - 1) \
421      << ERTS_ML_STATE_ALIAS_SHIFT)
422 
423 #define ERTS_ML_STATE_ALIAS_NONE        (((Uint16) 0) << ERTS_ML_STATE_ALIAS_SHIFT)
424 #define ERTS_ML_STATE_ALIAS_UNALIAS     (((Uint16) 1) << ERTS_ML_STATE_ALIAS_SHIFT)
425 #define ERTS_ML_STATE_ALIAS_DEMONITOR   (((Uint16) 2) << ERTS_ML_STATE_ALIAS_SHIFT)
426 #define ERTS_ML_STATE_ALIAS_ONCE        (((Uint16) 3) << ERTS_ML_STATE_ALIAS_SHIFT)
427 
428 #define ERTS_MON_TYPE_MAX               ((Uint16) 8)
429 
430 #define ERTS_MON_TYPE_PROC              ((Uint16) 0)
431 #define ERTS_MON_TYPE_PORT              ((Uint16) 1)
432 #define ERTS_MON_TYPE_TIME_OFFSET       ((Uint16) 2)
433 #define ERTS_MON_TYPE_DIST_PROC         ((Uint16) 3)
434 #define ERTS_MON_TYPE_RESOURCE          ((Uint16) 4)
435 #define ERTS_MON_TYPE_NODE              ((Uint16) 5)
436 #define ERTS_MON_TYPE_NODES             ((Uint16) 6)
437 #define ERTS_MON_TYPE_SUSPEND           ((Uint16) 7)
438 #define ERTS_MON_TYPE_ALIAS             ERTS_MON_TYPE_MAX
439 
440 #define ERTS_MON_LNK_TYPE_MAX           (ERTS_MON_TYPE_MAX + ((Uint16) 3))
441 #define ERTS_LNK_TYPE_MAX               ERTS_MON_LNK_TYPE_MAX
442 
443 #define ERTS_LNK_TYPE_PROC              (ERTS_MON_TYPE_MAX + ((Uint16) 1))
444 #define ERTS_LNK_TYPE_PORT              (ERTS_MON_TYPE_MAX + ((Uint16) 2))
445 #define ERTS_LNK_TYPE_DIST_PROC         ERTS_LNK_TYPE_MAX
446 
447 #define ERTS_ML_FLG_TARGET              (((Uint16) 1) << 0)
448 #define ERTS_ML_FLG_IN_TABLE            (((Uint16) 1) << 1)
449 #define ERTS_ML_FLG_IN_SUBTABLE         (((Uint16) 1) << 2)
450 #define ERTS_ML_FLG_NAME                (((Uint16) 1) << 3)
451 #define ERTS_ML_FLG_EXTENDED            (((Uint16) 1) << 4)
452 #define ERTS_ML_FLG_SPAWN_PENDING       (((Uint16) 1) << 5)
453 #define ERTS_ML_FLG_SPAWN_MONITOR       (((Uint16) 1) << 6)
454 #define ERTS_ML_FLG_SPAWN_LINK          (((Uint16) 1) << 7)
455 #define ERTS_ML_FLG_SPAWN_ABANDONED     (((Uint16) 1) << 8)
456 #define ERTS_ML_FLG_SPAWN_NO_SMSG       (((Uint16) 1) << 9)
457 #define ERTS_ML_FLG_SPAWN_NO_EMSG       (((Uint16) 1) << 10)
458 #define ERTS_ML_FLG_ALIAS_BIT1          (((Uint16) 1) << 11)
459 #define ERTS_ML_FLG_ALIAS_BIT2          (((Uint16) 1) << 12)
460 #define ERTS_ML_FLG_TAG                 (((Uint16) 1) << 13)
461 
462 #define ERTS_ML_FLG_DBG_VISITED         (((Uint16) 1) << 15)
463 
464 #define ERTS_ML_FLGS_SPAWN              (ERTS_ML_FLG_SPAWN_PENDING      \
465                                          | ERTS_ML_FLG_SPAWN_MONITOR    \
466                                          | ERTS_ML_FLG_SPAWN_LINK       \
467                                          | ERTS_ML_FLG_SPAWN_ABANDONED  \
468                                          | ERTS_ML_FLG_SPAWN_NO_SMSG    \
469                                          | ERTS_ML_FLG_SPAWN_NO_EMSG)
470 
471 /* Flags that should be the same on both monitor/link halves */
472 #define ERTS_ML_FLGS_SAME \
473     (ERTS_ML_FLG_EXTENDED|ERTS_ML_FLG_NAME)
474 
475 typedef struct ErtsMonLnkNode__ ErtsMonLnkNode;
476 typedef int (*ErtsMonLnkNodeFunc)(ErtsMonLnkNode *, void *, Sint);
477 
478 typedef struct {
479     UWord parent; /* Parent ptr and flags... */
480     ErtsMonLnkNode *right;
481     ErtsMonLnkNode *left;
482 } ErtsMonLnkTreeNode;
483 
484 typedef struct {
485     ErtsMonLnkNode *next;
486     ErtsMonLnkNode *prev;
487 } ErtsMonLnkListNode;
488 
489 struct ErtsMonLnkNode__ {
490     union {
491         ErtsSignalCommon signal;
492         ErtsMonLnkTreeNode tree;
493         ErtsMonLnkListNode list;
494     } node;
495     union {
496         Eterm item;
497         void *ptr;
498     } other;
499     Uint16 offset; /* offset from monitor/link data to this structure (node) */
500     Uint16 key_offset; /* offset from this structure (node) to key */
501     Uint16 flags;
502     Uint16 type;
503 };
504 
505 typedef struct ErtsMonLnkDist__ {
506     Eterm nodename;
507     Uint32 connection_id;
508     erts_atomic_t refc;
509     erts_mtx_t mtx;
510     int alive;
511     ErtsMonLnkNode *links; /* Link double linked circular list */
512     ErtsMonLnkNode *monitors; /* Monitor double linked circular list */
513     ErtsMonLnkNode *orig_name_monitors; /* Origin named monitors
514                                            read-black tree */
515     ErtsMonLnkNode *dist_pend_spawn_exit;
516     ErtsThrPrgrLaterOp cleanup_lop;
517 } ErtsMonLnkDist;
518 
519 /* * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * *\
520  * Misc                                                                      *
521 \*                                                                           */
522 
523 /**
524  *
525  * @brief Initialize monitor/link implementation
526  *
527  */
528 void erts_monitor_link_init(void);
529 
530 /**
531  *
532  * @brief Create monitor/link dist structure to attach to dist entry
533  *
534  * Create dist structure containing monitor and link containers. This
535  * structure is to be attached to a connected dist entry.
536  *
537  * @param[in]     nodename      Node name as an atom
538  *
539  * @returns                     Pointer to dist structure
540  *
541  */
542 ErtsMonLnkDist *erts_mon_link_dist_create(Eterm nodename);
543 
544 /**
545  *
546  * @brief Increase reference count of monitor/link dist structure
547  *
548  * @param[in]     mld           Pointer to dist structure
549  *
550  */
551 ERTS_GLB_INLINE void erts_mon_link_dist_inc_refc(ErtsMonLnkDist *mld);
552 
553 /**
554  *
555  * @brief Decrease reference count of monitor/link dist structure
556  *
557  * @param[in]     mld           Pointer to dist structure
558  *
559  */
560 ERTS_GLB_INLINE void erts_mon_link_dist_dec_refc(ErtsMonLnkDist *mld);
561 
562 /* internal functions... */
563 ERTS_GLB_INLINE void erts_ml_dl_list_insert__(ErtsMonLnkNode **list,
564                                               ErtsMonLnkNode *ml);
565 ERTS_GLB_INLINE void erts_ml_dl_list_delete__(ErtsMonLnkNode **list,
566                                               ErtsMonLnkNode *ml);
567 ERTS_GLB_INLINE ErtsMonLnkNode *erts_ml_dl_list_first__(ErtsMonLnkNode *list);
568 ERTS_GLB_INLINE ErtsMonLnkNode *erts_ml_dl_list_last__(ErtsMonLnkNode *list);
569 void erts_schedule_mon_link_dist_destruction__(ErtsMonLnkDist *mld);
570 ERTS_GLB_INLINE void *erts_ml_node_to_main_struct__(ErtsMonLnkNode *mln);
571 
572 /* implementations for globally inlined misc functions... */
573 #if ERTS_GLB_INLINE_INCL_FUNC_DEF
574 
575 ERTS_GLB_INLINE void
erts_mon_link_dist_inc_refc(ErtsMonLnkDist * mld)576 erts_mon_link_dist_inc_refc(ErtsMonLnkDist *mld)
577 {
578     ERTS_ML_ASSERT(erts_atomic_read_nob(&mld->refc) > 0);
579     erts_atomic_inc_nob(&mld->refc);
580 }
581 
582 ERTS_GLB_INLINE void
erts_mon_link_dist_dec_refc(ErtsMonLnkDist * mld)583 erts_mon_link_dist_dec_refc(ErtsMonLnkDist *mld)
584 {
585     ERTS_ML_ASSERT(erts_atomic_read_nob(&mld->refc) > 0);
586     if (erts_atomic_dec_read_nob(&mld->refc) == 0)
587         erts_schedule_mon_link_dist_destruction__(mld);
588 }
589 
590 ERTS_GLB_INLINE void *
erts_ml_node_to_main_struct__(ErtsMonLnkNode * mln)591 erts_ml_node_to_main_struct__(ErtsMonLnkNode *mln)
592 {
593     return (void *) (((char *) mln) - ((size_t) mln->offset));
594 }
595 
596 ERTS_GLB_INLINE void
erts_ml_dl_list_insert__(ErtsMonLnkNode ** list,ErtsMonLnkNode * ml)597 erts_ml_dl_list_insert__(ErtsMonLnkNode **list, ErtsMonLnkNode *ml)
598 {
599     ErtsMonLnkNode *first = *list;
600     ERTS_ML_ASSERT(!(ml->flags & ERTS_ML_FLG_IN_TABLE));
601     if (!first) {
602         ml->node.list.next = ml->node.list.prev = ml;
603         *list = ml;
604     }
605     else {
606         ERTS_ML_ASSERT(first->node.list.prev->node.list.next == first);
607         ERTS_ML_ASSERT(first->node.list.next->node.list.prev == first);
608         ml->node.list.next = first;
609         ml->node.list.prev = first->node.list.prev;
610         first->node.list.prev = ml;
611         ml->node.list.prev->node.list.next = ml;
612     }
613     ml->flags |= ERTS_ML_FLG_IN_TABLE;
614 }
615 
616 ERTS_GLB_INLINE void
erts_ml_dl_list_delete__(ErtsMonLnkNode ** list,ErtsMonLnkNode * ml)617 erts_ml_dl_list_delete__(ErtsMonLnkNode **list, ErtsMonLnkNode *ml)
618 {
619     ERTS_ML_ASSERT(ml->flags & ERTS_ML_FLG_IN_TABLE);
620     if (ml->node.list.next == ml) {
621         ERTS_ML_ASSERT(ml->node.list.prev == ml);
622         ERTS_ML_ASSERT(*list == ml);
623 
624         *list = NULL;
625     }
626     else {
627         ERTS_ML_ASSERT(ml->node.list.prev->node.list.next == ml);
628         ERTS_ML_ASSERT(ml->node.list.prev != ml);
629         ERTS_ML_ASSERT(ml->node.list.next->node.list.prev == ml);
630         ERTS_ML_ASSERT(ml->node.list.next != ml);
631 
632         if (*list == ml)
633             *list = ml->node.list.next;
634         ml->node.list.prev->node.list.next = ml->node.list.next;
635         ml->node.list.next->node.list.prev = ml->node.list.prev;
636     }
637     ml->flags &= ~ERTS_ML_FLG_IN_TABLE;
638 }
639 
640 ERTS_GLB_INLINE ErtsMonLnkNode *
erts_ml_dl_list_first__(ErtsMonLnkNode * list)641 erts_ml_dl_list_first__(ErtsMonLnkNode *list)
642 {
643     return list;
644 }
645 
646 ERTS_GLB_INLINE ErtsMonLnkNode *
erts_ml_dl_list_last__(ErtsMonLnkNode * list)647 erts_ml_dl_list_last__(ErtsMonLnkNode *list)
648 {
649     if (!list)
650         return NULL;
651     return list->node.list.prev;
652 }
653 
654 #endif /* ERTS_GLB_INLINE_INCL_FUNC_DEF */
655 
656 /* * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * *\
657  * Monitor Operations                                                        *
658 \*                                                                           */
659 
660 
661 typedef struct ErtsMonLnkNode__ ErtsMonitor;
662 typedef int (*ErtsMonitorFunc)(ErtsMonitor *, void *, Sint);
663 
664 typedef struct {
665     ErtsMonitor origin;
666     union {
667         ErtsMonitor target;
668         Eterm ref_heap[ERTS_MAX_INTERNAL_REF_SIZE];
669     } u;
670     Eterm ref;
671     erts_atomic32_t refc;
672 } ErtsMonitorData;
673 
674 typedef struct {
675     ErtsMonitorData md;
676     Eterm ref_heap[ERTS_MAX_INTERNAL_REF_SIZE];
677 } ErtsMonitorDataHeap;
678 
679 typedef struct {
680     ErtsMonitorData md;
681     Eterm heap[1 + ERTS_MAX_INTERNAL_REF_SIZE];
682 } ErtsMonitorDataTagHeap;
683 
684 typedef struct ErtsMonitorDataExtended__ ErtsMonitorDataExtended;
685 
686 struct ErtsMonitorDataExtended__ {
687     ErtsMonitorData md;
688     union {
689         Eterm name;
690         Uint refc;
691     } u;
692     union {
693         struct erl_off_heap_header *ohhp;
694         ErtsMonitor *node_monitors;
695     } uptr;
696     ErtsMonLnkDist *dist;
697     Eterm heap[1]; /* heap start... */
698 };
699 
700 typedef struct ErtsMonitorSuspend__ ErtsMonitorSuspend;
701 
702 
703 struct ErtsMonitorSuspend__ {
704     ErtsMonitorData md; /* origin = suspender; target = suspendee */
705     ErtsMonitorSuspend *next;
706     erts_atomic_t state;
707 };
708 #define ERTS_MSUSPEND_STATE_FLG_ACTIVE ((erts_aint_t) (((Uint) 1) << (sizeof(Uint)*8 - 1)))
709 #define ERTS_MSUSPEND_STATE_COUNTER_MASK (~ERTS_MSUSPEND_STATE_FLG_ACTIVE)
710 
711 /*
712  * --- Monitor tree operations ---
713  */
714 
715 /**
716  *
717  * @brief Lookup a monitor in a monitor tree
718  *
719  *
720  * @param[in]     root          Pointer to root of monitor tree
721  *
722  * @param[in]     key           Key of monitor to lookup
723  *
724  * @returns                     Pointer to a monitor with the
725  *                              key 'key', or NULL if no such
726  *                              monitor was found
727  *
728  */
729 ErtsMonitor *erts_monitor_tree_lookup(ErtsMonitor *root, Eterm key);
730 
731 /**
732  *
733  * @brief Lookup or insert a monitor in a monitor tree
734  *
735  * When the function is called it is assumed that:
736  * - 'mon' monitor is not part of any tree or list
737  * If the above is not true, bad things will happen.
738  *
739  * @param[in,out] root          Pointer to pointer to root of monitor tree
740  *
741  * @param[in]     mon           Monitor to insert if no monitor
742  *                              with the same key already exists
743  *
744  * @returns                     Pointer to a monitor with the
745  *                              key 'key'. If no monitor with the key
746  *                              'key' was found and 'mon' was inserted
747  *                              'NULL' is returned.
748  *
749  */
750 ErtsMonitor *erts_monotor_tree_lookup_insert(ErtsMonitor **root,
751                                              ErtsMonitor *mon);
752 
753 /**
754  *
755  * @brief Lookup or create a node or a nodes monitor in a monitor tree.
756  *
757  * Looks up an origin monitor with the key 'target' in the monitor tree.
758  * If it is not found, creates a monitor and returns a pointer to the
759  * origin monitor.
760  *
761  * When the function is called it is assumed that:
762  * - no target monitors with the key 'target' exists in the tree.
763  * If the above is not true, bad things will happen.
764  *
765  * @param[in,out] root          Pointer to pointer to root of monitor tree
766  *
767  * @param[out]    created       Pointer to integer. The integer is set to
768  *                              a non-zero value if no monitor with key
769  *                              'target' was found, and a new monitor
770  *                              was created. If a monitor was found, it
771  *                              is set to zero.
772  *
773  * @param[in]     type          ERTS_MON_TYPE_NODE | ERTS_MON_TYPE_NODES
774  *
775  * @param[in]     origin        The key of the origin
776  *
777  * @param[in]     target        The key of the target
778  *
779  */
780 ErtsMonitor *erts_monitor_tree_lookup_create(ErtsMonitor **root, int *created,
781                                              Uint16 type, Eterm origin,
782                                              Eterm target);
783 
784 /**
785  *
786  * @brief Insert a monitor in a monitor tree
787  *
788  * When the function is called it is assumed that:
789  * - no monitors with the same key that 'mon' exist in the tree
790  * - 'mon' is not part of any list of tree
791  * If the above are not true, bad things will happen.
792  *
793  * @param[in,out] root          Pointer to pointer to root of monitor tree
794  *
795  * @param[in]     mon           Monitor to insert.
796  *
797  */
798 void erts_monitor_tree_insert(ErtsMonitor **root, ErtsMonitor *mon);
799 
800 /**
801  *
802  * @brief Replace a monitor in a monitor tree
803  *
804  * When the function is called it is assumed that:
805  * - 'old' monitor and 'new' monitor have exactly the same key
806  * - 'old' monitor is part of the tree
807  * - 'new' monitor is not part of any tree or list
808  * If the above are not true, bad things will happen.
809  *
810  * @param[in,out] root          Pointer to pointer to root of monitor tree
811  *
812  * @param[in]     old           Monitor to remove from the tree
813  *
814  * @param[in]     new_           Monitor to insert into the tree
815  *
816  */
817 void erts_monitor_tree_replace(ErtsMonitor **root, ErtsMonitor *old,
818                                ErtsMonitor *new_);
819 
820 /**
821  *
822  * @brief Delete a monitor from a monitor tree
823  *
824  * When the function is called it is assumed that:
825  * - 'mon' monitor is part of the tree
826  * If the above is not true, bad things will happen.
827  *
828  * @param[in,out] root          Pointer to pointer to root of monitor tree
829  *
830  * @param[in]     mon           Monitor to remove from the tree
831  *
832  */
833 void erts_monitor_tree_delete(ErtsMonitor **root, ErtsMonitor *mon);
834 
835 /**
836  *
837  * @brief Call a function for each monitor in a monitor tree
838  *
839  * The function 'func' will be called with a pointer to a monitor
840  * as first argument and 'arg' as second argument for each monitor
841  * in the tree referred to by 'root'.
842  *
843  * @param[in]     root          Pointer to root of monitor tree
844  *
845  * @param[in]     func          Pointer to function to call
846  *
847  * @param[in]     arg           Argument to pass as second argument in
848  *                              calls to 'func'
849  *
850  */
851 void erts_monitor_tree_foreach(ErtsMonitor *root,
852                                ErtsMonitorFunc func,
853                                void *arg);
854 
855 /**
856  *
857  * @brief Call a function for each monitor in a monitor tree. Yield
858  *        if lots of monitors exist.
859  *
860  * The function 'func' will be called with a pointer to a monitor
861  * as first argument and 'arg' as second argument for each monitor
862  * in the tree referred to by 'root'. It should return the number of
863  * reductions the operator took to perform.
864  *
865  * It is assumed that:
866  * - *yspp equals NULL on first call
867  * - this function is repetedly called with *yspp set
868  *   as set when previous call returned until a non-zero
869  *   value is returned.
870  * - no modifications are made on the tree between first call
871  *   and the call that returns a non-zero value
872  * If the above are not true, bad things will happen.
873  *
874  * @param[in]     root          Pointer to root of monitor tree
875  *
876  * @param[in]     func          Pointer to function to call
877  *
878  * @param[in]     arg           Argument to pass as second argument in
879  *                              calls to 'func'
880  *
881  * @param[in,out] vyspp         Pointer to a pointer to an internal state
882  *                              used by this function. At initial call
883  *                              *yspp should be NULL. When done *yspp
884  *                              will be NULL.
885  *
886  * @param[in]     reds          Reductions available to execute before yielding.
887  *
888  * @returns                     The unconsumed reductions when all monitors
889  *                              have been processed, and zero when more work
890  *                              is needed.
891  *
892  */
893 int erts_monitor_tree_foreach_yielding(ErtsMonitor *root,
894                                        ErtsMonitorFunc func,
895                                        void *arg,
896                                        void **vyspp,
897                                        Sint reds);
898 
899 /**
900  *
901  * @brief Delete all monitors from a monitor tree and call a function for
902  *        each monitor
903  *
904  * The function 'func' will be called with a pointer to a monitor
905  * as first argument and 'arg' as second argument for each monitor
906  * in the tree referred to by 'root'. It should return the number of
907  * reductions the operator took to perform.
908  *
909  * @param[in,out] root          Pointer to pointer to root of monitor tree
910  *
911  * @param[in]     func          Pointer to function to call
912  *
913  * @param[in]     arg           Argument to pass as second argument in
914  *                              calls to 'func'
915  *
916  */
917 void erts_monitor_tree_foreach_delete(ErtsMonitor **root,
918                                       ErtsMonitorFunc func,
919                                       void *arg);
920 
921 /**
922  *
923  * @brief Delete all monitors from a monitor tree and call a function for
924  *        each monitor
925  *
926  * The function 'func' will be called with a pointer to a monitor
927  * as first argument and 'arg' as second argument for each monitor
928  * in the tree referred to by 'root'. It should return the number of
929  * reductions the operator took to perform.
930  *
931  * It is assumed that:
932  * - *yspp equals NULL on first call
933  * - this function is repetededly called with *yspp set
934  *   as set when previous call returned until a non-zero
935  *   value is returned.
936  * - no modifications are made on the tree between first call
937  *   and the call that returns a non-zero value
938  * If the above are not true, bad things will happen.
939  *
940  * @param[in,out] root          Pointer to pointer to root of monitor tree
941  *
942  * @param[in]     func          Pointer to function to call
943  *
944  * @param[in]     arg           Argument to pass as second argument in
945  *                              calls to 'func'
946  *
947  * @param[in,out] vyspp         Pointer to a pointer to an internal state
948  *                              used by this function. At initial call
949  *                              *yspp should be NULL. When done *yspp
950  *                              will be NULL.
951  *
952  * @param[in]     reds          Reductions available to execute before yielding.
953  *
954  * @returns                     The unconsumed reductions when all monitors
955  *                              have been processed, and zero when more work
956  *                              is needed.
957  *
958  */
959 int erts_monitor_tree_foreach_delete_yielding(ErtsMonitor **root,
960                                               ErtsMonitorFunc func,
961                                               void *arg,
962                                               void **vyspp,
963                                               Sint reds);
964 
965 /*
966  * --- Monitor list operations --
967  */
968 
969 /**
970  *
971  * @brief Insert a monitor in a monitor list
972  *
973  * When the function is called it is assumed that:
974  * - 'mon' monitor is not part of any list or tree
975  * If the above is not true, bad things will happen.
976  *
977  * @param[in,out] list          Pointer to pointer to monitor list
978  *
979  * @param[in]     mon           Monitor to insert
980  *
981  */
982 ERTS_GLB_INLINE void erts_monitor_list_insert(ErtsMonitor **list, ErtsMonitor *mon);
983 
984 /**
985  *
986  * @brief Delete a monitor from a monitor list
987  *
988  * When the function is called it is assumed that:
989  * - 'mon' monitor is part of the list
990  * If the above is not true, bad things will happen.
991  *
992  * @param[in,out] list          Pointer to pointer to monitor list
993  *
994  * @param[in]     mon           Monitor to remove from the list
995  *
996  */
997 ERTS_GLB_INLINE void erts_monitor_list_delete(ErtsMonitor **list, ErtsMonitor *mon);
998 
999 /**
1000  *
1001  * @brief Get a pointer to first monitor in a monitor list
1002  *
1003  * The monitor will still remain in the list after the return
1004  *
1005  * @param[in] list              Pointer to monitor list
1006  *
1007  * @returns                     Pointer to first monitor in list if
1008  *                              list is not empty. If list is empty
1009  *                              NULL is returned.
1010  *
1011  */
1012 ERTS_GLB_INLINE ErtsMonitor *erts_monitor_list_first(ErtsMonitor *list);
1013 
1014 /**
1015  *
1016  * @brief Get a pointer to last monitor in a monitor list
1017  *
1018  * The monitor will still remain in the list after the return
1019  *
1020  * @param[in] list              Pointer to monitor list
1021  *
1022  * @returns                     Pointer to last monitor in list if
1023  *                              list is not empty. If list is empty
1024  *                              NULL is returned.
1025  *
1026  */
1027 ERTS_GLB_INLINE ErtsMonitor *erts_monitor_list_last(ErtsMonitor *list);
1028 
1029 /**
1030  *
1031  * @brief Call a function for each monitor in a monitor list
1032  *
1033  * The function 'func' will be called with a pointer to a monitor
1034  * as first argument and 'arg' as second argument for each monitor
1035  * in the tree referred to by 'list'.
1036  *
1037  * @param[in]     list          Pointer to root of monitor list
1038  *
1039  * @param[in]     func          Pointer to function to call
1040  *
1041  * @param[in]     arg           Argument to pass as second argument in
1042  *                              calls to 'func'
1043  *
1044  */
1045 void erts_monitor_list_foreach(ErtsMonitor *list,
1046                                ErtsMonitorFunc func,
1047                                void *arg);
1048 
1049 /**
1050  *
1051  * @brief Call a function for each monitor in a monitor list. Yield
1052  *        if lots of monitors exist.
1053  *
1054  * The function 'func' will be called with a pointer to a monitor
1055  * as first argument and 'arg' as second argument for each monitor
1056  * in the tree referred to by 'root'. It should return the number of
1057  * reductions the operator took to perform.
1058  *
1059  * It is assumed that:
1060  * - *yspp equals NULL on first call
1061  * - this function is repetedly called with *yspp set
1062  *   as set when previous call returned until a non-zero
1063  *   value is returned.
1064  * - no modifications are made on the tree between first call
1065  *   and the call that returns a non-zero value
1066  * If the above are not true, bad things will happen.
1067  *
1068  * @param[in]     list          Pointer to monitor list
1069  *
1070  * @param[in]     func          Pointer to function to call
1071  *
1072  * @param[in]     arg           Argument to pass as second argument in
1073  *                              calls to 'func'
1074  *
1075  * @param[in,out] vyspp         Pointer to a pointer to an internal state
1076  *                              used by this function. At initial call
1077  *                              *yspp should be NULL. When done *yspp
1078  *                              will be NULL.
1079  *
1080  * @param[in]     reds          Reductions available to execute before yielding.
1081  *
1082  * @returns                     The unconsumed reductions when all monitors
1083  *                              have been processed, and zero when more work
1084  *                              is needed.
1085  *
1086  */
1087 int erts_monitor_list_foreach_yielding(ErtsMonitor *list,
1088                                        ErtsMonitorFunc func,
1089                                        void *arg,
1090                                        void **vyspp,
1091                                        Sint reds);
1092 
1093 /**
1094  *
1095  * @brief Delete all monitors from a monitor list and call a function for
1096  *        each monitor
1097  *
1098  * The function 'func' will be called with a pointer to a monitor
1099  * as first argument and 'arg' as second argument for each monitor
1100  * in the tree referred to by 'root'.
1101  *
1102  * @param[in,out] list          Pointer to pointer to monitor list
1103  *
1104  * @param[in]     func          Pointer to function to call
1105  *
1106  * @param[in]     arg           Argument to pass as second argument in
1107  *                              calls to 'func'
1108  *
1109  */
1110 void erts_monitor_list_foreach_delete(ErtsMonitor **list,
1111                                       ErtsMonitorFunc func,
1112                                       void *arg);
1113 
1114 /**
1115  *
1116  * @brief Delete all monitors from a monitor list and call a function for
1117  *        each monitor
1118  *
1119  * The function 'func' will be called with a pointer to a monitor
1120  * as first argument and 'arg' as second argument for each monitor
1121  * in the tree referred to by 'root'. It should return the number of
1122  * reductions the operator took to perform.
1123  *
1124  * It is assumed that:
1125  * - *yspp equals NULL on first call
1126  * - this function is repetededly called with *yspp set
1127  *   as set when previous call returned until a non-zero
1128  *   value is returned.
1129  * - no modifications are made on the tree between first
1130  *   and the call that returns a non-zero value
1131  * If the above are not true, bad things will happen.
1132  *
1133  * @param[in,out] list          Pointer to pointer to monitor list
1134  *
1135  * @param[in]     func          Pointer to function to call
1136  *
1137  * @param[in]     arg           Argument to pass as second argument in
1138  *                              calls to 'func'
1139  *
1140  * @param[in,out] vyspp         Pointer to a pointer to an internal state
1141  *                              used by this function. At initial call
1142  *                              *yspp should be NULL. When done *yspp
1143  *                              will be NULL.
1144  *
1145  * @param[in]     reds          Reductions available to execute before yielding.
1146  *
1147  * @returns                     The unconsumed reductions when all monitors
1148  *                              have been processed, and zero when more work
1149  *                              is needed.
1150  *
1151  */
1152 int erts_monitor_list_foreach_delete_yielding(ErtsMonitor **list,
1153                                               ErtsMonitorFunc func,
1154                                               void *arg,
1155                                               void **vyspp,
1156                                               Sint reds);
1157 
1158 /*
1159  * --- Misc monitor operations ---
1160  */
1161 
1162 /**
1163  *
1164  * @brief Create a monitor
1165  *
1166  * Can create all types of monitors
1167  *
1168  * When the function is called it is assumed that:
1169  * - 'ref' is an internal ordinary reference if type is ERTS_MON_TYPE_PROC,
1170  *   ERTS_MON_TYPE_PORT, ERTS_MON_TYPE_TIME_OFFSET, or ERTS_MON_TYPE_RESOURCE
1171  * - 'ref' is NIL if type is ERTS_MON_TYPE_NODE, ERTS_MON_TYPE_NODES, or
1172  *   ERTS_MON_TYPE_SUSPEND
1173  * - 'ref' is and ordinary internal reference or an external reference if
1174  *   type is ERTS_MON_TYPE_DIST_PROC
1175  * - 'name' is an atom or NIL if type is ERTS_MON_TYPE_PROC,
1176  *   ERTS_MON_TYPE_PORT, or ERTS_MON_TYPE_DIST_PROC
1177  * - 'name is NIL if type is ERTS_MON_TYPE_TIME_OFFSET, ERTS_MON_TYPE_RESOURCE,
1178  *   ERTS_MON_TYPE_NODE, ERTS_MON_TYPE_NODES, or ERTS_MON_TYPE_SUSPEND
1179  * If the above is not true, bad things will happen.
1180  *
1181  * @param[in]     type          ERTS_MON_TYPE_PROC, ERTS_MON_TYPE_PORT,
1182  *                              ERTS_MON_TYPE_TIME_OFFSET, ERTS_MON_TYPE_DIST_PROC,
1183  *                              ERTS_MON_TYPE_RESOURCE, ERTS_MON_TYPE_NODE,
1184  *                              ERTS_MON_TYPE_NODES, or ERTS_MON_TYPE_SUSPEND
1185  *
1186  * @param[in]     ref           A reference or NIL depending on type
1187  *
1188  * @param[in]     origin        The key of the origin
1189  *
1190  * @param[in]     target        The key of the target
1191  *
1192  * @param[in]     name          An atom (the name) or NIL depending on type
1193  *
1194  * @param[in]     tag           Tag to use in message when monitor is
1195  *                              triggered or THE_NON_VALUE if default
1196  *                              should be used.
1197  *
1198  * @returns                     A pointer to monitor data structure
1199  *
1200  */
1201 ErtsMonitorData *erts_monitor_create(Uint16 type, Eterm ref, Eterm origin,
1202                                      Eterm target, Eterm name, Eterm tag);
1203 
1204 /**
1205  *
1206  * @brief Get pointer to monitor data structure
1207  *
1208  * @param[in]    mon            Pointer to monitor
1209  *
1210  * @returns                     Pointer to monitor data structure
1211  *
1212  */
1213 ERTS_GLB_INLINE ErtsMonitorData *erts_monitor_to_data(ErtsMonitor *mon);
1214 
1215 /**
1216  *
1217  * @brief Check if monitor is a target monitor
1218  *
1219  * @param[in]    mon            Pointer to monitor to check
1220  *
1221  * @returns                     A non-zero value if target monitor;
1222  *                              otherwise zero
1223  *
1224  */
1225 ERTS_GLB_INLINE int erts_monitor_is_target(ErtsMonitor *mon);
1226 
1227 /**
1228  *
1229  * @brief Check if monitor is an origin monitor
1230  *
1231  * @param[in]    mon            Pointer to monitor to check
1232  *
1233  * @returns                     A non-zero value if origin monitor;
1234  *                              otherwise zero
1235  *
1236  */
1237 ERTS_GLB_INLINE int erts_monitor_is_origin(ErtsMonitor *mon);
1238 
1239 /**
1240  *
1241  * @brief Check if monitor is in tree or list
1242  *
1243  * @param[in]    mon            Pointer to monitor to check
1244  *
1245  * @returns                     A non-zero value if in tree or list;
1246  *                              otherwise zero
1247  *
1248  */
1249 ERTS_GLB_INLINE int erts_monitor_is_in_table(ErtsMonitor *mon);
1250 
1251 /**
1252  *
1253  * @brief Release monitor
1254  *
1255  * When both the origin and the target part of the monitor have
1256  * been released the monitor structure will be deallocated.
1257  *
1258  * When the function is called it is assumed that:
1259  * - 'mon' monitor is not part of any list or tree
1260  * - 'mon' is not referred to by any other structures
1261  * If the above are not true, bad things will happen.
1262  *
1263  * @param[in]    mon            Pointer to monitor
1264  *
1265  */
1266 ERTS_GLB_INLINE void erts_monitor_release(ErtsMonitor *mon);
1267 
1268 /**
1269  *
1270  * @brief Release both target and origin monitor structures simultaneously
1271  *
1272  * Release both the origin and target parts of the monitor
1273  * simultaneously and deallocate the structure.
1274  *
1275  * When the function is called it is assumed that:
1276  * - Neither the origin part nor the target part of the monitor
1277  *   are not part of any list or tree
1278  * - Neither the origin part nor the target part of the monitor
1279  *   are referred to by any other structures
1280  * If the above are not true, bad things will happen.
1281  *
1282  * @param[in]    mdp            Pointer to monitor data structure
1283  *
1284  */
1285 ERTS_GLB_INLINE void erts_monitor_release_both(ErtsMonitorData *mdp);
1286 
1287 /**
1288  *
1289  * @brief Insert monitor in dist monitor tree or list
1290  *
1291  * When the function is called it is assumed that:
1292  * - 'mon' monitor is not part of any list or tree
1293  * If the above is not true, bad things will happen.
1294  *
1295  * @param[in]    mon            Pointer to monitor
1296  *
1297  * @param[in]    dist           Pointer to dist structure
1298  *
1299  * @returns                     A non-zero value if inserted;
1300  *                              otherwise, zero. The monitor
1301  *                              is not inserted if the dist
1302  *                              structure has been set in a
1303  *                              dead state.
1304  *
1305  */
1306 ERTS_GLB_INLINE int erts_monitor_dist_insert(ErtsMonitor *mon, ErtsMonLnkDist *dist);
1307 
1308 /**
1309  *
1310  * @brief Delete monitor from dist monitor tree or list
1311  *
1312  * When the function is called it is assumed that:
1313  * - 'mon' monitor earler has been inserted into 'dist'
1314  * If the above is not true, bad things will happen.
1315  *
1316  * @param[in]    mon            Pointer to monitor
1317  *
1318  * @param[in]    dist           Pointer to dist structure
1319  *
1320  * @returns                     A non-zero value if deleted;
1321  *                              otherwise, zero. The monitor
1322  *                              is not deleted if the dist
1323  *                              structure has been set in a
1324  *                              dead state or if it has already
1325  *                              been deleted.
1326  *
1327  */
1328 ERTS_GLB_INLINE int erts_monitor_dist_delete(ErtsMonitor *mon);
1329 
1330 /**
1331  *
1332  * @brief Set dead dist structure on monitor
1333  *
1334  * @param[in]    mon            Pointer to monitor
1335  *
1336  * @param[in]    nodename       Name of remote node
1337  *
1338  */
1339 void
1340 erts_monitor_set_dead_dist(ErtsMonitor *mon, Eterm nodename);
1341 
1342 /**
1343  *
1344  * @brief Get charged size of monitor
1345  *
1346  * If the other side of the monitor has been released, the
1347  * whole size of the monitor data structure is returned; otherwise,
1348  * half of the size is returned.
1349  *
1350  * When the function is called it is assumed that:
1351  * - 'mon' has not been released
1352  * If the above is not true, bad things will happen.
1353  *
1354  * @param[in]    mon            Pointer to monitor
1355  *
1356  * @returns                     Charged size in bytes
1357  *
1358  */
1359 Uint erts_monitor_size(ErtsMonitor *mon);
1360 
1361 
1362 /* internal function... */
1363 void erts_monitor_destroy__(ErtsMonitorData *mdp);
1364 
1365 /* implementations for globally inlined monitor functions... */
1366 #if ERTS_GLB_INLINE_INCL_FUNC_DEF
1367 
1368 ERTS_GLB_INLINE int
erts_monitor_is_target(ErtsMonitor * mon)1369 erts_monitor_is_target(ErtsMonitor *mon)
1370 {
1371     return !!(mon->flags & ERTS_ML_FLG_TARGET);
1372 }
1373 
1374 ERTS_GLB_INLINE int
erts_monitor_is_origin(ErtsMonitor * mon)1375 erts_monitor_is_origin(ErtsMonitor *mon)
1376 {
1377     return !(mon->flags & ERTS_ML_FLG_TARGET);
1378 }
1379 
1380 ERTS_GLB_INLINE int
erts_monitor_is_in_table(ErtsMonitor * mon)1381 erts_monitor_is_in_table(ErtsMonitor *mon)
1382 {
1383     return !!(mon->flags & ERTS_ML_FLG_IN_TABLE);
1384 }
1385 
1386 ERTS_GLB_INLINE void
erts_monitor_list_insert(ErtsMonitor ** list,ErtsMonitor * mon)1387 erts_monitor_list_insert(ErtsMonitor **list, ErtsMonitor *mon)
1388 {
1389     erts_ml_dl_list_insert__((ErtsMonLnkNode **) list, (ErtsMonLnkNode *) mon);
1390 }
1391 
1392 ERTS_GLB_INLINE void
erts_monitor_list_delete(ErtsMonitor ** list,ErtsMonitor * mon)1393 erts_monitor_list_delete(ErtsMonitor **list, ErtsMonitor *mon)
1394 {
1395     erts_ml_dl_list_delete__((ErtsMonLnkNode **) list, (ErtsMonLnkNode *) mon);
1396 }
1397 
1398 ERTS_GLB_INLINE ErtsMonitor *
erts_monitor_list_first(ErtsMonitor * list)1399 erts_monitor_list_first(ErtsMonitor *list)
1400 {
1401     return (ErtsMonitor *) erts_ml_dl_list_first__((ErtsMonLnkNode *) list);
1402 }
1403 
1404 ERTS_GLB_INLINE ErtsMonitor *
erts_monitor_list_last(ErtsMonitor * list)1405 erts_monitor_list_last(ErtsMonitor *list)
1406 {
1407     return (ErtsMonitor *) erts_ml_dl_list_last__((ErtsMonLnkNode *) list);
1408 }
1409 
1410 #ifdef ERTS_ML_DEBUG
1411 extern size_t erts_monitor_origin_offset;
1412 extern size_t erts_monitor_origin_key_offset;
1413 extern size_t erts_monitor_target_offset;
1414 extern size_t erts_monitor_target_key_offset;
1415 extern size_t erts_monitor_node_key_offset;
1416 #endif
1417 
1418 ERTS_GLB_INLINE ErtsMonitorData *
erts_monitor_to_data(ErtsMonitor * mon)1419 erts_monitor_to_data(ErtsMonitor *mon)
1420 {
1421     ErtsMonitorData *mdp = (ErtsMonitorData *)erts_ml_node_to_main_struct__((ErtsMonLnkNode *) mon);
1422 
1423 #ifdef ERTS_ML_DEBUG
1424     ERTS_ML_ASSERT(!(mdp->origin.flags & ERTS_ML_FLG_TARGET));
1425     ERTS_ML_ASSERT(erts_monitor_origin_offset == (size_t) mdp->origin.offset);
1426     ERTS_ML_ASSERT(mon->type == ERTS_MON_TYPE_ALIAS
1427                    || !!(mdp->u.target.flags & ERTS_ML_FLG_TARGET));
1428     ERTS_ML_ASSERT(mon->type == ERTS_MON_TYPE_ALIAS
1429                    || erts_monitor_target_offset == (size_t) mdp->u.target.offset);
1430     if (mon->type == ERTS_MON_TYPE_NODE || mon->type == ERTS_MON_TYPE_NODES
1431         || mon->type == ERTS_MON_TYPE_SUSPEND) {
1432         ERTS_ML_ASSERT(erts_monitor_node_key_offset == (size_t) mdp->origin.key_offset);
1433         ERTS_ML_ASSERT(erts_monitor_node_key_offset == (size_t) mdp->u.target.key_offset);
1434     }
1435     else {
1436         ERTS_ML_ASSERT(erts_monitor_origin_key_offset == (size_t) mdp->origin.key_offset);
1437         ERTS_ML_ASSERT(mon->type == ERTS_MON_TYPE_ALIAS
1438                        || erts_monitor_target_key_offset == (size_t) mdp->u.target.key_offset);
1439     }
1440 #endif
1441 
1442     return mdp;
1443 }
1444 
1445 ERTS_GLB_INLINE void
erts_monitor_release(ErtsMonitor * mon)1446 erts_monitor_release(ErtsMonitor *mon)
1447 {
1448     ErtsMonitorData *mdp = erts_monitor_to_data(mon);
1449     ERTS_ML_ASSERT(erts_atomic32_read_nob(&mdp->refc) > 0);
1450 
1451     if (erts_atomic32_dec_read_mb(&mdp->refc) == 0) {
1452         ERTS_ML_ASSERT(!(mdp->origin.flags & ERTS_ML_FLG_IN_TABLE));
1453         ERTS_ML_ASSERT(mon->type == ERTS_MON_TYPE_ALIAS
1454                        || !(mdp->u.target.flags & ERTS_ML_FLG_IN_TABLE));
1455 
1456         erts_monitor_destroy__(mdp);
1457     }
1458 }
1459 
1460 ERTS_GLB_INLINE void
erts_monitor_release_both(ErtsMonitorData * mdp)1461 erts_monitor_release_both(ErtsMonitorData *mdp)
1462 {
1463     ERTS_ML_ASSERT((mdp->origin.flags & ERTS_ML_FLGS_SAME)
1464                    == (mdp->u.target.flags & ERTS_ML_FLGS_SAME));
1465     ERTS_ML_ASSERT(erts_atomic32_read_nob(&mdp->refc) >= 2);
1466 
1467     if (erts_atomic32_add_read_mb(&mdp->refc, (erts_aint32_t) -2) == 0) {
1468         ERTS_ML_ASSERT(!(mdp->origin.flags & ERTS_ML_FLG_IN_TABLE));
1469         ERTS_ML_ASSERT(!(mdp->u.target.flags & ERTS_ML_FLG_IN_TABLE));
1470 
1471         erts_monitor_destroy__(mdp);
1472     }
1473 }
1474 
1475 ERTS_GLB_INLINE int
erts_monitor_dist_insert(ErtsMonitor * mon,ErtsMonLnkDist * dist)1476 erts_monitor_dist_insert(ErtsMonitor *mon, ErtsMonLnkDist *dist)
1477 {
1478     ErtsMonitorDataExtended *mdep;
1479     int insert;
1480 
1481     ERTS_ML_ASSERT(mon->flags & ERTS_ML_FLG_EXTENDED);
1482     ERTS_ML_ASSERT(mon->type == ERTS_MON_TYPE_DIST_PROC
1483                    || mon->type == ERTS_MON_TYPE_NODE);
1484 
1485     mdep = (ErtsMonitorDataExtended *) erts_monitor_to_data(mon);
1486 
1487     ERTS_ML_ASSERT(!mdep->dist);
1488     ERTS_ML_ASSERT(dist);
1489 
1490     erts_mtx_lock(&dist->mtx);
1491 
1492     insert = dist->alive;
1493     if (insert) {
1494         mdep->dist = dist;
1495         erts_mon_link_dist_inc_refc(dist);
1496 
1497         if ((mon->flags & (ERTS_ML_FLG_NAME
1498                            | ERTS_ML_FLG_TARGET)) == ERTS_ML_FLG_NAME)
1499             erts_monitor_tree_insert(&dist->orig_name_monitors, mon);
1500         else
1501             erts_monitor_list_insert(&dist->monitors, mon);
1502     }
1503 
1504     erts_mtx_unlock(&dist->mtx);
1505 
1506     return insert;
1507 }
1508 
1509 ERTS_GLB_INLINE int
erts_monitor_dist_delete(ErtsMonitor * mon)1510 erts_monitor_dist_delete(ErtsMonitor *mon)
1511 {
1512     ErtsMonitorDataExtended *mdep;
1513     ErtsMonLnkDist *dist;
1514     Uint16 flags;
1515     int delete_;
1516 
1517     ERTS_ML_ASSERT(mon->flags & ERTS_ML_FLG_EXTENDED);
1518     ERTS_ML_ASSERT(mon->type == ERTS_MON_TYPE_DIST_PROC
1519                    || mon->type == ERTS_MON_TYPE_NODE);
1520 
1521     mdep = (ErtsMonitorDataExtended *) erts_monitor_to_data(mon);
1522     dist = mdep->dist;
1523     ERTS_ML_ASSERT(dist);
1524 
1525     erts_mtx_lock(&dist->mtx);
1526 
1527     flags = mon->flags;
1528     delete_ = !!dist->alive & !!(flags & ERTS_ML_FLG_IN_TABLE);
1529     if (delete_) {
1530         if ((flags & (ERTS_ML_FLG_NAME
1531                       | ERTS_ML_FLG_TARGET)) == ERTS_ML_FLG_NAME)
1532             erts_monitor_tree_delete(&dist->orig_name_monitors, mon);
1533         else
1534             erts_monitor_list_delete(&dist->monitors, mon);
1535     }
1536 
1537     erts_mtx_unlock(&dist->mtx);
1538 
1539     return delete_;
1540 }
1541 
1542 
1543 #endif /* ERTS_GLB_INLINE_INCL_FUNC_DEF */
1544 
1545 /* suspend monitors... */
1546 ErtsMonitorSuspend *erts_monitor_suspend_create(Eterm pid);
1547 ErtsMonitorSuspend *erts_monitor_suspend_tree_lookup_create(ErtsMonitor **root,
1548                                                             int *created,
1549                                                             Eterm pid);
1550 void erts_monitor_suspend_destroy(ErtsMonitorSuspend *msp);
1551 
1552 ERTS_GLB_INLINE ErtsMonitorSuspend *erts_monitor_suspend(ErtsMonitor *mon);
1553 
1554 #if ERTS_GLB_INLINE_INCL_FUNC_DEF
1555 
erts_monitor_suspend(ErtsMonitor * mon)1556 ERTS_GLB_INLINE ErtsMonitorSuspend *erts_monitor_suspend(ErtsMonitor *mon)
1557 {
1558     ERTS_ML_ASSERT(!mon || mon->type == ERTS_MON_TYPE_SUSPEND);
1559     return (ErtsMonitorSuspend *) mon;
1560 }
1561 
1562 #endif
1563 
1564 void
1565 erts_debug_monitor_tree_destroying_foreach(ErtsMonitor *root,
1566                                            ErtsMonitorFunc func,
1567                                            void *arg,
1568                                            void *vysp);
1569 void
1570 erts_debug_monitor_list_destroying_foreach(ErtsMonitor *list,
1571                                            ErtsMonitorFunc func,
1572                                            void *arg,
1573                                            void *vysp);
1574 
1575 /* * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * * *\
1576  * Link Operations                                                           *
1577 \*                                                                           */
1578 
1579 typedef struct ErtsMonLnkNode__ ErtsLink;
1580 
1581 typedef int (*ErtsLinkFunc)(ErtsLink *, void *, Sint);
1582 
1583 /* Internal Link */
1584 typedef struct {
1585     ErtsLink link;
1586     Uint64 unlinking;
1587 } ErtsILink;
1588 
1589 typedef struct {
1590     ErtsLink proc;
1591     ErtsLink dist;
1592     erts_atomic32_t refc;
1593 } ErtsLinkData;
1594 
1595 /* External Link */
1596 typedef struct {
1597     ErtsLinkData ld;
1598     struct erl_off_heap_header *ohhp;
1599     ErtsMonLnkDist *dist;
1600     Uint64 unlinking;
1601     Eterm heap[1]; /* heap start... */
1602 } ErtsELink;
1603 
1604 /*
1605  * --- Link tree operations ---
1606  */
1607 
1608 /**
1609  *
1610  * @brief Lookup a link in a link tree
1611  *
1612  *
1613  * @param[in]     root          Pointer to root of link tree
1614  *
1615  * @param[in]     key           Key of link to lookup
1616  *
1617  * @returns                     Pointer to a link with the
1618  *                              key 'key', or NULL if no such
1619  *                              link was found
1620  *
1621  */
1622 ErtsLink *erts_link_tree_lookup(ErtsLink *root, Eterm item);
1623 
1624 /**
1625  *
1626  * @brief Lookup or insert a link in a link tree
1627  *
1628  * When the function is called it is assumed that:
1629  * - 'lnk' link is not part of any tree or list
1630  * If the above is not true, bad things will happen.
1631  *
1632  * @param[in,out] root          Pointer to pointer to root of link tree
1633  *
1634  * @param[in]     lnk           Link to insert if no link
1635  *                              with the same key already exists
1636  *
1637  * @returns                     Pointer to a link with the
1638  *                              key 'key'. If no link with the key
1639  *                              'key' was found and 'lnk' was inserted
1640  *                              'NULL' is returned.
1641  *
1642  */
1643 ErtsLink *erts_link_tree_lookup_insert(ErtsLink **root, ErtsLink *lnk);
1644 
1645 /**
1646  *
1647  * @brief Lookup or create an external link in a link tree.
1648  *
1649  * Looks up a link with the key 'other' in the link tree. If it is not
1650  * found, creates and insert a link with the key 'other'.
1651  *
1652  * @param[in,out] root          Pointer to pointer to root of link tree
1653  *
1654  * @param[out]    created       Pointer to integer. The integer is set to
1655  *                              a non-zero value if no link with key
1656  *                              'other' was found, and a new link
1657  *                              was created. If a link was found, it
1658  *                              is set to zero.
1659  *
1660  * @param[in]     type          Type of link
1661  *
1662  * @param[in]     this          Id of this entity
1663  *
1664  * @param[in]     other         Id of other entity
1665  *
1666  * @returns                     Pointer to either an already existing
1667  *                              link in the tree or a newly created
1668  *                              and inserted link.
1669  *
1670  */
1671 ErtsLink *erts_link_external_tree_lookup_create(ErtsLink **root, int *created,
1672                                                 Uint16 type, Eterm this_, Eterm other);
1673 
1674 /**
1675  *
1676  * @brief Lookup or create an internal link in a link tree.
1677  *
1678  * Looks up a link with the key 'other' in the link tree. If it is not
1679  * found, creates and insert a link with the key 'other'.
1680  *
1681  * @param[in,out] root          Pointer to pointer to root of link tree
1682  *
1683  * @param[out]    created       Pointer to integer. The integer is set to
1684  *                              a non-zero value if no link with key
1685  *                              'other' was found, and a new link
1686  *                              was created. If a link was found, it
1687  *                              is set to zero.
1688  *
1689  * @param[in]     type          Type of link
1690  *
1691  * @param[in]     other         Id of other entity
1692  *
1693  * @returns                     Pointer to either an already existing
1694  *                              link in the tree or a newly created
1695  *                              and inserted link.
1696  *
1697  */
1698 ErtsLink *erts_link_internal_tree_lookup_create(ErtsLink **root, int *created,
1699                                                 Uint16 type, Eterm other);
1700 
1701 /**
1702  *
1703  * @brief Insert a link in a link tree
1704  *
1705  * When the function is called it is assumed that:
1706  * - no links with the same key that 'lnk' exist in the tree
1707  * - 'lnk' is not part of any list of tree
1708  * If the above are not true, bad things will happen.
1709  *
1710  * @param[in,out] root          Pointer to pointer to root of link tree
1711  *
1712  * @param[in]     lnk           Link to insert.
1713  *
1714  */
1715 void erts_link_tree_insert(ErtsLink **root, ErtsLink *lnk);
1716 
1717 /**
1718  *
1719  * @brief Replace a link in a link tree
1720  *
1721  * When the function is called it is assumed that:
1722  * - 'old' link and 'new' link have exactly the same key
1723  * - 'old' link is part of the tree
1724  * - 'new' link is not part of any tree or list
1725  * If the above are not true, bad things will happen.
1726  *
1727  * @param[in,out] root          Pointer to pointer to root of link tree
1728  *
1729  * @param[in]     old           Link to remove from the tree
1730  *
1731  * @param[in]     new           Link to insert into the tree
1732  *
1733  */
1734 void erts_link_tree_replace(ErtsLink **root, ErtsLink *old, ErtsLink *new_);
1735 
1736 /**
1737  *
1738  * @brief Replace a link in a link tree if key already exist based on adress
1739  *
1740  * Inserts the link 'lnk' in the tree if no link with the same key
1741  * already exists in tree. If a link with the same key exists in
1742  * the tree and 'lnk' has a lower address than the link in the
1743  * tree, the existing link in the tree is replaced by 'lnk'.
1744  *
1745  * When the function is called it is assumed that:
1746  * - 'lnk' link is not part of any tree or list
1747  * If the above are not true, bad things will happen.
1748  *
1749  * @param[in,out] root          Pointer to pointer to root of link tree
1750  *
1751  * @param[in]     lnk           Link to insert into the tree
1752  *
1753  * @returns                     A pointer to the link that is not part
1754  *                              of the tree after this operation.
1755  *
1756  */
1757 ERTS_GLB_INLINE ErtsLink *erts_link_tree_insert_addr_replace(ErtsLink **root,
1758                                                              ErtsLink *lnk);
1759 
1760 /**
1761  *
1762  * @brief Delete a link from a link tree
1763  *
1764  * When the function is called it is assumed that:
1765  * - 'lnk' link is part of the tree
1766  * If the above is not true, bad things will happen.
1767  *
1768  * @param[in,out] root          Pointer to pointer to root of link tree
1769  *
1770  * @param[in]     lnk           Link to remove from the tree
1771  *
1772  */
1773 void erts_link_tree_delete(ErtsLink **root, ErtsLink *lnk);
1774 
1775 /**
1776  *
1777  * @brief Delete a link from a link tree based on key
1778  *
1779  * If link 'lnk' is in the tree, 'lnk' is deleted from the tree.
1780  * If link 'lnk' is not in the tree, another link with the same
1781  * key as 'lnk' is deleted from the tree if such a link exist.
1782  *
1783  * When the function is called it is assumed that:
1784  * - if 'lnk' link is part of a tree or list, it is part of this tree
1785  * If the above is not true, bad things will happen.
1786  *
1787  * @param[in,out] root          Pointer to pointer to root of link tree
1788  *
1789  * @param[in]     lnk           Link to remove from the tree
1790  *
1791  * @returns                     A pointer to the link that was deleted
1792  *                              from the tree, or NULL in case no link
1793  *                              was deleted from the tree
1794  *
1795  */
1796 ERTS_GLB_INLINE ErtsLink *erts_link_tree_key_delete(ErtsLink **root, ErtsLink *lnk);
1797 
1798 /**
1799  *
1800  * @brief Call a function for each link in a link tree
1801  *
1802  * The function 'func' will be called with a pointer to a link
1803  * as first argument and 'arg' as second argument for each link
1804  * in the tree referred to by 'root'.
1805  *
1806  * @param[in]     root          Pointer to root of link tree
1807  *
1808  * @param[in]     func          Pointer to function to call
1809  *
1810  * @param[in]     arg           Argument to pass as second argument in
1811  *                              calls to 'func'
1812  *
1813  */
1814 void erts_link_tree_foreach(ErtsLink *root,
1815                             ErtsLinkFunc,
1816                             void *arg);
1817 
1818 /**
1819  *
1820  * @brief Call a function for each link in a link tree. Yield if lots
1821  *        of links exist.
1822  *
1823  * The function 'func' will be called with a pointer to a link
1824  * as first argument and 'arg' as second argument for each link
1825  * in the tree referred to by 'root'. It should return the number of
1826  * reductions the operator took to perform.
1827  *
1828  * It is assumed that:
1829  * - *yspp equals NULL on first call
1830  * - this function is repetedly called with *yspp set
1831  *   as set when previous call returned until a non-zero
1832  *   value is returned.
1833  * - no modifications are made on the tree between first call
1834  *   and the call that returns a non-zero value
1835  * If the above are not true, bad things will happen.
1836  *
1837  * @param[in]     root          Pointer to root of link tree
1838  *
1839  * @param[in]     func          Pointer to function to call
1840  *
1841  * @param[in]     arg           Argument to pass as second argument in
1842  *                              calls to 'func'
1843  *
1844  * @param[in,out] vyspp         Pointer to a pointer to an internal state
1845  *                              used by this function. At initial call
1846  *                              *yspp should be NULL. When done *yspp
1847  *                              will be NULL.
1848  *
1849  * @param[in]     reds          Reductions available to execute before yielding.
1850  *
1851  * @returns                     The unconsumed reductions when all links
1852  *                              have been processed, and zero when more work
1853  *                              is needed.
1854  *
1855  */
1856 int erts_link_tree_foreach_yielding(ErtsLink *root,
1857                                     ErtsLinkFunc func,
1858                                     void *arg,
1859                                     void **vyspp,
1860                                     Sint reds);
1861 
1862 /**
1863  *
1864  * @brief Delete all links from a link tree and call a function for
1865  *        each link
1866  *
1867  * The function 'func' will be called with a pointer to a link
1868  * as first argument and 'arg' as second argument for each link
1869  * in the tree referred to by 'root'.
1870  *
1871  * @param[in,out] root          Pointer to pointer to root of link tree
1872  *
1873  * @param[in]     func          Pointer to function to call
1874  *
1875  * @param[in]     arg           Argument to pass as second argument in
1876  *                              calls to 'func'
1877  *
1878  */
1879 void erts_link_tree_foreach_delete(ErtsLink **root,
1880                                    ErtsLinkFunc func,
1881                                    void *arg);
1882 
1883 /**
1884  *
1885  * @brief Delete all links from a link tree and call a function for
1886  *        each link
1887  *
1888  * The function 'func' will be called with a pointer to a link
1889  * as first argument and 'arg' as second argument for each link
1890  * in the tree referred to by 'root'. It should return the number of
1891  * reductions the operator took to perform.
1892  *
1893  * It is assumed that:
1894  * - *yspp equals NULL on first call
1895  * - this function is repetededly called with *yspp set
1896  *   as set when previous call returned until a non-zero
1897  *   value is returned.
1898  * - no modifications are made on the tree between first call
1899  *   and the call that returns a non-zero value
1900  * If the above are not true, bad things will happen.
1901  *
1902  * @param[in,out] root          Pointer to pointer to root of link tree
1903  *
1904  * @param[in]     func          Pointer to function to call
1905  *
1906  * @param[in]     arg           Argument to pass as second argument in
1907  *                              calls to 'func'
1908  *
1909  * @param[in,out] vyspp         Pointer to a pointer to an internal state
1910  *                              used by this function. At initial call
1911  *                              *yspp should be NULL. When done *yspp
1912  *                              will be NULL.
1913  *
1914  * @param[in]     reds          Reductions available to execute before yielding.
1915  *
1916  * @returns                     The unconsumed reductions when all links
1917  *                              have been processed, and zero when more work
1918  *                              is needed.
1919  *
1920  */
1921 int erts_link_tree_foreach_delete_yielding(ErtsLink **root,
1922                                            ErtsLinkFunc func,
1923                                            void *arg,
1924                                            void **vyspp,
1925                                            Sint reds);
1926 
1927 /*
1928  * --- Link list operations ---
1929  */
1930 
1931 /**
1932  *
1933  * @brief Insert a link in a link list
1934  *
1935  * When the function is called it is assumed that:
1936  * - 'lnk' link is not part of any list or tree
1937  * If the above is not true, bad things will happen.
1938  *
1939  * @param[in,out] list          Pointer to pointer to link list
1940  *
1941  * @param[in]     lnk           Link to insert
1942  *
1943  */
1944 ERTS_GLB_INLINE void erts_link_list_insert(ErtsLink **list, ErtsLink *lnk);
1945 
1946 /**
1947  *
1948  * @brief Delete a link from a link list
1949  *
1950  * When the function is called it is assumed that:
1951  * - 'lnk' link is part of the list
1952  * If the above is not true, bad things will happen.
1953  *
1954  * @param[in,out] list          Pointer to pointer to link list
1955  *
1956  * @param[in]     lnk           Link to remove from the list
1957  *
1958  */
1959 ERTS_GLB_INLINE void erts_link_list_delete(ErtsLink **list, ErtsLink *lnk);
1960 
1961 /**
1962  *
1963  * @brief Get a pointer to first link in a link list
1964  *
1965  * The link will still remain in the list after the return
1966  *
1967  * @param[in] list              Pointer to link list
1968  *
1969  * @returns                     Pointer to first link in list if
1970  *                              list is not empty. If list is empty
1971  *                              NULL is returned.
1972  *
1973  */
1974 ERTS_GLB_INLINE ErtsLink *erts_link_list_first(ErtsLink *list);
1975 
1976 /**
1977  *
1978  * @brief Get a pointer to last link in a link list
1979  *
1980  * The link will still remain in the list after the return
1981  *
1982  * @param[in] list              Pointer to link list
1983  *
1984  * @returns                     Pointer to last link in list if
1985  *                              list is not empty. If list is empty
1986  *                              NULL is returned.
1987  *
1988  */
1989 ERTS_GLB_INLINE ErtsLink *erts_link_list_last(ErtsLink *list);
1990 
1991 /**
1992  *
1993  * @brief Call a function for each link in a link list
1994  *
1995  * The function 'func' will be called with a pointer to a link
1996  * as first argument and 'arg' as second argument for each link
1997  * in the tree referred to by 'list'.
1998  *
1999  * @param[in]     list          Pointer to root of link list
2000  *
2001  * @param[in]     func          Pointer to function to call
2002  *
2003  * @param[in]     arg           Argument to pass as second argument in
2004  *                              calls to 'func'
2005  *
2006  */
2007 void erts_link_list_foreach(ErtsLink *list,
2008                             ErtsLinkFunc func,
2009                             void *arg);
2010 
2011 /**
2012  *
2013  * @brief Call a function for each link in a link list. Yield
2014  *        if lots of links exist.
2015  *
2016  * The function 'func' will be called with a pointer to a link
2017  * as first argument and 'arg' as second argument for each link
2018  * in the tree referred to by 'root'. It should return the number of
2019  * reductions the operator took to perform.
2020  *
2021  * It is assumed that:
2022  * - *yspp equals NULL on first call
2023  * - this function is repetedly called with *yspp set
2024  *   as set when previous call returned until a non-zero
2025  *   value is returned.
2026  * - no modifications are made on the tree between first call
2027  *   and the call that returns a non-zero value
2028  * If the above are not true, bad things will happen.
2029  *
2030  * @param[in]     list          Pointer to link list
2031  *
2032  * @param[in]     func          Pointer to function to call
2033  *
2034  * @param[in]     arg           Argument to pass as second argument in
2035  *                              calls to 'func'
2036  *
2037  * @param[in,out] vyspp         Pointer to a pointer to an internal state
2038  *                              used by this function. At initial call
2039  *                              *yspp should be NULL. When done *yspp
2040  *                              will be NULL.
2041  *
2042  * @param[in]     reds          Reductions available to execute before yielding.
2043  *
2044  * @returns                     The unconsumed reductions when all links
2045  *                              have been processed, and zero when more work
2046  *                              is needed.
2047  *
2048  */
2049 int erts_link_list_foreach_yielding(ErtsLink *list,
2050                                     ErtsLinkFunc func,
2051                                     void *arg,
2052                                     void **vyspp,
2053                                     Sint reds);
2054 
2055 /**
2056  *
2057  * @brief Delete all links from a link list and call a function for
2058  *        each link
2059  *
2060  * The function 'func' will be called with a pointer to a link
2061  * as first argument and 'arg' as second argument for each link
2062  * in the tree referred to by 'root'.
2063  *
2064  * @param[in,out] list          Pointer to pointer to link list
2065  *
2066  * @param[in]     func          Pointer to function to call
2067  *
2068  * @param[in]     arg           Argument to pass as second argument in
2069  *                              calls to 'func'
2070  *
2071  */
2072 void erts_link_list_foreach_delete(ErtsLink **list,
2073                                    ErtsLinkFunc func,
2074                                    void *arg);
2075 
2076 /**
2077  *
2078  * @brief Delete all links from a link list and call a function for
2079  *        each link
2080  *
2081  * The function 'func' will be called with a pointer to a link
2082  * as first argument and 'arg' as second argument for each link
2083  * in the tree referred to by 'root'. It should return the number of
2084  * reductions the operator took to perform.
2085  *
2086  * It is assumed that:
2087  * - *yspp equals NULL on first call
2088  * - this function is repetededly called with *yspp set
2089  *   as set when previous call returned until a non-zero
2090  *   value is returned.
2091  * - no modifications are made on the tree between first
2092  *   and the call that returns a non-zero value
2093  * If the above are not true, bad things will happen.
2094  *
2095  * @param[in,out] list          Pointer to pointer to link list
2096  *
2097  * @param[in]     func          Pointer to function to call
2098  *
2099  * @param[in]     arg           Argument to pass as second argument in
2100  *                              calls to 'func'
2101  *
2102  * @param[in,out] vyspp         Pointer to a pointer to an internal state
2103  *                              used by this function. At initial call
2104  *                              *yspp should be NULL. When done *yspp
2105  *                              will be NULL.
2106  *
2107  * @param[in]     reds          Reductions available to execute before yielding.
2108  *
2109  * @returns                     The unconsumed reductions when all links
2110  *                              have been processed, and zero when more work
2111  *                              is needed.
2112  *
2113  */
2114 int erts_link_list_foreach_delete_yielding(ErtsLink **list,
2115                                            ErtsLinkFunc func,
2116                                            void *arg,
2117                                            void **vyspp,
2118                                            Sint reds);
2119 
2120 /*
2121  * --- Misc link operations ---
2122  */
2123 
2124 /**
2125  *
2126  * @brief Create an external link
2127  *
2128  * An external link structure contains two links, one for usage in
2129  * the link tree of the process and one for usage in the dist entry.
2130  *
2131  *
2132  * @param[in]     type          ERTS_MON_TYPE_DIST_PROC
2133  *
2134  * @param[in]     this          The process identifier of the local
2135  *                              process. The link structure in the
2136  *                              'dist' field a will have its
2137  *                              'other.item' field set to 'this'.
2138  *                              The 'dist' link structure is to be
2139  *                              inserted on the distribution entry.
2140  *
2141  * @param[in]     other         The process identifier of the remote
2142  *                              process. The link structure in the
2143  *                              'proc' field a will have its
2144  *                              'other.item' field set to 'other'.
2145  *                              The 'proc' link structure is to be
2146  *                              inserted on the local process.
2147  *
2148  * @returns                     A pointer to the link data structure
2149  *                              containing the link structures. The
2150  *                              link data structure is in turn part
2151  *                              of the external link structure
2152  *                              (ErtsELink).
2153  *
2154  */
2155 ErtsLinkData *erts_link_external_create(Uint16 type, Eterm this_, Eterm other);
2156 
2157 /**
2158  *
2159  * @brief Create an internal link
2160  *
2161  * @param[in]     type          ERTS_MON_TYPE_PROC, ERTS_MON_TYPE_PORT,
2162  *
2163  * @param[in]     id            Id of the entity linked.
2164  *
2165  * @returns                     A pointer to the link stucture.
2166  */
2167 ErtsLink *erts_link_internal_create(Uint16 type, Eterm id);
2168 
2169 /**
2170  *
2171  * @brief Get pointer to external link data structure
2172  *
2173  * @param[in]    lnk            Pointer to link
2174  *
2175  * @returns                     Pointer to external link structure
2176  *
2177  */
2178 ERTS_GLB_INLINE ErtsELink *erts_link_to_elink(ErtsLink *lnk);
2179 
2180 /**
2181  *
2182  * @brief Get pointer to the other link structure part of the link
2183  *
2184  * @param[in]    lnk            Pointer to link structure
2185  *
2186  * @param[out]   elnkpp         Pointer to pointer to external link
2187  *                              data structure, if a non-NULL value
2188  *                              is passed in the call
2189  *
2190  * @returns                     Pointer to other link structure
2191  *
2192  */
2193 ERTS_GLB_INLINE ErtsLink *erts_link_to_other(ErtsLink *lnk, ErtsELink **elnkpp);
2194 
2195 /**
2196  *
2197  * @brief Check if link is in tree or list
2198  *
2199  * @param[in]    lnk            Pointer to lnk to check
2200  *
2201  * @returns                     A non-zero value if in tree or list;
2202  *                              otherwise zero
2203  *
2204  */
2205 ERTS_GLB_INLINE int erts_link_is_in_table(ErtsLink *lnk);
2206 
2207 /**
2208  *
2209  * @brief Release an internal link
2210  *
2211  * When the function is called it is assumed that:
2212  * - 'lnk' link is not part of any list or tree
2213  * - 'lnk' is not referred to by any other structures
2214  * If the above are not true, bad things will happen.
2215  *
2216  * @param[in]    lnk            Pointer to link
2217  *
2218  */
2219 ERTS_GLB_INLINE void erts_link_internal_release(ErtsLink *lnk);
2220 
2221 /**
2222  *
2223  * @brief Release link
2224  *
2225  * Can be used to release a link half of an external
2226  * link as well as an internal link. In the external
2227  * case both link halves part of the external link have
2228  * to been released before the link structure will be
2229  * deallocated.
2230  *
2231  * When the function is called it is assumed that:
2232  * - 'lnk' link is not part of any list or tree
2233  * - 'lnk' is not referred to by any other structures
2234  * If the above are not true, bad things will happen.
2235  *
2236  * @param[in]    lnk            Pointer to link
2237  *
2238  */
2239 ERTS_GLB_INLINE void erts_link_release(ErtsLink *lnk);
2240 
2241 /**
2242  *
2243  * @brief Release both link halves of an external link
2244  *        simultaneously
2245  *
2246  * Release both halves of an external link simultaneously and
2247  * deallocate the structure.
2248  *
2249  * When the function is called it is assumed that:
2250  * - Neither of the parts of the link are part of any list or tree
2251  * - Neither of the parts of the link or the link data structure
2252  *   are referred to by any other structures
2253  * If the above are not true, bad things will happen.
2254  *
2255  * @param[in]    mdp            Pointer to link data structure
2256  *
2257  */
2258 ERTS_GLB_INLINE void erts_link_release_both(ErtsLinkData *ldp);
2259 
2260 /**
2261  *
2262  * @brief Insert link in dist link list
2263  *
2264  * When the function is called it is assumed that:
2265  * - 'lnk' link is not part of any list or tree
2266  * If the above is not true, bad things will happen.
2267  *
2268  * @param[in]    lnk            Pointer to link
2269  *
2270  * @param[in]    dist           Pointer to dist structure
2271  *
2272  * @returns                     A non-zero value if inserted;
2273  *                              otherwise, zero. The link
2274  *                              is not inserted if the dist
2275  *                              structure has been set in a
2276  *                              dead state.
2277  *
2278  */
2279 ERTS_GLB_INLINE int erts_link_dist_insert(ErtsLink *lnk, ErtsMonLnkDist *dist);
2280 
2281 /**
2282  *
2283  * @brief Delete link from dist link list
2284  *
2285  * When the function is called it is assumed that:
2286  * - 'lnk' link earler has been inserted into 'dist'
2287  * If the above is not true, bad things will happen.
2288  *
2289  * @param[in]    lnk            Pointer to link
2290  *
2291  * @param[in]    dist           Pointer to dist structure
2292  *
2293  * @returns                     A non-zero value if deleted;
2294  *                              otherwise, zero. The link
2295  *                              is not deleted if the dist
2296  *                              structure has been set in a
2297  *                              dead state or if it has already
2298  *                              been deleted.
2299  *
2300  */
2301 ERTS_GLB_INLINE int erts_link_dist_delete(ErtsLink *lnk);
2302 
2303 /**
2304  *
2305  * @brief Set dead dist structure on link
2306  *
2307  * @param[in]    lnk            Pointer to link
2308  *
2309  * @param[in]    nodename       Name of remote node
2310  *
2311  */
2312 void
2313 erts_link_set_dead_dist(ErtsLink *lnk, Eterm nodename);
2314 
2315 /**
2316  *
2317  * @brief Get charged size of link
2318  *
2319  * If the other side of the link has been released, the
2320  * whole size of the link data structure is returned; otherwise,
2321  * half of the size is returned.
2322  *
2323  * When the function is called it is assumed that:
2324  * - 'lnk' has not been released
2325  * If the above is not true, bad things will happen.
2326  *
2327  * @param[in]    lnk            Pointer to link
2328  *
2329  * @returns                     Charged size in bytes
2330  *
2331  */
2332 Uint erts_link_size(ErtsLink *lnk);
2333 
2334 /* internal function... */
2335 void erts_link_destroy_elink__(ErtsELink *elnk);
2336 
2337 /* implementations for globally inlined link functions... */
2338 #if ERTS_GLB_INLINE_INCL_FUNC_DEF
2339 
2340 #ifdef ERTS_ML_DEBUG
2341 extern size_t erts_link_proc_offset;
2342 extern size_t erts_link_dist_offset;
2343 extern size_t erts_link_key_offset;
2344 #endif
2345 
2346 ERTS_GLB_INLINE ErtsELink *
erts_link_to_elink(ErtsLink * lnk)2347 erts_link_to_elink(ErtsLink *lnk)
2348 {
2349     ErtsELink *elnk;
2350 
2351     ERTS_ML_ASSERT(lnk->flags & ERTS_ML_FLG_EXTENDED);
2352 
2353     elnk = (ErtsELink *) erts_ml_node_to_main_struct__((ErtsMonLnkNode *) lnk);
2354 
2355 #ifdef ERTS_ML_DEBUG
2356     ERTS_ML_ASSERT(erts_link_proc_offset == (size_t) elnk->ld.proc.offset);
2357     ERTS_ML_ASSERT(erts_link_key_offset == (size_t) elnk->ld.proc.key_offset);
2358     ERTS_ML_ASSERT(erts_link_dist_offset == (size_t) elnk->ld.dist.offset);
2359     ERTS_ML_ASSERT(erts_link_key_offset == (size_t) elnk->ld.dist.key_offset);
2360 #endif
2361 
2362     return elnk;
2363 }
2364 
2365 ERTS_GLB_INLINE ErtsLink *
erts_link_to_other(ErtsLink * lnk,ErtsELink ** elnkpp)2366 erts_link_to_other(ErtsLink *lnk, ErtsELink **elnkpp)
2367 {
2368     ErtsELink *elnk = erts_link_to_elink(lnk);
2369     if (elnkpp)
2370         *elnkpp = elnk;
2371     return lnk == &elnk->ld.proc ? &elnk->ld.dist : &elnk->ld.proc;
2372 }
2373 
2374 ERTS_GLB_INLINE int
erts_link_is_in_table(ErtsLink * lnk)2375 erts_link_is_in_table(ErtsLink *lnk)
2376 {
2377     return !!(lnk->flags & ERTS_ML_FLG_IN_TABLE);
2378 }
2379 
2380 ERTS_GLB_INLINE void
erts_link_list_insert(ErtsLink ** list,ErtsLink * lnk)2381 erts_link_list_insert(ErtsLink **list, ErtsLink *lnk)
2382 {
2383     erts_ml_dl_list_insert__((ErtsMonLnkNode **) list, (ErtsMonLnkNode *) lnk);
2384 }
2385 
2386 ERTS_GLB_INLINE void
erts_link_list_delete(ErtsLink ** list,ErtsLink * lnk)2387 erts_link_list_delete(ErtsLink **list, ErtsLink *lnk)
2388 {
2389     erts_ml_dl_list_delete__((ErtsMonLnkNode **) list, (ErtsMonLnkNode *) lnk);
2390 }
2391 
2392 ERTS_GLB_INLINE ErtsLink *
erts_link_list_first(ErtsLink * list)2393 erts_link_list_first(ErtsLink *list)
2394 {
2395     return (ErtsLink *) erts_ml_dl_list_first__((ErtsMonLnkNode *) list);
2396 }
2397 
2398 ERTS_GLB_INLINE ErtsLink *
erts_link_list_last(ErtsLink * list)2399 erts_link_list_last(ErtsLink *list)
2400 {
2401     return (ErtsLink *) erts_ml_dl_list_last__((ErtsMonLnkNode *) list);
2402 }
2403 
2404 ERTS_GLB_INLINE void
erts_link_internal_release(ErtsLink * lnk)2405 erts_link_internal_release(ErtsLink *lnk)
2406 {
2407     ERTS_ML_ASSERT(lnk->type == ERTS_LNK_TYPE_PROC
2408                    || lnk->type == ERTS_LNK_TYPE_PORT);
2409     ERTS_ML_ASSERT(!(lnk->flags & ERTS_ML_FLG_EXTENDED));
2410     erts_free(ERTS_ALC_T_LINK, lnk);
2411 }
2412 
2413 ERTS_GLB_INLINE void
erts_link_release(ErtsLink * lnk)2414 erts_link_release(ErtsLink *lnk)
2415 {
2416     if (!(lnk->flags & ERTS_ML_FLG_EXTENDED))
2417         erts_link_internal_release(lnk);
2418     else {
2419         ErtsELink *elnk = erts_link_to_elink(lnk);
2420         ERTS_ML_ASSERT(!(lnk->flags & ERTS_ML_FLG_IN_TABLE));
2421         ERTS_ML_ASSERT(erts_atomic32_read_nob(&elnk->ld.refc) > 0);
2422         if (erts_atomic32_dec_read_nob(&elnk->ld.refc) == 0)
2423             erts_link_destroy_elink__(elnk);
2424     }
2425 }
2426 
2427 ERTS_GLB_INLINE void
erts_link_release_both(ErtsLinkData * ldp)2428 erts_link_release_both(ErtsLinkData *ldp)
2429 {
2430     ERTS_ML_ASSERT(!(ldp->proc.flags & ERTS_ML_FLG_IN_TABLE));
2431     ERTS_ML_ASSERT(!(ldp->dist.flags & ERTS_ML_FLG_IN_TABLE));
2432     ERTS_ML_ASSERT(erts_atomic32_read_nob(&ldp->refc) >= 2);
2433     ERTS_ML_ASSERT(ldp->proc.flags & ERTS_ML_FLG_EXTENDED);
2434     ERTS_ML_ASSERT(ldp->dist.flags & ERTS_ML_FLG_EXTENDED);
2435     if (erts_atomic32_add_read_nob(&ldp->refc, (erts_aint32_t) -2) == 0)
2436         erts_link_destroy_elink__((ErtsELink *) ldp);
2437 }
2438 
2439 ERTS_GLB_INLINE ErtsLink *
erts_link_tree_insert_addr_replace(ErtsLink ** root,ErtsLink * lnk)2440 erts_link_tree_insert_addr_replace(ErtsLink **root, ErtsLink *lnk)
2441 {
2442     ErtsLink *lnk2 = erts_link_tree_lookup_insert(root, lnk);
2443     if (!lnk2)
2444         return NULL;
2445     if (lnk2 < lnk)
2446         return lnk;
2447     erts_link_tree_replace(root, lnk2, lnk);
2448     return lnk2;
2449 }
2450 
2451 ERTS_GLB_INLINE ErtsLink *
erts_link_tree_key_delete(ErtsLink ** root,ErtsLink * lnk)2452 erts_link_tree_key_delete(ErtsLink **root, ErtsLink *lnk)
2453 {
2454     ErtsLink *dlnk;
2455     if (erts_link_is_in_table(lnk))
2456         dlnk = lnk;
2457     else
2458         dlnk = erts_link_tree_lookup(*root, lnk->other.item);
2459     if (dlnk)
2460         erts_link_tree_delete(root, dlnk);
2461     return dlnk;
2462 }
2463 
2464 ERTS_GLB_INLINE int
erts_link_dist_insert(ErtsLink * lnk,ErtsMonLnkDist * dist)2465 erts_link_dist_insert(ErtsLink *lnk, ErtsMonLnkDist *dist)
2466 {
2467     ErtsELink *elnk;
2468     int insert;
2469 
2470     ERTS_ML_ASSERT(lnk->flags & ERTS_ML_FLG_EXTENDED);
2471     ERTS_ML_ASSERT(lnk->type == ERTS_LNK_TYPE_DIST_PROC);
2472 
2473     elnk = erts_link_to_elink(lnk);
2474 
2475     ERTS_ML_ASSERT(!elnk->dist);
2476     ERTS_ML_ASSERT(dist);
2477 
2478     erts_mtx_lock(&dist->mtx);
2479 
2480     insert = dist->alive;
2481     if (insert) {
2482         elnk->dist = dist;
2483         erts_mon_link_dist_inc_refc(dist);
2484         erts_link_list_insert(&dist->links, lnk);
2485     }
2486 
2487     erts_mtx_unlock(&dist->mtx);
2488 
2489     return insert;
2490 }
2491 
2492 ERTS_GLB_INLINE int
erts_link_dist_delete(ErtsLink * lnk)2493 erts_link_dist_delete(ErtsLink *lnk)
2494 {
2495     ErtsELink *elnk;
2496     ErtsMonLnkDist *dist;
2497     int delete_;
2498 
2499     ERTS_ML_ASSERT(lnk->flags & ERTS_ML_FLG_EXTENDED);
2500     ERTS_ML_ASSERT(lnk->type == ERTS_LNK_TYPE_DIST_PROC);
2501 
2502     elnk = erts_link_to_elink(lnk);
2503     dist = elnk->dist;
2504     if (!dist)
2505         return -1;
2506 
2507     erts_mtx_lock(&dist->mtx);
2508 
2509     delete_ = !!dist->alive & !!(lnk->flags & ERTS_ML_FLG_IN_TABLE);
2510     if (delete_)
2511         erts_link_list_delete(&dist->links, lnk);
2512 
2513     erts_mtx_unlock(&dist->mtx);
2514 
2515     return delete_;
2516 }
2517 
2518 
2519 #endif /* ERTS_GLB_INLINE_INCL_FUNC_DEF */
2520 
2521 void
2522 erts_debug_link_tree_destroying_foreach(ErtsLink *root,
2523                                         ErtsLinkFunc func,
2524                                         void *arg,
2525                                         void *vysp);
2526 
2527 #endif /* ERL_MONITOR_LINK_H__ */
2528