module Test.Tests where import Prelude hiding (null) import Test.QuickCheck import Data.Bimap instance (Ord a, Arbitrary a, Ord b, Arbitrary b) => Arbitrary (Bimap a b) where arbitrary = fromList `fmap` arbitrary coarbitrary = coarbitrary . toList prop_size_empty = size empty == 0 prop_null_empty = null empty -- (heh, this is probably made redundant by polymorphism) prop_fromList_toList xs = let xs' = toList . fromList $ xs in all (flip elem xs) xs' where _ = xs :: [(Int, Integer)] -- when converting a list to a bimap, each list element either -- ends up in the bimap, or could conceivably have been clobbered prop_fromList_account xs = all (\x -> isMember x || notUnique x) xs where _ = xs :: [(Int, Integer)] bi = fromList xs isMember x = x `pairMember` bi notUnique (x, y) = ((>1) . length . filter (== x) . map fst $ xs) || ((>1) . length . filter (== y) . map snd $ xs) prop_fromList_size xs = (size $ fromList xs) <= length xs where _ = xs :: [(Int, Integer)] -- if we insert a pair with an existing value, the old value's twin -- is no longer in the bimap prop_clobberL bi b' = (not . null $ bi) && (Right b' `notMember` bi) ==> (a, b) `pairNotMember` insert (a, b') bi where (a, b) = head . toList $ bi :: (Int, Integer) prop_clobberR bi a' = (not . null $ bi) && (Left a' `notMember` bi) ==> (a, b) `pairNotMember` insert (a', b) bi where (a, b) = head . toList $ bi :: (Int, Integer) -- an arbitrary bimap is valid prop_valid bi = valid bi where _ = bi :: Bimap Int Integer prop_member_twin bi = flip all (toList bi) $ \(x, y) -> and [ (Right . snd $ bi ! Left x) `member` bi , (Left . fst $ bi ! Right y) `member` bi ] where _ = bi :: Bimap Int Integer prop_delete bi = flip all (toList bi) $ \(x, y) -> and [ (Left x) `notMember` delete (Left x) bi , (Right y) `notMember` delete (Right y) bi ] where _ = bi :: Bimap Int Integer prop_delete_twin bi = flip all (toList bi) $ \(x, y) -> and [ (Right . snd $ bi ! Left x) `notMember` delete (Left x) bi , (Left . fst $ bi ! Right y) `notMember` delete (Right y) bi ] where _ = bi :: Bimap Int Integer