Looser bounds.

Support recent versions of QuickCheck, aeson, http-client, servant,
        servant-client, and servant-server.
This commit is contained in:
Julian K. Arni 2016-10-03 16:30:46 +02:00
parent f36f544ee6
commit 8eb5c334c1
5 changed files with 27 additions and 14 deletions

View File

@ -33,26 +33,26 @@ library
, Servant.QuickCheck.Internal.ErrorTypes , Servant.QuickCheck.Internal.ErrorTypes
build-depends: base >=4.8 && <4.10 build-depends: base >=4.8 && <4.10
, base-compat == 0.9.* , base-compat == 0.9.*
, aeson > 0.8 && < 0.12 , aeson > 0.8 && < 2
, bytestring == 0.10.* , bytestring == 0.10.*
, case-insensitive == 1.2.* , case-insensitive == 1.2.*
, data-default-class >= 0.0 && < 0.2 , data-default-class >= 0.0 && < 0.2
, hspec == 2.2.* , hspec == 2.2.*
, http-client >= 0.4.30 && < 0.5 , http-client >= 0.4.30 && < 0.6
, http-media == 0.6.* , http-media == 0.6.*
, http-types > 0.8 && < 0.10 , http-types > 0.8 && < 0.10
, mtl > 2.1 && < 2.3 , mtl > 2.1 && < 2.3
, pretty == 1.1.* , pretty == 1.1.*
, process >= 1.2 && < 1.5 , process >= 1.2 && < 1.5
, QuickCheck > 2.7 && < 2.9 , QuickCheck > 2.7 && < 2.10
, servant > 0.6 && < 0.9 , servant > 0.6 && < 0.10
, servant-client > 0.6 && < 0.9 , servant-client > 0.6 && < 0.10
, servant-server > 0.6 && < 0.9 , servant-server > 0.6 && < 0.10
, split == 0.2.* , split == 0.2.*
, string-conversions > 0.3 && < 0.5 , string-conversions > 0.3 && < 0.5
, temporary == 1.2.* , temporary == 1.2.*
, text == 1.* , text == 1.*
, time == 1.5.* , time >= 1.5 && < 1.7
, warp >= 3.2.4 && < 3.3 , warp >= 3.2.4 && < 3.3
hs-source-dirs: src hs-source-dirs: src

View File

@ -2,7 +2,6 @@
{-# LANGUAGE PolyKinds #-} {-# LANGUAGE PolyKinds #-}
module Servant.QuickCheck.Internal.HasGenRequest where module Servant.QuickCheck.Internal.HasGenRequest where
import Data.Default.Class (def)
import Data.Monoid ((<>)) import Data.Monoid ((<>))
import Data.String (fromString) import Data.String (fromString)
import Data.String.Conversions (cs) import Data.String.Conversions (cs)
@ -10,7 +9,7 @@ import qualified Data.ByteString as BS
import GHC.TypeLits (KnownSymbol, Nat, symbolVal) import GHC.TypeLits (KnownSymbol, Nat, symbolVal)
import Network.HTTP.Client (Request, RequestBody (..), host, method, path, import Network.HTTP.Client (Request, RequestBody (..), host, method, path,
port, queryString, requestBody, requestHeaders, port, queryString, requestBody, requestHeaders,
secure) secure, defaultRequest)
import Network.HTTP.Media (renderHeader) import Network.HTTP.Media (renderHeader)
import Prelude.Compat import Prelude.Compat
import Servant import Servant
@ -125,7 +124,7 @@ instance (KnownSymbol x, HasGenRequest b)
instance (ReflectMethod method) instance (ReflectMethod method)
=> HasGenRequest (Verb (method :: k) (status :: Nat) (cts :: [*]) a) where => HasGenRequest (Verb (method :: k) (status :: Nat) (cts :: [*]) a) where
genRequest _ = return $ \burl -> def genRequest _ = return $ \burl -> defaultRequest
{ host = cs $ baseUrlHost burl { host = cs $ baseUrlHost burl
, port = baseUrlPort burl , port = baseUrlPort burl
, secure = baseUrlScheme burl == Https , secure = baseUrlScheme burl == Https

View File

@ -1,4 +1,5 @@
{-# LANGUAGE RecordWildCards #-} {-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE CPP #-}
module Servant.QuickCheck.Internal.QuickCheck where module Servant.QuickCheck.Internal.QuickCheck where
import Control.Concurrent (modifyMVar_, newMVar, readMVar) import Control.Concurrent (modifyMVar_, newMVar, readMVar)
@ -144,7 +145,11 @@ serverDoesntSatisfy api burl args preds = do
InsufficientCoverage {} -> expectationFailure $ "Insufficient coverage" InsufficientCoverage {} -> expectationFailure $ "Insufficient coverage"
noCheckStatus :: C.Request -> C.Request noCheckStatus :: C.Request -> C.Request
#if MIN_VERSION_http_client(0,5,0)
noCheckStatus = id
#else
noCheckStatus r = r { C.checkStatus = \_ _ _ -> Nothing} noCheckStatus r = r { C.checkStatus = \_ _ _ -> Nothing}
#endif
defManager :: C.Manager defManager :: C.Manager
defManager = unsafePerformIO $ C.newManager C.defaultManagerSettings defManager = unsafePerformIO $ C.newManager C.defaultManagerSettings

View File

@ -1,10 +1,10 @@
# Specifies the GHC version and set of packages available (e.g., lts-3.5, nightly-2015-09-21, ghc-7.10.2) # Specifies the GHC version and set of packages available (e.g., lts-3.5, nightly-2015-09-21, ghc-7.10.2)
resolver: nightly-2016-09-07 resolver: nightly-2016-10-03
packages: packages:
- '.' - '.'
extra-deps: extra-deps:
- 'servant-0.8.1' - 'servant-0.9'
- 'servant-server-0.8.1' - 'servant-server-0.9'
- 'servant-client-0.8.1' - 'servant-client-0.9'
flags: {} flags: {}
extra-package-dbs: [] extra-package-dbs: []

View File

@ -5,7 +5,11 @@ import Control.Concurrent.MVar (newMVar, readMVar, swapMVar)
import Control.Monad.IO.Class (liftIO) import Control.Monad.IO.Class (liftIO)
import Prelude.Compat import Prelude.Compat
import Servant import Servant
#if MIN_VERSION_servant(0,8,0)
import Servant.API.Internal.Test.ComprehensiveAPI (comprehensiveAPIWithoutRaw) import Servant.API.Internal.Test.ComprehensiveAPI (comprehensiveAPIWithoutRaw)
#else
import Servant.API.Internal.Test.ComprehensiveAPI (comprehensiveAPI, ComprehensiveAPI)
#endif
import Test.Hspec (Spec, context, describe, it, import Test.Hspec (Spec, context, describe, it,
shouldBe, shouldContain) shouldBe, shouldContain)
import Test.Hspec.Core.Spec (Arg, Example, Result (..), import Test.Hspec.Core.Spec (Arg, Example, Result (..),
@ -135,3 +139,8 @@ noOfTestCases = 20000
#else #else
noOfTestCases = 1000 noOfTestCases = 1000
#endif #endif
#if !MIN_VERSION_servant(0,8,0)
comprehensiveAPIWithoutRaw :: Proxy ComprehensiveAPI
comprehensiveAPIWithoutRaw = comprehensiveAPI
#endif