2

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 Monads 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 Functors 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?

SEC
  • 799
  • 4
  • 16
  • 4
    I think your obvious solution is correct. When working with typeclasses, we need to extend our concept of a type from "set-like" to "algebraic-structure-like". `Compose g f` is already an `Applicative` in one way, and you propose to make it one in a different way. In this way of thinking, it's now a different type -- much like we use `Sum Int` to indicate that we mean to take the `Monoid` that adds as opposed to the several other possibilities. – luqui Sep 28 '17 at 22:52
  • Can you say what you mean by "hacky"? Why don't you like the "roll your own `Compose`" solution? – Daniel Wagner Sep 28 '17 at 22:59
  • The issue might be that I've been misconstruing type class parameters. I've been reading `instance (Applicative f, Applicative g) => Applicative (Compose f g)` as "whenever `f` and `g` are `Applicative`, so is `Compose f g`. So if either `f` or `g` isn't known to be `Applicative`, GHC shouldn't conclude that `Compose f g` is. Obviously this isn't what's happening! But it seems like sensible enough behavior (though maybe it has bad consequences downstream). So perhaps my resistance to "roll your own `Compose`" is just me being stubborn about my naive understanding of type class parameters. – SEC Sep 29 '17 at 15:24
  • 1
    @SimonC Right. One could definitely imagine a type class system with that behavior, and nothing semantically would go wrong. The problem is that then finding an instance involves a backtracking search, and the committee wanted to avoid that both to avoid forcing a complex implementation (remember, at the time, this was the first type class system in existence and nobody knew how complicated it would be!) and to avoid users discovering deep in a development that long instance searches were causing enormous compilation times. – Daniel Wagner Oct 03 '17 at 18:25

1 Answers1

4

Generally, if you need a different instance, you need a new type. Should be pretty straightforward; just a few lines of code:

newtype AdjointCompose f g a = AdjointCompose { runAdjointCompose :: f (g a) }

instance (Functor f, Functor g) => Functor (AdjointCompose f g) where
    fmap = liftM

instance Adjoint f g => Applicative (AdjointCompose g f) where
    pure = return
    (<*>) = ap

instance Adjoint f g => Monad (AdjointCompose g f) where
    -- as in your proposed instance

Now you can have your cake and eat it, too: when you want the composition of Applicatives, use Compose, and when you want the Applicative you get from adjointness, use AdjointCompose.

If you want some of the other instances that Compose defines for free, you could write AdjointCompose as a newtype over Compose instead and get them via GeneralizedNewtypeDeriving.

Daniel Wagner
  • 145,880
  • 9
  • 220
  • 380