Safe Haskell | None |
---|---|
Language | Haskell98 |
- type WebSocketsT = ReaderT Connection
- webSockets :: (MonadBaseControl IO m, MonadHandler m) => WebSocketsT m () -> m ()
- receiveData :: (MonadIO m, WebSocketsData a) => WebSocketsT m a
- sendTextData :: (MonadIO m, WebSocketsData a) => a -> WebSocketsT m ()
- sendBinaryData :: (MonadIO m, WebSocketsData a) => a -> WebSocketsT m ()
- sourceWS :: (MonadIO m, WebSocketsData a) => Producer (WebSocketsT m) a
- sinkWSText :: (MonadIO m, WebSocketsData a) => Consumer a (WebSocketsT m) ()
- sinkWSBinary :: (MonadIO m, WebSocketsData a) => Consumer a (WebSocketsT m) ()
- race :: MonadBaseControl IO m => m a -> m b -> m (Either a b)
- race_ :: MonadBaseControl IO m => m a -> m b -> m ()
- concurrently :: MonadBaseControl IO m => m a -> m b -> m (a, b)
- concurrently_ :: MonadBaseControl IO m => m a -> m b -> m ()
Core API
type WebSocketsT = ReaderT Connection Source
A transformer for a WebSockets handler.
Since 0.1.0
webSockets :: (MonadBaseControl IO 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
receiveData :: (MonadIO m, WebSocketsData a) => WebSocketsT m a Source
Receive a piece of data from the client.
Since 0.1.0
sendTextData :: (MonadIO m, WebSocketsData a) => a -> WebSocketsT m () Source
Send a textual message to the client.
Since 0.1.0
sendBinaryData :: (MonadIO m, WebSocketsData a) => a -> WebSocketsT m () Source
Send a binary message to the client.
Since 0.1.0
Conduit API
sourceWS :: (MonadIO m, WebSocketsData a) => Producer (WebSocketsT m) a Source
A Source
of WebSockets data from the user.
Since 0.1.0
sinkWSText :: (MonadIO m, WebSocketsData a) => Consumer a (WebSocketsT m) () Source
A Sink
for sending textual data to the user.
Since 0.1.0
sinkWSBinary :: (MonadIO m, WebSocketsData a) => Consumer a (WebSocketsT m) () Source
A Sink
for sending binary data to the user.
Since 0.1.0
Async helpers
race :: MonadBaseControl IO m => m a -> m b -> m (Either a b) Source
Generalized version of race
.
Since 0.1.0
race_ :: MonadBaseControl IO m => m a -> m b -> m () Source
Generalized version of race_
.
Since 0.1.0
concurrently :: MonadBaseControl IO m => m a -> m b -> m (a, b) Source
Generalized version of concurrently
. Note that if your underlying
monad has some kind of mutable state, the state from the second action will
overwrite the state from the first.
Since 0.1.0
concurrently_ :: MonadBaseControl IO m => m a -> m b -> m () Source
Run two actions concurrently (like concurrently
), but discard their
results and any modified monadic state.
Since 0.1.0