QueryParams: fix ampersand, improve test

* Simplify test API to use `()` - no awkward values at all.
 * The test asserts on _entire_ of resulting path now...
 * ...and fix the ampersand placement, but preserving the order of params left to right. The code also reads a bit better this way...
This commit is contained in:
Nick B 2017-03-07 21:25:11 +00:00
parent a5224276d5
commit 6be6697165
2 changed files with 5 additions and 5 deletions

View File

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

View File

@ -4,7 +4,7 @@ module Servant.QuickCheck.InternalSpec (spec) where
import Control.Concurrent.MVar (newMVar, readMVar, swapMVar)
import Control.Monad.IO.Class (liftIO)
import qualified Data.ByteString as BS
import qualified Data.ByteString.Char8 as C
import qualified Data.ByteString.Char8 as C
import Prelude.Compat
import Servant
import Test.Hspec (Spec, context, describe, it, shouldBe,
@ -121,8 +121,7 @@ queryParamsSpec = describe "QueryParams" $ do
gen = genRequest paramsAPI
req = (unGen gen rng 0) burl
qs = C.unpack $ queryString req
qs `shouldContain` ("one=")
qs `shouldContain` ("&two=")
qs `shouldBe` "one=&two="
------------------------------------------------------------------------------
-- APIs
@ -135,7 +134,7 @@ type API = ReqBody '[JSON] String :> Post '[JSON] String
api :: Proxy API
api = Proxy
type ParamsAPI = QueryParam "one" String :> QueryParam "two" String :> Get '[JSON] String
type ParamsAPI = QueryParam "one" String :> QueryParam "two" String :> Get '[JSON] ()
paramsAPI :: Proxy ParamsAPI
paramsAPI = Proxy