6

In this answer I made up on the spot something which looks a bit like a "higher order Traversable": like Traversable but for functors from the category of endofunctors on Hask to Hask.

{-# LANGUAGE RankNTypes #-}
import Data.Functor.Compose
import Data.Functor.Identity

class HFunctor t where
    hmap :: (forall x. f x -> g x) -> t f -> t g

class HFunctor t => HTraversable t where
    htraverse :: Applicative g => (forall x. f x -> g x) -> t f -> g (t Identity)
    htraverse eta = hsequence . hmap eta
    hsequence :: Applicative f => t f -> f (t Identity)
    hsequence = htraverse id

I made HFunctor a superclass of HTraversable because it seemed right, but when I sat down to write hmapDefault I got stuck.

hmapDefault :: HTraversable t => (forall x. f x -> g x) -> t f -> t g
hmapDefault eta = runIdentity . htraverse (Identity . eta)

-- • Couldn't match type ‘x’ with ‘g x’
--   Expected type: f x -> Identity x
--     Actual type: f x -> Identity (g x)

Identity . eta has a type forall y. f y -> Identity (g y), so when I pass it into htraverse g unifies with Identity and x has to unify with both y and g y, so it fails because the traversal function is not a natural transformation.

I attempted to patch it up using Compose:

hmapDefault :: HTraversable t => (forall x. f x -> g x) -> t f -> t g
hmapDefault eta = runIdentity . getCompose . htraverse (Compose . Identity . eta)

Now Compose . Identity . eta is a natural transformation, but you can't htraverse with it because you don't know Applicative g. And even if you could do that, the runIdentity call returns g (t Identity) and you're left with no way to put the g back inside the t.


I then realised that my htraverse isn't really analogous to plain old traverse. The traversal function of traverse puts the new value inside an Applicative effect, making the type expression bigger. So htraverse should probably look like this:

class HFunctor t => HTraversable t where
    htraverse :: Applicative a => (forall x. f x -> a (g x)) -> t f -> a (t g)

It's promising that this definition looks more like Traversable, and hmapDefault goes off without a hitch,

hmapDefault :: HTraversable t => (forall x. f x -> g x) -> t f -> t g
hmapDefault eta = runIdentity . htraverse (Identity . eta)

but I'm struggling to come up with a good analogue for sequenceA. I tried

hsequence :: (HTraversable t, Applicative f) => t f -> f (t Identity)
hsequence = htraverse (fmap Identity)

but I can't come up with a way of implementing htraverse in terms of hsequence. As before, f is not a natural transformation.

htraverse f = hsequence . hmap f

-- • Couldn't match type ‘x’ with ‘g x’
--   Expected type: f x -> a x
--     Actual type: f x -> a (g x)

I suspect I have my hsequence type signature wrong. Is Applicative the problem - do I need to go all the way up to indexed monads? What should a class for "traversable functors from the Functor category to Hask" look like? Does such a thing even exist?

Benjamin Hodgson
  • 42,952
  • 15
  • 108
  • 157
  • If `~>` is the natural transformation arrow, then `sequenceA :: (Applicative f) => t . f ~> f . t`, which can be reinterpreted in a higher context, so that's what I'd focus on. But yeah looks like you need higher applicatives for that. – luqui May 25 '17 at 19:11
  • @luqui I was under the impression that higher applicatives don't actually exist, it's indexed monads or bust. ["In general, demonic activity makes this structure hard to attain. Applicative functors sequence computations with no value dependency: in `(<*>) :: Applicative a => a (s -> t) -> a s -> a t` there is no way for the value of the function computation to influence our choice of argument computation, only the way in which its value is used in turn."](https://personal.cis.strath.ac.uk/conor.mcbride/Kleisli.pdf) – Benjamin Hodgson May 25 '17 at 19:14
  • Interesting! My normal approach is useless here. – luqui May 25 '17 at 19:15

1 Answers1

7

In first order, we have sequence = traverse id.

Here the first argument of htraverse has type forall x. f x -> a (g x), we can't have id, but we can try with an isomorphism instead. For f x to be isomorphic to a (g x), we can pick f ~ Compose a g.

htraverse = hsequence . hmap (Compose . eta)

hsequence :: Applicative a => t (Compose a g) -> a (t g)
hsequence = htraverse getCompose
Li-yao Xia
  • 31,896
  • 2
  • 33
  • 56
  • I take it you meant `htraverse eta = hsequence . hmap (Compose . eta)` and `hsequence :: Applicative a => t (Compose a g) -> a (t g)`? This appears to work! Thanks! – Benjamin Hodgson May 25 '17 at 20:33
  • Oops, that's what I meant indeed. – Li-yao Xia May 25 '17 at 20:34
  • 2
    In that case I think the most elegant version of these types is `htraverse :: Applicative a => (f ~> Compose a g) -> t f -> a (t g)`, `hsequence :: Applicative a => t (Compose a g) -> a (t g)`. Then the code of `htraverse` and `hsequence` is exactly the same as for regular `Traversable` – Benjamin Hodgson May 25 '17 at 20:38
  • 1
    Nowadays we have: https://hackage.haskell.org/package/rank2classes/docs/Rank2.html#t:Traversable – Dmitry Olshansky Mar 03 '23 at 18:04