[Haskell-cafe] monoids induced by Applicative/Alternative/Monad/MonadPlus?

Petr Pudlák petr.mvd at gmail.com
Tue Aug 20 18:55:19 CEST 2013


Dear Haskellers,

are these monoids defined somewhere?

import Control.Applicativeimport Data.Monoid
newtype AppMonoid m a = AppMonoid (m a)instance (Monoid a, Applicative
m) => Monoid (AppMonoid m a) where
    mempty = AppMonoid $ pure mempty
    mappend (AppMonoid x) (AppMonoid y) = AppMonoid $ mappend <$> x
<*> y-- With the () monoid for `a` this becames the monoid of effects.
newtype AltMonoid m a = AltMonoid (m a)instance Alternative m =>
Monoid (AltMonoid m a) where
    mempty = AltMonoid empty
    mappend (AltMonoid x) (AltMonoid y) = AltMonoid $ x <|> y

(and similarly for Monad/MonadPlus, until they become subclasses of
Applicative?)

Best regards,
Petr
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20130820/4e6d00b3/attachment.htm>


More information about the Haskell-Cafe mailing list