8

By multiple values I mean something like so:

data Foo a = Bar a | Baz a a

I can't think of a clear way to define >>= for Baz:

instance Monad Foo where
    Bar x   >>= f = f x -- Great, that works perfectly!
    Baz x y >>= f = ??? -- What the heck do I even put here?
Cœur
  • 37,241
  • 25
  • 195
  • 267
ptkato
  • 668
  • 1
  • 7
  • 14
  • Have you tried `f x`? – Lazersmoke Apr 28 '17 at 16:03
  • @Lazersmoke, yes, but the problem is, what do I do with the `y`? Discard it? – ptkato Apr 28 '17 at 16:05
  • 2
    It depends completely what you want to do. I think the only two sensible and general possibilities are discarding x and discarding y. Why are you making a Monad instance? What is your use case? That should inform your implementation. – Lazersmoke Apr 28 '17 at 16:09
  • That's clarifying. Is there any reason for something among the lines of `m a -> (a -> a -> m b) -> m b` not exist? – ptkato Apr 28 '17 at 16:19
  • 1
    Only that no one has had a good use case for it. If that type signature truly matches your use case, then you should use that instead of Monad. Also, `a -> a -> m b` is isomorphic to `(a,a) -> m b` fwiw. – Lazersmoke Apr 28 '17 at 16:28
  • 2
    @Lazersmoke I suspect either discarding `x` or discarding `y` will lead to trouble with the `m >>= return = m` law. See my answer for a proposed instance which discards neither. – Daniel Wagner Apr 28 '17 at 16:41
  • Yeah that is correct, my bad – Lazersmoke Apr 29 '17 at 05:05

1 Answers1

14

Perhaps:

