Skip to content

Commit affadb3

Browse files
committed
collate where arbitrary instances for intset and set are
1 parent 46c2e55 commit affadb3

File tree

5 files changed

+85
-124
lines changed

5 files changed

+85
-124
lines changed

containers-tests/containers-tests.cabal

Lines changed: 7 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -324,6 +324,7 @@ test-suite map-lazy-properties
324324

325325
other-modules:
326326
Utils.ArbitrarySetMap
327+
Utils.ArbitraryInstances
327328

328329
ghc-options: -O2
329330
other-extensions:
@@ -340,6 +341,7 @@ test-suite map-strict-properties
340341

341342
other-modules:
342343
Utils.ArbitrarySetMap
344+
Utils.ArbitraryInstances
343345

344346
ghc-options: -O2
345347
other-extensions:
@@ -366,6 +368,7 @@ test-suite set-properties
366368

367369
other-modules:
368370
Utils.ArbitrarySetMap
371+
Utils.ArbitraryInstances
369372

370373
ghc-options: -O2
371374
other-extensions:
@@ -405,7 +408,10 @@ test-suite intset-properties
405408
hs-source-dirs: tests
406409
main-is: intset-properties.hs
407410
type: exitcode-stdio-1.0
408-
other-modules: IntSetValidity
411+
other-modules:
412+
IntSetValidity
413+
Utils.ArbitraryInstances
414+
Utils.ArbitrarySetMap
409415

