Monoid instance for IO

Edward Kmett ekmett at gmail.com
Fri Nov 14 16:59:21 UTC 2014


+1 from me.

On Thu, Nov 13, 2014 at 10:13 AM, Gabriel Gonzalez <gabriel439 at gmail.com>
wrote:

> I would like to add the following `Monoid` instance for `IO` to
> `Data.Monoid`:
>
> ```
> instance Monoid a => Monoid (IO a) where
>    mempty  = pure mempty
>    mappend = liftA2 mappend
> ```
>
> I describe the benefit of this particular instance in this blog post:
>
> http://www.haskellforall.com/2014/07/equational-reasoning-at-scale.html
>
> ... and Conal Elliot describes the general trick of recursively lifting
> `Monoid` instances in his type class morphisms paper:
>
> http://conal.net/papers/type-class-morphisms/type-class-morphisms-long.pdf
>
> The primary benefit of the `Monoid` instance is that it chains well with
> other `Monoid` instances in `base` to create derived `Monoid` instances.
> The following types are examples of useful derived `Monoid` instances:
>
> ```
> IO ()  -- Because `()` is a `Monoid`
>
> a -> IO ()  -- Because `a -> r` is a `Monoid` if `r` is a `Monoid`
>
> IO (a -> IO ())  -- This comment explains the utility of this instance:
> http://www.reddit.com/r/haskell/comments/22bn1m/monads_lifting_join_and_
> sideeffecting_actions/cglhgu0
> ```
>
> Here are other alternatives that I considered:
>
> **Alternative A)** Define a newtype for the `Monoid` instance, either
> specialized to `IO`:
>
> ```
> newtype IOMonoid a = IOMonoid { getIOMonoid :: IO a } deriving (Functor,
> Applicative, Monad)
>
> instance Monoid a => Monoid (IOMonoid a) where
>     mempty = pure mempty
>     mappend = liftA2 mappend
> ```
>
> ... or generalized to all applicatives:
>
> ```
> newtype LiftMonoid f a = LiftMonoid ( getLiftMonoid :: f a }
>
> instance (Applicative f, Monoid a) => Monoid (LiftMonoid f a) where ...
> ```
>
> I prefer not to use a newtype because the principle benefit of a `Monoid`
> instance for `IO` is for the derived instances.  Using the example `IO (a
> -> IO ())` type, suppose that I had two values of that type which I wanted
> to mappend:
>
> ```
> m :: IO (a -> IO ())
> n :: IO (a -> IO ())
> ```
>
> Using newtypes (either one), I'd have to write:
>
> ```
> getNewtype (Newtype (fmap (fmap Newtype) m) <> Newtype (fmap (fmap
> Newtype) n))
> ```
>
> ... instead of just:
>
> ```
> m <> n
> ```
>
> **Alternative B)** Provide a different `Monoid` instance for `IO`, such as
> one that uses concurrency
>
> There are two issues with this approach:
>
> 1.  There is not a well-defined semantics for non-`STM` concurrency that
> we could use to prove the `Monoid` laws
> 2.  Even if there were a well-defined semantics, it would be better suited
> as an `Alternative` instance instead of a `Monoid` instance
>
> To clarify the latter point, Peaker convinced me [[
> http://www.reddit.com/r/haskell/comments/2guo44/what_
> is_wrong_with_the_monoid_instance_for_maybe/ckmrcux | here ]] that for
> certain `Applicative`s it's worth distinguishing the behavior of the
> `Alternative` instance from the behavior of the `Monoid` instance.  The
> `Monoid` instance can recursively delegate to the `Monoid` instance of the
> `Applicative`'s type parameter, whereas the `Alternative` instance cannot.
>
> I also created a task on phabricator here since I'm used to the Github
> style of discussing issues on the repository issue tracker:
>
> https://phabricator.haskell.org/T55?workflow=create
> _______________________________________________
> Libraries mailing list
> Libraries at haskell.org
> http://www.haskell.org/mailman/listinfo/libraries
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/libraries/attachments/20141114/a5f0830b/attachment.html>


More information about the Libraries mailing list