Favorites.hs 2.2 KB

12345678910111213141516171819202122232425262728293031323334353637383940414243444546474849505152535455565758596061626364656667686970
  1. {-# LANGUAGE TemplateHaskell #-}
  2. module Internal.Utils.Favorites ( tests ) where
  3. import Agda.Utils.Favorites
  4. import Agda.Utils.Null
  5. import Agda.Utils.PartialOrd
  6. import Agda.Utils.Singleton (singleton)
  7. import Internal.Utils.PartialOrd ( ISet(ISet) )
  8. import Prelude hiding ( null )
  9. import Internal.Helpers
  10. ------------------------------------------------------------------------
  11. -- * Instances
  12. ------------------------------------------------------------------------
  13. instance (PartialOrd a, Arbitrary a) => Arbitrary (Favorites a) where
  14. arbitrary = fromList <$> arbitrary
  15. ------------------------------------------------------------------------
  16. -- * Properties
  17. ------------------------------------------------------------------------
  18. property_null_empty :: Bool
  19. property_null_empty = null (empty :: Favorites ())
  20. property_not_null_singleton :: forall a. a -> Bool
  21. property_not_null_singleton x = not $ null (singleton x :: Favorites a)
  22. -- Remember: less is better!
  23. prop_compareWithFavorites :: ISet -> Favorites ISet -> Bool
  24. prop_compareWithFavorites a@ISet{} as =
  25. case compareWithFavorites a as of
  26. Dominates dominated notDominated ->
  27. all (related a POLT) dominated &&
  28. all (related a POAny) notDominated
  29. IsDominated dominator ->
  30. related a POGE dominator
  31. prop_fromList_after_toList :: Favorites ISet -> Bool
  32. prop_fromList_after_toList as =
  33. fromList (toList as) == as
  34. -- | A second way to compute the 'union' is to use 'compareFavorites'.
  35. prop_union_union2 :: Favorites ISet -> Favorites ISet -> Bool
  36. prop_union_union2 as bs =
  37. union as bs == union2 as bs
  38. where union2 as bs = unionCompared $ compareFavorites as bs
  39. ------------------------------------------------------------------------
  40. -- * All tests
  41. ------------------------------------------------------------------------
  42. -- Template Haskell hack to make the following $allProperties work
  43. -- under ghc-7.8.
  44. return [] -- KEEP!
  45. -- | All tests as collected by 'allProperties'.
  46. --
  47. -- Using 'allProperties' is convenient and superior to the manual
  48. -- enumeration of tests, since the name of the property is added
  49. -- automatically.
  50. tests :: TestTree
  51. tests = testProperties "Internal.Utils.Favorites" $allProperties