Safe Haskell | None |
---|---|
Language | Haskell2010 |
- data Node a = Node {}
- node :: (Functor m, Applicative m, MonadIO m, Binary a, Show a) => Int -> SockAddr -> Handlers a -> m (Node a)
- data NodeConn a = NodeConn (Node a) Connection
- data NodeConnT a m r
- data Connection = Connection SockAddr Socket
- data Handlers a = Handlers {
- ohandshake :: HandShaker a
- ihandshake :: HandShaker a
- onConnect :: Handler a
- onDisconnect :: Handler a
- msgConsumer :: forall m. (MonadIO m, MonadMask m) => a -> Consumer (Either (Relay a) a) (NodeConnT a m) ()
- launch :: (Functor m, Applicative m, MonadIO m, MonadMask m, Binary a) => Node a -> [SockAddr] -> m ()
- runNodeConn :: (Functor m, MonadIO m, MonadMask m, Binary a) => Node a -> Bool -> SockAddr -> Socket -> m ()
- deliver :: (Binary a, MonadIO m) => a -> MaybeT (NodeConnT a m) ()
- expect :: (MonadIO m, Binary a, Eq a) => a -> MaybeT (NodeConnT a m) ()
- fetch :: (MonadIO m, Binary a) => MaybeT (NodeConnT a m) a
- data Relay a = Relay ThreadId a
- serialize :: Binary a => Int -> a -> ByteString
- class Monad m => MonadIO m where
- liftIO :: MonadIO m => forall a. IO a -> m a
Nodes and Connections
:: (Functor m, Applicative m, MonadIO m, Binary a, Show a) | |
=> Int | Magic bytes. |
-> SockAddr | Listening address. |
-> Handlers a | Functions to define the behavior of the |
-> m (Node a) |
Smart constructor to create a Node
.
Convenient data type to put together a Node
and a Connection
.
NodeConn (Node a) Connection |
Monad m => MonadReader (NodeConn a) (NodeConnT a m) |
Monad m => MonadReader (NodeConn a) (NodeConnT a m) | |
Monad m => Monad (NodeConnT a m) | |
Functor m => Functor (NodeConnT a m) | |
Applicative m => Applicative (NodeConnT a m) | |
MonadThrow m => MonadThrow (NodeConnT a m) | |
MonadCatch m => MonadCatch (NodeConnT a m) | |
MonadMask m => MonadMask (NodeConnT a m) | |
MonadIO m => MonadIO (NodeConnT a m) |
data Connection Source
Convenient data type to put together a network address and its corresponding socket.
Functions to define the behavior of a Node
.
Handlers | |
|
:: (Functor m, Applicative m, MonadIO m, MonadMask m, Binary a) | |
=> Node a | |
-> [SockAddr] | Addresses to try to connect on launch. |
-> m () |
Launch a Node
.
Handshaking utilities
Send an expected message.
The message is automatically serialized and prepended with the magic bytes.
Receive a message and make sure it's the same as the expected message.
The message is automatically deserialized and checked for the correct magic bytes.
fetch :: (MonadIO m, Binary a) => MaybeT (NodeConnT a m) a Source
Fetch next message.
The message is automatically deserialized and checked for the correct magic bytes. Uses the length bytes in the header to pull the exact number of bytes of the message.
Messaging
Internal message to relay to the rest of connections in the node.
:: Binary a | |
=> Int | Magic bytes. |
-> a | Message. |
-> ByteString |
Serializes and prepends a Header
to a message.
Re-exports
class Monad m => MonadIO m where
Monads in which IO
computations may be embedded.
Any monad built by applying a sequence of monad transformers to the
IO
monad will be an instance of this class.
Instances should satisfy the following laws, which state that liftIO
is a transformer of monads:
MonadIO IO | |
MonadIO m => MonadIO (IdentityT m) | |
MonadIO m => MonadIO (MaybeT m) | |
MonadIO m => MonadIO (ListT m) | |
MonadIO m => MonadIO (ListT m) | |
MonadIO m => MonadIO (RandT g m) | |
MonadIO m => MonadIO (ContT r m) | |
(Error e, MonadIO m) => MonadIO (ErrorT e m) | |
MonadIO m => MonadIO (ReaderT r m) | |
MonadIO m => MonadIO (StateT s m) | |
MonadIO m => MonadIO (StateT s m) | |
(Monoid w, MonadIO m) => MonadIO (WriterT w m) | |
(Monoid w, MonadIO m) => MonadIO (WriterT w m) | |
MonadIO m => MonadIO (ExceptT e m) | |
MonadIO m => MonadIO (NodeConnT a m) | |
(Monoid w, MonadIO m) => MonadIO (RWST r w s m) | |
(Monoid w, MonadIO m) => MonadIO (RWST r w s m) | |
MonadIO m => MonadIO (Proxy a' a b' b m) |