A little curiosity

Yeah, this does not really fit the “Show and Tell” category, but neither does it others, so maybe you’ll forgive this chatter here.

Maybe this is part of Haskell folklore and seasoned veterans will know this curious tidbit, but I was quite surprised – and it was by no means obvious for me:

The type of fmap fmap fmap fmap fmap is quite interesting and even useful:

GHCI> :t fmap fmap fmap fmap fmap
fmap fmap fmap fmap fmap
  :: Functor f => (b -> c) -> (a -> b) -> f a -> f c

So, for (<.>) = fmap fmap fmap fmap fmap, we essentially have function composition and application inside a functor.

With

f :: a -> b
g :: b -> c
c :: [a]

We can write

g <.> f $ a      -- :: [c]

Also, I was quite surprised that a five-times fmap produces such a “clean” and immediately human-interpretable type. Any other syntactical sequence of fmaps (like three, four; then six or more) result in a rather garbled and less immediately easily-to-understand signatures, so the five-sequence (four-times-applied) fmap came as a real surprise:

Generally, sequentially applied fmaps will result in more Functor constraints than one.

Also it goes into a cycle after six repetitions of fmap, with a cycle of 4, so, with pseudo-operator ^ for self-application,

fmap^5 == (<.>)
fmap^n == fmap^(n+4)   -- forall `n >= 6`

So yeah, that’s some curious tidbit.

10 Likes

That’s surprising, thank for sharing.

That would be even more surprising, so I checked. What I see in GHCi 9.0.1 is

ghci> :t fmap fmap fmap fmap fmap fmap fmap fmap fmap -- 9 repetitions
fmap fmap fmap fmap fmap fmap fmap fmap fmap -- 9 repetitions
  :: (Functor f1, Functor f2, Functor f3, Functor f4) =>
     f1 (f2 (f3 (a -> b))) -> f1 (f2 (f3 (f4 a -> f4 b)))
ghci> :t fmap fmap fmap fmap fmap fmap fmap fmap fmap fmap -- 10 repetitions
fmap fmap fmap fmap fmap fmap fmap fmap fmap fmap -- 10 repetitions
  :: (Functor f1, Functor f2) =>
     (a1 -> a2 -> b) -> f1 a1 -> f1 (f2 a2 -> f2 b)

Interesting, indeed. I’d say the following is a complete catalog of interesting fmap sequences:

1x fmap :: Functor f => (a -> b) -> f a -> f b
3x fmap :: (Functor f, Functor g) => (a -> b) -> f (g a) -> f (g b)
5x fmap :: Functor f => (b -> c) -> (a -> b) -> f a -> f c
8x/12x/16x/… fmap :: (Functor f, Functor g, Functor h) => (a -> b) -> f (g (h a)) -> f (g (h b))

The others on the list besides 5x are all essentially fmap for composed functors, so I wouldn’t call them less easy to understand! I agree with you both that the 5x version is surprising, and that the cycle at the end is surprising as well.

Noticing that (.) is fmap for functions, we get:

    fmap fmap fmap fmap
=== ((fmap fmap) fmap) fmap   -- add implicit parens
=== (((.) fmap) fmap) fmap    -- param to first fmap is a function, so can replace it with (.)
=== (fmap . fmap) fmap        -- convert to infix
=== fmap (fmap fmap)          -- definition of (.)
=== fmap ((.) fmap)
=== fmap (fmap .)

So that means that we also have:

    fmap fmap fmap fmap fmap
=== fmap (fmap .) fmap          -- following from above
=== (.) (fmap .) fmap           -- first fmap is (.) because argument is a function
=== (fmap .) . fmap             -- make it infix
=== \f -> ((fmap .) . fmap) f   -- eta expansion
=== \f -> (fmap .) (fmap f)     -- definition of (.)
=== \f -> fmap . (fmap f)       -- remove explicit parens
=== \f g -> (fmap . (fmap f)) g -- eta expansion
=== \f g -> fmap ((fmap f) g)   -- definition of (.)
=== \f g -> (f <$> g <$>)

And then:

    fmap fmap fmap fmap fmap fmap fmap  -- fmap^7
=== (((fmap .) . fmap) fmap) fmap
=== ((fmap .) (fmap fmap)) fmap
=== (fmap . (fmap fmap)) fmap
=== fmap ((fmap fmap) fmap)
=== fmap (((.) fmap) fmap)
=== fmap (fmap . fmap)

And with 8:

    fmap^8
=== fmap (fmap . fmap) fmap
=== (fmap . fmap) . fmap
=== fmap . fmap . fmap

And so on.

2 Likes