Skip to content
Snippets Groups Projects
Commit a6455ed0 authored by Mikhail Glushenkov's avatar Mikhail Glushenkov Committed by GitHub
Browse files

Merge pull request #3555 from phadej/QuickCheck-2.9

Support QuickCheck-2.9
parents 317b9864 84c63df9
No related branches found
No related tags found
No related merge requests found
......@@ -396,7 +396,7 @@ test-suite unit-tests
tasty-quickcheck,
tagged,
pretty,
QuickCheck >= 2.7 && < 2.9,
QuickCheck >= 2.7 && < 2.10,
Cabal
ghc-options: -Wall
default-language: Haskell98
......
{-# LANGUAGE CPP #-}
{-# OPTIONS_GHC -fno-warn-orphans
-fno-warn-incomplete-patterns
-fno-warn-deprecations
......@@ -12,9 +13,12 @@ import Text.PrettyPrint as Disp (text, render, parens, hcat
import Test.Tasty
import Test.Tasty.QuickCheck
import Test.QuickCheck.Utils
import qualified Test.Laws as Laws
#if !MIN_VERSION_QuickCheck(2,9,0)
import Test.QuickCheck.Utils
#endif
import Control.Monad (liftM, liftM2)
import Data.Maybe (isJust, fromJust)
import Data.List (sort, sortBy, nub)
......@@ -100,6 +104,7 @@ versionTests =
-- -- , property prop_parse_disp5
-- ]
#if !MIN_VERSION_QuickCheck(2,9,0)
instance Arbitrary Version where
arbitrary = do
branch <- smallListOf1 $
......@@ -115,6 +120,7 @@ instance Arbitrary Version where
[ Version branch' [] | branch' <- shrink branch, not (null branch') ]
shrink (Version branch _tags) =
[ Version branch [] ]
#endif
instance Arbitrary VersionRange where
arbitrary = sized verRangeExp
......
......@@ -67,6 +67,7 @@ instance Arbitrary ShortToken where
arbitraryShortToken :: Gen String
arbitraryShortToken = getShortToken <$> arbitrary
#if !MIN_VERSION_QuickCheck(2,9,0)
instance Arbitrary Version where
arbitrary = do
branch <- shortListOf1 4 $
......@@ -81,6 +82,7 @@ instance Arbitrary Version where
[ Version branch' [] | branch' <- shrink branch, not (null branch') ]
shrink (Version branch _tags) =
[ Version branch [] ]
#endif
instance Arbitrary VersionRange where
arbitrary = canonicaliseVersionRange <$> sized verRangeExp
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment