com.ericsson.otp.erlang
Class AbstractConnection

java.lang.Object
  |
  +--java.lang.Thread
        |
        +--com.ericsson.otp.erlang.AbstractConnection
Direct Known Subclasses:
OtpConnection, OtpCookedConnection

public abstract class AbstractConnection
extends java.lang.Thread

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, java.lang.String reason)
           
protected  void sendExit2(OtpErlangPid from, OtpErlangPid dest, java.lang.String 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

headerLen

protected static final int headerLen

passThrough

protected static final byte passThrough

version

protected static final byte version

linkTag

protected static final int linkTag

sendTag

protected static final int sendTag

exitTag

protected static final int exitTag

unlinkTag

protected static final int unlinkTag

nodeLinkTag

protected static final int nodeLinkTag

regSendTag

protected static final int regSendTag

groupLeaderTag

protected static final int groupLeaderTag

exit2Tag

protected static final int exit2Tag

sendTTTag

protected static final int sendTTTag

exitTTTag

protected static final int exitTTTag

regSendTTTag

protected static final int regSendTTTag

exit2TTTag

protected static final int exit2TTTag

ChallengeReply

protected static final int ChallengeReply

ChallengeAck

protected static final int ChallengeAck

ChallengeStatus

protected static final int ChallengeStatus

connected

protected boolean connected

socket

protected java.net.Socket socket

peer

protected OtpPeer peer

self

protected OtpLocalNode self

cookieOk

protected boolean cookieOk

sendCookie

protected boolean sendCookie

traceLevel

protected int traceLevel

defaultLevel

protected static int defaultLevel

sendThreshold

protected static int sendThreshold

ctrlThreshold

protected static int ctrlThreshold

handshakeThreshold

protected static int handshakeThreshold

random

protected static java.util.Random random
Constructor Detail

AbstractConnection

protected AbstractConnection(OtpLocalNode self,
                             java.net.Socket s)
                      throws java.io.IOException,
                             OtpAuthException

AbstractConnection

protected AbstractConnection(OtpLocalNode self,
                             OtpPeer other)
                      throws java.io.IOException,
                             OtpAuthException
Method Detail

deliver

public abstract void deliver(java.lang.Exception e)
Deliver communication exceptions to the recipient.

deliver

public abstract void deliver(OtpMsg msg)
Deliver messages to the recipient.

sendBuf

protected void sendBuf(OtpErlangPid from,
                       java.lang.String dest,
                       OtpOutputStream payload)
                throws java.io.IOException
Send a pre-encoded message to a named process on a remote node.
Parameters:
dest - the name of the remote process.
payload - the encoded message to send.
Throws:
java.io.IOException - if the connection is not active or a communication error occurs.

sendBuf

protected void sendBuf(OtpErlangPid from,
                       OtpErlangPid dest,
                       OtpOutputStream payload)
                throws java.io.IOException
Send a pre-encoded message to a process on a remote node.
Parameters:
dest - the Erlang PID of the remote process.
msg - the encoded message to send.
Throws:
java.io.IOException - if the connection is not active or a communication error occurs.

sendLink

protected void sendLink(OtpErlangPid from,
                        OtpErlangPid dest)
                 throws java.io.IOException
Create a link between the local node and the specified process on the remote node. If the link is still active when the remote process terminates, an exit signal will be sent to this connection. Use unlink() to remove the link.
Parameters:
dest - the Erlang PID of the remote process.
Throws:
java.io.IOException - if the connection is not active or a communication error occurs.

sendUnlink

protected void sendUnlink(OtpErlangPid from,
                          OtpErlangPid dest)
                   throws java.io.IOException
Remove a link between the local node and the specified process on the remote node. This method deactivates links created with link().
Parameters:
dest - the Erlang PID of the remote process.
Throws:
java.io.IOException - if the connection is not active or a communication error occurs.

sendExit

protected void sendExit(OtpErlangPid from,
                        OtpErlangPid dest,
                        java.lang.String reason)
                 throws java.io.IOException

sendExit2

protected void sendExit2(OtpErlangPid from,
                         OtpErlangPid dest,
                         java.lang.String reason)
                  throws java.io.IOException
Send an exit signal to a remote process.
Parameters:
dest - the Erlang PID of the remote process.
reason - a string describing the exit reason.
Throws:
java.io.IOException - if the connection is not active or a communication error occurs.

run

public void run()
Overrides:
run in class java.lang.Thread

setTraceLevel

public 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.

Parameters:
level - the level to set.
Returns:
the previous trace level.

getTraceLevel

public int getTraceLevel()
Get the trace level for this connection.
Returns:
the current trace level.

close

public void close()
Close the connection to the remote node.

finalize

protected void finalize()
Overrides:
finalize in class java.lang.Object

isConnected

public boolean isConnected()
Determine if the connection is still alive. Note that this method only reports the status of the connection, and that it is possible that there are unread messages waiting in the receive queue.
Returns:
true if the connection is alive.

do_send

protected void do_send(OtpOutputStream header,
                       OtpOutputStream payload)
                throws java.io.IOException

do_send

protected void do_send(OtpOutputStream header)
                throws java.io.IOException

headerType

protected java.lang.String headerType(OtpErlangObject h)

readSock

protected int readSock(java.net.Socket s,
                       byte[] b)
                throws java.io.IOException

doAccept

protected void doAccept()
                 throws java.io.IOException,
                        OtpAuthException

doConnect

protected void doConnect(int port)
                  throws java.io.IOException,
                         OtpAuthException

genChallenge

protected static int genChallenge()

genDigest

protected byte[] genDigest(int challenge,
                           java.lang.String cookie)

sendName

protected void sendName(int dist,
                        int flags)
                 throws java.io.IOException

sendChallenge

protected void sendChallenge(int dist,
                             int flags,
                             int challenge)
                      throws java.io.IOException

read2BytePackage

protected byte[] read2BytePackage()
                           throws java.io.IOException,
                                  OtpErlangDecodeException

recvName

protected void recvName(OtpPeer peer)
                 throws java.io.IOException

recvChallenge

protected int recvChallenge()
                     throws java.io.IOException

sendChallengeReply

protected void sendChallengeReply(int challenge,
                                  byte[] digest)
                           throws java.io.IOException

recvChallengeReply

protected int recvChallengeReply(int our_challenge)
                          throws java.io.IOException,
                                 OtpAuthException

sendChallengeAck

protected void sendChallengeAck(byte[] digest)
                         throws java.io.IOException

recvChallengeAck

protected void recvChallengeAck(int our_challenge)
                         throws java.io.IOException,
                                OtpAuthException

sendStatus

protected void sendStatus(java.lang.String status)
                   throws java.io.IOException

recvStatus

protected void recvStatus()
                   throws java.io.IOException