module Data.GenValidity.Hspec
( module Data.GenValidity
, proxy
, genspec
, arbitrarySpec
, validitySpec
, producesValidsOnGen
, alwaysProducesValid
, producesValidsOnValids
, producesValidsOnGens2
, alwaysProducesValid2
, producesValidsOnValids2
, CanFail(..)
, succeedsOnGen
, succeedsOnValidInput
, failsOnGen
, failsOnInvalidInput
, validIfSucceedsOnGen
, validIfSucceeds
) where
import Data.GenValidity
import Test.Hspec
import Test.QuickCheck
import Data.Data
proxy :: a
proxy = undefined
genspec
:: (Show a, Eq a, Data a, GenValidity a, Arbitrary a)
=> a
-> Spec
genspec proxy = do
let name = show $ typeOf proxy
describe ("GenSpec for " ++ name) $ do
arbitrarySpec proxy
validitySpec proxy
arbitrarySpec
:: (Typeable a, Show a, Eq a, Data a, GenValidity a, Arbitrary a)
=> a
-> Spec
arbitrarySpec proxy = do
let name = show $ typeOf proxy
describe ("Arbitrary " ++ name) $ do
it ("is instantiated such that 'arbitrary' only generates valid \'"
++ name
++ "\'s") $ do
forAll arbitrary $ \a ->
(a `asTypeOf` proxy) `shouldSatisfy` isValid
it ("is instantiated such that 'shrink' only produces valid \'"
++ name
++ "\'s") $ do
forAll arbitrary $ \a ->
shrink (a `asTypeOf` proxy) `shouldSatisfy` all isValid
validitySpec
:: (Typeable a, Show a, Eq a, Data a, GenValidity a, Arbitrary a)
=> a
-> Spec
validitySpec proxy = do
let name = show $ typeOf proxy
describe "genValid" $ do
it ("only generates valid \'" ++ name ++ "\'s") $ do
forAll genValid $ \a ->
(a `asTypeOf` proxy) `shouldSatisfy` isValid
describe "genInvalid" $ do
it ("only generates invalid \'" ++ name ++ "\'s") $ do
forAll genInvalid $ \a ->
(a `asTypeOf` proxy) `shouldNotSatisfy` isValid
class CanFail f where
hasFailed :: f a -> Bool
resultIfSucceeded :: f a -> Maybe a
instance CanFail Maybe where
hasFailed Nothing = True
hasFailed _ = False
resultIfSucceeded Nothing = Nothing
resultIfSucceeded (Just r) = Just r
instance CanFail (Either e) where
hasFailed (Left _) = True
hasFailed _ = False
resultIfSucceeded (Left _) = Nothing
resultIfSucceeded (Right r) = Just r
producesValidsOnGen
:: (Show a, Show b, Validity b)
=> (a -> b)
-> Gen a
-> Property
producesValidsOnGen func gen
= forAll gen $ \a -> func a `shouldSatisfy` isValid
alwaysProducesValid
:: (Show a, Show b, GenValidity a, Validity b)
=> (a -> b)
-> Property
alwaysProducesValid = (`producesValidsOnGen` genUnchecked)
producesValidsOnValids
:: (Show a, Show b, GenValidity a, Validity b)
=> (a -> b)
-> Property
producesValidsOnValids = (`producesValidsOnGen` genValid)
producesValidsOnGens2
:: (Show a, Show b, Show c, Validity c)
=> (a -> b -> c)
-> Gen a -> Gen b
-> Property
producesValidsOnGens2 func gen1 gen2
= forAll gen1 $ \a ->
forAll gen2 $ \b ->
func a b `shouldSatisfy` isValid
alwaysProducesValid2
:: (Show a, Show b, Show c, GenValidity a, GenValidity b, Validity c)
=> (a -> b -> c)
-> Property
alwaysProducesValid2 func
= producesValidsOnGens2 func genUnchecked genUnchecked
producesValidsOnValids2
:: (Show a, Show b, Show c, GenValidity a, GenValidity b, Validity c)
=> (a -> b -> c)
-> Property
producesValidsOnValids2 func
= producesValidsOnGens2 func genValid genValid
succeedsOnGen
:: (Show a, Show b, Show (f b), CanFail f)
=> (a -> f b)
-> Gen a
-> Property
succeedsOnGen func gen
= forAll gen $ \a -> func a `shouldNotSatisfy` hasFailed
succeedsOnValidInput
:: (Show a, Show b, Show (f b), GenValidity a, CanFail f)
=> (a -> f b)
-> Property
succeedsOnValidInput = (`succeedsOnGen` genValid)
failsOnGen
:: (Show a, Show b, Show (f b), CanFail f)
=> (a -> f b)
-> Gen a
-> Property
failsOnGen func gen
= forAll gen $ \a -> func a `shouldSatisfy` hasFailed
failsOnInvalidInput
:: (Show a, Show b, Show (f b), GenValidity a, CanFail f)
=> (a -> f b)
-> Property
failsOnInvalidInput = (`failsOnGen` genInvalid)
validIfSucceedsOnGen
:: (Show a, Show b, Show (f b), Validity b, CanFail f)
=> (a -> f b)
-> Gen a
-> Property
validIfSucceedsOnGen func gen
= forAll gen $ \a ->
case resultIfSucceeded (func a) of
Nothing -> return ()
Just res -> res `shouldSatisfy` isValid
validIfSucceeds
:: (Show a, Show b, Show (f b), GenValidity a, Validity b, CanFail f)
=> (a -> f b)
-> Property
validIfSucceeds = (`validIfSucceedsOnGen` genUnchecked)