I was playing around with the wonderful answer given here. I naively expected this to work:
{-# LANGUAGE MultiParamTypeClasses #-}
import Data.Functor.Compose
import Control.Monad
class (Functor f, Functor g) => Adjoint f g where
counit :: f (g a) -> a
unit :: a -> g (f a)
instance (Adjoint f g) => Monad (Compose g f) where
return x = Compose $ unit x
x >>= f = Compose . fmap counit . getCompose $ fmap (getCompose . f) x
It doesn't, though. I get the following error:
adjoint.hs:10:10: error:
• Could not deduce (Applicative g)
arising from the superclasses of an instance declaration
Here's what seems to be happening. GHC requires all Monad
s to have an Applicative
instance, so the compiler goes looking for one for Compose g f
.
Data.Functor.Compose
defines such an instance, but it requires g
(and f
) to be Applicative
:
instance (Applicative f, Applicative g) => Applicative (Compose f g) where
pure x = Compose (pure (pure x))
Compose f <*> Compose x = Compose ((<*>) <$> f <*> x)
But in the general case, Compose g f
can be a Monad
(and thereby Applicative
) even when g
and f
aren't both Applicative
. The usual example is when f
is (,) s
, and g
is (->) s
. Then Compose g f
is the State
Monad
, even though (,) s
isn't (always) Applicative
.
This seems a bit suboptimal. For one, it would be nice to use Adjoint
to define Monad
instances for two Functor
s that aren't both Applicative
. More generally, though, there are ways for the composition of two Functors
to be Applicative
, even when one or both of them fails to be. Currently, though, the way that GHC behaves, combined with the way Data.Functor.Compose
is set up, precludes you from ever realizing these use cases. If you try to define an Applicative
instance for any Compose g f
, GHC will complain about a duplicate instance declaration.
The obvious solution is just to roll your own version of Data.Functor.Compose
with the Applicative
lines scrapped. That's straightforward enough, if a bit hacky. Are there other more principled ways to approach the issue?