1 /*
2  * %CopyrightBegin%
3  *
4  * Copyright Ericsson AB 2000-2016. 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 carrier for Erlang messages.
25  * </p>
26  *
27  * <p>
28  * Instances of this class are created to package header and payload information
29  * in received Erlang messages so that the recipient can obtain both parts with
30  * a single call to {@link OtpMbox#receiveMsg receiveMsg()}.
31  * </p>
32  *
33  * <p>
34  * The header information that is available is as follows:
35  * <ul>
36  * <li>a tag indicating the type of message
37  * <li>the intended recipient of the message, either as a {@link OtpErlangPid
38  * pid} or as a String, but never both.
39  * <li>(sometimes) the sender of the message. Due to some eccentric
40  * characteristics of the Erlang distribution protocol, not all messages have
41  * information about the sending process. In particular, only messages whose tag
42  * is {@link OtpMsg#regSendTag regSendTag} contain sender information.
43  * </ul>
44  *
45  * <p>
46  * Message are sent using the Erlang external format (see separate
47  * documentation). When a message is received and delivered to the recipient
48  * {@link OtpMbox mailbox}, the body of the message is still in this external
49  * representation until {@link #getMsg getMsg()} is called, at which point the
50  * message is decoded. A copy of the decoded message is stored in the OtpMsg so
51  * that subsequent calls to {@link #getMsg getMsg()} do not require that the
52  * message be decoded a second time.
53  * </p>
54  */
55 public class OtpMsg {
56     public static final int linkTag = 1;
57     public static final int sendTag = 2;
58     public static final int exitTag = 3;
59     public static final int unlinkTag = 4;
60     public static final int regSendTag = 6;
61     /* public static final int groupLeaderTag = 7; */
62     public static final int exit2Tag = 8;
63 
64     protected int tag; // what type of message is this (send, link, exit etc)
65     protected OtpInputStream paybuf;
66     protected OtpErlangObject payload;
67 
68     protected OtpErlangPid from;
69     protected OtpErlangPid to;
70     protected String toName;
71     protected long unlink_id;
72 
73     // send has receiver pid but no sender information
OtpMsg(final OtpErlangPid to, final OtpInputStream paybuf)74     OtpMsg(final OtpErlangPid to, final OtpInputStream paybuf) {
75         tag = sendTag;
76         from = null;
77         this.to = to;
78         toName = null;
79         this.paybuf = paybuf;
80         payload = null;
81         this.unlink_id = 0;
82     }
83 
84     // send has receiver pid but no sender information
OtpMsg(final OtpErlangPid to, final OtpErlangObject payload)85     OtpMsg(final OtpErlangPid to, final OtpErlangObject payload) {
86         tag = sendTag;
87         from = null;
88         this.to = to;
89         toName = null;
90         paybuf = null;
91         this.payload = payload;
92         this.unlink_id = 0;
93     }
94 
95     // send_reg has sender pid and receiver name
OtpMsg(final OtpErlangPid from, final String toName, final OtpInputStream paybuf)96     OtpMsg(final OtpErlangPid from, final String toName,
97             final OtpInputStream paybuf) {
98         tag = regSendTag;
99         this.from = from;
100         this.toName = toName;
101         to = null;
102         this.paybuf = paybuf;
103         payload = null;
104         this.unlink_id = 0;
105     }
106 
107     // send_reg has sender pid and receiver name
OtpMsg(final OtpErlangPid from, final String toName, final OtpErlangObject payload)108     OtpMsg(final OtpErlangPid from, final String toName,
109             final OtpErlangObject payload) {
110         tag = regSendTag;
111         this.from = from;
112         this.toName = toName;
113         to = null;
114         paybuf = null;
115         this.payload = payload;
116         this.unlink_id = 0;
117     }
118 
119     // exit (etc) has from, to, reason
OtpMsg(final int tag, final OtpErlangPid from, final OtpErlangPid to, final OtpErlangObject reason)120     OtpMsg(final int tag, final OtpErlangPid from, final OtpErlangPid to,
121             final OtpErlangObject reason) {
122         this.tag = tag;
123         this.from = from;
124         this.to = to;
125         this.unlink_id = 0;
126         paybuf = null;
127         payload = reason;
128         this.unlink_id = 0;
129     }
130 
131     // special case when reason is an atom (i.e. most of the time)
OtpMsg(final int tag, final OtpErlangPid from, final OtpErlangPid to, final String reason)132     OtpMsg(final int tag, final OtpErlangPid from, final OtpErlangPid to,
133             final String reason) {
134         this.tag = tag;
135         this.from = from;
136         this.to = to;
137         paybuf = null;
138         payload = new OtpErlangAtom(reason);
139         this.unlink_id = 0;
140     }
141 
142     // other message types (link and old unlink)
OtpMsg(final int tag, final OtpErlangPid from, final OtpErlangPid to)143     OtpMsg(final int tag, final OtpErlangPid from, final OtpErlangPid to) {
144         // convert TT-tags to equiv non-TT versions
145         this.tag = drop_tt_tag(tag);
146         this.from = from;
147         this.to = to;
148         this.unlink_id = 0;
149     }
150 
151     // unlink
OtpMsg(final int tag, final OtpErlangPid from, final OtpErlangPid to, final long unlink_id)152     OtpMsg(final int tag, final OtpErlangPid from, final OtpErlangPid to,
153            final long unlink_id) {
154         // convert TT-tags to equiv non-TT versions
155         this.tag = drop_tt_tag(tag);
156         this.from = from;
157         this.to = to;
158         this.unlink_id = unlink_id;
159     }
160 
drop_tt_tag(final int tag)161     private int drop_tt_tag(final int tag) {
162         switch (tag) {
163         case AbstractConnection.sendTTTag:
164             return OtpMsg.sendTag;
165         case AbstractConnection.exitTTTag:
166             return OtpMsg.exitTag;
167         case AbstractConnection.regSendTTTag:
168             return OtpMsg.regSendTag;
169         case AbstractConnection.exit2TTTag:
170             return OtpMsg.exit2Tag;
171         default:
172             return tag;
173         }
174     }
175 
176     /**
177      * Get unlink identifier of an unlink or unlink acknowledgment
178      * message. For package internal use only.
179      *
180      * @return the serialized Erlang term contained in this message.
181      *
182      */
getUnlinkId()183     long getUnlinkId() {
184         return this.unlink_id;
185     }
186 
187     /**
188      * Get the payload from this message without deserializing it.
189      *
190      * @return the serialized Erlang term contained in this message.
191      *
192      */
getMsgBuf()193     OtpInputStream getMsgBuf() {
194         return paybuf;
195     }
196 
197     /**
198      * <p>
199      * Get the type marker from this message. The type marker identifies the
200      * type of message. Valid values are the ``tag'' constants defined in this
201      * class.
202      * </p>
203      *
204      * <p>
205      * The tab identifies not only the type of message but also the content of
206      * the OtpMsg object, since different messages have different components, as
207      * follows:
208      * </p>
209      *
210      * <ul>
211      * <li>sendTag identifies a "normal" message. The recipient is a
212      * {@link OtpErlangPid Pid} and it is available through
213      * {@link #getRecipientPid getRecipientPid()}. Sender information is not
214      * available. The message body can be retrieved with {@link #getMsg
215      * getMsg()}.</li>
216      *
217      * <li>regSendTag also identifies a "normal" message. The recipient here is
218      * a String and it is available through {@link #getRecipientName
219      * getRecipientName()}. Sender information is available through
220      * #getSenderPid getSenderPid()}. The message body can be retrieved with
221      * {@link #getMsg getMsg()}.</li>
222      *
223      * <li>linkTag identifies a link request. The Pid of the sender is
224      * available, as well as the Pid to which the link should be made.</li>
225      *
226      * <li>exitTag and exit2Tag messages are sent as a result of broken links.
227      * Both sender and recipient Pids and are available through the
228      * corresponding methods, and the "reason" is available through
229      * {@link #getMsg getMsg()}.</li>
230      * </ul>
231      */
type()232     public int type() {
233         return tag;
234     }
235 
236     /**
237      * <p>
238      * Deserialize and return a new copy of the message contained in this
239      * OtpMsg.
240      * </p>
241      *
242      * <p>
243      * The first time this method is called the actual payload is deserialized
244      * and the Erlang term is created. Calling this method subsequent times will
245      * not cuase the message to be deserialized additional times, instead the
246      * same Erlang term object will be returned.
247      * </p>
248      *
249      * @return an Erlang term.
250      *
251      * @exception OtpErlangDecodeException
252      *                if the byte stream could not be deserialized.
253      *
254      */
getMsg()255     public OtpErlangObject getMsg() throws OtpErlangDecodeException {
256         if (payload == null) {
257             payload = paybuf.read_any();
258         }
259         return payload;
260     }
261 
262     /**
263      * <p>
264      * Get the name of the recipient for this message.
265      * </p>
266      *
267      * <p>
268      * Messages are sent to Pids or names. If this message was sent to a name
269      * then the name is returned by this method.
270      * </p>
271      *
272      * @return the name of the recipient, or null if the recipient was in fact a
273      *         Pid.
274      */
getRecipientName()275     public String getRecipientName() {
276         return toName;
277     }
278 
279     /**
280      * <p>
281      * Get the Pid of the recipient for this message, if it is a sendTag
282      * message.
283      * </p>
284      *
285      * <p>
286      * Messages are sent to Pids or names. If this message was sent to a Pid
287      * then the Pid is returned by this method. The recipient Pid is also
288      * available for link, unlink and exit messages.
289      * </p>
290      *
291      * @return the Pid of the recipient, or null if the recipient was in fact a
292      *         name.
293      */
getRecipientPid()294     public OtpErlangPid getRecipientPid() {
295         return to;
296     }
297 
298     /**
299      * <p>
300      * Get the name of the recipient for this message, if it is a regSendTag
301      * message.
302      * </p>
303      *
304      * <p>
305      * Messages are sent to Pids or names. If this message was sent to a name
306      * then the name is returned by this method.
307      * </p>
308      *
309      * @return the Pid of the recipient, or null if the recipient was in fact a
310      *         name.
311      */
getRecipient()312     public Object getRecipient() {
313         if (toName != null) {
314             return toName;
315         }
316         return to;
317     }
318 
319     /**
320      * <p>
321      * Get the Pid of the sender of this message.
322      * </p>
323      *
324      * <p>
325      * For messages sent to names, the Pid of the sender is included with the
326      * message. The sender Pid is also available for link, unlink and exit
327      * messages. It is not available for sendTag messages sent to Pids.
328      * </p>
329      *
330      * @return the Pid of the sender, or null if it was not available.
331      */
getSenderPid()332     public OtpErlangPid getSenderPid() {
333         return from;
334     }
335 }
336