8

Foldable is a superclass of Traversable, similarly to how Functor is a superclass of Applicative and Monad.

Similar to the case of Monad, where it is possible to basically implement fmap as

liftM :: Monad m => (a->b) -> m a -> m b
liftM f q = return . f =<< q

we could also emulate foldMap as

foldLiftT :: (Traversable t, Monoid m) => (a -> m) -> t a -> m
foldLiftT f = fst . traverse (f >>> \x -> (x,x))
           -- or: . sequenceA . fmap (f >>> \x -> (x, x))

using the Monoid m => (,) m monad. So the combination of superclass and methods bears in both cases a certain redundancy.

In case of monads, it can be argued that a “better” definition of the type class would be (I'll skip applicative / monoidal)

class (Functor m) => Monad m where
  return :: a -> m a
  join :: m (m a) -> m a

at least that's what's used in category theory. This definition does, without using the Functor superclass, not permit liftM, so it is without this redundancy.

Is a similar transformation possible for the Traversable class?


To clarify: what I'm after is a re-definition, let's call it,

class (Functor t, Foldable t) => Traversable t where
  skim :: ???

such that we could make the actual Traverse methods top-level functions

sequenceA :: (Traversable t, Applicative f) => t (f a) -> f (t a)

but it would not be possible to make generically

instance (Traversable t) => Foldable t where
  foldMap = ... skim ...

data T
instance Traversable T where
  skim = ...

I'm not asking because I need this for something particular; it's a conceptual question so as to better understand the difference between Foldable and Traversable. Again much like Monad vs Functor: while >>= is much more convenient than join for everyday Haskell programming (because you usually need precisely this combination of fmap and join), the latter makes it simpler to grasp what a monad is about.

duplode
  • 33,731
  • 7
  • 79
  • 150
leftaroundabout
  • 117,950
  • 5
  • 174
  • 319
  • 1
    The distinct method is `traverse`. You cannot implement that in terms of `Foldable`. – Gabriella Gonzalez Jan 13 '14 at 01:39
  • Of course not, but you can implement `Foldable` in terms of `traverse`. – leftaroundabout Jan 13 '14 at 01:47
  • 1
    ... which is why `Foldable` is a super-class of `Traversable`. A super class should be implementable in terms of the sub class. – Gabriella Gonzalez Jan 13 '14 at 02:10
  • 1
    I think @leftaroundabout is asking the equivalent of: Could you define a class `TraversableMinusFoldable` , so that ` class (Foldable t, TraversableMinusFoldable t) => Traversable t where` has no new functions but the existing functions are made compatible. As in, could you define `traverse` without referring to anything in `Foldable`. But even if that's the question, I am not convinced it isn't he right way to study the situation. The old Monad was a mess and should best be forgotten :-) – misterbee Jan 13 '14 at 04:14
  • 1
    @misterbee: that's pretty much it, but not quite. What I'm interested in is just the "weakest possible signature" you could give the methods of `Traversable`, so practical use would actually require the superclass `Foldable`. At the moment, you could basically just omit the superclass like in historic `Monad`, and as you say that's not good. – leftaroundabout Jan 13 '14 at 07:58

2 Answers2

3

Foldable is to Functor as Traversable is to Monad, i.e. Foldable and Functor are superclasses of Monad and Traversable (modulo all the applicative/monad proposal noise).

Indeed, that's already in the code

instance Foldable f => Traversable f where
  ...

So, it's not clear what more there is to want. Foldable is characterized by toList :: Foldable f => f a -> [a] while Traversable depends ultimately on not only being able to abstract the content as a list like toList does, but also to be able to extract the shape

shape :: Functor f => f a -> f ()
shape = fmap (const ())

and then recombine them

combine :: Traversable f => f () -> [a] -> Maybe (f a)
combine f_ = evalStateT (traverse pop f_) where
  pop :: StateT [a] Maybe a
  pop = do x <- get
           case x of
             [] = empty
             (a:as) = set as >> return a

which depends on traverse.

For more information on this property see this blog post by Russell O'Connor.

J. Abrahamson
  • 72,246
  • 9
  • 135
  • 180
  • So, if `combine` was the sole method of `Traversable`, would be be able to define `traverse` / `sequenceA` in terms of it? – leftaroundabout Jan 13 '14 at 07:41
  • 2
    I'd perhaps say that Foldable is to Functor as Traversable is to *Applicative*. – Petr Jan 13 '14 at 08:07
  • @leftaroundabout try it, and post if you get stuck :-) – misterbee Jan 13 '14 at 16:48
  • I think it needs to be slightly more general—`combine` is pretty hand-wavey but there's a McBride paper somewhere that goes into more detail about this. – J. Abrahamson Jan 13 '14 at 17:53
  • 1
    Ok, so we _can_ implement `sequenceA q = let { structure = fmap (const()) q; values = toList q } in fmap (fromJust . combine structure) $ Prelude.sequence values`. I suppose that's sound enough if we require the axiom that `combine (fmap (const()) q) (toList q)` always "works", with `Just` result. That seems to answer my question, though as you say `combine` doesn't appear exactly elegant. – leftaroundabout Jan 14 '14 at 00:18
  • Yeah, the property would certainly be that `combine <$> shape <*> toList == id`. – J. Abrahamson Jan 14 '14 at 02:21
  • This is a more complete description of this property: http://r6.ca/blog/20121209T182914Z.html. I'm adding it to the main post as well. – J. Abrahamson Jan 14 '14 at 19:29
  • 2
    If we had dependent types we could write `combine :: Traversable f => Πx:f (). Vec a (length x) -> f a`. The fact that we can make the Traversable class without using dependent types is kinda amazing. It probably has something to do with the fact that it uses the auxiliary class of applicative functors and assumes they follow their laws. – Russell O'Connor Oct 12 '15 at 16:25
3

Super hand-wavy because it's late, but the extra power that Traversable has over Foldable is a way to reconstruct the original structure. For example, with lists:

module MyTraverse where

import Data.Foldable
import Data.Traversable
import Control.Applicative
import Data.Monoid

data ListRec f x = ListRec
  { el :: f (Endo [x])
  }

instance Applicative f => Monoid (ListRec f x) where
    mempty = ListRec (pure mempty)
    mappend (ListRec l) (ListRec r) =
        ListRec (mappend <$> l <*> r)

toM :: Functor f => f b -> ListRec f b
toM this = ListRec $ (Endo . (:)) <$> this

fromM :: Functor f => ListRec f b -> f [b]
fromM (ListRec l) = flip appEndo [] <$> l

myTraverse :: Applicative f => (a-> f b)  -> [a] -> f [b]
myTraverse f xs = fromM $ foldMap (toM . f) xs

I think this myTraverse behaves the same as traverse, using only the classes Applicative, Foldable, and Monoid. You could re-write it to use foldr instead of foldMap if you wanted to get rid of Monoid.

lists are easy because they're a flat structure. However, I strongly suspect that you could use a Zipper to get the proper reconstruction function for any structure (since zippers are generically derivable, they should always exists).

But even with a zipper, you don't have any way of indicating that structure to the monoid/function. Notionally, it seems Traversable adds something like

class Traversed t where
  type Path t :: *
  annotate :: t a -> [(Path t, a)]
  fromKeyed :: [(Path t, a)] -> t a

this seems to overlap heavily with Foldable, but I think that's inevitable when trying to associate the paths with their constituent values.

John L
  • 27,937
  • 4
  • 73
  • 88