frst (Bar a) = a
frst (Baz a a') = a

scnd (Bar a) = a
scnd (Baz a a') = a'

instance Monad Foo where
    return = Bar
    Bar x >>= f = f x
    Baz x y >>= f = Baz (frst (f x)) (scnd (f y))

This definition is inspired by the definition of (>>=) for (Bool ->). Ask me if it's not clear how.

Let's check the laws. The "return is unit" laws are pretty straightforward:

  return x >>= f
= Bar x >>= f
= f x

  m >>= return
= case m of
      Bar x -> return x
      Baz x y -> Baz (frst (return x)) (scnd (return y))
= case m of
      Bar x -> Bar x
      Baz x y -> Baz x y
= m

I believe I've convinced myself of the "(>>=) is associative" law, too, but I'm sure this proof is completely unreadable to anybody else... I encourage you to try proving it yourself, and refer to my calculations as a cheat-sheet if you get stuck.

  m >>= (\v -> f v >>= g)
= case m of
      Bar x -> (\v -> f v >>= g) x
      Baz x y -> Baz (frst ((\v -> f v >>= g) x))
                     (scnd ((\v -> f v >>= g) y))
= case m of
      Bar x -> f x >>= g
      Baz x y -> Baz (frst (f x >>= g)) (scnd (f y >>= g))
= case m of
      Bar x -> case f x of
          Bar y -> g y
          Baz a b -> Baz (frst (g a)) (scnd (g b))
      Baz x y -> Baz (frst l) (scnd r) where
          l = case f x of
                  Bar a -> g a
                  Baz a b -> Baz (frst (g a)) (scnd (g b))
          r = case f y of
                  Bar a -> g a
                  Baz a b -> Baz (frst (g a)) (scnd (g b))
= case m of
      Bar x -> case f x of
          Bar y -> g y
          Baz a b -> Baz (frst (g a)) (scnd (g b))
      Baz x y -> Baz (frst (g (frst (f x))))
                     (scnd (g (scnd (f y))))
= case m of
      Bar a -> case f a of
          Bar x -> g x
          Baz x y -> Baz (frst (g x)) (scnd (g y))
      Baz a b -> case Baz (frst (f a)) (scnd (f b)) of
          Bar x -> g x
          Baz x y -> Baz (frst (g x)) (scnd (g y))
= case v of
      Bar x -> g x
      Baz x y -> Baz (frst (g x)) (scnd (g y))
  where v = case m of
                Bar a -> f a
                Baz a b -> Baz (frst (f a)) (scnd (f b))
= case m >>= f of
      Bar x -> g x
      Baz x y -> Baz (frst (g x)) (scnd (g y))
= (m >>= f) >>= g

edit Okay, I decided to write a short explanation of how this is inspired by (Bool ->) even though nobody asked. So, recall:

instance Monad (e ->) where
    m >>= f = \e -> f (m e) e

Now we're going to define

data Pair a = Pair a a

and observe that Bool -> a and Pair a are very similar:

to :: Pair a -> (Bool -> a)
to (Pair false true) = \bool -> case bool of
    False -> false
    True  -> true

from :: (Bool -> a) -> Pair a
from f = Pair (f False) (f True)

It turns out that from and to are an isomorphism. In other words: you can alternately think of Bool -> a as a "two-element container". Well, what happens if we try to translate the (e ->) instance for Monad into the Pair type? It certainly ought to be possible, since they're isomorphic. In fact, let's start with the isomorphism:

instance Monad Pair where
    return x = from (return x)
    m >>= f = from (to m >>= to . f)

Now we can "just turn the crank":

  return x
= from (return x)
= from (\e -> x)
= Pair ((\e -> x) False) ((\e -> x) True)
= Pair x x

and:

  m@(Pair false true) >>= f
= from (to m >>= to . f)
= from (\e -> (to . f) (to m e) e)
= from (\e -> to (f (to m e)) e)
= Pair (g False) (g True) where
      g = \e -> to (f (to m e)) e
= Pair (to (f (to m False)) False) (to (f (to m True)) True)
= Pair (case f (to m False) of Pair false true -> false)
       (case f (to m True ) of Pair false true -> true )
= Pair (case f false of Pair false true -> false)
       (case f true  of Pair false true -> true )

So we can now rewrite the instance without relying on (Bool ->) by just copying and pasting the first and last line of the above calculations:

frstPair (Pair false true) = false
scndPair (Pair false true) = true

instance Monad Pair where
    return x = Pair x x
    Pair false true >>= f = Pair (frstPair (f false)) (scndPair (f true))

Hopefully you can recognize how similar this is to the definition of (>>=) I gave above for Foo.

edit 2 Another (different!) monad for this is possible. Check out the behavior of the isomorphic type from base:

type Foo = Product Identity Maybe

See the docs for Product. Written without the isomorphism, it would be:

instance Monad Foo where
    return x = Baz x x
    Bar x >>= f = Bar (frst (f x))
    Baz x y >>= f = case f y of
        Bar a -> Bar (frst (f x))
        Baz a b -> Baz (frst (f x)) b

In a sense, my original proposal "expands" the number of results as you add more monadic actions -- starting with a Bar in return and converting Bars irrevocably to Bazs in the bind -- while this instance "contracts" the number of results possible as you add more monadic actions -- starting with a Baz in return and converting Bazs to Bars irrevocably in the bind. Quite an interesting design choice, if you ask me! It also makes me wonder if another Monad instance for Product is possible (perhaps with different constraints on the functors involved).

Daniel Wagner
  • 145,880
  • 9
  • 220
  • 380
  • I'm not convinced of your associativity proof. I tried it with `data Pair a = Pair { one :: a, two :: a }` (I suspected the `Baz`-`Baz` case, and I didn't want to have to think about case analysis) and it didn't work out. Intuitively it makes sense that `Pair` isn't a monad, because you have no way of combining `a`s. – Benjamin Hodgson Apr 28 '17 at 16:51
  • 1
    @BenjaminHodgson For that type, we have `return x = Pair x x; Pair x y >>= f = Pair (one (f x)) (two (f y))` and this is *definitely* a Monad because it is completely isomorphic to `type Pair a = Bool -> a`. What did you try exactly that suggests it "didn't work out"? – Daniel Wagner Apr 28 '17 at 16:53
  • Scratch that, I'd made an error in my calculation :) – Benjamin Hodgson Apr 28 '17 at 16:55
  • Your `Bool ->` analogue could mention `Representable` functors. The `Foo` isn't representable however. I use a different logic there, the "representation" forms a `Monoid`, your example is `Max`, `Product` is a `Min`. I'm not sure whether `Max` approach would work for `Foo = Bar a | Baz a a | Quu a a a` – phadej Apr 29 '17 at 21:07
  • `Foo` is also isomorphic to `Either a (Pair a)`. That gives rise to the first monad instance, via the `Monad m => Either a (m a)` construction winitzki told us about [here](https://stackoverflow.com/a/49703783/2751851). – duplode Apr 15 '18 at 21:15