Fix serversEqual and tests.

This commit is contained in:
Julian K. Arni 2016-04-23 11:50:04 +02:00
parent 2050487058
commit c1b92215c3
3 changed files with 21 additions and 12 deletions

View File

@ -17,10 +17,12 @@ import System.IO (hPutStrLn, hFlush)
import System.IO.Temp (withSystemTempFile) import System.IO.Temp (withSystemTempFile)
import System.Mem (performGC) import System.Mem (performGC)
import System.Process (callCommand) import System.Process (callCommand)
import Test.Hspec (Expectation, expectationFailure) import Test.Hspec (Expectation, expectationFailure, shouldBe)
import Test.QuickCheck (Args (..), Property, forAll, Result (..), import Test.QuickCheck (Args (..), Property, forAll, Result (..),
Testable, property, ioProperty, Testable, property, ioProperty,
quickCheckWithResult, stdArgs) quickCheckWithResult, stdArgs)
import System.IO.Unsafe (unsafePerformIO)
import Test.QuickCheck.Monadic
import Servant.QuickCheck.Internal.HasGenRequest import Servant.QuickCheck.Internal.HasGenRequest
import Servant.QuickCheck.Internal.Predicates import Servant.QuickCheck.Internal.Predicates
@ -47,12 +49,21 @@ withServantServer api server t
-- Evidently, if the behaviour of the server is expected to be -- Evidently, if the behaviour of the server is expected to be
-- non-deterministic, this function may produce spurious failures -- non-deterministic, this function may produce spurious failures
serversEqual :: HasGenRequest a => serversEqual :: HasGenRequest a =>
Proxy a -> BaseUrl -> BaseUrl -> Manager -> Property Proxy a -> BaseUrl -> BaseUrl -> Args -> Expectation
serversEqual api burl1 burl2 mgr = serversEqual api burl1 burl2 args = do
let reqs = (\f -> (f burl1, f burl2)) <$> genRequest api let reqs = (\f -> (f burl1, f burl2)) <$> genRequest api
in forAll reqs $ \(req1, req2) -> ioProperty $ do r <- quickCheckWithResult args $ monadicIO $ forAllM reqs $ \(req1, req2) -> do
resp1 <- httpLbs req1 mgr resp1 <- run $ httpLbs req1 defManager
resp2 <- httpLbs req2 mgr resp2 <- run $ httpLbs req2 defManager
return $ resp1 == resp2 assert $ resp1 == resp2
case r of
Success {} -> return ()
GaveUp { numTests = n } -> expectationFailure $ "Gave up after " ++ show n ++ " tests"
Failure { output = m } -> expectationFailure $ "Failed:\n" ++ show m
NoExpectedFailure {} -> expectationFailure $ "No expected failure"
InsufficientCoverage {} -> expectationFailure $ "Insufficient coverage"
defManager :: Manager
defManager = unsafePerformIO $ newManager defaultManagerSettings
{-# NOINLINE defManager #-}

View File

@ -23,11 +23,9 @@ serversEqualSpec :: Spec
serversEqualSpec = describe "serversEqual" $ do serversEqualSpec = describe "serversEqual" $ do
it "considers equal servers equal" $ do it "considers equal servers equal" $ do
mgr <- newManager defaultManagerSettings
withServantServer api server $ \burl1 -> withServantServer api server $ \burl1 ->
withServantServer api server $ \burl2 -> do withServantServer api server $ \burl2 -> do
return $ serversEqual api burl1 burl2 mgr serversEqual api burl1 burl2 stdArgs { maxSuccess = 10000 }
@ -44,7 +42,7 @@ api = Proxy
server :: IO (Server API) server :: IO (Server API)
server = do server = do
mvar <- newMVar "" mvar <- newMVar ""
return $ (\x -> liftIO $ print 'a' >> swapMVar mvar x) return $ (\x -> liftIO $ swapMVar mvar x)
:<|> (liftIO $ readMVar mvar >>= return . length) :<|> (liftIO $ readMVar mvar >>= return . length)

View File

@ -1 +1 @@
{-# OPTIONS_GHC -F -pgmF hspec-discover -optF --module-name=Spec #-} {-# OPTIONS_GHC -F -pgmF hspec-discover #-}