servant-websockets-2.0.0: Small library providing WebSocket endpoints for servant.

Safe HaskellNone
LanguageHaskell2010

Servant.API.WebSocket

Synopsis

Documentation

data WebSocket Source #

Endpoint for defining a route to provide a web socket. The handler function gets an already negotiated websocket Connection to send and receive data.

Example:

type WebSocketApi = "stream" :> WebSocket

server :: Server WebSocketApi
server = streamData
 where
  streamData :: MonadIO m => Connection -> m ()
  streamData c = do
    liftIO $ forkPingThread c 10
    liftIO . forM_ [1..] $ \i -> do
       sendTextData c (pack $ show (i :: Int)) >> threadDelay 1000000
Instances
HasServer WebSocket ctx Source # 
Instance details

Defined in Servant.API.WebSocket

Associated Types

type ServerT WebSocket m :: Type #

Methods

route :: Proxy WebSocket -> Context ctx -> Delayed env (Server WebSocket) -> Router env #

hoistServerWithContext :: Proxy WebSocket -> Proxy ctx -> (forall x. m x -> n x) -> ServerT WebSocket m -> ServerT WebSocket n #

type ServerT WebSocket m Source # 
Instance details

Defined in Servant.API.WebSocket

type ServerT WebSocket m = Connection -> m ()

data WebSocketPending Source #

Endpoint for defining a route to provide a web socket. The handler function gets a PendingConnection. It can either rejectRequest or acceptRequest. This function is provided for greater flexibility to reject connections.

Example:

type WebSocketApi = "stream" :> WebSocketPending

server :: Server WebSocketApi
server = streamData
 where
  streamData :: MonadIO m => PendingConnection -> m ()
  streamData pc = do
     c <- acceptRequest pc
     liftIO $ forkPingThread c 10
     liftIO . forM_ [1..] $ \i ->
       sendTextData c (pack $ show (i :: Int)) >> threadDelay 1000000
Instances
HasServer WebSocketPending ctx Source # 
Instance details

Defined in Servant.API.WebSocket

Associated Types

type ServerT WebSocketPending m :: Type #

type ServerT WebSocketPending m Source # 
Instance details

Defined in Servant.API.WebSocket