{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module Test.Tasty.Runners.Reducers where
import Control.Applicative
import Prelude
import qualified Data.Semigroup as Sem
#if !MIN_VERSION_base(4,11,0)
import Data.Monoid
#endif
newtype Traversal f = Traversal { forall (f :: * -> *). Traversal f -> f ()
getTraversal :: f () }
instance Applicative f => Sem.Semigroup (Traversal f) where
Traversal f ()
f1 <> :: Traversal f -> Traversal f -> Traversal f
<> Traversal f ()
f2 = f () -> Traversal f
forall (f :: * -> *). f () -> Traversal f
Traversal (f () -> Traversal f) -> f () -> Traversal f
forall a b. (a -> b) -> a -> b
$ f ()
f1 f () -> f () -> f ()
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> f ()
f2
instance Applicative f => Monoid (Traversal f) where
mempty :: Traversal f
mempty = f () -> Traversal f
forall (f :: * -> *). f () -> Traversal f
Traversal (f () -> Traversal f) -> f () -> Traversal f
forall a b. (a -> b) -> a -> b
$ () -> f ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
#if !MIN_VERSION_base(4,11,0)
mappend = (Sem.<>)
#endif
newtype Ap f a = Ap { forall (f :: * -> *) a. Ap f a -> f a
getApp :: f a }
deriving ((forall a b. (a -> b) -> Ap f a -> Ap f b)
-> (forall a b. a -> Ap f b -> Ap f a) -> Functor (Ap f)
forall a b. a -> Ap f b -> Ap f a
forall a b. (a -> b) -> Ap f a -> Ap f b
forall (f :: * -> *) a b. Functor f => a -> Ap f b -> Ap f a
forall (f :: * -> *) a b. Functor f => (a -> b) -> Ap f a -> Ap f b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: forall a b. a -> Ap f b -> Ap f a
$c<$ :: forall (f :: * -> *) a b. Functor f => a -> Ap f b -> Ap f a
fmap :: forall a b. (a -> b) -> Ap f a -> Ap f b
$cfmap :: forall (f :: * -> *) a b. Functor f => (a -> b) -> Ap f a -> Ap f b
Functor, Functor (Ap f)
Functor (Ap f)
-> (forall a. a -> Ap f a)
-> (forall a b. Ap f (a -> b) -> Ap f a -> Ap f b)
-> (forall a b c. (a -> b -> c) -> Ap f a -> Ap f b -> Ap f c)
-> (forall a b. Ap f a -> Ap f b -> Ap f b)
-> (forall a b. Ap f a -> Ap f b -> Ap f a)
-> Applicative (Ap f)
forall a. a -> Ap f a
forall a b. Ap f a -> Ap f b -> Ap f a
forall a b. Ap f a -> Ap f b -> Ap f b
forall a b. Ap f (a -> b) -> Ap f a -> Ap f b
forall a b c. (a -> b -> c) -> Ap f a -> Ap f b -> Ap f c
forall (f :: * -> *).
Functor f
-> (forall a. a -> f a)
-> (forall a b. f (a -> b) -> f a -> f b)
-> (forall a b c. (a -> b -> c) -> f a -> f b -> f c)
-> (forall a b. f a -> f b -> f b)
-> (forall a b. f a -> f b -> f a)
-> Applicative f
forall {f :: * -> *}. Applicative f => Functor (Ap f)
forall (f :: * -> *) a. Applicative f => a -> Ap f a
forall (f :: * -> *) a b.
Applicative f =>
Ap f a -> Ap f b -> Ap f a
forall (f :: * -> *) a b.
Applicative f =>
Ap f a -> Ap f b -> Ap f b
forall (f :: * -> *) a b.
Applicative f =>
Ap f (a -> b) -> Ap f a -> Ap f b
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> Ap f a -> Ap f b -> Ap f c
<* :: forall a b. Ap f a -> Ap f b -> Ap f a
$c<* :: forall (f :: * -> *) a b.
Applicative f =>
Ap f a -> Ap f b -> Ap f a
*> :: forall a b. Ap f a -> Ap f b -> Ap f b
$c*> :: forall (f :: * -> *) a b.
Applicative f =>
Ap f a -> Ap f b -> Ap f b
liftA2 :: forall a b c. (a -> b -> c) -> Ap f a -> Ap f b -> Ap f c
$cliftA2 :: forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> Ap f a -> Ap f b -> Ap f c
<*> :: forall a b. Ap f (a -> b) -> Ap f a -> Ap f b
$c<*> :: forall (f :: * -> *) a b.
Applicative f =>
Ap f (a -> b) -> Ap f a -> Ap f b
pure :: forall a. a -> Ap f a
$cpure :: forall (f :: * -> *) a. Applicative f => a -> Ap f a
Applicative, Applicative (Ap f)
Applicative (Ap f)
-> (forall a b. Ap f a -> (a -> Ap f b) -> Ap f b)
-> (forall a b. Ap f a -> Ap f b -> Ap f b)
-> (forall a. a -> Ap f a)
-> Monad (Ap f)
forall a. a -> Ap f a
forall a b. Ap f a -> Ap f b -> Ap f b
forall a b. Ap f a -> (a -> Ap f b) -> Ap f b
forall {f :: * -> *}. Monad f => Applicative (Ap f)
forall (f :: * -> *) a. Monad f => a -> Ap f a
forall (f :: * -> *) a b. Monad f => Ap f a -> Ap f b -> Ap f b
forall (f :: * -> *) a b.
Monad f =>
Ap f a -> (a -> Ap f b) -> Ap f b
forall (m :: * -> *).
Applicative m
-> (forall a b. m a -> (a -> m b) -> m b)
-> (forall a b. m a -> m b -> m b)
-> (forall a. a -> m a)
-> Monad m
return :: forall a. a -> Ap f a
$creturn :: forall (f :: * -> *) a. Monad f => a -> Ap f a
>> :: forall a b. Ap f a -> Ap f b -> Ap f b
$c>> :: forall (f :: * -> *) a b. Monad f => Ap f a -> Ap f b -> Ap f b
>>= :: forall a b. Ap f a -> (a -> Ap f b) -> Ap f b
$c>>= :: forall (f :: * -> *) a b.
Monad f =>
Ap f a -> (a -> Ap f b) -> Ap f b
Monad)
instance (Applicative f, Monoid a) => Sem.Semigroup (Ap f a) where
<> :: Ap f a -> Ap f a -> Ap f a
(<>) = (a -> a -> a) -> Ap f a -> Ap f a -> Ap f a
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 a -> a -> a
forall a. Monoid a => a -> a -> a
mappend
instance (Applicative f, Monoid a) => Monoid (Ap f a) where
mempty :: Ap f a
mempty = a -> Ap f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure a
forall a. Monoid a => a
mempty
#if !MIN_VERSION_base(4,11,0)
mappend = (Sem.<>)
#endif