courier-0.1.0.13: A message-passing library for simplifying network applications

Portabilitynon-portable (requires STM)
Stabilityexperimental
Maintainerphil@haphazardhouse.net
Safe HaskellNone

Network.Endpoints

Contents

Description

Endpoints are a generalized abstraction for communication between parts of a program, whether on the same physical host or distributed over a network. Endpoints are intended to simplify the development of network-centric applications by providing a small transport-independent message-passing interface, and application writers can independently alter their implementation by enabling their Endpoints with different Transports without modifying the logic of their application that sends / receives Messages.

Synopsis

How to use courier in an application

A sample of how to use this library:

 module HelloWorld (
     main
 ) where

 -- Just import this package to access the primary APIs
 import Network.Endpoints

 -- A specific transport is necessary, however
 import Network.Transport.TCP

 -- Needed for serialization
 import Data.Serialize

 main :: IO ()
 main = do
    let name1 = "endpoint1"
        name2 = "endpoint2"
        resolver = resolverFromList [(name1,"localhost:2000"),
                                (name2,"localhost:2001")]
    transport <- newTCPTransport resolver
    endpoint1 <- newEndpoint [transport]
    endpoint2 <- newEndpoint [transport]
    Right () <- bindEndpoint endpoint1 name1
    Right () <- bindEndpoint endpoint2 name2
    sendMessage_ endpoint1 name2 $ encode "hello world!"
    msg <- receiveMessage endpoint2
    let Right txt = decode msg
        in print (txt :: String)
    Right () <- unbindEndpoint endpoint1 name1
    Right () <- unbindEndpoint endpoint2 name2
    shutdown transport

Primary API

data Endpoint Source

Endpoints are a locus of communication, used for sending and receive messages.

newEndpoint :: [Transport] -> IO EndpointSource

Create a new Endpoint using the provided transports.

bindEndpoint :: Endpoint -> Name -> IO (Either String ())Source

Binding an Endpoint to a Name prepares the Endpoint to receive messages sent to the bound name. Upon success, the result will be Right (), but if failed, Left text-of-error-message.

bindEndpoint_ :: Endpoint -> Name -> IO ()Source

Invoke bindEndpoint, but ignore any returned result (success or failure).

unbindEndpoint :: Endpoint -> Name -> IO (Either String ())Source

Unbind an Endpoint from a Name, after which the Endpoint will eventually not receive messages sent to that Name. Note that there is no guarantee that after Unbind succeeds that additional messages to that Name will not be delivered: the only guarantee is that eventually messages will no longer be delivered. Upon success, the result will be Right () but if failed, Left text-of-error-message.

unbindEndpoint_ :: Endpoint -> Name -> IO ()Source

Invoke unbindEndpoint, but ignore any returned result (success or failure).

sendMessage :: Endpoint -> Name -> Message -> IO (Either String ())Source

Send a Message to specific Name via the indicated Endpoint. While a successful response (indicated by returning Right ()) indicates that there was no error initiating transport of the message, success does not guarantee that an Endpoint received the message. Failure initiating transport is indicated by returning Left text-of-error-message.

sendMessage_ :: Endpoint -> Name -> Message -> IO ()Source

A variant of sendMessage for use when the return value can be ignored.

broadcastMessage :: Endpoint -> [Name] -> Message -> IO [Either String ()]Source

Helper for sending a single Message to several Endpoints.

broadcastMessage_ :: Endpoint -> [Name] -> Message -> IO ()Source

Variant of broadcastMessage that ignores the results of sending.

receiveMessage :: Endpoint -> IO MessageSource

Receive the next Message sent to the Endpoint, blocking until a message is available.

receiveMessageTimeout :: Endpoint -> Int -> IO (Maybe Message)Source

Wait for a message to be received within the timeout, blocking until either a message is available or the timeout has occurred. If a message was available, returns Just message, but returns Nothing if no message available before the timeout occurred.

postMessage :: Endpoint -> Message -> IO ()Source

Posts a Message directly to an Endpoint, without use of a transport. This may be useful for applications that prefer to use the Endpoint's Mailbox as a general queue of ordered messages.

Selective message reception

selectMessage :: Endpoint -> (Message -> Maybe v) -> IO vSource

Select the next available message in the Endpoint Mailbox matching the supplied test function, or blocking until one is available. This function differs from receiveMessage in that it supports out of order message reception.

selectMessageTimeout :: Endpoint -> Int -> (Message -> Maybe v) -> IO (Maybe v)Source

Wait for a message to be selected within the timeout, blocking until either a message is available or the timeout has occurred. If a message was available, returns Just message, but returns Nothing if no message available before the timeout occurred. Like selectMessage, this function enables out of order message reception.

detectMessage :: Endpoint -> (Message -> Maybe v) -> IO vSource

Find a Message in the Endpoint Mailbox matching the supplied test function, or block until one is available. Note that any such message is left in the mailbox, and thus repeated calls to this function could find the message if it is not consumed immediately.

detectMessageTimeout :: Endpoint -> Int -> (Message -> Maybe v) -> IO (Maybe v)Source

Find a Message in the Endpoint Mailbox matching the supplied test function, or block until either one is available or the timeout expires. Note that any such message is left in the mailbox, and thus repeated calls to this function could find the message if it is not consumed immediately.

dispatchMessage :: Endpoint -> (Message -> Maybe v) -> (v -> IO r) -> IO rSource

Dispatch the next available message in the Endpoint Mailbox matching the supplied test function, or blocking until one is available. Once a matching message is found, handle the message with the supplied handler and return any result obtained. This function differs from receiveMessage in that it supports out of order message reception.

dispatchMessageTimeout :: Endpoint -> Int -> (Message -> Maybe v) -> (v -> IO r) -> IO (Maybe r)Source

Transports

Transports define specific implementations of message-passing techniques (e.g., memory-based, TCP, UDP, HTTP, etc.). Typical use of the Endpoints does not require direct use of Transports, beyond creating specific Transports (such as found in Network.Transport.Memory and Network.Transport.TCP) and adding them to an Endpoint.