| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
Servant.API.RawRequest
Description
Synopsis
- data RawRequest
Documentation
data RawRequest Source #
RawRequest provides the Request field from the WAI request.
Example:
import Control.Monad.IO.Class (liftIO)
import Network.Wai
import Servant
import ServantExtras.RawRequest
type MyAPI = "my-request-endpoint"
:> RawRequest
:> Get '[JSON] NoContent
myServer :: Server MyAPI
myServer = requestEndpointHandler
where
requestEndpointHandler :: Request -> Handler NoContent
requestEndpointHandler req =
-- Do something clever with the request
pure NoContent
Instances
| HasServer api ctx => HasServer (RawRequest :> api :: Type) ctx Source # | |
Defined in Servant.API.RawRequest Associated Types type ServerT (RawRequest :> api) m # Methods route :: Proxy (RawRequest :> api) -> Context ctx -> Delayed env (Server (RawRequest :> api)) -> Router env # hoistServerWithContext :: Proxy (RawRequest :> api) -> Proxy ctx -> (forall x. m x -> n x) -> ServerT (RawRequest :> api) m -> ServerT (RawRequest :> api) n # | |
| type ServerT (RawRequest :> api :: Type) m Source # | |
Defined in Servant.API.RawRequest | |