servant-combinators-0.0.2: Extra servant combinators for full WAI functionality.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Servant.API.PathInfo

Description

 
Synopsis

Documentation

data PathInfo Source #

PathInfo provides handlers access to the path segments from the request, without the domain name or query parameters. We re-generate this from the rawPathInfo via Network.HTTP.Types.decodePathSegments because Servant removes all fields from the pathInfo field of a request as part of routing the request to the appropriate handler.

Example:

import Data.ByteString (ByteString)
import Control.Monad.IO.Class (liftIO)
import Servant
import ServantExtras.RawPathInfo

type MyAPI = "merlin" :> "my-path-info-endpoint"
           :> PathInfo
           :> Get '[JSON] NoContent

myServer :: Server MyAPI
myServer = pathInfoEndpointHandler
 where
   pathInfoEndpointHandler :: [Text] -> Handler NoContent
   pathInfoEndpointHandler pInfo = do
     case (elem "merlin" pInfo) of
      False -> do
        liftIO $ print "This example has a bug!"
        throwError err400 { errBody = "Patches accepted!" }
      True -> do
        liftIO $ print "Hopefully this demonstrates how path info works."
        pure NoContent

Instances

Instances details
HasServer api ctx => HasServer (PathInfo :> api :: Type) ctx Source # 
Instance details

Defined in Servant.API.PathInfo

Associated Types

type ServerT (PathInfo :> api) m #

Methods

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

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

type ServerT (PathInfo :> api :: Type) m Source # 
Instance details

Defined in Servant.API.PathInfo

type ServerT (PathInfo :> api :: Type) m = [Text] -> ServerT api m