module Control.Applicative.Monoid (
MonoidApplicative(..), MonoidAlternative(..)
)
where
import Control.Applicative (Applicative (pure, (<*>)), Alternative ((<|>)), (<$>))
import Data.Monoid (Monoid, mempty)
import Data.Semigroup (Semigroup, (<>))
class Applicative f => MonoidApplicative f where
infixl 4 +<*>
(+<*>) :: f (a -> a) -> f a -> f a
(+<*>) = f (a -> a) -> f a -> f a
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
(<*>)
infixl 5 ><
(><) :: Semigroup a => f a -> f a -> f a
f a
a >< f a
b = a -> a -> a
forall a. Semigroup a => a -> a -> a
(<>) (a -> a -> a) -> f a -> f (a -> a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> f a
a f (a -> a) -> f a -> f a
forall (f :: * -> *) a.
MonoidApplicative f =>
f (a -> a) -> f a -> f a
+<*> f a
b
class (Alternative f, MonoidApplicative f) => MonoidAlternative f where
moptional :: (Semigroup a, Monoid a) => f a -> f a
moptional f a
x = f a
x f a -> f a -> f a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure a
forall a. Monoid a => a
mempty
concatMany :: (Semigroup a, Monoid a) => f a -> f a
concatMany f a
x = f a
many'
where many' :: f a
many' = f a
some' f a -> f a -> f a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure a
forall a. Monoid a => a
mempty
some' :: f a
some' = f a
x f a -> f a -> f a
forall (f :: * -> *) a.
(MonoidApplicative f, Semigroup a) =>
f a -> f a -> f a
>< f a
many'
concatSome :: (Semigroup a, Monoid a) => f a -> f a
concatSome f a
x = f a
some'
where many' :: f a
many' = f a
some' f a -> f a -> f a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure a
forall a. Monoid a => a
mempty
some' :: f a
some' = f a
x f a -> f a -> f a
forall (f :: * -> *) a.
(MonoidApplicative f, Semigroup a) =>
f a -> f a -> f a
>< f a
many'