| 
 | ||||||||
| PREV CLASS NEXT CLASS | FRAMES NO FRAMES | |||||||
| SUMMARY: INNER | FIELD | CONSTR | METHOD | DETAIL: FIELD | CONSTR | METHOD | |||||||
java.lang.Object
  |
  +--java.lang.Thread
        |
        +--com.ericsson.otp.erlang.AbstractConnection
Maintains a connection between a Java process and a remote Erlang, Java or C node. The object maintains connection state and allows data to be sent to and received from the peer.
This abstract class provides the neccesary methods to maintain the actual connection and encode the messages and headers in the proper format according to the Erlang distribution protocol. Subclasses can use these methods to provide a more or less transparent communication channel as desired.
Note that no receive methods are provided. Subclasses must provide methods for message delivery, and may implement their own receive methods.
If an exception occurs in any of the methods in this class, the connection will be closed and must be reopened in order to resume communication with the peer. This will be indicated to the subclass by passing the exception to its delivery() method.
 The System property OtpConnection.trace can be used to change
 the initial trace level setting for all connections. Normally the
 initial trace level is 0 and connections are not traced unless
 setTraceLevel() is used to change the
 setting for a particular connection. OtpConnection.trace can be
 used to turn on tracing by default for all connections. 
| Field Summary | |
| protected static int | ChallengeAck | 
| protected static int | ChallengeReply | 
| protected static int | ChallengeStatus | 
| protected  boolean | connected | 
| protected  boolean | cookieOk | 
| protected static int | ctrlThreshold | 
| protected static int | defaultLevel | 
| protected static int | exit2Tag | 
| protected static int | exit2TTTag | 
| protected static int | exitTag | 
| protected static int | exitTTTag | 
| protected static int | groupLeaderTag | 
| protected static int | handshakeThreshold | 
| protected static int | headerLen | 
| protected static int | linkTag | 
| protected static int | nodeLinkTag | 
| protected static byte | passThrough | 
| protected  OtpPeer | peer | 
| protected static java.util.Random | random | 
| protected static int | regSendTag | 
| protected static int | regSendTTTag | 
| protected  OtpLocalNode | self | 
| protected  boolean | sendCookie | 
| protected static int | sendTag | 
| protected static int | sendThreshold | 
| protected static int | sendTTTag | 
| protected  java.net.Socket | socket | 
| protected  int | traceLevel | 
| protected static int | unlinkTag | 
| protected static byte | version | 
| Fields inherited from class java.lang.Thread | 
| MAX_PRIORITY, MIN_PRIORITY, NORM_PRIORITY | 
| Constructor Summary | |
| protected  | AbstractConnection(OtpLocalNode self,
                   OtpPeer other) | 
| protected  | AbstractConnection(OtpLocalNode self,
                   java.net.Socket s) | 
| Method Summary | |
|  void | close()Close the connection to the remote node. | 
| abstract  void | deliver(java.lang.Exception e)Deliver communication exceptions to the recipient. | 
| abstract  void | deliver(OtpMsg msg)Deliver messages to the recipient. | 
| protected  void | do_send(OtpOutputStream header) | 
| protected  void | do_send(OtpOutputStream header,
        OtpOutputStream payload) | 
| protected  void | doAccept() | 
| protected  void | doConnect(int port) | 
| protected  void | finalize() | 
| protected static int | genChallenge() | 
| protected  byte[] | genDigest(int challenge,
          java.lang.String cookie) | 
|  int | getTraceLevel()Get the trace level for this connection. | 
| protected  java.lang.String | headerType(OtpErlangObject h) | 
|  boolean | isConnected()Determine if the connection is still alive. | 
| protected  byte[] | read2BytePackage() | 
| protected  int | readSock(java.net.Socket s,
         byte[] b) | 
| protected  int | recvChallenge() | 
| protected  void | recvChallengeAck(int our_challenge) | 
| protected  int | recvChallengeReply(int our_challenge) | 
| protected  void | recvName(OtpPeer peer) | 
| protected  void | recvStatus() | 
|  void | run() | 
| protected  void | sendBuf(OtpErlangPid from,
        OtpErlangPid dest,
        OtpOutputStream payload)Send a pre-encoded message to a process on a remote node. | 
| protected  void | sendBuf(OtpErlangPid from,
        java.lang.String dest,
        OtpOutputStream payload)Send a pre-encoded message to a named process on a remote node. | 
| protected  void | sendChallenge(int dist,
              int flags,
              int challenge) | 
| protected  void | sendChallengeAck(byte[] digest) | 
| protected  void | sendChallengeReply(int challenge,
                   byte[] digest) | 
| protected  void | sendExit(OtpErlangPid from,
         OtpErlangPid dest,
         OtpErlangObject reason) | 
| protected  void | sendExit2(OtpErlangPid from,
          OtpErlangPid dest,
          OtpErlangObject reason)Send an exit signal to a remote process. | 
| protected  void | sendLink(OtpErlangPid from,
         OtpErlangPid dest)Create a link between the local node and the specified process on the remote node. | 
| protected  void | sendName(int dist,
         int flags) | 
| protected  void | sendStatus(java.lang.String status) | 
| protected  void | sendUnlink(OtpErlangPid from,
           OtpErlangPid dest)Remove a link between the local node and the specified process on the remote node. | 
