client tests: QueryParams
This commit is contained in:
parent
0802221789
commit
c2be4f3377
2 changed files with 16 additions and 2 deletions
|
@ -7,6 +7,7 @@
|
|||
{-# LANGUAGE ScopedTypeVariables #-}
|
||||
module Servant.API.QueryParam where
|
||||
|
||||
import Data.List
|
||||
import Data.Maybe
|
||||
import Data.Proxy
|
||||
import Data.String.Conversions
|
||||
|
@ -104,7 +105,7 @@ instance (KnownSymbol sym, ToText a, HasClient sublayout)
|
|||
|
||||
clientWithRoute Proxy req paramlist =
|
||||
clientWithRoute (Proxy :: Proxy sublayout) $
|
||||
foldr (appendToQueryString pname) req paramlist'
|
||||
foldl' (\ value req -> appendToQueryString pname req value) req paramlist'
|
||||
|
||||
where pname = cs pname'
|
||||
pname' = symbolVal (Proxy :: Proxy sym)
|
||||
|
|
|
@ -27,6 +27,7 @@ type Api =
|
|||
:<|> "capture" :> Capture "name" String :> Get Person
|
||||
:<|> "body" :> ReqBody Person :> Post Person
|
||||
:<|> "param" :> QueryParam "name" String :> Get Person
|
||||
:<|> "params" :> QueryParams "names" String :> Get [Person]
|
||||
api :: Proxy Api
|
||||
api = Proxy
|
||||
|
||||
|
@ -39,6 +40,7 @@ server = serve api (
|
|||
Just "alice" -> return alice
|
||||
Just name -> left (400, name ++ " not found")
|
||||
Nothing -> left (400, "missing parameter"))
|
||||
:<|> (\ names -> return (zipWith Person names [0..]))
|
||||
)
|
||||
|
||||
withServer :: (URIAuth -> IO a) -> IO a
|
||||
|
@ -48,7 +50,13 @@ getGet :: URIAuth -> EitherT String IO Person
|
|||
getCapture :: String -> URIAuth -> EitherT String IO Person
|
||||
getBody :: Person -> URIAuth -> EitherT String IO Person
|
||||
getQueryParam :: Maybe String -> URIAuth -> EitherT String IO Person
|
||||
(getGet :<|> getCapture :<|> getBody :<|> getQueryParam) = client api
|
||||
getQueryParams :: [String] -> URIAuth -> EitherT String IO [Person]
|
||||
( getGet
|
||||
:<|> getCapture
|
||||
:<|> getBody
|
||||
:<|> getQueryParam
|
||||
:<|> getQueryParams)
|
||||
= client api
|
||||
|
||||
spec :: Spec
|
||||
spec = do
|
||||
|
@ -67,6 +75,11 @@ spec = do
|
|||
Left result <- runEitherT (getQueryParam (Just "bob") host)
|
||||
result `shouldContain` "bob not found"
|
||||
|
||||
it "Servant.API.QueryParam.QueryParams" $ withServer $ \ host -> do
|
||||
runEitherT (getQueryParams [] host) `shouldReturn` Right []
|
||||
runEitherT (getQueryParams ["alice", "bob"] host)
|
||||
`shouldReturn` Right [Person "alice" 0, Person "bob" 1]
|
||||
|
||||
context "client correctly handles error status codes" $ do
|
||||
let test :: WrappedApi -> Spec
|
||||
test (WrappedApi api) =
|
||||
|
|
Loading…
Reference in a new issue