| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
Servant.API.QueryString
Description
Synopsis
- data QueryString
Documentation
data QueryString Source #
QueryString provides handlers access to the full query string from
the WAI request, rather than pulling each element explicitly. This
allows for dynamic query management, or to simply take in many
queries in one argument.
Example:
import Control.Monad.IO.Class (liftIO)
import Network.HTTP.Types (Query, renderQuery)
import Servant
import ServantExtras.QueryString
type MyAPI = "my-cookie-enabled-endpoint"
:> QueryString
:> Get '[JSON] NoContent
myServer :: Server MyAPI
myServer = queryEndpointHandler
where
queryEndpointHandler :: Query -> Handler NoContent
queryEndpointHandler query = do
liftIO $ print $ renderQuery True query
let mCookieValue = lookup "merlinWasHere" query in
case mCookieValue of
Nothing -> do
liftIO $ print "Merlin was *NOT* here!"
throwError err400 { errBody = "Clearly you've missed something." }
Just message -> do
liftIO $ do
print "Merlin WAS here, and he left us a message!"
print message
pure NoContent
Instances
| HasServer api ctx => HasServer (QueryString :> api :: Type) ctx Source # | |
Defined in Servant.API.QueryString Associated Types type ServerT (QueryString :> api) m # Methods route :: Proxy (QueryString :> api) -> Context ctx -> Delayed env (Server (QueryString :> api)) -> Router env # hoistServerWithContext :: Proxy (QueryString :> api) -> Proxy ctx -> (forall x. m x -> n x) -> ServerT (QueryString :> api) m -> ServerT (QueryString :> api) n # | |
| type ServerT (QueryString :> api :: Type) m Source # | |
Defined in Servant.API.QueryString | |