DEV Community

Yuriy Syrovetskiy
Yuriy Syrovetskiy

Posted on

Reverse Maybe as Another Applicative-not-Monad

Applicative vs. Monad

Every time somebody wants to show the difference between Applicative and Monad, they always pick ZipList, which is an Applicative but not a Monad.

I recently found yet another example which is less common.

First'

Consider the following type:

newtype First' a b = First' (Maybe a)
Enter fullscreen mode Exit fullscreen mode

It is bivariant (both covariant and contravariant) in its tail argument b. Compiler sees this clearly:

{-# LANGUAGE DeriveFunctor #-}
newtype First' a b = First' (Maybe a)
    deriving (Functor)
Enter fullscreen mode Exit fullscreen mode

I leave writing non-derived Functor instance to you as an excercise.

Please note that this functor ignores its argument completely, unlike pure Maybe.

The name First' isn't a coincidence. We're going to use semantics of Data.Monoid.First here. Namely, First allows to mappend two Maybe values without descending into them:

λ> Nothing <> Just 'A'

<interactive>:
    No instance for (Monoid Char) arising from a use of <>'
    ...
Enter fullscreen mode Exit fullscreen mode
λ> First Nothing <> First (Just 'A')
First {getFirst = Just 'A'}
Enter fullscreen mode Exit fullscreen mode

Monoid

Let's write Monoid for our First' with the same semantics:

instance Monoid (First' a b) where
    mempty = First' Nothing
    x@(First' (Just _)) `mappend` _ = x
    _ `mappend` y = y
Enter fullscreen mode Exit fullscreen mode

Let's try it in repl:

λ> First' Nothing <> First' (Just 'A')
First' (Just 'A')
Enter fullscreen mode Exit fullscreen mode

It works!

Applicative

Let's go next level. We're going to write Applicative instance with this semantics. We also can reuse monoid instance.

instance Applicative (First' a) where
    pure _ = First' Nothing
    First' x <*> First' y = First' x <> First' y
Enter fullscreen mode Exit fullscreen mode

Check:

λ> First' Nothing <*> First' (Just 'A')
First' (Just 'A')
λ> First' Nothing *> First' (Just 'A')
First' (Just 'A')
Enter fullscreen mode Exit fullscreen mode

Reverse Maybe

Why this is a reverse Maybe?

Maybe semantics may be expresses as:

  • Nothing -> failure, stop
  • Just x -> continue with x
λ> Nothing *> Just 1
Nothing
λ> Just 1 *> Just 2
Just 2
Enter fullscreen mode Exit fullscreen mode

First' semantics is:

  • Nothing -> continue
  • Just x -> result is x, stop
λ> First' Nothing *> First' (Just 2)
First' (Just 2)
λ> First' (Just 1) *> First' (Just 2)
First' (Just 1)
Enter fullscreen mode Exit fullscreen mode

Monad?

First' doesn't seem to be a Monad though. But I'm too lazy to prove it. If you can provide such a proof, please let me take a look at it.

Const

Vladislav Zavialov noted that First' is merely

type First' a b = Const (First a) b
Enter fullscreen mode Exit fullscreen mode

where First is from Data.Monoid.

Indeed,

λ> Const (First Nothing) *> Const (First (Just 2))
Const (First {getFirst = Just 2})
λ> Const (First (Just 1)) *> Const (First (Just 2))
Const (First {getFirst = Just 1})
Enter fullscreen mode Exit fullscreen mode

And Const is yet another interesting Applicative-not-Monad example.

Top comments (0)