Holumbus-Distribution-0.1.1: intra- and inter-program communication

Portabilityportable
Stabilityexperimental
MaintainerStefan Schmidt (stefanschmidt@web.de)

Holumbus.Network.Port

Contents

Description

Version : 0.1

Stream and Port datatype for internal an external process communication. Useful for communikation of distributed systems.

Synopsis

Constants

time1 :: IntSource

One second

time10 :: IntSource

10 seconds

time30 :: IntSource

30 seconds

time60 :: IntSource

60 seconds

time120 :: IntSource

120 seconds

timeIndefinitely :: IntSource

Wait how long it takes

Datatypes

data SocketId Source

All data, that is needed to address a socket. Contains the hostname and the portNumber.

data MessageType Source

Message Type Is it an internal Message or does it come from an external Node?

data (Show a, Binary a) => Message a Source

Message Datatype. We are sending additional information, to do debugging

Instances

(Show a, Binary a) => Show (Message a) 
(Show a, Binary a) => Binary (Message a) 

type StreamName = StringSource

The name of a stream.

data StreamType Source

The stream type, determines the accessibility of a stream

Constructors

STGlobal 
STLocal 
STPrivate 

data Stream a Source

The stream datatype

Instances

(Show a, Binary a) => Show (Stream a) 

data Port a Source

The port datatype.

Constructors

Port 

Fields

p_StreamName :: StreamName

the name of the destination stream

p_SocketId :: Maybe SocketId
 

Instances

Eq (Port a) 
Show (Port a) 
(Show a, Binary a) => Binary (Port a) 
(Show a, Binary a) => XmlPickler (Port a) 

Message-Operations

getMessageType :: (Show a, Binary a) => Message a -> MessageTypeSource

Gets the type of a message.

getMessageData :: (Show a, Binary a) => Message a -> aSource

Gets the data of a message.

getGenericData :: (Show a, Binary a) => Message a -> Maybe ByteStringSource

Gets the generic data (usually the return port) of a message.

Global-Operations

setPortRegistry :: PortRegistry r => r -> IO ()Source

Sets the link to the PortRegistry in the stream controller

Stream-Operations

newGlobalStream :: (Show a, Binary a) => StreamName -> IO (Stream a)Source

Creates a new global stream.

newLocalStream :: (Show a, Binary a) => Maybe StreamName -> IO (Stream a)Source

Creates a new local stream.

newPrivateStream :: (Show a, Binary a) => Maybe StreamName -> IO (Stream a)Source

Creates a new private stream.

newStream :: (Show a, Binary a) => StreamType -> Maybe StreamName -> Maybe PortNumber -> IO (Stream a)Source

General function for creating a new stream.

closeStream :: (Show a, Binary a) => Stream a -> IO ()Source

Closes a stream.

isEmptyStream :: Stream a -> IO BoolSource

Test, if the stream contains new messages.

readStream :: (Show a, Binary a) => Stream a -> IO aSource

Reads the data packet of the next message from a stream. If stream is empty, this function will block until a new message arrives.

readStreamMsg :: (Show a, Binary a) => Stream a -> IO (Message a)Source

Reads the next message from a stream (data packet + message header). If stream is empty, this function will block until a new message arrives.

tryReadStream :: (Show a, Binary a) => Stream a -> IO (Maybe a)Source

Reads the data packet of the next message from a stream. If stream is empty, this function will immediately return with Nothing.

tryReadStreamMsg :: (Show a, Binary a) => Stream a -> IO (Maybe (Message a))Source

Reads the next message from a stream (data packet + message header). If stream is empty, this function will immediately return with Nothing.

tryWaitReadStream :: (Show a, Binary a) => Stream a -> Int -> IO (Maybe a)Source

Reads the data packet of the next message from a stream. If stream is empty, this function will wait for new messages until the time is up and if no message has arrived, return with Nothing.

tryWaitReadStreamMsg :: (Show a, Binary a) => Stream a -> Int -> IO (Maybe (Message a))Source

Reads the next message from a stream (data packet + message header). If stream is empty, this function will wait for new messages until the time is up and if no message has arrived, return with Nothing.

withStream :: (Show a, Binary a) => (Stream a -> IO b) -> IO bSource

Encapsulates a stream. A new stream is created, then some user-action is done an after that the stream is closed.

Port-Operations

newPortFromStream :: Stream a -> IO (Port a)Source

Creates a new Port, which is bound to a stream.

newPort :: StreamName -> Maybe SocketId -> IO (Port a)Source

Creates a new port from a streamname and its socketId.

newGlobalPort :: StreamName -> IO (Port a)Source

Creates a new port to a global stream, only its name is needed.

isPortLocal :: Port a -> IO BoolSource

Test, if a port is local.

send :: (Show a, Binary a) => Port a -> a -> IO ()Source

Send data to the stream of the port. The data is send via network, if the stream is located on an external processor

sendWithGeneric :: (Show a, Binary a) => Port a -> a -> ByteString -> IO ()Source

Like send, but here we can give some generic data (e.g. a port for reply messages).

sendWithMaybeGeneric :: (Show a, Binary a) => Port a -> a -> Maybe ByteString -> IO ()Source

Like sendWithGeneric, but the generic data is optional

writePortToFile :: (Show a, Binary a) => Port a -> FilePath -> IO ()Source

Writes a port-description to a file. Quite useful fpr sharing ports between programs

readPortFromFile :: (Show a, Binary a) => FilePath -> IO (Port a)Source

Reads a port-description from a file. Quite useful fpr sharing ports between programs

Debug

printStreamController :: IO ()Source

Prints the internal data of the stream controller to stdout, useful for debugging.