summaryrefslogtreecommitdiff
path: root/Utility/QuickCheck.hs
diff options
context:
space:
mode:
authorJoey Hess <joeyh@joeyh.name>2020-01-02 12:34:10 -0400
committerJoey Hess <joeyh@joeyh.name>2020-01-02 12:42:57 -0400
commit9df8a6eb9405dde4464d27133c04f5ee539a85de (patch)
tree8a7ac5f52be8679f8a2525515a0b2c1b715c99ad /Utility/QuickCheck.hs
parent16022a8b98f4bc134542e78a42538364d2f97d92 (diff)
downloadgit-repair-9df8a6eb9405dde4464d27133c04f5ee539a85de.tar.gz
merge from git-annex and relicense accordingly
Merge git library and utility from git-annex. The former is now relicensed AGPL, so git-repair as a whole becomes AGPL. For simplicity, I am relicensing the remainder of the code in git-repair AGPL as well, per the header changes in this commit. While that code is also technically available under the GPL license, as it's been released under that license before, changes going forward will be only released by me under the AGPL.
Diffstat (limited to 'Utility/QuickCheck.hs')
-rw-r--r--Utility/QuickCheck.hs32
1 files changed, 15 insertions, 17 deletions
diff --git a/Utility/QuickCheck.hs b/Utility/QuickCheck.hs
index e89d103..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,29 +15,24 @@ module Utility.QuickCheck
import Test.QuickCheck as X
import Data.Time.Clock.POSIX
+import Data.Ratio
import System.Posix.Types
-#if ! MIN_VERSION_QuickCheck(2,8,2)
-import qualified Data.Map as M
-import qualified Data.Set as S
-#endif
-import Control.Applicative
+import Data.List.NonEmpty (NonEmpty(..))
import Prelude
-#if ! MIN_VERSION_QuickCheck(2,8,2)
-instance (Arbitrary k, Arbitrary v, Ord k) => Arbitrary (M.Map k v) where
- arbitrary = M.fromList <$> arbitrary
-
-instance (Arbitrary 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
@@ -47,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)