{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
module Test.QuickCheck.HigherOrder.Internal.Testable.Class where
import Test.QuickCheck
import Test.QuickCheck.HigherOrder.Internal.Constructible
class Testable' prop where
property' :: prop -> Property
forAll_
:: forall a prop
. (Constructible a, Testable' prop)
=> (a -> prop) -> Property
forAll_ f =
forAllShrinkShow
(arbitrary @(Repr a))
(shrink @(Repr a))
(show @(Repr a))
(property' . f . fromRepr)
instance Testable' Property where
property' = id
instance Testable' Bool where
property' = property
instance Testable' a => Testable' (Gen a) where
property' = property . fmap property'
instance (Constructible a, Testable' b) => Testable' (a -> b) where
property' = forAll_