mqtt-0.1.1.0: An MQTT protocol implementation.

Copyright(c) Lars Petersen 2016
LicenseMIT
Maintainerinfo@lars-petersen.net
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Network.Stack.Server

Description

 

Synopsis

Documentation

data TLS a Source #

Instances

Eq (ServerException (TLS a)) Source # 
Ord (ServerException (TLS a)) Source # 
Show (ServerException (TLS a)) Source # 
Show (ServerConnectionInfo a) => Show (ServerConnectionInfo (TLS a)) Source # 
Typeable * a => Exception (ServerException (TLS a)) Source # 
StreamServerStack a => StreamServerStack (TLS a) Source # 
(StreamServerStack a, Typeable * a) => ServerStack (TLS a) Source # 

Associated Types

data Server (TLS a) :: * Source #

data ServerConfig (TLS a) :: * Source #

data ServerException (TLS a) :: * Source #

data ServerConnection (TLS a) :: * Source #

data ServerConnectionInfo (TLS a) :: * Source #

Methods

withServer :: ServerConfig (TLS a) -> (Server (TLS a) -> IO b) -> IO b Source #

withConnection :: Server (TLS a) -> (ServerConnection (TLS a) -> ServerConnectionInfo (TLS a) -> IO b) -> IO (Async b) Source #

(StreamServerStack a, MqttServerTransportStack a) => MqttServerTransportStack (TLS a) Source # 
data Server (TLS a) Source # 
data ServerConfig (TLS a) Source # 
data ServerException (TLS a) Source # 
data ServerConnection (TLS a) Source # 
data ServerConnectionInfo (TLS a) Source # 

data WebSocket a Source #

Instances

Show (ServerConnectionInfo a) => Show (ServerConnectionInfo (WebSocket a)) Source # 
StreamServerStack a => StreamServerStack (WebSocket a) Source # 
StreamServerStack a => ServerStack (WebSocket a) Source # 
(StreamServerStack a, MqttServerTransportStack a) => MqttServerTransportStack (WebSocket a) Source # 
data Server (WebSocket a) Source # 
data ServerConfig (WebSocket a) Source # 
data ServerException (WebSocket a) Source # 
data ServerConnection (WebSocket a) Source # 
data ServerConnectionInfo (WebSocket a) Source # 

class Typeable a => ServerStack a where Source #

Minimal complete definition

withServer, withConnection

Methods

withServer :: ServerConfig a -> (Server a -> IO b) -> IO b Source #

Creates a new server from a configuration and passes it to a handler function.

The server given to the handler function shall be bound and in listening state. The handler function is usually a forever loop that accepts and handles new connections.

withServer config $ \server->
  forever $ withConnection handleConnection

withConnection :: Server a -> (ServerConnection a -> ServerConnectionInfo a -> IO b) -> IO (Async b) Source #

Waits for and accepts a new connection from a listening server and passes it to a handler function.

This operation is blocking until the lowest layer in the stack accepts a new connection. The handlers of all other layers are executed within an Async which is returned. This allows the main thread waiting on the underlying socket to block just as long as necessary. Upper layer protocol handshakes (TLS etc) will be executed in the new thread.

withServer config $ \server-> forever $
  future <- withConnection server handleConnection
  putStrLn "The lowest layer accepted a new connection!"
  async $ do
      result <- wait future
      putStrLn "The connection handler returned:"
      print result

Instances

StreamServerStack a => ServerStack (WebSocket a) Source # 
(StreamServerStack a, Typeable * a) => ServerStack (TLS a) Source # 

Associated Types

data Server (TLS a) :: * Source #

data ServerConfig (TLS a) :: * Source #

data ServerException (TLS a) :: * Source #

data ServerConnection (TLS a) :: * Source #

data ServerConnectionInfo (TLS a) :: * Source #

Methods

withServer :: ServerConfig (TLS a) -> (Server (TLS a) -> IO b) -> IO b Source #

withConnection :: Server (TLS a) -> (ServerConnection (TLS a) -> ServerConnectionInfo (TLS a) -> IO b) -> IO (Async b) Source #

StreamServerStack transport => ServerStack (MQTT transport) Source # 

Associated Types

data Server (MQTT transport) :: * Source #

data ServerConfig (MQTT transport) :: * Source #

data ServerException (MQTT transport) :: * Source #

data ServerConnection (MQTT transport) :: * Source #

data ServerConnectionInfo (MQTT transport) :: * Source #

Methods

withServer :: ServerConfig (MQTT transport) -> (Server (MQTT transport) -> IO b) -> IO b Source #

withConnection :: Server (MQTT transport) -> (ServerConnection (MQTT transport) -> ServerConnectionInfo (MQTT transport) -> IO b) -> IO (Async b) Source #

(Family f, Type t, Protocol p, Typeable * f, Typeable * t, Typeable * p) => ServerStack (Socket f t p) Source # 

Associated Types

data Server (Socket f t p) :: * Source #

data ServerConfig (Socket f t p) :: * Source #

data ServerException (Socket f t p) :: * Source #

data ServerConnection (Socket f t p) :: * Source #

data ServerConnectionInfo (Socket f t p) :: * Source #

Methods

withServer :: ServerConfig (Socket f t p) -> (Server (Socket f t p) -> IO b) -> IO b Source #

withConnection :: Server (Socket f t p) -> (ServerConnection (Socket f t p) -> ServerConnectionInfo (Socket f t p) -> IO b) -> IO (Async b) Source #

class ServerStack a => StreamServerStack a where Source #

Instances

class ServerStack a => MessageServerStack a where Source #

This class is an abstraction for ServerStacks that support the transmission and reception of finite messages.

Associated Types

type ClientMessage a Source #

type ServerMessage a Source #

Methods

sendMessage :: ServerConnection a -> ServerMessage a -> IO Int64 Source #

Send a message.

  • Returns the encoded message size.

sendMessages :: Foldable t => ServerConnection a -> t (ServerMessage a) -> IO Int64 Source #

Send several messages. This might lead to an improvement for very short messages.

  • Returns the summed size of all encoded messages.

receiveMessage :: ServerConnection a -> Int64 -> IO (ClientMessage a) Source #

Receive a message.

  • The second parameter determines the maximum encoded message size which must not be exceeded by the client or an exception will be thrown. Implementations shall track the consumed bytes and shall throw an exception as soon as the limit is exceeded even if the message is not yet complete. This is important to prevent _denial of service_ attacks.

consumeMessages :: ServerConnection a -> Int64 -> (ClientMessage a -> IO Bool) -> IO () Source #

Consumes incoming messages with a supplied consumer callback.

  • The second parameter limits the size of a single encoded message (see receiveMessage).

Instances

StreamServerStack transport => MessageServerStack (MQTT transport) Source # 

Associated Types

type ClientMessage (MQTT transport) :: * Source #

type ServerMessage (MQTT transport) :: * Source #

Methods

sendMessage :: ServerConnection (MQTT transport) -> ServerMessage (MQTT transport) -> IO Int64 Source #

sendMessages :: Foldable t => ServerConnection (MQTT transport) -> t (ServerMessage (MQTT transport)) -> IO Int64 Source #

receiveMessage :: ServerConnection (MQTT transport) -> Int64 -> IO (ClientMessage (MQTT transport)) Source #

consumeMessages :: ServerConnection (MQTT transport) -> Int64 -> (ClientMessage (MQTT transport) -> IO Bool) -> IO () Source #