Fix multiple QueryParams

* Add test API taking multiple `QueryParam`s
 * Add basic test using this API, generating an endpoint to ensure correct HTTP `one=foo&two=bar` query string generation is happening (that fails on `master`)
 * Fix (re)creation of query string to append `&` before the new parameter if there is already a built query string.

Fixes #23.
This commit is contained in:
Nick B 2017-03-06 13:32:55 +00:00
parent 47391784ce
commit a5224276d5
2 changed files with 24 additions and 3 deletions

View File

@ -91,9 +91,9 @@ instance (KnownSymbol x, Arbitrary c, ToHttpApiData c, HasGenRequest b)
genRequest _ = do genRequest _ = do
new' <- new new' <- new
old' <- old old' <- old
return $ \burl -> let r = old' burl in r { return $ \burl -> let r = old' burl
queryString = queryString r qs = queryString r in r {
<> param <> "=" <> cs (toQueryParam new') } queryString = (if BS.null qs then "" else "&") <> qs <> param <> "=" <> cs (toQueryParam new') }
where where
old = genRequest (Proxy :: Proxy b) old = genRequest (Proxy :: Proxy b)
param = cs $ symbolVal (Proxy :: Proxy x) param = cs $ symbolVal (Proxy :: Proxy x)

View File

@ -4,12 +4,16 @@ module Servant.QuickCheck.InternalSpec (spec) where
import Control.Concurrent.MVar (newMVar, readMVar, swapMVar) import Control.Concurrent.MVar (newMVar, readMVar, swapMVar)
import Control.Monad.IO.Class (liftIO) import Control.Monad.IO.Class (liftIO)
import qualified Data.ByteString as BS import qualified Data.ByteString as BS
import qualified Data.ByteString.Char8 as C
import Prelude.Compat import Prelude.Compat
import Servant import Servant
import Test.Hspec (Spec, context, describe, it, shouldBe, import Test.Hspec (Spec, context, describe, it, shouldBe,
shouldContain) shouldContain)
import Test.Hspec.Core.Spec (Arg, Example, Result (..), import Test.Hspec.Core.Spec (Arg, Example, Result (..),
defaultParams, evaluateExample) defaultParams, evaluateExample)
import Test.QuickCheck.Gen (unGen)
import Test.QuickCheck.Random (mkQCGen)
import Network.HTTP.Client (queryString)
#if MIN_VERSION_servant(0,8,0) #if MIN_VERSION_servant(0,8,0)
import Servant.API.Internal.Test.ComprehensiveAPI (comprehensiveAPIWithoutRaw) import Servant.API.Internal.Test.ComprehensiveAPI (comprehensiveAPIWithoutRaw)
@ -28,6 +32,7 @@ spec = do
isComprehensiveSpec isComprehensiveSpec
onlyJsonObjectSpec onlyJsonObjectSpec
notLongerThanSpec notLongerThanSpec
queryParamsSpec
serversEqualSpec :: Spec serversEqualSpec :: Spec
serversEqualSpec = describe "serversEqual" $ do serversEqualSpec = describe "serversEqual" $ do
@ -107,6 +112,17 @@ isComprehensiveSpec = describe "HasGenRequest" $ do
let _g = genRequest comprehensiveAPIWithoutRaw let _g = genRequest comprehensiveAPIWithoutRaw
True `shouldBe` True -- This is a type-level check True `shouldBe` True -- This is a type-level check
queryParamsSpec :: Spec
queryParamsSpec = describe "QueryParams" $ do
it "reduce to an HTTP query string correctly" $ do
let rng = mkQCGen 0
burl = BaseUrl Http "localhost" 80 ""
gen = genRequest paramsAPI
req = (unGen gen rng 0) burl
qs = C.unpack $ queryString req
qs `shouldContain` ("one=")
qs `shouldContain` ("&two=")
------------------------------------------------------------------------------ ------------------------------------------------------------------------------
-- APIs -- APIs
@ -119,6 +135,11 @@ type API = ReqBody '[JSON] String :> Post '[JSON] String
api :: Proxy API api :: Proxy API
api = Proxy api = Proxy
type ParamsAPI = QueryParam "one" String :> QueryParam "two" String :> Get '[JSON] String
paramsAPI :: Proxy ParamsAPI
paramsAPI = Proxy
server :: IO (Server API) server :: IO (Server API)
server = do server = do
mvar <- newMVar "" mvar <- newMVar ""