8

The following typechecks:

instance (Applicative f, Alternative f, Foldable f) => Monad f where 
  (>>=) = flip $ \f -> foldr (<|>) empty . fmap f
  -- Or equivalently
  a >>= b = getAlt . foldMap Alt . fmap b $ a

Is this actually a valid Monad instance? If yes, why is it not used? If no, does it break any laws or such? I have not proved that the laws hold, but I couldn't find a counterexample either.

duplode
  • 33,731
  • 7
  • 79
  • 150
user1747134
  • 2,374
  • 1
  • 19
  • 26
  • 2
    It's not because it does not *break* any laws, that it is *desired*. I think one usually do not want automatic Monad derivation, since one can decide to implement a monad another way. – Willem Van Onsem May 24 '17 at 11:21
  • For example if you have a type class that supports an associative array (dictionary), you could define it as some kind of state monad. But perhaps you want some kind of associative array not to work as state monad at all, but as an (emulated) processor. – Willem Van Onsem May 24 '17 at 12:04

2 Answers2

7

This should be a counterexample to the right identity monad law.

Below, we exploit the functor product Maybe :*: Maybe from GHC.Generics, but it could be inlined, if wished. This is also an applicative, alternative, foldable, and monad. I trust the libraries on these instances to be law-abiding.

We then compare the proposed instance Monad (the one in the question) to the standard library one. We find that the right identity law is not satisfied for the proposed instance, while it appears to hold (at least in my very limited tests) in the library instance.

{-# LANGUAGE FlexibleInstances, GeneralizedNewtypeDeriving, TypeOperators #-}
{-# OPTIONS -Wall #-}

module NotAMonad where

import Control.Applicative
import GHC.Generics ((:*:)(..))

-- A basic wrapper to avoid overlapping instances, and to be able to
-- define a custom monad instance.
newtype Wrap m a = Wrap { unWrap :: m a }
    deriving (Functor, Applicative, Alternative, Foldable, Show)

-- The proposed instance
instance (Applicative f, Alternative f, Foldable f) => Monad (Wrap f) where 
  (>>=) = flip $ \f -> foldr (<|>) empty . fmap f

-- This is Applicative, Alternative, and Foldable
type T = Maybe :*: Maybe

-- A basic test
test :: Wrap T Int
test = Wrap (Just 3 :*: Just 4) >>= return
-- result:
-- Wrap {unWrap = Just 3 :*: Just 3}

The 4 is now replaced by 3. I have not tried to explain why, though. I guess it is caused by Just 3 <|> Just 4 = Just 3.

Using the library monad instance, instead, everything looks fine:

> (Just 3 :*: Just 4) >>= return
Just 3 :*: Just 4
chi
  • 111,837
  • 3
  • 133
  • 218
6

Alternative is a bit of a hacky beast. It's essentially the class of monoid constructors: type constructors T such that for any contained type X, T X is a monoid. This doesn't really have a lot to do with functors...monads, and is considerably less mathematically deep. (So, only for mathematical elegance, it would be a bit bad to set Monad underneath Alternative.)

Let's write that instance in terms of Monoid for clarity (this won't actually compile):

instance (Foldable f, (∀ x . Monoid (f x))) => Monad f where
  (>>=) = flip $ \f -> foldr mappend empty . fmap f
        ≡ flip $ \f -> fold . fmap f
        ≡ flip foldMap

or indeed

  (=<<) = foldMap

so, this is definitely not something unknown.

To check the laws, we best look at the Kleisli formulation:

  (f <=< g) x = f =<< g x
              ≡ foldMap f $ g x

i.e.

  f <=< g = foldMap f . g

Then the monad laws are

  • Left identity

    f <=< pure ≡ foldMap f . pure =! f
    
  • Right identity

    pure <=< f ≡ foldMap pure . f =! f
    
  • Associativity

    (f <=< g) <=< h ≡ foldMap (foldMap f . g) . h
                    =! foldMap f . foldMap g . h
                    ≡ foldMap f . (foldMap g . h) ≡ f <=< (g <=< h)
    

So in brief, we need

  • foldMap f . pure =! f =! foldMap pure . ff
  • foldMap (foldMap f . g) =! foldMap f . foldMap gf,g

That certainly looks not unreasonable, but I don't see whence you could rigorously conclude it for arbitrary Foldable+Alternative instances.

Really, the big problem I see with this instance is that it's not nearly general enough. Most monads are neither Foldable nor Alternative. If there was a cover-all definition like the one you propose, it would require OverlappingInstances to define any instance of your own, and those are generally considered something you shouldn't use without good reason.

I do wonder however if there would be any problems with the following default definition for the bind method:

{-# LANGUAGE DefaultSignatures #-}
class Applicative f => Monad f where
  return :: a -> m a
  return = pure
  (>>=) :: m a -> (a -> m b) -> m b
  default (>>=) :: (Foldable m, Monoid m b)
          => m a -> (a -> m b) -> m b
  (>>=) = flip foldMap

That would at least allow defining e.g. the list instance simply as

instance Monad []

without needing to write out the methods at all since sure enough, foldMap ≡ concatMap ≡ (=<<).

leftaroundabout
  • 117,950
  • 5
  • 174
  • 319
  • I wonder if a foldable monoid is essentially a list, up to iso. I can't see problems in the default definition, but maybe it would only apply to `[]` and little else (?) – chi May 24 '17 at 13:17
  • 1
    @chi, that's not *too* far off, but it's not enough. Think about the definition of a free monoid. `foldMap` gets you one bit, but you also need `singleton`, with `foldMap f (singleton x) = f x`. And of course you need `foldMap f (x <> y) = foldMap f x <> foldMap f y`. Of course, at that point you should surely toss in `Traversable` because you can do so for fdree. – dfeuer May 24 '17 at 14:37
  • @chi `Last` and `First`. – Alexey Romanov May 26 '17 at 14:38