| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
Servant.API.RawPathInfo
Description
Synopsis
- data RawPathInfo
Documentation
data RawPathInfo Source #
RawPathInfo provides handlers access to the raw, unparsed path
information the WAI request.
If you wish to get the path segments, you can either use the
PathInfo combinator in Servant.API.PathInfo or parse it yourself
with Network.HTTP.Types.decodePathSegments
Example:
import Data.ByteString (ByteString)
import Control.Monad.IO.Class (liftIO)
import Servant
import ServantExtras.RawPathInfo
type MyAPI = "my-path-info-endpoint"
:> RawPathInfo
:> Get '[JSON] NoContent
myServer :: Server MyAPI
myServer = queryEndpointHandler
where
queryEndpointHandler :: ByteString -> Handler NoContent
queryEndpointHandler rawPath = do
case rawPath of
"/my-path-info-endpoint" -> do
liftIO $ print "Servant routed us to the right place!"
pure NoContent
_ -> do
liftIO $ print "My example has a bug!"
throwError err400 { errBody = "Patches accepted!" }
Instances
| HasServer api ctx => HasServer (RawPathInfo :> api :: Type) ctx Source # | |
Defined in Servant.API.RawPathInfo Associated Types type ServerT (RawPathInfo :> api) m # Methods route :: Proxy (RawPathInfo :> api) -> Context ctx -> Delayed env (Server (RawPathInfo :> api)) -> Router env # hoistServerWithContext :: Proxy (RawPathInfo :> api) -> Proxy ctx -> (forall x. m x -> n x) -> ServerT (RawPathInfo :> api) m -> ServerT (RawPathInfo :> api) n # | |
| type ServerT (RawPathInfo :> api :: Type) m Source # | |
Defined in Servant.API.RawPathInfo | |