{-# LANGUAGE RankNTypes #-}
module Test.Lawful.QuickCheck
( testLaws,
toProperty,
)
where
import Test.Lawful.Types (Law, Laws)
import Test.QuickCheck (Property, discard)
import Test.QuickCheck.Monadic (PropertyM, assert, monadicIO)
import Test.Tasty (TestName, TestTree, testGroup)
import Test.Tasty.QuickCheck (testProperty)
toProperty :: (forall a. m a -> PropertyM IO a) -> Law m -> Property
toProperty :: forall (m :: * -> *).
(forall a. m a -> PropertyM IO a) -> Law m -> Property
toProperty forall a. m a -> PropertyM IO a
run Law m
law = PropertyM IO () -> Property
forall a. Testable a => PropertyM IO a -> Property
monadicIO (PropertyM IO () -> Property) -> PropertyM IO () -> Property
forall a b. (a -> b) -> a -> b
$ PropertyM IO ()
-> (Bool -> PropertyM IO ()) -> Maybe Bool -> PropertyM IO ()
forall b a. b -> (a -> b) -> Maybe a -> b
maybe PropertyM IO ()
forall a. a
discard Bool -> PropertyM IO ()
forall (m :: * -> *). Monad m => Bool -> PropertyM m ()
assert (Maybe Bool -> PropertyM IO ())
-> PropertyM IO (Maybe Bool) -> PropertyM IO ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< Law m -> PropertyM IO (Maybe Bool)
forall a. m a -> PropertyM IO a
run Law m
law
testLaws :: TestName -> (forall a. m a -> PropertyM IO a) -> Laws m -> TestTree
testLaws :: forall (m :: * -> *).
TestName -> (forall a. m a -> PropertyM IO a) -> Laws m -> TestTree
testLaws TestName
name forall a. m a -> PropertyM IO a
run Laws m
laws = TestName -> [TestTree] -> TestTree
testGroup TestName
name [TestName -> Property -> TestTree
forall a. Testable a => TestName -> a -> TestTree
testProperty TestName
n ((forall a. m a -> PropertyM IO a) -> Law m -> Property
forall (m :: * -> *).
(forall a. m a -> PropertyM IO a) -> Law m -> Property
toProperty m a -> PropertyM IO a
forall a. m a -> PropertyM IO a
run Law m
l) | (TestName
n, Law m
l) <- Laws m
laws]