yesod-websockets-0.3.0.3: WebSockets support for Yesod
Safe HaskellNone
LanguageHaskell2010

Yesod.WebSockets

Synopsis

Core API

type WebSocketsT = ReaderT Connection Source #

A transformer for a WebSockets handler.

Since 0.1.0

webSockets :: (MonadUnliftIO m, MonadHandler m) => WebSocketsT m () -> m () Source #

Attempt to run a WebSockets handler. This function first checks if the client initiated a WebSockets connection and, if so, runs the provided application, short-circuiting the rest of your handler. If the client did not request a WebSockets connection, the rest of your handler will be called instead.

Since 0.1.0

webSocketsWith Source #

Arguments

:: (MonadUnliftIO m, MonadHandler m) 
=> (RequestHead -> m (Maybe AcceptRequest))

A Nothing indicates that the websocket upgrade request should not happen and instead the rest of the handler will be called instead. This allows you to use getRequestSubprotocols and only accept the request if a compatible subprotocol is given. Also, the action runs before upgrading the request to websockets, so you can also use short-circuiting handler actions such as invalidArgs.

-> WebSocketsT m () 
-> m () 

Varient of webSockets which allows you to specify the AcceptRequest setttings when upgrading to a websocket connection.

Since 0.2.4

webSocketsOptions :: (MonadUnliftIO m, MonadHandler m) => ConnectionOptions -> WebSocketsT m () -> m () Source #

Varient of webSockets which allows you to specify the WS.ConnectionOptions setttings when upgrading to a websocket connection.

Since 0.2.5

webSocketsOptionsWith Source #

Arguments

:: (MonadUnliftIO m, MonadHandler m) 
=> ConnectionOptions

Custom websockets options

-> (RequestHead -> m (Maybe AcceptRequest))

A Nothing indicates that the websocket upgrade request should not happen and instead the rest of the handler will be called instead. This allows you to use getRequestSubprotocols and only accept the request if a compatible subprotocol is given. Also, the action runs before upgrading the request to websockets, so you can also use short-circuiting handler actions such as invalidArgs.

-> WebSocketsT m () 
-> m () 

Varient of webSockets which allows you to specify both the WS.ConnectionOptions and the AcceptRequest setttings when upgrading to a websocket connection.

Since 0.2.5

receiveData :: (MonadIO m, MonadReader Connection m, WebSocketsData a) => m a Source #

Receive a piece of data from the client.

Since 0.1.0

receiveDataE :: (MonadIO m, MonadReader Connection m, WebSocketsData a) => m (Either SomeException a) Source #

Receive a piece of data from the client. Capture SomeException as the result or operation Since 0.2.2

receiveDataMessageE :: (MonadIO m, MonadReader Connection m) => m (Either SomeException DataMessage) Source #

Receive an application message. Capture SomeException as the result or operation Since 0.2.3

sendPing :: (MonadIO m, WebSocketsData a, MonadReader Connection m) => a -> m () Source #

Send a ping message to the client.

Since 0.2.2

sendPingE :: (MonadIO m, WebSocketsData a, MonadReader Connection m) => a -> m (Either SomeException ()) Source #

Send a ping message to the client. Capture SomeException as the result of operation Since 0.2.2

sendClose :: (MonadIO m, WebSocketsData a, MonadReader Connection m) => a -> m () Source #

Send a close request to the client.

Since 0.2.2

sendCloseE :: (MonadIO m, WebSocketsData a, MonadReader Connection m) => a -> m (Either SomeException ()) Source #

Send a close request to the client. Capture SomeException as the result of operation Since 0.2.2

sendTextData :: (MonadIO m, WebSocketsData a, MonadReader Connection m) => a -> m () Source #

Send a textual message to the client.

Since 0.1.0

sendTextDataE :: (MonadIO m, WebSocketsData a, MonadReader Connection m) => a -> m (Either SomeException ()) Source #

Send a textual message to the client. Capture SomeException as the result or operation and can be used like `either handle_exception return =<< sendTextDataE (Welcome :: Text)` Since 0.2.2

sendBinaryData :: (MonadIO m, WebSocketsData a, MonadReader Connection m) => a -> m () Source #

Send a binary message to the client.

Since 0.1.0

sendBinaryDataE :: (MonadIO m, WebSocketsData a, MonadReader Connection m) => a -> m (Either SomeException ()) Source #

Send a binary message to the client. Capture SomeException as the result of operation Since 0.2.2

sendDataMessageE :: (MonadIO m, MonadReader Connection m) => DataMessage -> m (Either SomeException ()) Source #

Send a DataMessage to the client. Capture SomeException as the result of operation Since 0.2.3

Conduit API

sourceWS :: (MonadIO m, WebSocketsData a, MonadReader Connection m) => ConduitT i a m () Source #

A Source of WebSockets data from the user.

Since 0.1.0

sinkWSText :: (MonadIO m, WebSocketsData a, MonadReader Connection m) => ConduitT a o m () Source #

A Sink for sending textual data to the user.

Since 0.1.0

sinkWSBinary :: (MonadIO m, WebSocketsData a, MonadReader Connection m) => ConduitT a o m () Source #

A Sink for sending binary data to the user.

Since 0.1.0

Async helpers

race :: MonadUnliftIO m => m a -> m b -> m (Either a b) #

Unlifted race.

Since: unliftio-0.1.0.0

race_ :: MonadUnliftIO m => m a -> m b -> m () #

Unlifted race_.

Since: unliftio-0.1.0.0

concurrently :: MonadUnliftIO m => m a -> m b -> m (a, b) #

Unlifted concurrently.

Since: unliftio-0.1.0.0

concurrently_ :: MonadUnliftIO m => m a -> m b -> m () #

Unlifted concurrently_.

Since: unliftio-0.1.0.0

Re-exports from websockets

defaultConnectionOptions :: ConnectionOptions #

The default connection options:

  • Nothing happens when a pong is received.
  • Compression is disabled.
  • Lenient unicode decoding.

data ConnectionOptions #

Set options for a Connection. Please do not use this constructor directly, but rather use defaultConnectionOptions and then set the fields you want, e.g.:

myOptions = defaultConnectionOptions {connectionStrictUnicode = True}

This way your code does not break if the library introduces new fields.

Constructors

ConnectionOptions 

Fields

  • connectionOnPong :: !(IO ())

    Whenever a pong is received, this IO action is executed. It can be used to tickle connections or fire missiles.

  • connectionCompressionOptions :: !CompressionOptions
  • connectionStrictUnicode :: !Bool

    Enable strict unicode on the connection. This means that if a client (or server) sends invalid UTF-8, we will throw a UnicodeException rather than replacing it by the unicode replacement character U+FFFD.

  • connectionFramePayloadSizeLimit :: !SizeLimit

    The maximum size for incoming frame payload size in bytes. If a frame exceeds this limit, a ParseException is thrown.

  • connectionMessageDataSizeLimit :: !SizeLimit

    connectionFrameSizeLimit is often not enough since a malicious client can send many small frames to create a huge message. This limit allows you to protect from that. If a message exceeds this limit, a ParseException is thrown.

    Note that, if compression is enabled, we check the size of the compressed messages, as well as the size of the uncompressed messages as we are deflating them to ensure we don't use too much memory in any case.