1
votes

I suspect that all applicative, foldable monoids are traversable in the same manner. In other words, for any type t :: * -> * that satisfies Applicative and Foldable, and for which all instantiations t a satisfy Monoid, there is a free instance of Traversable.

Here is how I would implement sequenceA:

sequenceA :: (Applicative t, Foldable t, Monoid (t a), Applicative f) =>
  t (f a) -> f (t a)
sequenceA = foldl (liftA2 $ \b a -> mappend b (pure a)) (pure mempty)

We can e.g. use this to traverse a list containing functions into a function that will produce a list (since [] is applicative, foldable, and a monoid for all types [a]):

sequenceA [\a -> 2 * a, \a -> 2 + a] $ 5
-- [10, 7]

Unfortunately, I can't figure out how to actually specify a Traversable instance with this implementation of sequenceA. Here's what I tried:

instance (Applicative t, Foldable t, Monoid (t a)) => Traversable t where
  sequenceA = foldl (liftA2 $ \b a -> mappend b (pure a)) (pure mempty)

If I try to compile this without any extensions I get:

<interactive>:3:55: error:
    • Illegal instance declaration for ‘Traversable t’
        (All instance types must be of the form (T a1 ... an)
         where a1 ... an are *distinct type variables*,
         and each type variable appears at most once in the instance head.
         Use FlexibleInstances if you want to disable this.)
    • In the instance declaration for ‘(Traversable t)’

What is the correct way for me to express this instance in Haskell?


On the off chance that recursively adding whatever extensions the compiler errors mention might fix the problem, I tried that out and have pasted the results here. If any of the error messages there are relevant, please let me know and I'll move them directly into the question body.

1
Have you tried enabling FlexibleInstances? - Fyodor Soikin
@FyodorSoikin Yes, see the linked gist. - Asad Saeeduddin

1 Answers

4
votes

Your conjecture is wrong. Consider the type

{-# LANGUAGE GeneralizedNewtypeDeriving #-}

import Data.Semigroup
import Data.Monoid hiding ((<>))

newtype FL a = FL [a] deriving (Functor, Foldable, Applicative)
instance Semigroup (FL a) where
  FL as <> FL bs = FL $ as ++ drop (length as) bs
instance Monoid (FL a) where
  mempty = FL []
  mappend = (<>)

This is based on the Alternative instance for ZipList. mempty is obviously the identity for mappend, and mappend is somewhat less obviously associative, so it's a valid Monoid instance. However, it does not lead to a valid Traversable instance using your definition. Your definition works for lists (and a few other types, like Data.Sequence.Seq and Data.Vector.Vector) because they have a very special structure.

In particular, [a] is (modulo some laziness considerations) the free monoid over a with pure and foldMap satisfying a particular universal property:

Whenever m is a Monoid and f :: a -> m, foldMap f is the unique monoid homomorphism such that foldMap f . pure = f.

In other situations, such as FL above, you're generally not going to end up satisfying the identity law for Traversable, although I suppose you might find somewhat weaker conditions under which it works out.


What if you want to muck about with your idea anyway? The easiest thing is to replace the Monoid (t a) constraint with an Alternative t constraint. Then you can use empty instead of mempty and (<|>) instead of mappend, and the types (although not the laws) should work out.

If you're really stuck on Monoid, you have to bring in some much heavier machinery from Data.Constraint.Forall. What you want to say is that for each a, Monoid (t a). You can express that as ForallF Monoid t. But you can't just use Monoid methods under that constraint, because it's not natively supported by GHC. Rather, you'll have to use instF:

{-# LANGUAGE TypeOperators, ScopedTypeVariables, InstanceSigs, ... #-}

import Data.Constraint
import Data.Constraint.Forall

instance (Applicative t, Foldable t, ForallF Monoid t)
  => Traversable t where
  sequenceA :: forall f a. Applicative f => t (f a) -> f (t a)
  sequenceA =
   case instF :: ForallF Monoid t :- Monoid (t a) of
     Sub Dict -> foldl (liftA2 $ \b a -> mappend b (pure a)) (pure mempty)

Of course, once you've gone to all that trouble, you'll discover that your Traversable instance overlaps with every other Traversable instance, which is pretty much a total disaster.

Addendum: as Benjamin Hodgson notes, there is an accepted GHC proposal to support quantified (and implication) constraints. When that is implemented (likely to be soon), you'll be able to simply write forall a. Monoid (t a) as a constraint, and things should work out much more easily.