|  int | setTraceLevel(int level)Set the trace level for this connection. | 
| Methods inherited from class java.lang.Thread | 
| activeCount, checkAccess, countStackFrames, currentThread, destroy, dumpStack, enumerate, getContextClassLoader, getName, getPriority, getThreadGroup, interrupt, interrupted, isAlive, isDaemon, isInterrupted, join, join, join, resume, setContextClassLoader, setDaemon, setName, setPriority, sleep, sleep, start, stop, stop, suspend, toString, yield | 
| Methods inherited from class java.lang.Object | 
| clone, equals, getClass, hashCode, notify, notifyAll, wait, wait, wait | 
| Field Detail | 
protected static final int headerLen
protected static final byte passThrough
protected static final byte version
protected static final int linkTag
protected static final int sendTag
protected static final int exitTag
protected static final int unlinkTag
protected static final int nodeLinkTag
protected static final int regSendTag
protected static final int groupLeaderTag
protected static final int exit2Tag
protected static final int sendTTTag
protected static final int exitTTTag
protected static final int regSendTTTag
protected static final int exit2TTTag
protected static final int ChallengeReply
protected static final int ChallengeAck
protected static final int ChallengeStatus
protected boolean connected
protected java.net.Socket socket
protected OtpPeer peer
protected OtpLocalNode self
protected boolean cookieOk
protected boolean sendCookie
protected int traceLevel
protected static int defaultLevel
protected static int sendThreshold
protected static int ctrlThreshold
protected static int handshakeThreshold
protected static java.util.Random random
| Constructor Detail | 
protected AbstractConnection(OtpLocalNode self,
                             java.net.Socket s)
                      throws java.io.IOException,
                             OtpAuthException
protected AbstractConnection(OtpLocalNode self,
                             OtpPeer other)
                      throws java.io.IOException,
                             OtpAuthException
| Method Detail | 
public abstract void deliver(java.lang.Exception e)
public abstract void deliver(OtpMsg msg)
protected void sendBuf(OtpErlangPid from,
                       java.lang.String dest,
                       OtpOutputStream payload)
                throws java.io.IOException
dest - the name of the remote process.payload - the encoded message to send.java.io.IOException - if the connection is not active or
 a communication error occurs.
protected void sendBuf(OtpErlangPid from,
                       OtpErlangPid dest,
                       OtpOutputStream payload)
                throws java.io.IOException
dest - the Erlang PID of the remote process.msg - the encoded message to send.java.io.IOException - if the connection is not active
 or a communication error occurs.
protected void sendLink(OtpErlangPid from,
                        OtpErlangPid dest)
                 throws java.io.IOException
unlink() to remove the link.dest - the Erlang PID of the remote process.java.io.IOException - if the connection is not active
 or a communication error occurs.
protected void sendUnlink(OtpErlangPid from,
                          OtpErlangPid dest)
                   throws java.io.IOException
link().dest - the Erlang PID of the remote process.java.io.IOException - if the connection is not active or
 a communication error occurs.
protected void sendExit(OtpErlangPid from,
                        OtpErlangPid dest,
                        OtpErlangObject reason)
                 throws java.io.IOException
protected void sendExit2(OtpErlangPid from,
                         OtpErlangPid dest,
                         OtpErlangObject reason)
                  throws java.io.IOException
dest - the Erlang PID of the remote process.reason - an Erlang term describing the exit reason.java.io.IOException - if the connection is not active or
 a communication error occurs.public void run()
run in class java.lang.Threadpublic int setTraceLevel(int level)
Set the trace level for this connection. Normally tracing is off by default unless System property OtpConnection.trace was set.
The following levels are valid: 0 turns off tracing completely, 1 shows ordinary send and receive messages, 2 shows control messages such as link and unlink, 3 shows handshaking at connection setup, and 4 shows communication with Epmd. Each level includes the information shown by the lower ones.
level - the level to set.public int getTraceLevel()
public void close()
protected void finalize()
finalize in class java.lang.Objectpublic boolean isConnected()
protected void do_send(OtpOutputStream header,
                       OtpOutputStream payload)
                throws java.io.IOException
protected void do_send(OtpOutputStream header)
                throws java.io.IOException
protected java.lang.String headerType(OtpErlangObject h)
protected int readSock(java.net.Socket s,
                       byte[] b)
                throws java.io.IOException
protected void doAccept()
                 throws java.io.IOException,
                        OtpAuthException
protected void doConnect(int port)
                  throws java.io.IOException,
                         OtpAuthException
protected static int genChallenge()
protected byte[] genDigest(int challenge,
                           java.lang.String cookie)
protected void sendName(int dist,
                        int flags)
                 throws java.io.IOException
protected void sendChallenge(int dist,
                             int flags,
                             int challenge)
                      throws java.io.IOException
protected byte[] read2BytePackage()
                           throws java.io.IOException,
                                  OtpErlangDecodeException
protected void recvName(OtpPeer peer)
                 throws java.io.IOException
protected int recvChallenge()
                     throws java.io.IOException
protected void sendChallengeReply(int challenge,
                                  byte[] digest)
                           throws java.io.IOException
protected int recvChallengeReply(int our_challenge)
                          throws java.io.IOException,
                                 OtpAuthException
protected void sendChallengeAck(byte[] digest)
                         throws java.io.IOException
protected void recvChallengeAck(int our_challenge)
                         throws java.io.IOException,
                                OtpAuthException
protected void sendStatus(java.lang.String status)
                   throws java.io.IOException
protected void recvStatus()
                   throws java.io.IOException
| 
 | ||||||||
| PREV CLASS NEXT CLASS | FRAMES NO FRAMES | |||||||
| SUMMARY: INNER | FIELD | CONSTR | METHOD | DETAIL: FIELD | CONSTR | METHOD | |||||||