410416
ghc-options: -O2
411417
other-extensions:
Lines changed: 48 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,48 @@
1+
{-# LANGUAGE TypeFamilies #-}
2+
{-# LANGUAGE TypeOperators #-}
3+
4+
module Utils.ArbitraryInstances () where
5+
6+
import Data.IntSet as IS
7+
import Data.Set as S
8+
9+
import Utils.ArbitrarySetMap
10+
11+
import Control.Monad.Trans.State.Strict
12+
import Control.Monad.Trans.Class
13+
14+
import Test.Tasty
15+
import Test.Tasty.HUnit
16+
import Test.Tasty.QuickCheck
17+
18+
{--------------------------------------------------------------------
19+
Arbitrary, reasonably balanced trees
20+
--------------------------------------------------------------------}
21+
instance Arbitrary IntSet where
22+
arbitrary = IS.fromList <$> oneof [arbitrary, fmap (fmap getLarge) arbitrary]
23+
shrink = fmap IS.fromList . shrink . IS.toAscList
24+
25+
instance (Int ~ a) => Arbitrary (Set a) where
26+
arbitrary = sized (\sz0 -> do
27+
sz <- choose (0, sz0)
28+
middle <- choose (-positionFactor * (sz + 1), positionFactor * (sz + 1))
29+
let shift = (sz * (gapRange) + 1) `quot` 2
30+
start = middle - shift
31+
t <- evalStateT (mkArbSet step sz) start
32+
if valid t then pure t else error "Test generated invalid tree!")
33+
where
34+
step = do
35+
i <- get
36+
diff <- lift $ choose (1, gapRange)
37+
let i' = i + diff
38+
put i'
39+
pure i'
40+
41+
-- How much the minimum value of an arbitrary set should vary
42+
positionFactor :: Int
43+
positionFactor = 1
44+
45+
-- How much the gap between consecutive elements in an arbitrary
46+
-- set should vary
47+
gapRange :: Int
48+
gapRange = 5

containers-tests/tests/intset-properties.hs

Lines changed: 1 addition & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -16,6 +16,7 @@ import Prelude hiding (lookup, null, map, filter, foldr, foldl, foldl', foldMap)
1616
import Test.Tasty
1717
import Test.Tasty.HUnit
1818
import Test.Tasty.QuickCheck hiding ((.&.))
19+
import Utils.ArbitraryInstances ()
1920

2021
main :: IO ()
2122
main = defaultMain $ testGroup "intset-properties"
@@ -146,13 +147,6 @@ test_compareSize = do
146147
compareSize (fromList [1]) minBound @?= GT
147148
compareSize (fromList [1]) maxBound @?= LT
148149

149-
{--------------------------------------------------------------------
150-
Arbitrary, reasonably balanced trees
151-
--------------------------------------------------------------------}
152-
instance Arbitrary IntSet where
153-
arbitrary = fromList <$> oneof [arbitrary, fmap (fmap getLarge) arbitrary]
154-
shrink = fmap fromList . shrink . toAscList
155-
156150
{--------------------------------------------------------------------
157151
Valid IntMaps
158152
--------------------------------------------------------------------}

containers-tests/tests/map-properties.hs

Lines changed: 13 additions & 41 deletions
Original file line numberDiff line numberDiff line change
@@ -1,5 +1,7 @@
11
{-# LANGUAGE CPP #-}
22
{-# LANGUAGE TupleSections #-}
3+
{-# LANGUAGE TypeOperators #-}
4+
{-# LANGUAGE TypeFamilies #-}
35

46
#ifdef STRICT
57
import Data.Map.Strict as Data.Map
@@ -313,46 +315,7 @@ main = defaultMain $ testGroup "map-properties"
313315
, testProperty "mapAccumRWithKey" prop_mapAccumRWithKey
314316
]
315317

316-
{--------------------------------------------------------------------
317-
Arbitrary, reasonably balanced trees
318-
--------------------------------------------------------------------}
319-
320-
-- | The IsInt class lets us constrain a type variable to be Int in an entirely
321-
-- standard way. The constraint @ IsInt a @ is essentially equivalent to the
322-
-- GHC-only constraint @ a ~ Int @, but @ IsInt @ requires manual intervention
323-
-- to use. If ~ is ever standardized, we should certainly use it instead.
324-
-- Earlier versions used an Enum constraint, but this is confusing because
325-
-- not all Enum instances will work properly for the Arbitrary instance here.
326-
class (Show a, Read a, Integral a, Arbitrary a) => IsInt a where
327-
fromIntF :: f Int -> f a
328-
329-
instance IsInt Int where
330-
fromIntF = id
331-
332-
-- | Convert an Int to any instance of IsInt
333-
fromInt :: IsInt a => Int -> a
334-
fromInt = runIdentity . fromIntF . Identity
335-
336-
{- We don't actually need this, but we can add it if we ever do
337-
toIntF :: IsInt a => g a -> g Int
338-
toIntF = unf . fromIntF . F $ id
339-
340-
newtype F g a b = F {unf :: g b -> a}
341-
342-
toInt :: IsInt a => a -> Int
343-
toInt = runIdentity . toIntF . Identity -}
344-
345-
346-
-- How much the minimum key of an arbitrary map should vary
347-
positionFactor :: Int
348-
positionFactor = 1
349-
350-
-- How much the gap between consecutive keys in an arbitrary
351-
-- map should vary
352-
gapRange :: Int
353-
gapRange = 5
354-
355-
instance (IsInt k, Arbitrary v) => Arbitrary (Map k v) where
318+
instance (Int ~ k, Arbitrary v) => Arbitrary (Map k v) where
356319
arbitrary = sized (\sz0 -> do
357320
sz <- choose (0, sz0)
358321
middle <- choose (-positionFactor * (sz + 1), positionFactor * (sz + 1))
@@ -366,7 +329,16 @@ instance (IsInt k, Arbitrary v) => Arbitrary (Map k v) where
366329
diff <- lift $ choose (1, gapRange)
367330
let i' = i + diff
368331
put i'
369-
pure (fromInt i')
332+
pure i'
333+
334+
-- How much the minimum key of an arbitrary map should vary
335+
positionFactor :: Int
336+
positionFactor = 1
337+
338+
-- How much the gap between consecutive keys in an arbitrary
339+
-- map should vary
340+
gapRange :: Int
341+
gapRange = 5
370342

371343
-- A type with a peculiar Eq instance designed to make sure keys
372344
-- come from where they're supposed to.

containers-tests/tests/set-properties.hs

Lines changed: 16 additions & 75 deletions
Original file line numberDiff line numberDiff line change
@@ -21,6 +21,7 @@ import Data.List.NonEmpty (NonEmpty(..))
2121
import qualified Data.List.NonEmpty as NE
2222

2323
import Utils.ArbitrarySetMap (mkArbSet, setFromList)
24+
import Utils.ArbitraryInstances ()
2425

2526
main :: IO ()
2627
main = defaultMain $ testGroup "set-properties"
@@ -192,94 +193,34 @@ test_deleteAt = do
192193
Arbitrary, reasonably balanced trees
193194
--------------------------------------------------------------------}
194195

195-
-- | The IsInt class lets us constrain a type variable to be Int in an entirely
196-
-- standard way. The constraint @ IsInt a @ is essentially equivalent to the
197-
-- GHC-only constraint @ a ~ Int @, but @ IsInt @ requires manual intervention
198-
-- to use. If ~ is ever standardized, we should certainly use it instead.
199-
-- Earlier versions used an Enum constraint, but this is confusing because
200-
-- not all Enum instances will work properly for the Arbitrary instance here.
201-
class (Show a, Read a, Integral a, Arbitrary a) => IsInt a where
202-
fromIntF :: f Int -> f a
203-
204-
instance IsInt Int where
205-
fromIntF = id
206-
207-
-- | Convert an Int to any instance of IsInt
208-
fromInt :: IsInt a => Int -> a
209-
fromInt = runIdentity . fromIntF . Identity
210-
211-
{- We don't actually need this, but we can add it if we ever do
212-
toIntF :: IsInt a => g a -> g Int
213-
toIntF = unf . fromIntF . F $ id
214-
215-
newtype F g a b = F {unf :: g b -> a}
216-
217-
toInt :: IsInt a => a -> Int
218-
toInt = runIdentity . toIntF . Identity -}
219-
220-
221-
-- How much the minimum value of an arbitrary set should vary
222-
positionFactor :: Int
223-
positionFactor = 1
224-
225-
-- How much the gap between consecutive elements in an arbitrary
226-
-- set should vary
227-
gapRange :: Int
228-
gapRange = 5
229-
230-
instance IsInt a => Arbitrary (Set a) where
231-
arbitrary = sized (\sz0 -> do
232-
sz <- choose (0, sz0)
233-
middle <- choose (-positionFactor * (sz + 1), positionFactor * (sz + 1))
234-
let shift = (sz * (gapRange) + 1) `quot` 2
235-
start = middle - shift
236-
t <- evalStateT (mkArbSet step sz) start
237-
if valid t then pure t else error "Test generated invalid tree!")
238-
where
239-
step = do
240-
i <- get
241-
diff <- lift $ choose (1, gapRange)
242-
let i' = i + diff
243-
put i'
244-
pure (fromInt i')
245-
246196
data TwoSets = TwoSets (Set Int) (Set Int) deriving (Show)
247197

248-
data TwoLists a = TwoLists [a] [a]
249-
250-
data Options2 = One2 | Two2 | Both2 deriving (Bounded, Enum)
251-
instance Arbitrary Options2 where
252-
arbitrary = arbitraryBoundedEnum
253-
254198
-- We produce two lists from a simple "universe". This instance
255199
-- is intended to give good results when the two lists are then
256200
-- combined with each other; if other elements are used with them,
257201
-- they may or may not behave particularly well.
258-
instance IsInt a => Arbitrary (TwoLists a) where
259-
arbitrary = sized $ \sz0 -> do
260-
sz <- choose (0, sz0)
261-
let universe = [0,3..3*(fromInt sz - 1)]
262-
divide2Gen universe
263-
264202
instance Arbitrary TwoSets where
265203
arbitrary = do
266-
TwoLists l r <- arbitrary
204+
(l, r) <- sized $ \sz0 -> do
205+
sz <- choose (0, sz0)
206+
let universe = [0,3..3*(sz - 1)]
207+
divide2Gen universe
267208
TwoSets <$> setFromList l <*> setFromList r
268-
269-
divide2Gen :: [a] -> Gen (TwoLists a)
270-
divide2Gen [] = pure (TwoLists [] [])
271-
divide2Gen (x : xs) = do
272-
way <- arbitrary
273-
TwoLists ls rs <- divide2Gen xs
274-
case way of
275-
One2 -> pure (TwoLists (x : ls) rs)
276-
Two2 -> pure (TwoLists ls (x : rs))
277-
Both2 -> pure (TwoLists (x : ls) (x : rs))
209+
where
210+
divide2Gen :: [a] -> Gen ([a], [a])
211+
divide2Gen [] = pure ([], [])
212+
divide2Gen (x : xs) = do
213+
mIsFirst <- arbitrary
214+
(ls, rs) <- divide2Gen xs
215+
pure $ case mIsFirst of
216+
Just True -> ((x : ls), rs)
217+
Just False -> (ls, (x : rs))
218+
Nothing -> ((x : ls), (x : rs))
278219

279220
{--------------------------------------------------------------------
280221
Valid trees
281222
--------------------------------------------------------------------}
282-
forValid :: (IsInt a,Testable b) => (Set a -> b) -> Property
223+
forValid :: (Testable b) => (Set Int -> b) -> Property
283224
forValid f = forAll arbitrary $ \t ->
284225
classify (size t == 0) "empty" $
285226
classify (size t > 0 && size t <= 10) "small" $

0 commit comments

Comments
 (0)