Search code examples
haskelldepthtraversable

Is it impossible to get the depth of elements inside a Traversable?


Suppose I have this Tree type:

{-# LANGUAGE DeriveFoldable, DeriveFunctor #-}

data Tree a = Leaf | Branch (Tree a) a (Tree a) deriving(Functor,Foldable)

instance Traversable Tree where -- equivalent to the one I could derive, but written out for clarity
  traverse _ Leaf = pure Leaf
  traverse f (Branch l x r) = Branch <$> traverse f l <*> f x <*> traverse f r

It's easy to write a function to calculate the maximum depth of things inside that specific type:

depth Leaf = 0
depth (Branch l _ r) = 1 + max (depth l) (depth r)

But it's not so easy to calculate the maximum depth of things inside an arbitrary Traversable. I already know that just Functor isn't enough for this, since you get no information about the "position" of things inside of them via fmap, and I also already know that just Foldable isn't enough for this, since foldr and foldMap both only give as much structure as lists have. Traversable might be, though, because it's more general than both Functor and Foldable.

However, after doing some experimentation, I don't think there's a way to do it with Traversable either. Here's my logic so far. Consider these two trees:

fooTree = Branch (Branch Leaf () Leaf) () (Branch Leaf () Leaf)
barTree = Branch (Branch Leaf () (Branch Leaf () Leaf)) () Leaf

Now, traverse (\() -> thingy) fooTree is:

Branch <$> (Branch <$> pure Leaf <*> thingy <*> pure Leaf) <*> thingy <*> (Branch <$> pure Leaf <*> thingy <*> pure Leaf)

After lots of use of the Applicative laws and some simplification, that becomes:

(\x y z -> Branch (Branch Leaf x Leaf) y (Branch Leaf z Leaf)) <$> thingy <*> thingy <*> thingy

Similarly, traverse (\() -> thingy) barTree is:

Branch <$> (Branch <$> pure Leaf <*> thingy <*> (Branch <$> pure Leaf <*> thingy <*> pure Leaf)) <*> thingy <*> pure Leaf

After lots of use of the Applicative laws and some simplification, that becomes:

(\x y z -> Branch (Branch Leaf x (Branch Leaf y Leaf)) z Leaf) <$> thingy <*> thingy <*> thingy

Now traverse (\() -> thingy) fooTree and traverse (\() -> thingy) barTree look like they have the same "shape" (the only difference is the lambda at the beginning, and even the types of those are the same), but they came from trees that have different depths. This leads me to believe that it's impossible to find the depth in terms of traverse, but I'm not 100% sure about it and I'm not sure how to explain it rigorously.

Am I right that it's impossible? If so, then how can this actually be explained rigorously? If not, then how would you implement it?


Solution

  • It is indeed impossible, as going from Foldable to Traversable cant't actually help. Obtaining the depths of your Trees requires merging information from both subtrees under a branch. As far as...

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

    ... is concerned, any such merger can only be attained through the combined applicative effect f of the result (a lawful traverse must preserve the shape of the t structure, and each b value is obtained from an individual a value through the a -> f b function). Obtaining a combined effect, though, is already possible through Foldable...

    traverse_ :: (Foldable t, Applicative f) => (a -> f b) -> t a -> f ()
    

    ... and so the additional power of Traversable makes no difference here.

    If merely pointing to traverse_ feels insufficiently sharp, here is an alternative way of presenting the final step of the argument above. One of the naturality properties of traverse is the one called "'naturality' in the datatype" by Bird et al. in Understanding Idiomatic Traversals Backwards and Forwards (see section 6 of that paper for details):

    -- r is a natural transformation that preserves toList:
    -- toList = toList . r
    fmap r . traverse f = traverse f . r
    

    Consider an arbitrary toList-preserving tree rearrangement r :: Tree a -> Tree a, and some f such that the result of traverse f somehow encodes the depth of the tree. Since, as discussed above, only the combined effect matters for the purposes of computing the depth, fmap (const ()) . traverse f will encode the depth just as well as traverse f. Now, let's take the naturality property and compose fmap (const ()) on both sides:

    fmap (const ()) . fmap r . traverse f = fmap (const ()) . traverse f . r
    -- Or simply:
    fmap (const ()) . traverse f = fmap (const ()) . traverse f . r
    

    Since fmap (const ()) . traverse f encodes the depth, this means r, whatever it is, won't change the depth of the tree. That, however, is not the case, as illustrated, for instance, by this counterexample:

    -- Makes a tree with only leaves as left subtrees, preserving traversal order.
    -- Assuming a toList that matches your traverse, or the derived one. 
    straighten :: Tree a -> Tree a
    straighten = foldr dangle Leaf . toList
        where
        dangle x t = Branch Leaf x t