1 /*
2  * %CopyrightBegin%
3  *
4  * Copyright Ericsson AB 2000-2017. 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 package com.ericsson.otp.erlang;
21 
22 /**
23  * <p>
24  * Provides a simple mechanism for exchanging messages with Erlang processes or
25  * other instances of this class.
26  * </p>
27  *
28  * <p>
29  * Each mailbox is associated with a unique {@link OtpErlangPid pid} that
30  * contains information necessary for delivery of messages. When sending
31  * messages to named processes or mailboxes, the sender pid is made available to
32  * the recipient of the message. When sending messages to other mailboxes, the
33  * recipient can only respond if the sender includes the pid as part of the
34  * message contents. The sender can determine his own pid by calling
35  * {@link #self() self()}.
36  * </p>
37  *
38  * <p>
39  * Mailboxes can be named, either at creation or later. Messages can be sent to
40  * named mailboxes and named Erlang processes without knowing the
41  * {@link OtpErlangPid pid} that identifies the mailbox. This is necessary in
42  * order to set up initial communication between parts of an application. Each
43  * mailbox can have at most one name.
44  * </p>
45  *
46  * <p>
47  * Since this class was intended for communication with Erlang, all of the send
48  * methods take {@link OtpErlangObject OtpErlangObject} arguments. However this
49  * class can also be used to transmit arbitrary Java objects (as long as they
50  * implement one of java.io.Serializable or java.io.Externalizable) by
51  * encapsulating the object in a {@link OtpErlangBinary OtpErlangBinary}.
52  * </p>
53  *
54  * <p>
55  * Messages to remote nodes are externalized for transmission, and as a result
56  * the recipient receives a <b>copy</b> of the original Java object. To ensure
57  * consistent behaviour when messages are sent between local mailboxes, such
58  * messages are cloned before delivery.
59  * </p>
60  *
61  * <p>
62  * Additionally, mailboxes can be linked in much the same way as Erlang
63  * processes. If a link is active when a mailbox is {@link #close closed}, any
64  * linked Erlang processes or OtpMboxes will be sent an exit signal. As well,
65  * exit signals will be (eventually) sent if a mailbox goes out of scope and its
66  * {@link #finalize finalize()} method called. However due to the nature of
67  * finalization (i.e. Java makes no guarantees about when {@link #finalize
68  * finalize()} will be called) it is recommended that you always explicitly
69  * close mailboxes if you are using links instead of relying on finalization to
70  * notify other parties in a timely manner.
71  * </p>
72  *
73  * <p>
74  * When retrieving messages from a mailbox that has received an exit signal, an
75  * {@link OtpErlangExit OtpErlangExit} exception will be raised. Note that the
76  * exception is queued in the mailbox along with other messages, and will not be
77  * raised until it reaches the head of the queue and is about to be retrieved.
78  * </p>
79  *
80  */
81 public class OtpMbox {
82     OtpNode home;
83     OtpErlangPid self;
84     GenericQueue queue;
85     String name;
86     Links links;
87     private long unlink_id;
88 
89     // package constructor: called by OtpNode:createMbox(name)
90     // to create a named mbox
OtpMbox(final OtpNode home, final OtpErlangPid self, final String name)91     OtpMbox(final OtpNode home, final OtpErlangPid self, final String name) {
92         this.self = self;
93         this.home = home;
94         this.name = name;
95         this.unlink_id = 1;
96         queue = new GenericQueue();
97         links = new Links(10);
98     }
99 
100     // package constructor: called by OtpNode:createMbox()
101     // to create an anonymous
OtpMbox(final OtpNode home, final OtpErlangPid self)102     OtpMbox(final OtpNode home, final OtpErlangPid self) {
103         this(home, self, null);
104     }
105 
106     /**
107      * <p>
108      * Get the identifying {@link OtpErlangPid pid} associated with this
109      * mailbox.
110      * </p>
111      *
112      * <p>
113      * The {@link OtpErlangPid pid} associated with this mailbox uniquely
114      * identifies the mailbox and can be used to address the mailbox. You can
115      * send the {@link OtpErlangPid pid} to a remote communicating part so that
116      * he can know where to send his response.
117      * </p>
118      *
119      * @return the self pid for this mailbox.
120      */
self()121     public OtpErlangPid self() {
122         return self;
123     }
124 
125     /**
126      * <p>
127      * Register or remove a name for this mailbox. Registering a name for a
128      * mailbox enables others to send messages without knowing the
129      * {@link OtpErlangPid pid} of the mailbox. A mailbox can have at most one
130      * name; if the mailbox already had a name, calling this method will
131      * supercede that name.
132      * </p>
133      *
134      * @param aname
135      *            the name to register for the mailbox. Specify null to
136      *            unregister the existing name from this mailbox.
137      *
138      * @return true if the name was available, or false otherwise.
139      */
registerName(final String aname)140     public synchronized boolean registerName(final String aname) {
141         return home.registerName(aname, this);
142     }
143 
144     /**
145      * Get the registered name of this mailbox.
146      *
147      * @return the registered name of this mailbox, or null if the mailbox had
148      *         no registered name.
149      */
getName()150     public String getName() {
151         return name;
152     }
153 
154     /**
155      * Block until a message arrives for this mailbox.
156      *
157      * @return an {@link OtpErlangObject OtpErlangObject} representing the body
158      *         of the next message waiting in this mailbox.
159      *
160      * @exception OtpErlangDecodeException
161      *                if the message cannot be decoded.
162      *
163      * @exception OtpErlangExit
164      *                if a linked {@link OtpErlangPid pid} has exited or has
165      *                sent an exit signal to this mailbox.
166      */
receive()167     public OtpErlangObject receive() throws OtpErlangExit,
168             OtpErlangDecodeException {
169         try {
170             return receiveMsg().getMsg();
171         } catch (final OtpErlangExit e) {
172             throw e;
173         } catch (final OtpErlangDecodeException f) {
174             throw f;
175         }
176     }
177 
178     /**
179      * Wait for a message to arrive for this mailbox.
180      *
181      * @param timeout
182      *            the time, in milliseconds, to wait for a message before
183      *            returning null.
184      *
185      * @return an {@link OtpErlangObject OtpErlangObject} representing the body
186      *         of the next message waiting in this mailbox.
187      *
188      * @exception OtpErlangDecodeException
189      *                if the message cannot be decoded.
190      *
191      * @exception OtpErlangExit
192      *                if a linked {@link OtpErlangPid pid} has exited or has
193      *                sent an exit signal to this mailbox.
194      */
receive(final long timeout)195     public OtpErlangObject receive(final long timeout) throws OtpErlangExit,
196             OtpErlangDecodeException {
197         try {
198             final OtpMsg m = receiveMsg(timeout);
199             if (m != null) {
200                 return m.getMsg();
201             }
202         } catch (final OtpErlangExit e) {
203             throw e;
204         } catch (final OtpErlangDecodeException f) {
205             throw f;
206         } catch (final InterruptedException g) {
207         }
208         return null;
209     }
210 
211     /**
212      * Block until a message arrives for this mailbox.
213      *
214      * @return a byte array representing the still-encoded body of the next
215      *         message waiting in this mailbox.
216      *
217      * @exception OtpErlangExit
218      *                if a linked {@link OtpErlangPid pid} has exited or has
219      *                sent an exit signal to this mailbox.
220      *
221      */
receiveBuf()222     public OtpInputStream receiveBuf() throws OtpErlangExit {
223         return receiveMsg().getMsgBuf();
224     }
225 
226     /**
227      * Wait for a message to arrive for this mailbox.
228      *
229      * @param timeout
230      *            the time, in milliseconds, to wait for a message before
231      *            returning null.
232      *
233      * @return a byte array representing the still-encoded body of the next
234      *         message waiting in this mailbox.
235      *
236      * @exception OtpErlangExit
237      *                if a linked {@link OtpErlangPid pid} has exited or has
238      *                sent an exit signal to this mailbox.
239      *
240      * @exception InterruptedException
241      *                if no message if the method times out before a message
242      *                becomes available.
243      */
receiveBuf(final long timeout)244     public OtpInputStream receiveBuf(final long timeout)
245             throws InterruptedException, OtpErlangExit {
246         final OtpMsg m = receiveMsg(timeout);
247         if (m != null) {
248             return m.getMsgBuf();
249         }
250 
251         return null;
252     }
253 
254     /**
255      * Block until a message arrives for this mailbox.
256      *
257      * @return an {@link OtpMsg OtpMsg} containing the header information as
258      *         well as the body of the next message waiting in this mailbox.
259      *
260      * @exception OtpErlangExit
261      *                if a linked {@link OtpErlangPid pid} has exited or has
262      *                sent an exit signal to this mailbox.
263      *
264      */
receiveMsg()265     public OtpMsg receiveMsg() throws OtpErlangExit {
266 
267         final OtpMsg m = (OtpMsg) queue.get();
268 
269         switch (m.type()) {
270         case OtpMsg.exitTag:
271         case OtpMsg.exit2Tag:
272             try {
273                 final OtpErlangObject o = m.getMsg();
274                 throw new OtpErlangExit(o, m.getSenderPid());
275             } catch (final OtpErlangDecodeException e) {
276                 throw new OtpErlangExit("unknown", m.getSenderPid());
277             }
278 
279         default:
280             return m;
281         }
282     }
283 
284     /**
285      * Wait for a message to arrive for this mailbox.
286      *
287      * @param timeout
288      *            the time, in milliseconds, to wait for a message.
289      *
290      * @return an {@link OtpMsg OtpMsg} containing the header information as
291      *         well as the body of the next message waiting in this mailbox.
292      *
293      * @exception OtpErlangExit
294      *                if a linked {@link OtpErlangPid pid} has exited or has
295      *                sent an exit signal to this mailbox.
296      *
297      * @exception InterruptedException
298      *                if no message if the method times out before a message
299      *                becomes available.
300      */
receiveMsg(final long timeout)301     public OtpMsg receiveMsg(final long timeout) throws InterruptedException,
302             OtpErlangExit {
303         final OtpMsg m = (OtpMsg) queue.get(timeout);
304 
305         if (m == null) {
306             return null;
307         }
308 
309         switch (m.type()) {
310         case OtpMsg.exitTag:
311         case OtpMsg.exit2Tag:
312             try {
313                 final OtpErlangObject o = m.getMsg();
314                 throw new OtpErlangExit(o, m.getSenderPid());
315             } catch (final OtpErlangDecodeException e) {
316                 throw new OtpErlangExit("unknown", m.getSenderPid());
317             }
318 
319         default:
320             return m;
321         }
322     }
323 
324     /**
325      * Send a message to a remote {@link OtpErlangPid pid}, representing either
326      * another {@link OtpMbox mailbox} or an Erlang process.
327      *
328      * @param to
329      *            the {@link OtpErlangPid pid} identifying the intended
330      *            recipient of the message.
331      *
332      * @param msg
333      *            the body of the message to send.
334      *
335      */
send(final OtpErlangPid to, final OtpErlangObject msg)336     public void send(final OtpErlangPid to, final OtpErlangObject msg) {
337         try {
338             final String node = to.node();
339             if (node.equals(home.node())) {
340                 home.deliver(new OtpMsg(to, (OtpErlangObject) msg.clone()));
341             } else {
342                 final OtpCookedConnection conn = home.getConnection(node);
343                 if (conn == null) {
344                     return;
345                 }
346                 conn.send(self, to, msg);
347             }
348         } catch (final Exception e) {
349         }
350     }
351 
352     /**
353      * Send a message to a named mailbox created from the same node as this
354      * mailbox.
355      *
356      * @param aname
357      *            the registered name of recipient mailbox.
358      *
359      * @param msg
360      *            the body of the message to send.
361      *
362      */
send(final String aname, final OtpErlangObject msg)363     public void send(final String aname, final OtpErlangObject msg) {
364         home.deliver(new OtpMsg(self, aname, (OtpErlangObject) msg.clone()));
365     }
366 
367     /**
368      * Send a message to a named mailbox created from another node.
369      *
370      * @param aname
371      *            the registered name of recipient mailbox.
372      *
373      * @param node
374      *            the name of the remote node where the recipient mailbox is
375      *            registered.
376      *
377      * @param msg
378      *            the body of the message to send.
379      *
380      */
send(final String aname, final String node, final OtpErlangObject msg)381     public void send(final String aname, final String node,
382             final OtpErlangObject msg) {
383         try {
384             final String currentNode = home.node();
385             if (node.equals(currentNode)) {
386                 send(aname, msg);
387             } else if (node.indexOf('@', 0) < 0
388                     && node.equals(currentNode.substring(0,
389                             currentNode.indexOf('@', 0)))) {
390                 send(aname, msg);
391             } else {
392                 // other node
393                 final OtpCookedConnection conn = home.getConnection(node);
394                 if (conn == null) {
395                     return;
396                 }
397                 conn.send(self, aname, msg);
398             }
399         } catch (final Exception e) {
400         }
401     }
402 
403     /**
404      * Close this mailbox with the given reason.
405      *
406      * <p>
407      * After this operation, the mailbox will no longer be able to receive
408      * messages. Any delivered but as yet unretrieved messages can still be
409      * retrieved however.
410      * </p>
411      *
412      * <p>
413      * If there are links from this mailbox to other {@link OtpErlangPid pids},
414      * they will be broken when this method is called and exit signals will be
415      * sent.
416      * </p>
417      *
418      * @param reason
419      *            an Erlang term describing the reason for the exit.
420      */
exit(final OtpErlangObject reason)421     public void exit(final OtpErlangObject reason) {
422         home.closeMbox(this, reason);
423     }
424 
425     /**
426      * Equivalent to <code>exit(new OtpErlangAtom(reason))</code>.
427      *
428      * @see #exit(OtpErlangObject)
429      */
exit(final String reason)430     public void exit(final String reason) {
431         exit(new OtpErlangAtom(reason));
432     }
433 
434     /**
435      * <p>
436      * Send an exit signal to a remote {@link OtpErlangPid pid}. This method
437      * does not cause any links to be broken, except indirectly if the remote
438      * {@link OtpErlangPid pid} exits as a result of this exit signal.
439      * </p>
440      *
441      * @param to
442      *            the {@link OtpErlangPid pid} to which the exit signal should
443      *            be sent.
444      *
445      * @param reason
446      *            an Erlang term indicating the reason for the exit.
447      */
448     // it's called exit, but it sends exit2
exit(final OtpErlangPid to, final OtpErlangObject reason)449     public void exit(final OtpErlangPid to, final OtpErlangObject reason) {
450         exit(2, to, reason);
451     }
452 
453     /**
454      * <p>
455      * Equivalent to <code>exit(to, new
456      * OtpErlangAtom(reason))</code>.
457      * </p>
458      *
459      * @see #exit(OtpErlangPid, OtpErlangObject)
460      */
exit(final OtpErlangPid to, final String reason)461     public void exit(final OtpErlangPid to, final String reason) {
462         exit(to, new OtpErlangAtom(reason));
463     }
464 
465     // this function used internally when "process" dies
466     // since Erlang discerns between exit and exit/2.
exit(final int arity, final OtpErlangPid to, final OtpErlangObject reason)467     private void exit(final int arity, final OtpErlangPid to,
468             final OtpErlangObject reason) {
469         try {
470             final String node = to.node();
471             if (node.equals(home.node())) {
472                 home.deliver(new OtpMsg(OtpMsg.exitTag, self, to, reason));
473             } else {
474                 final OtpCookedConnection conn = home.getConnection(node);
475                 if (conn == null) {
476                     return;
477                 }
478                 switch (arity) {
479                 case 1:
480                     conn.exit(self, to, reason);
481                     break;
482 
483                 case 2:
484                     conn.exit2(self, to, reason);
485                     break;
486                 }
487             }
488         } catch (final Exception e) {
489         }
490     }
491 
492     /**
493      * <p>
494      * Link to a remote mailbox or Erlang process. Links are idempotent, calling
495      * this method multiple times will not result in more than one link being
496      * created.
497      * </p>
498      *
499      * <p>
500      * If the remote process subsequently exits or the mailbox is closed, a
501      * subsequent attempt to retrieve a message through this mailbox will cause
502      * an {@link OtpErlangExit OtpErlangExit} exception to be raised. Similarly,
503      * if the sending mailbox is closed, the linked mailbox or process will
504      * receive an exit signal.
505      * </p>
506      *
507      * <p>
508      * If the remote process cannot be reached in order to set the link, the
509      * exception is raised immediately.
510      * </p>
511      *
512      * @param to
513      *            the {@link OtpErlangPid pid} representing the object to link
514      *            to.
515      *
516      * @exception OtpErlangExit
517      *                if the {@link OtpErlangPid pid} referred to does not exist
518      *                or could not be reached.
519      *
520      */
link(final OtpErlangPid to)521     public synchronized void link(final OtpErlangPid to) throws OtpErlangExit {
522         if (!links.addLink(self, to, true))
523             return; /* Already linked... */
524 
525         try {
526             final String node = to.node();
527             if (node.equals(home.node())) {
528                 if (!home.deliver(new OtpMsg(OtpMsg.linkTag, self, to))) {
529                     throw new OtpErlangExit("noproc", to);
530                 }
531             } else {
532                 final OtpCookedConnection conn = home.getConnection(node);
533                 if (conn != null) {
534                     conn.link(self, to); // may throw 'noproc'
535                     conn.node_link(self, to, true);
536                 } else {
537                     throw new OtpErlangExit("noproc", to);
538                 }
539             }
540         } catch (final OtpErlangExit e) {
541             links.removeLink(self, to);
542             throw e;
543         } catch (final Exception e) {
544         }
545 
546     }
547 
548     /**
549      * <p>
550      * Remove a link to a remote mailbox or Erlang process. This method removes
551      * a link created with {@link #link link()}. Links are idempotent; calling
552      * this method once will remove all links between this mailbox and the
553      * remote {@link OtpErlangPid pid}.
554      * </p>
555      *
556      * @param to
557      *            the {@link OtpErlangPid pid} representing the object to unlink
558      *            from.
559      *
560      */
unlink(final OtpErlangPid to)561     public synchronized void unlink(final OtpErlangPid to) {
562         long unlink_id = this.unlink_id++;
563         if (unlink_id == 0)
564             unlink_id = this.unlink_id++;
565         if (links.setUnlinking(self, to, unlink_id)) {
566             try {
567                 final String node = to.node();
568                 if (node.equals(home.node())) {
569                     home.deliver(new OtpMsg(OtpMsg.unlinkTag, self, to));
570                 } else {
571                     final OtpCookedConnection conn = home.getConnection(node);
572                     if (conn != null) {
573                         conn.unlink(self, to, unlink_id);
574                     }
575                 }
576             } catch (final Exception e) {
577             }
578         }
579     }
580 
581     /**
582      * <p>
583      * Get information about all processes and/or mail boxes currently
584      * linked to this mail box.
585      * </p>
586      *
587      * @return an array of all pids currently linked to this mail box.
588      *
589      */
linked()590     public synchronized OtpErlangPid[] linked() {
591         return links.remotePids();
592     }
593 
594     /**
595      * <p>
596      * Create a connection to a remote node.
597      * </p>
598      *
599      * <p>
600      * Strictly speaking, this method is not necessary simply to set up a
601      * connection, since connections are created automatically first time a
602      * message is sent to a {@link OtpErlangPid pid} on the remote node.
603      * </p>
604      *
605      * <p>
606      * This method makes it possible to wait for a node to come up, however, or
607      * check that a node is still alive.
608      * </p>
609      *
610      * <p>
611      * This method calls a method with the same name in {@link OtpNode#ping
612      * Otpnode} but is provided here for convenience.
613      * </p>
614      *
615      * @param node
616      *            the name of the node to ping.
617      *
618      * @param timeout
619      *            the time, in milliseconds, before reporting failure.
620      */
ping(final String node, final long timeout)621     public boolean ping(final String node, final long timeout) {
622         return home.ping(node, timeout);
623     }
624 
625     /**
626      * <p>
627      * Get a list of all known registered names on the same {@link OtpNode node}
628      * as this mailbox.
629      * </p>
630      *
631      * <p>
632      * This method calls a method with the same name in {@link OtpNode#getNames
633      * Otpnode} but is provided here for convenience.
634      * </p>
635      *
636      * @return an array of Strings containing all registered names on this
637      *         {@link OtpNode node}.
638      */
getNames()639     public String[] getNames() {
640         return home.getNames();
641     }
642 
643     /**
644      * Determine the {@link OtpErlangPid pid} corresponding to a registered name
645      * on this {@link OtpNode node}.
646      *
647      * <p>
648      * This method calls a method with the same name in {@link OtpNode#whereis
649      * Otpnode} but is provided here for convenience.
650      * </p>
651      *
652      * @return the {@link OtpErlangPid pid} corresponding to the registered
653      *         name, or null if the name is not known on this node.
654      */
whereis(final String aname)655     public OtpErlangPid whereis(final String aname) {
656         return home.whereis(aname);
657     }
658 
659     /**
660      * Close this mailbox.
661      *
662      * <p>
663      * After this operation, the mailbox will no longer be able to receive
664      * messages. Any delivered but as yet unretrieved messages can still be
665      * retrieved however.
666      * </p>
667      *
668      * <p>
669      * If there are links from this mailbox to other {@link OtpErlangPid pids},
670      * they will be broken when this method is called and exit signals with
671      * reason 'normal' will be sent.
672      * </p>
673      *
674      * <p>
675      * This is equivalent to {@link #exit(String) exit("normal")}.
676      * </p>
677      */
close()678     public void close() {
679         home.closeMbox(this);
680     }
681 
682     @Override
finalize()683     protected void finalize() {
684         close();
685         queue.flush();
686     }
687 
688     /**
689      * Determine if two mailboxes are equal.
690      *
691      * @return true if both Objects are mailboxes with the same identifying
692      *         {@link OtpErlangPid pids}.
693      */
694     @Override
equals(final Object o)695     public boolean equals(final Object o) {
696         if (!(o instanceof OtpMbox)) {
697             return false;
698         }
699 
700         final OtpMbox m = (OtpMbox) o;
701         return m.self.equals(self);
702     }
703 
704     @Override
hashCode()705     public int hashCode() {
706         return self.hashCode();
707     }
708 
709     /*
710      * called by OtpNode to deliver message to this mailbox.
711      *
712      * About exit and exit2: both cause exception to be raised upon receive().
713      * However exit (not 2) only has an effect if there exist a link.
714      */
deliver(final OtpMsg m)715     void deliver(final OtpMsg m) {
716         switch (m.type()) {
717         case OtpMsg.exitTag:
718         case OtpMsg.linkTag:
719         case OtpMsg.unlinkTag:
720         case AbstractConnection.unlinkIdTag:
721         case AbstractConnection.unlinkIdAckTag:
722             handle_link_operation(m);
723             break;
724         default:
725             queue.put(m);
726             break;
727         }
728     }
729 
handle_link_operation(final OtpMsg m)730     private synchronized void handle_link_operation(final OtpMsg m) {
731         final OtpErlangPid remote = m.getSenderPid();
732         final String node = remote.node();
733         final boolean is_local = node.equals(home.node());
734         final OtpCookedConnection conn = is_local ? null : home.getConnection(node);
735 
736         switch (m.type()) {
737         case OtpMsg.linkTag:
738             if (links.addLink(self, remote, false)) {
739                 if (!is_local) {
740                     if (conn != null)
741                         conn.node_link(self, remote, true);
742                     else {
743                         links.removeLink(self, remote);
744                         queue.put(new OtpMsg(OtpMsg.exitTag, remote, self,
745                                              new OtpErlangAtom("noconnection")));
746                     }
747                 }
748             }
749             break;
750 
751         case OtpMsg.unlinkTag:
752         case AbstractConnection.unlinkIdTag: {
753             final long unlink_id = m.getUnlinkId();
754             final boolean removed = links.removeActiveLink(self, remote);
755             try {
756                 if (is_local) {
757                     home.deliver(new OtpMsg(AbstractConnection.unlinkIdAckTag,
758                                             self, remote, unlink_id));
759                 } else if (conn != null) {
760                     if (removed)
761                         conn.node_link(self, remote, false);
762                     conn.unlink_ack(self, remote, unlink_id);
763                 }
764             } catch (final Exception e) {
765             }
766             break;
767         }
768 
769         case AbstractConnection.unlinkIdAckTag:
770             links.removeUnlinkingLink(self, m.getSenderPid(), m.getUnlinkId());
771             break;
772 
773         case OtpMsg.exitTag:
774             if (links.removeActiveLink(self, m.getSenderPid())) {
775                 queue.put(m);
776             }
777             break;
778         }
779     }
780 
781     // used to break all known links to this mbox
breakLinks(final OtpErlangObject reason)782     synchronized void breakLinks(final OtpErlangObject reason) {
783         final Link[] l = links.clearLinks();
784 
785         if (l != null) {
786             final int len = l.length;
787 
788             for (int i = 0; i < len; i++) {
789                 if (l[i].getUnlinking() == 0) {
790                     OtpErlangPid remote = l[i].remote();
791                     final String node = remote.node();
792                     if (!node.equals(home.node())) {
793                         final OtpCookedConnection conn = home.getConnection(node);
794                         if (conn != null)
795                             conn.node_link(self, remote, false);
796                     }
797                     exit(1, remote, reason);
798                 }
799             }
800         }
801     }
802 }
803