module Test.Hspec.Core.QuickCheck (
modifyArgs
, modifyMaxSuccess
, modifyMaxDiscardRatio
, modifyMaxSize
, modifyMaxShrinks
) where
import Prelude ()
import Test.Hspec.Core.Compat
import Test.QuickCheck
import Test.Hspec.Core.Spec
modifyMaxSuccess :: (Int -> Int) -> SpecWith a -> SpecWith a
modifyMaxSuccess :: forall a. (Int -> Int) -> SpecWith a -> SpecWith a
modifyMaxSuccess = forall a. (Args -> Args) -> SpecWith a -> SpecWith a
modifyArgs forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int -> Int) -> Args -> Args
modify
where
modify :: (Int -> Int) -> Args -> Args
modify :: (Int -> Int) -> Args -> Args
modify Int -> Int
f Args
args = Args
args {maxSuccess :: Int
maxSuccess = Int -> Int
f (Args -> Int
maxSuccess Args
args)}
modifyMaxDiscardRatio :: (Int -> Int) -> SpecWith a -> SpecWith a
modifyMaxDiscardRatio :: forall a. (Int -> Int) -> SpecWith a -> SpecWith a
modifyMaxDiscardRatio = forall a. (Args -> Args) -> SpecWith a -> SpecWith a
modifyArgs forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int -> Int) -> Args -> Args
modify
where
modify :: (Int -> Int) -> Args -> Args
modify :: (Int -> Int) -> Args -> Args
modify Int -> Int
f Args
args = Args
args {maxDiscardRatio :: Int
maxDiscardRatio = Int -> Int
f (Args -> Int
maxDiscardRatio Args
args)}
modifyMaxSize :: (Int -> Int) -> SpecWith a -> SpecWith a
modifyMaxSize :: forall a. (Int -> Int) -> SpecWith a -> SpecWith a
modifyMaxSize = forall a. (Args -> Args) -> SpecWith a -> SpecWith a
modifyArgs forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int -> Int) -> Args -> Args
modify
where
modify :: (Int -> Int) -> Args -> Args
modify :: (Int -> Int) -> Args -> Args
modify Int -> Int
f Args
args = Args
args {maxSize :: Int
maxSize = Int -> Int
f (Args -> Int
maxSize Args
args)}
modifyMaxShrinks :: (Int -> Int) -> SpecWith a -> SpecWith a
modifyMaxShrinks :: forall a. (Int -> Int) -> SpecWith a -> SpecWith a
modifyMaxShrinks = forall a. (Args -> Args) -> SpecWith a -> SpecWith a
modifyArgs forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int -> Int) -> Args -> Args
modify
where
modify :: (Int -> Int) -> Args -> Args
modify :: (Int -> Int) -> Args -> Args
modify Int -> Int
f Args
args = Args
args {maxShrinks :: Int
maxShrinks = Int -> Int
f (Args -> Int
maxShrinks Args
args)}
modifyArgs :: (Args -> Args) -> SpecWith a -> SpecWith a
modifyArgs :: forall a. (Args -> Args) -> SpecWith a -> SpecWith a
modifyArgs = forall a. (Params -> Params) -> SpecWith a -> SpecWith a
modifyParams forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Args -> Args) -> Params -> Params
modify
where
modify :: (Args -> Args) -> Params -> Params
modify :: (Args -> Args) -> Params -> Params
modify Args -> Args
f Params
p = Params
p {paramsQuickCheckArgs :: Args
paramsQuickCheckArgs = Args -> Args
f (Params -> Args
paramsQuickCheckArgs Params
p)}