{-# LANGUAGE TemplateHaskell #-} module Data.IntSet.Translatable.Test (main) where import Test.Framework.TH import Test.Framework import Test.Framework.Providers.HUnit import Test.Framework.Providers.QuickCheck2 import Test.HUnit import Test.QuickCheck import qualified Data.IntSet.Translatable as T import qualified Data.IntSet as R import Data.Monoid import qualified Data.List as L import Data.List import Data.Functor import Control.Arrow ((***), second) import Control.Monad (join) main = $(defaultMainGenerator) snub = nub . sort prop_eqRefl x = T.fromList x == T.fromList x prop_eqList x y = (T.fromList x == T.fromList y) == (snub x == snub y) prop_eqRef x y = (T.fromList x == T.fromList y) == (R.fromList x == R.fromList y) prop_ordList x y = T.fromList x `compare` T.fromList y == snub x `compare` snub y prop_ordRef x y = T.fromList x `compare` T.fromList y == R.fromList x `compare` R.fromList y prop_readShow x = xs == read (show xs) where xs = T.fromList x prop_monoidId x = xs == xs `mappend` mempty && xs == mempty `mappend` xs where xs = T.fromList x prop_monoidAssoc x y z = xs `mappend` (ys `mappend` zs) == (xs `mappend` ys) `mappend` zs where [xs, ys, zs] = map T.fromList [x, y, z] prop_nullList x = T.null (T.fromList x) == null x prop_nullRef x = T.null (T.fromList x) == R.null (R.fromList x) prop_sizeList x = T.size (T.fromList x) == length (nub x) prop_sizeRef x = T.size (T.fromList x) == R.size (R.fromList x) prop_memberList e x = T.member e (T.fromList x) == elem e x prop_memberRef e x = T.member e (T.fromList x) == R.member e (R.fromList x) case_emptyList = T.toAscList T.empty @=? [] case_emptyRef = T.toAscList T.empty @=? R.toAscList R.empty prop_singletonList x = T.toAscList (T.singleton x) == [x] prop_singletonRef x = T.toAscList (T.singleton x) == R.toAscList (R.singleton x) prop_insertRef e x = T.toAscList (T.insert e (T.fromList x)) == R.toAscList (R.insert e (R.fromList x)) prop_deleteRef e x = T.toAscList (T.delete e (T.fromList x)) == R.toAscList (R.delete e (R.fromList x)) prop_unionRef x y = T.toAscList (T.union (T.fromList x) (T.fromList y)) == R.toAscList (R.union (R.fromList x) (R.fromList y)) prop_differenceRef x y = T.toAscList (T.difference (T.fromList x) (T.fromList y)) == R.toAscList (R.difference (R.fromList x) (R.fromList y)) prop_intersectionRef x y = T.toAscList (T.intersection (T.fromList x) (T.fromList y)) == R.toAscList (R.intersection (R.fromList x) (R.fromList y)) prop_filterRef (Blind p) x = T.toAscList (T.filter p (T.fromList x)) == R.toAscList (R.filter p (R.fromList x)) prop_partitionRef (Blind p) x = join (***) T.toAscList (T.partition p (T.fromList x)) == join (***) R.toAscList (R.partition p (R.fromList x)) prop_splitRef (Blind p) x = join (***) T.toAscList (T.split p (T.fromList x)) == join (***) R.toAscList (R.split p (R.fromList x)) prop_splitMemberRef (Blind p) x = h T.toAscList (T.splitMember p (T.fromList x)) == h R.toAscList (R.splitMember p (R.fromList x)) where h f (a, b, c) = (f a, b, f c) prop_findMinRef (NonEmpty x) = T.findMin (T.fromList x) == R.findMin (R.fromList x) prop_findMaxRef (NonEmpty x) = T.findMax (T.fromList x) == R.findMax (R.fromList x) prop_deleteMinRef (NonEmpty x) = T.toAscList (T.deleteMin (T.fromList x)) == R.toAscList (R.deleteMin (R.fromList x)) prop_deleteMaxRef (NonEmpty x) = T.toAscList (T.deleteMax (T.fromList x)) == R.toAscList (R.deleteMax (R.fromList x)) prop_deleteFindMinRef (NonEmpty x) = second T.toAscList (T.deleteFindMin (T.fromList x)) == second R.toAscList (R.deleteFindMin (R.fromList x)) prop_deleteFindMaxRef (NonEmpty x) = second T.toAscList (T.deleteFindMax (T.fromList x)) == second R.toAscList (R.deleteFindMax (R.fromList x)) prop_minViewRef x = fmap (second T.toAscList) (T.minView (T.fromList x)) == fmap (second R.toAscList) (R.minView (R.fromList x)) prop_maxViewRef x = fmap (second T.toAscList) (T.maxView (T.fromList x)) == fmap (second R.toAscList) (R.maxView (R.fromList x)) prop_mapRef (Blind f) x = T.toAscList (T.map f (T.fromList x)) == R.toAscList (R.map f (R.fromList x)) prop_translateDef n x = T.translate n xs == T.map (+n) xs where xs = T.fromList x prop_toAscListFromListRef x = T.toAscList (T.fromList x) == R.toAscList (R.fromList x)