Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data WebSocketConduit i o
- data WebSocketSource o
- runConduitWebSocket :: (MonadBaseControl IO m, MonadUnliftIO m) => Connection -> ConduitT () Void (ResourceT m) () -> m ()
- upgradeRequired :: ServerError
Documentation
data WebSocketConduit i o Source #
Endpoint for defining a route to provide a websocket. In contrast
to the WebSocket
endpoint, WebSocketConduit
provides a
higher-level interface. The handler function must be of type
Conduit i m o
with i
and o
being instances of FromJSON
and
ToJSON
respectively. await
reads from the web socket while
yield
writes to it.
Example:
import Data.Aeson (Value) import qualified Data.Conduit.List as CL type WebSocketApi = "echo" :> WebSocketConduit Value Value server :: Server WebSocketApi server = echo where echo :: Monad m => ConduitT Value Value m () echo = CL.map id
Note that the input format on the web socket is JSON, hence this example only echos valid JSON data.
Instances
(FromJSON i, ToJSON o) => HasServer (WebSocketConduit i o :: Type) ctx Source # | |
Defined in Servant.API.WebSocketConduit type ServerT (WebSocketConduit i o) m :: Type # route :: Proxy (WebSocketConduit i o) -> Context ctx -> Delayed env (Server (WebSocketConduit i o)) -> Router env # hoistServerWithContext :: Proxy (WebSocketConduit i o) -> Proxy ctx -> (forall x. m x -> n x) -> ServerT (WebSocketConduit i o) m -> ServerT (WebSocketConduit i o) n # | |
type ServerT (WebSocketConduit i o :: Type) m Source # | |
Defined in Servant.API.WebSocketConduit |
data WebSocketSource o Source #
Endpoint for defining a route to provide a websocket. In contrast
to the WebSocketConduit
, this endpoint only produces data. It can
be useful when implementing web sockets that simply just send data
to clients.
Example:
import Data.Text (Text) import qualified Data.Conduit.List as CL type WebSocketApi = "hello" :> WebSocketSource Text server :: Server WebSocketApi server = hello where hello :: Monad m => Conduit Text m () hello = yield $ Just "hello"
Instances
ToJSON o => HasServer (WebSocketSource o :: Type) ctx Source # | |
Defined in Servant.API.WebSocketConduit type ServerT (WebSocketSource o) m :: Type # route :: Proxy (WebSocketSource o) -> Context ctx -> Delayed env (Server (WebSocketSource o)) -> Router env # hoistServerWithContext :: Proxy (WebSocketSource o) -> Proxy ctx -> (forall x. m x -> n x) -> ServerT (WebSocketSource o) m -> ServerT (WebSocketSource o) n # | |
type ServerT (WebSocketSource o :: Type) m Source # | |
Defined in Servant.API.WebSocketConduit |
runConduitWebSocket :: (MonadBaseControl IO m, MonadUnliftIO m) => Connection -> ConduitT () Void (ResourceT m) () -> m () Source #