module Test.Framework.Options where
import Test.Framework.Seed
import Test.Framework.Utilities
import Data.Monoid ( Last(Last, getLast) )
import Data.Semigroup as Sem ( Semigroup((<>)) )
type TestOptions = TestOptions' Maybe
type CompleteTestOptions = TestOptions' K
data TestOptions' f = TestOptions {
forall (f :: * -> *). TestOptions' f -> f Seed
topt_seed :: f Seed,
forall (f :: * -> *). TestOptions' f -> f Int
topt_maximum_generated_tests :: f Int,
forall (f :: * -> *). TestOptions' f -> f Int
topt_maximum_unsuitable_generated_tests :: f Int,
forall (f :: * -> *). TestOptions' f -> f Int
topt_maximum_test_size :: f Int,
forall (f :: * -> *). TestOptions' f -> f Int
topt_maximum_test_depth :: f Int,
forall (f :: * -> *). TestOptions' f -> f (Maybe Int)
topt_timeout :: f (Maybe Int)
}
instance Sem.Semigroup (TestOptions' Maybe) where
TestOptions' Maybe
to1 <> :: TestOptions' Maybe -> TestOptions' Maybe -> TestOptions' Maybe
<> TestOptions' Maybe
to2 = TestOptions {
topt_seed :: Maybe Seed
topt_seed = Last Seed -> Maybe Seed
forall a. Last a -> Maybe a
getLast ((TestOptions' Maybe -> Last Seed)
-> TestOptions' Maybe -> TestOptions' Maybe -> Last Seed
forall b a. Monoid b => (a -> b) -> a -> a -> b
mappendBy (Maybe Seed -> Last Seed
forall a. Maybe a -> Last a
Last (Maybe Seed -> Last Seed)
-> (TestOptions' Maybe -> Maybe Seed)
-> TestOptions' Maybe
-> Last Seed
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TestOptions' Maybe -> Maybe Seed
forall (f :: * -> *). TestOptions' f -> f Seed
topt_seed) TestOptions' Maybe
to1 TestOptions' Maybe
to2),
topt_maximum_generated_tests :: Maybe Int
topt_maximum_generated_tests = Last Int -> Maybe Int
forall a. Last a -> Maybe a
getLast ((TestOptions' Maybe -> Last Int)
-> TestOptions' Maybe -> TestOptions' Maybe -> Last Int
forall b a. Monoid b => (a -> b) -> a -> a -> b
mappendBy (Maybe Int -> Last Int
forall a. Maybe a -> Last a
Last (Maybe Int -> Last Int)
-> (TestOptions' Maybe -> Maybe Int)
-> TestOptions' Maybe
-> Last Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TestOptions' Maybe -> Maybe Int
forall (f :: * -> *). TestOptions' f -> f Int
topt_maximum_generated_tests) TestOptions' Maybe
to1 TestOptions' Maybe
to2),
topt_maximum_unsuitable_generated_tests :: Maybe Int
topt_maximum_unsuitable_generated_tests = Last Int -> Maybe Int
forall a. Last a -> Maybe a
getLast ((TestOptions' Maybe -> Last Int)
-> TestOptions' Maybe -> TestOptions' Maybe -> Last Int
forall b a. Monoid b => (a -> b) -> a -> a -> b
mappendBy (Maybe Int -> Last Int
forall a. Maybe a -> Last a
Last (Maybe Int -> Last Int)
-> (TestOptions' Maybe -> Maybe Int)
-> TestOptions' Maybe
-> Last Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TestOptions' Maybe -> Maybe Int
forall (f :: * -> *). TestOptions' f -> f Int
topt_maximum_unsuitable_generated_tests) TestOptions' Maybe
to1 TestOptions' Maybe
to2),
topt_maximum_test_size :: Maybe Int
topt_maximum_test_size = Last Int -> Maybe Int
forall a. Last a -> Maybe a
getLast ((TestOptions' Maybe -> Last Int)
-> TestOptions' Maybe -> TestOptions' Maybe -> Last Int
forall b a. Monoid b => (a -> b) -> a -> a -> b
mappendBy (Maybe Int -> Last Int
forall a. Maybe a -> Last a
Last (Maybe Int -> Last Int)
-> (TestOptions' Maybe -> Maybe Int)
-> TestOptions' Maybe
-> Last Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TestOptions' Maybe -> Maybe Int
forall (f :: * -> *). TestOptions' f -> f Int
topt_maximum_test_size) TestOptions' Maybe
to1 TestOptions' Maybe
to2),
topt_maximum_test_depth :: Maybe Int
topt_maximum_test_depth = Last Int -> Maybe Int
forall a. Last a -> Maybe a
getLast ((TestOptions' Maybe -> Last Int)
-> TestOptions' Maybe -> TestOptions' Maybe -> Last Int
forall b a. Monoid b => (a -> b) -> a -> a -> b
mappendBy (Maybe Int -> Last Int
forall a. Maybe a -> Last a
Last (Maybe Int -> Last Int)
-> (TestOptions' Maybe -> Maybe Int)
-> TestOptions' Maybe
-> Last Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TestOptions' Maybe -> Maybe Int
forall (f :: * -> *). TestOptions' f -> f Int
topt_maximum_test_depth) TestOptions' Maybe
to1 TestOptions' Maybe
to2),
topt_timeout :: Maybe (Maybe Int)
topt_timeout = Last (Maybe Int) -> Maybe (Maybe Int)
forall a. Last a -> Maybe a
getLast ((TestOptions' Maybe -> Last (Maybe Int))
-> TestOptions' Maybe -> TestOptions' Maybe -> Last (Maybe Int)
forall b a. Monoid b => (a -> b) -> a -> a -> b
mappendBy (Maybe (Maybe Int) -> Last (Maybe Int)
forall a. Maybe a -> Last a
Last (Maybe (Maybe Int) -> Last (Maybe Int))
-> (TestOptions' Maybe -> Maybe (Maybe Int))
-> TestOptions' Maybe
-> Last (Maybe Int)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TestOptions' Maybe -> Maybe (Maybe Int)
forall (f :: * -> *). TestOptions' f -> f (Maybe Int)
topt_timeout) TestOptions' Maybe
to1 TestOptions' Maybe
to2)
}
instance Monoid (TestOptions' Maybe) where
mempty :: TestOptions' Maybe
mempty = TestOptions {
topt_seed :: Maybe Seed
topt_seed = Maybe Seed
forall a. Maybe a
Nothing,
topt_maximum_generated_tests :: Maybe Int
topt_maximum_generated_tests = Maybe Int
forall a. Maybe a
Nothing,
topt_maximum_unsuitable_generated_tests :: Maybe Int
topt_maximum_unsuitable_generated_tests = Maybe Int
forall a. Maybe a
Nothing,
topt_maximum_test_size :: Maybe Int
topt_maximum_test_size = Maybe Int
forall a. Maybe a
Nothing,
topt_maximum_test_depth :: Maybe Int
topt_maximum_test_depth = Maybe Int
forall a. Maybe a
Nothing,
topt_timeout :: Maybe (Maybe Int)
topt_timeout = Maybe (Maybe Int)
forall a. Maybe a
Nothing
}
mappend :: TestOptions' Maybe -> TestOptions' Maybe -> TestOptions' Maybe
mappend = TestOptions' Maybe -> TestOptions' Maybe -> TestOptions' Maybe
forall a. Semigroup a => a -> a -> a
(Sem.<>)