base-compat for tests.

And test import cleanup.
This commit is contained in:
Julian K. Arni 2016-05-09 17:59:37 +02:00
parent eb51069cb5
commit c5172a1dc5
2 changed files with 15 additions and 13 deletions

View File

@ -68,12 +68,13 @@ library
test-suite spec test-suite spec
type: exitcode-stdio-1.0 type: exitcode-stdio-1.0
ghc-options: -Wall -O2 -threaded ghc-options: -Wall -threaded
default-language: Haskell2010 default-language: Haskell2010
hs-source-dirs: test hs-source-dirs: test
main-is: Spec.hs main-is: Spec.hs
other-modules: Servant.QuickCheck.InternalSpec other-modules: Servant.QuickCheck.InternalSpec
build-depends: base == 4.* build-depends: base == 4.*
, base-compat
, servant-quickcheck , servant-quickcheck
, hspec , hspec
, http-client , http-client
@ -88,5 +89,6 @@ test-suite spec
, FlexibleInstances , FlexibleInstances
, FlexibleContexts , FlexibleContexts
, DataKinds , DataKinds
, NoImplicitPrelude
if flag(long-tests) if flag(long-tests)
cpp-options: -DLONG_TESTS cpp-options: -DLONG_TESTS

View File

@ -1,18 +1,18 @@
{-# LANGUAGE CPP #-} {-# LANGUAGE CPP #-}
{-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE ScopedTypeVariables #-}
module Servant.QuickCheck.InternalSpec (spec) where module Servant.QuickCheck.InternalSpec (spec) where
import Control.Concurrent.MVar (newMVar, readMVar, swapMVar) import Control.Concurrent.MVar (newMVar, readMVar,
import Control.Monad.IO.Class (liftIO) swapMVar)
import Data.Proxy import Control.Monad.IO.Class (liftIO)
import Servant import Prelude.Compat
import Test.Hspec import Servant
import Test.QuickCheck import Servant.API.Internal.Test.ComprehensiveAPI (comprehensiveAPI)
import Servant.API.Internal.Test.ComprehensiveAPI import Test.Hspec (Spec, describe, it,
shouldBe)
import Servant.QuickCheck import Servant.QuickCheck
import Servant.QuickCheck.Internal (genRequest, serverDoesntSatisfy)
import Servant.QuickCheck.Internal (genRequest, serverDoesntSatisfy)
spec :: Spec spec :: Spec
spec = do spec = do
@ -79,7 +79,7 @@ ctx = BasicAuthCheck (const . return $ NoSuchUser) :. EmptyContext
------------------------------------------------------------------------------ ------------------------------------------------------------------------------
args :: Args args :: Args
args = stdArgs { maxSuccess = noOfTestCases } args = defaultArgs { maxSuccess = noOfTestCases }
noOfTestCases :: Int noOfTestCases :: Int
#if LONG_TESTS #if LONG_TESTS