[Haskell-cafe] Semigroup and Monoid instances for ReaderT

David Feuer david.feuer at gmail.com
Tue Mar 21 21:09:23 UTC 2017


Yes, this is valid, and we should probably do it.

mempty = pure mempty
mappend = liftA2 mappend

will make a valid Monoid for any Applicative instance, and

x <> y = (<>) <$> x <.> y

will make a valid Semigroup for any Apply instance. Proving this seems
a bit gross. It's probably best to go via a well-known alternative
formulation of Applicative:

class Functor f => Apply' f where
  pair :: f a -> f b -> f (a, b)
instance Apply' f => Applicative' f where
  pure' :: a -> f a

This formulation lets you reassociate by switching between  (a, (b,c))
and  ((a,b),c)  rather than shifting fmaps around.

On Tue, Mar 21, 2017 at 3:53 AM, Louis Pan <louis at pan.me> wrote:
> Hi all,
>
> In my Glazier GUI library, I had to use newtype wrappers to create Semigroup
> and Monoid instances for ReaderT.
>
> Is there a reason why ReaderT doesn't have an instance of Semigroup and
> Monoid?
>
> The reader ((->) a) is a Monoid and a Semigroup.
> https://hackage.haskell.org/package/base-4.9.1.0/docs/src/GHC.Base.html#line-268
> https://hackage.haskell.org/package/base-4.9.1.0/docs/src/Data.Semigroup.html#line-150
>
> Could the following be added to the transformers package? Or is it not
> lawful?
>
> instance (Applicative m, Semigroup a) => Semigroup (ReaderT r m a) where
>     f <> g = (<>) <$> f <*> g
>     {-# INLINABLE (<>) #-}
>
> instance (Applicative m, Monoid a) => Monoid (ReaderT r m a) where
>     mempty = pure mempty
>     {-# INLINABLE mempty #-}
>
>     f `mappend` g = mappend <$> f <*> g
>     {-# INLINABLE mappend #-}
>
> Does it make sense to extend the monoid instance to all the other
> transformers? Eg.
>
> instance (Monad m, Semigroup a) => Semigroup (StateT s m a) where
>     f <> g = (<>) <$> f <*> g
>     {-# INLINABLE (<>) #-}
>
> instance (Monad m, Monoid a) => Monoid (StateT s m a) where
>     mempty = pure mempty
>     {-# INLINABLE mempty #-}
>
>     f `mappend` g = mappend <$> f <*> g
>     {-# INLINABLE mappend #-}
>
> instance (Monad m, Monoid w, Semigroup a) => Semigroup (WriterT w m a) where
>     f <> g = (<>) <$> f <*> g
>     {-# INLINABLE (<>) #-}
>
> instance (Monad m, Monoid w, Monoid a) => Monoid (WriterT w m a) where
>     mempty = pure mempty
>     {-# INLINABLE mempty #-}
>
>     f `mappend` g = mappend <$> f <*> g
>     {-# INLINABLE mappend #-}
>
> and also for MaybeT, IdentityT, ExceptT, etc
>
>
> Regards,
>
> Louis
>
> _______________________________________________
> Haskell-Cafe mailing list
> To (un)subscribe, modify options or view archives go to:
> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
> Only members subscribed via the mailman list are allowed to post.


More information about the Haskell-Cafe mailing list