[commit: packages/binary] master: Switch to arbitrarySizedNatural from QuickCheck >= 2.8 (3c78d66)

git at git.haskell.org git at git.haskell.org
Mon Jun 1 08:47:35 UTC 2015


Repository : ssh://git@git.haskell.org/binary

On branch  : master
Link       : http://git.haskell.org/packages/binary.git/commitdiff/3c78d66f905c3fd45d0f2766672ab89e2dd3c9f0

>---------------------------------------------------------------

commit 3c78d66f905c3fd45d0f2766672ab89e2dd3c9f0
Author: Lennart Kolmodin <kolmodin at google.com>
Date:   Sat May 23 16:48:26 2015 +0200

    Switch to arbitrarySizedNatural from QuickCheck >= 2.8
    
    arbitrarySizedNatural got implemented in QuickCheck 2.8, so we no longer
    need to keep our own implementation.
    Bump the dependency on QuickCheck to >= 2.8.


>---------------------------------------------------------------

3c78d66f905c3fd45d0f2766672ab89e2dd3c9f0
 binary.cabal       |  2 +-
 tests/Arbitrary.hs | 22 ----------------------
 tests/QC.hs        | 12 ++++++------
 3 files changed, 7 insertions(+), 29 deletions(-)

diff --git a/binary.cabal b/binary.cabal
index b46ed48..322ff9b 100644
--- a/binary.cabal
+++ b/binary.cabal
@@ -71,7 +71,7 @@ test-suite qc
     random>=1.0.1.0,
     test-framework,
     test-framework-quickcheck2 >= 0.3,
-    QuickCheck>=2.7
+    QuickCheck>=2.8
 
   -- build dependencies from using binary source rather than depending on the library
   build-depends: array, containers
diff --git a/tests/Arbitrary.hs b/tests/Arbitrary.hs
index c19a192..dcb9d44 100644
--- a/tests/Arbitrary.hs
+++ b/tests/Arbitrary.hs
@@ -1,10 +1,6 @@
 {-# LANGUAGE CPP #-}
 {-# OPTIONS_GHC -fno-warn-orphans #-}
 
-#if MIN_VERSION_base(4,8,0)
-#define HAS_NATURAL
-#endif
-
 module Arbitrary where
 
 import Test.QuickCheck
@@ -12,10 +8,6 @@ import Test.QuickCheck
 import qualified Data.ByteString as B
 import qualified Data.ByteString.Lazy as L
 
-#ifdef HAS_NATURAL
-import Numeric.Natural
-#endif
-
 instance Arbitrary L.ByteString where
   arbitrary = fmap L.fromChunks arbitrary
 
@@ -61,17 +53,3 @@ instance (Arbitrary a, Arbitrary b, Arbitrary c, Arbitrary d, Arbitrary e,
     (a,b,c,d,e) <- arbitrary
     (f,g,h,i,j) <- arbitrary
     return (a,b,c,d,e,f,g,h,i,j)
-
-
-#ifdef HAS_NATURAL
--- | Generates a natural number. The number must be positive
--- and its maximum value depends on the size parameter.
-arbitrarySizedNatural :: Gen Natural
-arbitrarySizedNatural =
-  sized $ \n0 ->
-  let n = toInteger n0 in
-  inBounds fromInteger (choose (0, n*n))
-
-inBounds :: Integral a => (Integer -> a) -> Gen Integer -> Gen a
-inBounds fi g = fmap fi (g `suchThat` (\x -> toInteger (fi x) == x))
-#endif
\ No newline at end of file
diff --git a/tests/QC.hs b/tests/QC.hs
index 9e00616..b0b4c8f 100644
--- a/tests/QC.hs
+++ b/tests/QC.hs
@@ -16,16 +16,16 @@ import           Data.Int
 import           Data.Ratio
 import           System.IO.Unsafe
 
+#ifdef HAS_NATURAL
+import           Numeric.Natural
+#endif
+
 import           Test.Framework
 import           Test.Framework.Providers.QuickCheck2
 import           Test.QuickCheck
 
 import qualified Action                               (tests)
-import           Arbitrary                            (
-#ifdef HAS_NATURAL
-                                                       arbitrarySizedNatural
-#endif
-                                                      )
+import           Arbitrary                            ()
 import           Data.Binary
 import           Data.Binary.Get
 import           Data.Binary.Put
@@ -361,7 +361,7 @@ main = defaultMain tests
 -- | Until the QuickCheck library implements instance Arbitrary Natural,
 -- we need this test.
 prop_test_Natural :: Property
-prop_test_Natural = forAll arbitrarySizedNatural test
+prop_test_Natural = forAll (arbitrarySizedNatural :: Gen Natural) test
 #endif
 
 ------------------------------------------------------------------------



More information about the ghc-commits mailing list