summaryrefslogtreecommitdiff
path: root/Utility/QuickCheck.hs
diff options
context:
space:
mode:
Diffstat (limited to 'Utility/QuickCheck.hs')
-rw-r--r--Utility/QuickCheck.hs30
1 files changed, 15 insertions, 15 deletions
diff --git a/Utility/QuickCheck.hs b/Utility/QuickCheck.hs
index 2009476..b0a39f3 100644
--- a/Utility/QuickCheck.hs
+++ b/Utility/QuickCheck.hs
@@ -6,7 +6,7 @@
-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
-{-# LANGUAGE TypeSynonymInstances, CPP #-}
+{-# LANGUAGE TypeSynonymInstances #-}
module Utility.QuickCheck
( module X
@@ -15,27 +15,24 @@ module Utility.QuickCheck
import Test.QuickCheck as X
import Data.Time.Clock.POSIX
+import Data.Ratio
import System.Posix.Types
-import qualified Data.Map as M
-import qualified Data.Set as S
-import Control.Applicative
+import Data.List.NonEmpty (NonEmpty(..))
import Prelude
-#if ! MIN_VERSION_QuickCheck(2,8,2)
-instance (Arbitrary k, Arbitrary v, Eq k, Ord k) => Arbitrary (M.Map k v) where
- arbitrary = M.fromList <$> arbitrary
-
-instance (Arbitrary v, Eq v, Ord v) => Arbitrary (S.Set v) where
- arbitrary = S.fromList <$> arbitrary
-#endif
-
-{- Times before the epoch are excluded. -}
+{- Times before the epoch are excluded. Half with decimal and half without. -}
instance Arbitrary POSIXTime where
- arbitrary = fromInteger <$> nonNegative arbitrarySizedIntegral
+ arbitrary = do
+ n <- nonNegative arbitrarySizedBoundedIntegral :: Gen Int
+ d <- nonNegative arbitrarySizedIntegral
+ withd <- arbitrary
+ return $ if withd
+ then fromIntegral n + fromRational (1 % max d 1)
+ else fromIntegral n
{- Pids are never negative, or 0. -}
instance Arbitrary ProcessID where
- arbitrary = arbitrarySizedBoundedIntegral `suchThat` (> 0)
+ arbitrary = positive arbitrarySizedBoundedIntegral
{- Inodes are never negative. -}
instance Arbitrary FileID where
@@ -45,6 +42,9 @@ instance Arbitrary FileID where
instance Arbitrary FileOffset where
arbitrary = nonNegative arbitrarySizedIntegral
+instance Arbitrary l => Arbitrary (NonEmpty l) where
+ arbitrary = (:|) <$> arbitrary <*> arbitrary
+
nonNegative :: (Num a, Ord a) => Gen a -> Gen a
nonNegative g = g `suchThat` (>= 0)