import Test.Helper import Prelude () import Prelude.Plus hiding (assert) import qualified Data.Map as Map import qualified Data.Set as Set import qualified Data.Sequence as Seq import qualified Data.IntMap as IntMap import Data.List (nub) main = defaultMain [ testGroup "Tuple function properties" tuple_props , testGroup "Generic functions tests" generic_funcs ] tuple_props = [ testProperty "swap/id" (\(t::(Int,Int)) -> swap (swap t) == t) , testProperty "dup/id" (\(t::Int) -> uncurry (==) . dup $ t) ] generic_funcs = [ testGroup "null works for any Foldable data e.g." [ testCase "lists" $ assert (null null_list) , testCase "seqs" $ assert (null $ Seq.fromList null_list) , testCase "sets" $ assert (null $ Set.fromList null_list) , testCase "maps" $ assert (null $ Map.fromList null_assoclist) , testCase "intmaps" $ assert (null $ IntMap.fromList null_assoclist) ] , testGroup "size works for any Foldable data e.g." [ testProperty "lists" $ prop_size id , testProperty "seqs" $ prop_size Seq.fromList , testProperty "sets" $ prop_size Set.fromList , testProperty "maps" $ prop_size Map.fromList , testProperty "intmaps" $ prop_size IntMap.fromList ] ] null_list :: [Int] null_list = [] null_assoclist :: [(Int,Int)] null_assoclist = zip null_list null_list prop_size :: (Foldable t) => ([(Int,Int)] -> t a) -> [Int] -> Bool prop_size factory ns = size container == length ns' where ns' = nub ns container = factory (uncurry zip $ dup ns')