SmallSet.hs 2.8 KB

1234567891011121314151617181920212223242526272829303132333435363738394041424344454647484950515253545556575859606162636465666768697071727374757677787980
  1. {-# LANGUAGE TemplateHaskell #-}
  2. {-# LANGUAGE CPP #-}
  3. #if __GLASGOW_HASKELL__ > 800
  4. {-# OPTIONS_GHC -Wno-error=missing-signatures #-}
  5. #endif
  6. {-# OPTIONS_GHC -fno-warn-missing-signatures #-}
  7. module Internal.Utils.SmallSet ( tests ) where
  8. import Data.Array (Ix)
  9. import Data.Set (Set)
  10. import qualified Data.Set as Set
  11. import Agda.Utils.SmallSet (SmallSet)
  12. import qualified Agda.Utils.SmallSet as SmallSet
  13. import Internal.Helpers
  14. -- Small finite set of elements
  15. data A = A0 | A1 | A2 | A3 | A4 | A5
  16. deriving (Eq, Ord, Enum, Bounded, Ix, Show, Read)
  17. instance Arbitrary A where
  18. -- Ideally,
  19. -- arbitrary = chooseAny
  20. -- by then we have to implement the Random instance for A from System.Random,
  21. -- adding package random as direct dependency.
  22. arbitrary = toEnum <$> choose (fromEnum (minBound :: A), fromEnum (maxBound :: A))
  23. -- Logical relations between SmallSet and Set
  24. test1 :: Eq a => (SmallSet A -> a) -> (Set A -> a) -> [A] -> Bool
  25. test1 f g as = (==) (f $ SmallSet.fromList as) (g $ Set.fromList as)
  26. test2 :: Eq a => (SmallSet A -> SmallSet A -> a) -> (Set A -> Set A -> a) -> [A] -> [A] -> Bool
  27. test2 f g as bs = test1 (f $ SmallSet.fromList as) (g $ Set.fromList as) bs
  28. rel0 :: SmallSet A -> Set A -> Bool
  29. rel0 s t = SmallSet.toList s == Set.toList t
  30. rel1 :: (SmallSet A -> SmallSet A) -> (Set A -> Set A) -> [A] -> Bool
  31. rel1 f g as = rel0 (f $ SmallSet.fromList as) (g $ Set.fromList as)
  32. rel2 :: (SmallSet A -> SmallSet A -> SmallSet A) -> (Set A -> Set A -> Set A) -> [A] -> [A] -> Bool
  33. rel2 f g as bs = rel1 (f $ SmallSet.fromList as) (g $ Set.fromList as) bs
  34. -- Test SmallSet against Set
  35. prop_null = test1 (SmallSet.null) (Set.null)
  36. prop_member a = test1 (SmallSet.member a) (Set.member a)
  37. prop_notMember a = test1 (SmallSet.notMember a) (Set.notMember a)
  38. prop_isSubsetOf = test2 (SmallSet.isSubsetOf) (Set.isSubsetOf)
  39. prop_empty = rel0 (SmallSet.empty) (Set.empty)
  40. prop_singleton a = rel0 (SmallSet.singleton a) (Set.singleton a)
  41. prop_insert a = rel1 (SmallSet.insert a) (Set.insert a)
  42. prop_delete a = rel1 (SmallSet.delete a) (Set.delete a)
  43. prop_union = rel2 (SmallSet.union) (Set.union)
  44. prop_difference = rel2 (SmallSet.difference) (Set.difference)
  45. prop_intersection= rel2 (SmallSet.intersection)(Set.intersection)
  46. ---------------------------------------------------------------------------
  47. -- * All tests
  48. ---------------------------------------------------------------------------
  49. -- Template Haskell hack to make the following $allProperties work.
  50. return [] -- KEEP!
  51. -- | All tests as collected by 'allProperties'.
  52. --
  53. -- Using 'allProperties' is convenient and superior to the manual
  54. -- enumeration of tests, since the name of the property is added
  55. -- automatically.
  56. tests :: TestTree
  57. tests = testProperties "Internal.Utils.SmallSet" $allProperties