{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses, GeneralizedNewtypeDeriving, FlexibleContexts, TypeOperators #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE Trustworthy #-}
module Data.Semigroup.Alternative
( Alternate(..)
) where
import Control.Applicative
import Data.Semigroup.Reducer (Reducer(..))
#if !(MIN_VERSION_base(4,11,0))
import Data.Semigroup (Semigroup(..))
#endif
newtype Alternate f a = Alternate { forall (f :: * -> *) a. Alternate f a -> f a
getAlternate :: f a }
deriving ((forall a b. (a -> b) -> Alternate f a -> Alternate f b)
-> (forall a b. a -> Alternate f b -> Alternate f a)
-> Functor (Alternate f)
forall a b. a -> Alternate f b -> Alternate f a
forall a b. (a -> b) -> Alternate f a -> Alternate f b
forall (f :: * -> *) a b.
Functor f =>
a -> Alternate f b -> Alternate f a
forall (f :: * -> *) a b.
Functor f =>
(a -> b) -> Alternate f a -> Alternate f b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
$cfmap :: forall (f :: * -> *) a b.
Functor f =>
(a -> b) -> Alternate f a -> Alternate f b
fmap :: forall a b. (a -> b) -> Alternate f a -> Alternate f b
$c<$ :: forall (f :: * -> *) a b.
Functor f =>
a -> Alternate f b -> Alternate f a
<$ :: forall a b. a -> Alternate f b -> Alternate f a
Functor,Functor (Alternate f)
Functor (Alternate f) =>
(forall a. a -> Alternate f a)
-> (forall a b.
Alternate f (a -> b) -> Alternate f a -> Alternate f b)
-> (forall a b c.
(a -> b -> c) -> Alternate f a -> Alternate f b -> Alternate f c)
-> (forall a b. Alternate f a -> Alternate f b -> Alternate f b)
-> (forall a b. Alternate f a -> Alternate f b -> Alternate f a)
-> Applicative (Alternate f)
forall a. a -> Alternate f a
forall a b. Alternate f a -> Alternate f b -> Alternate f a
forall a b. Alternate f a -> Alternate f b -> Alternate f b
forall a b. Alternate f (a -> b) -> Alternate f a -> Alternate f b
forall a b c.
(a -> b -> c) -> Alternate f a -> Alternate f b -> Alternate 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 (Alternate f)
forall (f :: * -> *) a. Applicative f => a -> Alternate f a
forall (f :: * -> *) a b.
Applicative f =>
Alternate f a -> Alternate f b -> Alternate f a
forall (f :: * -> *) a b.
Applicative f =>
Alternate f a -> Alternate f b -> Alternate f b
forall (f :: * -> *) a b.
Applicative f =>
Alternate f (a -> b) -> Alternate f a -> Alternate f b
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> Alternate f a -> Alternate f b -> Alternate f c
$cpure :: forall (f :: * -> *) a. Applicative f => a -> Alternate f a
pure :: forall a. a -> Alternate f a
$c<*> :: forall (f :: * -> *) a b.
Applicative f =>
Alternate f (a -> b) -> Alternate f a -> Alternate f b
<*> :: forall a b. Alternate f (a -> b) -> Alternate f a -> Alternate f b
$cliftA2 :: forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> Alternate f a -> Alternate f b -> Alternate f c
liftA2 :: forall a b c.
(a -> b -> c) -> Alternate f a -> Alternate f b -> Alternate f c
$c*> :: forall (f :: * -> *) a b.
Applicative f =>
Alternate f a -> Alternate f b -> Alternate f b
*> :: forall a b. Alternate f a -> Alternate f b -> Alternate f b
$c<* :: forall (f :: * -> *) a b.
Applicative f =>
Alternate f a -> Alternate f b -> Alternate f a
<* :: forall a b. Alternate f a -> Alternate f b -> Alternate f a
Applicative,Applicative (Alternate f)
Applicative (Alternate f) =>
(forall a. Alternate f a)
-> (forall a. Alternate f a -> Alternate f a -> Alternate f a)
-> (forall a. Alternate f a -> Alternate f [a])
-> (forall a. Alternate f a -> Alternate f [a])
-> Alternative (Alternate f)
forall a. Alternate f a
forall a. Alternate f a -> Alternate f [a]
forall a. Alternate f a -> Alternate f a -> Alternate f a
forall (f :: * -> *).
Applicative f =>
(forall a. f a)
-> (forall a. f a -> f a -> f a)
-> (forall a. f a -> f [a])
-> (forall a. f a -> f [a])
-> Alternative f
forall (f :: * -> *). Alternative f => Applicative (Alternate f)
forall (f :: * -> *) a. Alternative f => Alternate f a
forall (f :: * -> *) a.
Alternative f =>
Alternate f a -> Alternate f [a]
forall (f :: * -> *) a.
Alternative f =>
Alternate f a -> Alternate f a -> Alternate f a
$cempty :: forall (f :: * -> *) a. Alternative f => Alternate f a
empty :: forall a. Alternate f a
$c<|> :: forall (f :: * -> *) a.
Alternative f =>
Alternate f a -> Alternate f a -> Alternate f a
<|> :: forall a. Alternate f a -> Alternate f a -> Alternate f a
$csome :: forall (f :: * -> *) a.
Alternative f =>
Alternate f a -> Alternate f [a]
some :: forall a. Alternate f a -> Alternate f [a]
$cmany :: forall (f :: * -> *) a.
Alternative f =>
Alternate f a -> Alternate f [a]
many :: forall a. Alternate f a -> Alternate f [a]
Alternative)
instance Alternative f => Semigroup (Alternate f a) where
Alternate f a
a <> :: Alternate f a -> Alternate f a -> Alternate f a
<> Alternate f a
b = f a -> Alternate f a
forall (f :: * -> *) a. f a -> Alternate f a
Alternate (f a
a f a -> f a -> f a
forall a. f a -> f a -> f a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> f a
b)
instance Alternative f => Monoid (Alternate f a) where
mempty :: Alternate f a
mempty = Alternate f a
forall a. Alternate f a
forall (f :: * -> *) a. Alternative f => f a
empty
#if !(MIN_VERSION_base(4,11,0))
Alternate a `mappend` Alternate b = Alternate (a <|> b)
#endif
instance Alternative f => Reducer (f a) (Alternate f a) where
unit :: f a -> Alternate f a
unit = f a -> Alternate f a
forall (f :: * -> *) a. f a -> Alternate f a
Alternate