The “neat alternative presentation” for Applicative
is based on the following two equivalencies
pure a = fmap (const a) unit
unit = pure ()
ff <*> fa = fmap (\(f,a) -> f a) $ ff ** fa
fa ** fb = pure (,) <*> fa <*> fb
The trick to get this “neat alternative presentation” for Applicative
is the same as the trick for zipWith
– replace explicit types and constructors in the interface with things that the type or constructor can be passed into to recover what the original interface was.
unit :: f ()
Is replaced with pure
which we can substitute the type ()
and the constructor () :: ()
into to recover unit
.
pure :: a -> f a
pure () :: f ()
And similarly (though not as straightforward) for substituting the type (a,b)
and the constructor (,) :: a -> b -> (a,b)
into liftA2
to recover **
.
liftA2 :: (a -> b -> c) -> f a -> f b -> f c
liftA2 (,) :: f a -> f b -> f (a,b)
Applicative
then gets the nice <*>
operator by lifting function application ($) :: (a -> b) -> a -> b
into the functor.
(<*>) :: f (a -> b) -> f a -> f b
(<*>) = liftA2 ($)
To find a “neat alternative presentation” for PtS
we need to find
- something we can substitute the type
Void
into to recoverunit
- something we can substitute the type
Either a b
and the constructorsLeft :: a -> Either a b
andRight :: b -> Either a b
into to recover**
(If you notice that we already have something the constructors Left
and Right
can be passed to you can probably figure out what we can replace **
with without following the steps I used; I didn’t notice this until after I solved it)
unit
This immediately gets us an alternative to unit
for sums:
empty :: f a
empty = fmap absurd unit
unit :: f Void
unit = empty
operator
We’d like to find an alternative to (**)
. There is an alternative to sums like Either
that allows them to be written as functions of products. It shows up as the visitor pattern in object oriented programming languages where sums don’t exist.
data Either a b = Left a | Right b
{-# LANGUAGE RankNTypes #-}
type Sum a b = forall c. (a -> c) -> (b -> c) -> c
It’s what you would get if you changed the order of either
‘s arguments and partially applied them.
either :: (a -> c) -> (b -> c) -> Either a b -> c
toSum :: Either a b -> Sum a b
toSum e = \forA forB -> either forA forB e
toEither :: Sum a b -> Either a b
toEither s = s Left Right
We can see that Either a b ≅ Sum a b
. This allows us to rewrite the type for (**)
(**) :: f a -> f b -> f (Either a b)
(**) :: f a -> f b -> f (Sum a b)
(**) :: f a -> f b -> f ((a -> c) -> (b -> c) -> c)
Now it’s clear what **
does. It delays fmap
ing something onto both of its arguments, and combines the results of those two mappings. If we introduce a new operator, <||> :: f c -> f c -> f c
which simply assumes that the fmap
ing was done already, then we can see that
fmap (\f -> f forA forB) (fa ** fb) = fmap forA fa <||> fmap forB fb
Or back in terms of Either
:
fa ** fb = fmap Left fa <||> fmap Right fb
fa1 <||> fa2 = fmap (either id id) $ fa1 ** fa2
So we can express everything PtS
can express with the following class, and everything that could implement PtS
can implement the following class:
class Functor f => AlmostAlternative f where
empty :: f a
(<||>) :: f a -> f a -> f a
This is almost certainly the same as the Alternative
class, except we didn’t require that the Functor
be Applicative
.
Conclusion
It’s just a Functor
that is a Monoid
for all types. It’d be equivalent to the following:
class (Functor f, forall a. Monoid (f a)) => MonoidalFunctor f
The forall a. Monoid (f a)
constraint is pseudo-code; I don’t know a way to express constraints like this in Haskell.