Question on map . map sum

I have a number of questions on these examples but am going to start with 1 as to not make it too confusing

> fmap sum [Just 1, Just 2, Just 3] -- [A]
[1,2,3]

> (fmap . fmap) sum Just [1, 2, 3] -- [B]
Just 6

> fmap sum (Just [1,2,3]) -- [C]
Just 6

Given the type of sum

sum :: (Foldable t, Num a) => t a -> a

> fmap sum [Just 1]

[1]

I think, perhaps incorrectly

  • [] is the t/foldable
  • a is Maybe a (or perhaps Maybe Int but not sure that matters for the question)
  • So you could say fmap puts sum inside of [] and sums Just 1 to 1.

Why does th Just go away? It would make sense if t a represented Just 1 so that t a -> a but that seems pretty wrong.

1 Like

It might be surprising, but there is a Foldable instance for Maybe so sum (Just n) == n and sum Nothing == 0 here.

The fmap lifts sum into [] (Lists have a Functor instance) - so:

fmap sum [Just 1, Just 2, Just 3]
= [sum (Just 1), sum (Just 2), sum (Just 3)]
= [1,2,3]
1 Like

So if you’re not already, I recommend using the Haskell Language Server. In the screenshot below, you can see the type of sum in your first example, which I obtained by mousing over sum. Both its general type and its specific type in this context, namely ``Maybe Integer → Integer`.

This confirms your doubt about what t is. It’s not [] here, it’s Maybe.

What’s happened is that fmap is expecting a function which it can apply to each element of the list. sum is the function you’ve given it.

I think the main thing to learn here is how to use the Haskell Language Server (or more manually, inserting _ in a repl) to see the types in context. Haskell’s type inference is extremely useful for this kind of debugging.

Yep, your guess is correct. The fact that Maybe has a Foldable instance is certainly a bit weird in the sense that you don’t usually think of Maybe a as being a collection of as, but if you look at the definition of the instance, you’ll see it follows the expectations of the Foldable typeclass.

What I did to confirm this was to go to the Foldable package, and look for an instance Foldable Maybe, which indeed I found. You can click to view the source, and see exactly how it’s defined. But the easiest thing to do is to try sum $ Just (1 :: Int) in ghci, followed by sum (Nothing :: Maybe Int)

Both answers were very helpful. I totally get that now.

[] is the structure fmap lifts sum over and Just 1 is the Foldable that gets summed. That covers [A]

I do use Haskell language server, but write questions is an different editor.

So for [C]

Just is the structure lifted over and [1,2,3] is the Foldable - correct?

That leaves [B]


> (fmap . fmap) sum Just [1, 2, 3] -- [B]

Just 6

I’m thinking the right most fmap lifts sum over Justand sums [1,2,3] to get Just 6. But that leaves nothing for the left most fmap to do so I seem to be wrong.

Additionally fmap sum Just [1,2,3] is an error, it needs parens fmap sum (Just [1,2,3]) so I’m wondering why the parens are not needed?

Just is the structure lifted over and [1,2,3] is the Foldable - correct?

Exactly!

[B] is a bit of a nightmare (definitely would be regarded as bad style in actual Haskell code) but let’s see.

OK, your observation about the parens is a good one; something else interesting is going on. In particular, this is a case of the (a ->) Functor.

To build up to [B], first consider

ex2 = fmap (>3) (+1)

Do you understand what fmap is mapping over here? I’ll let you have a go with this one, since it’s a fun puzzle, and if you’re stuck, let me know.

Coming-up empty handed on that one.

I don’t know what (a ->) means but I’ll guess “partially applied type or function”

ex2 = fmap (>3) (+1)
> :t ex2
ex2 :: Integer -> Bool

If I match ex2 up to the type for fmap

fmap :: Functor f => (a -> b) -> f a -> f b
fmap                   (>3)      (+1)   Bool

But Bool has no Functor instance so not helpful.

Rewriting it like this may be a clue but not one that helped me.

ex3 x = ((>3) . (+1)) x

Trying to put it into words: fmap lifts the function (>3) over the function (+1)

So maybe functions are functors? This article seems the say they aren’t in a way but they can be used as such in the case of a function which takes one argument which (+1) clearly is. I didn’t really understand much of the article.

Yep, let me explain.

So consider the type

Int -> Bool

One can think of (Int ->) as a thing which takes a type, here Bool, and “returns” the type Int -> Bool. In the same way, Maybe takes any type, e.g. Bool, and returns a new type, Maybe Bool.

Being a bit more precise, we can say that Maybe has kind Type -> Type, and similarly (Int ->) has kind Type -> Type.

(If that much is unclear, let me know, as the rest won’t make sense if the above doesn’t)

OK, so a prerequisite for having a Functor instance is being of kind Type -> Type. For example, Int could never have a Functor instance; it’s just the wrong kind of thing.

(Int ->) (or for that matter (a ->) for any a) has the right kind, but does it have a Functor instance? What would it mean to have one? It would mean we need to write a version of fmap of type:

(a -> b) -> (Int -> a) -> (Int -> b)

(It’s worth trying to write this yourself as an exercise. Hint: it is a very short definition).

So what’s happening in ex2, and also in [B], is that an fmap is being used with an (a ->) instance.

One way to look at this that might help is to use a type synonym:

type ReaderInt Bool = Int -> Bool

My claim is that ReaderInt is a Functor (in fact a very important and useful functor which comes up a lot)

There’s more to say but I’ll stop there for now.

Right, but you got it slightly wrong.

In fact, it’s:

fmap :: Functor f => (a -> b) -> f a -> f b
fmap                   (>3)      (+1)   (func :: Int -> Bool)

ex2 has type Int -> Bool, and you can find out what it does by applying it to integers.

By the way, this all might seem a bit abstruse, but it’s (up to naming conventions) precisely the Reader functor/monad, so it’s definitely a worthwhile thing to learn.

I think I got your message up to the type signature you asked me to write a functor instance (call that Part 1). I was going to give you how I interpreted Part 1 but it led be to look at this and I’m wondering if I’m on to something here.

ghci> aa = 3 :: Int

fmap :: Functor f =>              (a -> b) -> f a   -> f b      -- [A]

ghci> :t fmap (>aa)
fmap (>aa) :: Functor f =>                    f Int -> f Bool   -- [B]

ghci> :t fmap (>aa) (+1)
fmap (>aa) (+1) ::                            Int   -> Bool     -- [C]

ghci> :t fmap (>aa) (+1) 1
fmap (>aa) (+1) 1 ::                                   Bool     -- [D]

The interesting part is how the f goes away.

fmap (>3)        :: f Int -> f Bool  -- [B]
fmap (<3) (+1)   ::   Int ->   Bool  -- it removed the Functor [C]

One way to look at that would be that the next param needed in [B] was a Functor int but when given (+1) it received a Functor but is still waiting for the Int part of Int -> Bool.

:t (+1)
(+1) :: Num a => a -> a

So (+1) is kind * -> * so meets on prerequisite of a functor.

Am I getting there?

This is not what’s happening, instead it matches up like this:

fmap (>3)        :: f        Int -> f        Bool
fmap (>3) (+1)   ::                 (Int ->) Bool
(+1)             :: (Int ->) Int

You’re onto something, but not quite there yet.

The interesting part is how the f goes away.

Does it go away? What if (f Bool) is (Int -> Bool).

So (+1) is kind * -> * so meets on prerequisite of a functor.

So a common mistake people make when learning Haskell (at least I did) is to confuse types and values. Your statement that (+1) has kind * -> * is simply ill-formed, because (+1) is not a type. It’s a value, so it has a type, and its type, which is Int -> Int, has a kind, which is * (sometimes also written Type). The confusion is that you’ve seen (+1), which is a partially applied value, and confused it with something which is a partially applied type.

On the other hand, Maybe is a type that has kind * -> *. There are no values of type Maybe, although there are values of e.g. Maybe Int.

Let me know if all that makes sense. I think if it does then you’re over the hurdle of understanding what’s going on.

1 Like

I’m 0 for 2 in lining up types :slight_smile:

Just to be sure so I don’t spend time thinking about it the wrong way. Is this how you are lining-up the types?

Yes.

So f is instantiated to be equal to that Int -> part, which I think you can only actually write in Haskell as (->) Int, but that means the same thing (just like how (+) 1 2 means the same thing as 1 + 2).

I actually see now the (>3) and (<3). I intended that to both be the same thing. I meant this aligning in the same way for example these simpler functions align:

not      :: Bool -> Bool -- function
not True ::         Bool -- applied form (result)
True     :: Bool         -- argument

So the function is not the applied form is not True and the argument is True.

In your case the function is fmap (>3), the applied form is fmap (>3) (+1) and the argument is (+1).

Something that is probably obvious, but maybe worth adding is that (->) has kind * -> (* -> *), and like value-level partial application, takes its two type arguments one by one. So (->) a has kind * -> *, and (->) a b (usually written a -> b) has kind *.

And the Functor instance for (->) a, which you can find on Hackage, looks like:

instance Functor ((->) r) where
    fmap = (.)

I have a guess how (fmap . fmap) sum Just [1, 2, 3] works, not sure if it’s correct.

We can view (fmap . fmap) sum as lift sum :: t b -> b twice with different functors, so it has type (Functor f1, Functor f2, Foldable t, Num b) => f1 (f2 (t b)) -> f1 (f2 b).

Just has type a -> Maybe a, which can be viewed as wrapped with two functors. One is ((->) a), another is Maybe. Rewrite it as ((->) a) (Maybe a).

To apply the Just with (fmap . fmap) sum, we have f1 :: (->) a, f2 :: Maybe, and a :: t b.

So, finally, we have

(fmap . fmap) sum Just :: f1 (f2 b)
                       :: ((->) a) (Maybe b)
                       :: t b -> Maybe b

Here t is [].

Haven’t forgotten this question. You have opened my eyes to a few things and I think it will be helpful if I go back and re-read about Functor, so I’m in the middle of doing that.

If I look at

> :t (fmap . fmap)
(fmap . fmap) :: (Functor f1, Functor f2) => (a -> b) -> f1 (f2 a) -> f1 (f2 b)

Which fmap is Functor f1 and which is Functor f2, [A] or [B]?

  (fmap . fmap)
-- [A]     [B]

I’m guessing since composition goes right to left that [B] is Functor f1?

I think f1 and f2 are types which have a Functor instance written for them.

f1 (or f2) can certainly be []. However, the type signatures places no restriction; f1 or f2 could be any type which have a Functor instance. But perhaps I am probably misunderstanding what you mean by [A] or [B] in that context. Could you clarify ?