Portability | non-portable (requires STM) |
---|---|
Stability | experimental |
Maintainer | phil@haphazardhouse.net |
Safe Haskell | None |
Endpoint
s are a generalized abstraction for communication between parts of a program,
whether on the same physical host or distributed over a network. Endpoint
s 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 Endpoint
s with different Transport
s without modifying the logic of their
application that sends / receives Message
s.
- data Endpoint
- newEndpoint :: [Transport] -> IO Endpoint
- bindEndpoint :: Endpoint -> Name -> IO (Either String ())
- bindEndpoint_ :: Endpoint -> Name -> IO ()
- unbindEndpoint :: Endpoint -> Name -> IO (Either String ())
- unbindEndpoint_ :: Endpoint -> Name -> IO ()
- sendMessage :: Endpoint -> Name -> Message -> IO (Either String ())
- sendMessage_ :: Endpoint -> Name -> Message -> IO ()
- broadcastMessage :: Endpoint -> [Name] -> Message -> IO [Either String ()]
- broadcastMessage_ :: Endpoint -> [Name] -> Message -> IO ()
- receiveMessage :: Endpoint -> IO Message
- receiveMessageTimeout :: Endpoint -> Int -> IO (Maybe Message)
- postMessage :: Endpoint -> Message -> IO ()
- selectMessage :: Endpoint -> (Message -> Maybe v) -> IO v
- selectMessageTimeout :: Endpoint -> Int -> (Message -> Maybe v) -> IO (Maybe v)
- detectMessage :: Endpoint -> (Message -> Maybe v) -> IO v
- detectMessageTimeout :: Endpoint -> Int -> (Message -> Maybe v) -> IO (Maybe v)
- dispatchMessage :: Endpoint -> (Message -> Maybe v) -> (v -> IO r) -> IO r
- dispatchMessageTimeout :: Endpoint -> Int -> (Message -> Maybe v) -> (v -> IO r) -> IO (Maybe r)
- module Network.Transport
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
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 ()Source
Variant of broadcastMessage
that ignores the results of sending.
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
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.
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 Endpoint
s does not
require direct use of Transport
s, beyond creating specific Transport
s (such as
found in Network.Transport.Memory and Network.Transport.TCP) and adding
them to an Endpoint
.
module Network.Transport