Larry
Larry

Reputation: 938

What is ((+) . (+)) in Haskell?

In ghci,

:t ((+).(+))
> ((+).(+)) :: (Num (a -> a), Num a) => a -> (a -> a) -> a -> a

but what is this thing? Can any one give me an example of the use of this please?

How can one composite 2 functions that take 2 parameters each? for example, how does (map.map) :: (a -> b) -> [[a]] -> [[b]] work?

(^.^) (-.-) (+.+) (can't help making funny faces out of it. PS: I thought it means to tell the compiler how you feel today)

Upvotes: 11

Views: 1166

Answers (4)

Lee Duhem
Lee Duhem

Reputation: 15121

g . f means applying f first, then applying g to the result of f, in other words, it can be rewritten as

\x -> g (f x)

Therefore,

((+) . (+))

can be rewritten as

\x -> (\y -> (x +) + y)

According to the type of (+), in the above lambda abstraction, x needs having type Num a => a, y having type Num a => Num (a -> a), as inferred by ghci

(Num a, Num (a -> a)) => a -> (a -> a) -> a -> a

So if we have made a -> a an instance of type class Num a, for example, here is one way to achieve that

    {-# LANGUAGE FlexibleInstances #-}

    instance (Num a) => Num ((->) a a) where
        a + b = \x -> a x + b x
        a * b = \x -> a x * b x
        a - b = \x -> a x - b x
        negate a = \x -> negate $ a x
        abs a = \x -> abs $ a x
        signum a = \x -> signum $ a x
        fromInteger n = \_x -> fromInteger n

we can use ((+) . (+)) like this

    *Main> ((+) . (+)) 1 (+2) 3
    9

Because ((+) . (+)) equals

\x -> \y -> (x +) + y

which means ((+) . (+)) 1 (+2) 3 equals

((1 + ) + (+ 2)) 3

according to the definition of (+) in the instance of (a -> a), ((1+) + (+2)) equals

\x -> (1+x) + (x+2)

So ((1+) + (+2)) 3 equals (1+3) + (3+2), which is 9, as given by ghci.


map . map is similar, as indicated by its type, given by ghci:

    (a -> b) -> [[a]] -> [[b]]

the first argument of that function should be a function of type a->b, the second argument should be a nested list of type [[a]], and that composed function map . map will apply the first argument to each element of each list in its second argument, return a nested list of type [[b]]. For example

    *Main> (map . map) (+1) [[1,2], [3,4,5]]
    [[2,3],[4,5,6]]

Upvotes: 1

ecatmur
ecatmur

Reputation: 157484

f . f can make sense for a binary function f; it entirely depends on the signature of f. The key is that partial application of the inner f to its first argument has to give something that is a valid input to the outer f.

For example, with map :: (a -> b) -> [a] -> [b], we can hand-unify map . map:

map :: (a -> b) -> [a] -> [b]
map :: (c -> d) -> [c] -> [d]
. :: (e -> f) -> (f -> g) -> (e -> g)

e === a -> b
f === [a] -> [b]
  === c -> d
c === [a]
d === [b]
g === [c] -> [d] === [[a]] -> [[b]]

map . map :: e -> g
    :: (a -> b) -> [[a]] -> [[b]]

So, as expected, map . map takes a transformation a -> b and gives us a transformation from list-of-list-of-a to list-of-list-of-b. We can check this by hand-applying (map . map) f ll:

(map . map) f ll
    = map (map f) ll
    = map (\l -> map f l) ll

But if we try the same with (+) :: Num a => a -> a -> a, it all goes horribly wrong:

(+) :: Num a => a -> a -> a
(+) :: Num b => b -> b -> b
. :: (c -> d) -> (d -> e) -> (c -> e)

c === a
d === a -> a
  === b
e === b -> b === (a -> a) -> (a -> a)

(+) . (+) :: c -> e
    :: (Num a, Num (a -> a)) => a -> (a -> a) -> (a -> a)

So, partial application of the inner + is giving a transformation a -> a, the outer + is then trying to add that transformation to another function which we are expected to supply. Since it doesn't make sense to add transformations, the overall (+) . (+) doesn't make sense either.

Upvotes: 2

leftaroundabout
leftaroundabout

Reputation: 120751

Num (a -> a) (or e.g. Eq (a -> a)) is basically an indicator for code that doesn't make any sense1, but the compiler nevertheless deduces a (nonsensical) type signature. Usually it turns up when you've forgotten to apply a function to some argument. In this case, obviously (+) needs a "plain number" argument to become a "simple function" to which you can post-compose another such function.

However, (a -> a) is sure enough a valid type of functions that you can also pass on, just not as numbers. For instance, map . (+) is a perfectly good combination:

Prelude> :t map . (+)
map . (+) :: Num b => b -> [b] -> [b]
Prelude> zipWith (map . (+)) [10,20,30] [[1,2],[3,4]]
[[11,12],[23,24]]

because map actually expects a function as its first argument. Similarly,

Prelude> zipWith (map . map) [(+10),(+20),(+30)] [[[1,2],[3,4]],[[5,6]]]
[[[11,12],[13,14]],[[25,26]]]

Here, the right map takes a simple function (like numerical increment) and returns the corresponding list-map function. That function is then fed to the left map resulting in a function that maps nested lists.


1Actually, you can force it to make sense by defining

instance (Num a) => Num (b -> a) where
  fromInteger x = const $ fromInteger x
  f + g = \x -> f x + g x

Personally, I'm not a fan of this. It confusing, for instance let a = 3 in 4 a produces 4 when most people would expect multiplication to 12.

Upvotes: 12

Riccardo T.
Riccardo T.

Reputation: 8937

That won't work. As ghci tells you, you should have an instance of Num (a -> a) in order to use that function, but a -> a obviously isn't a number.

This is because (+) assumes to get two numerical parameters, but with the composition you wrote you gave it a partially applied function instead, the a -> a mentioned in the computed type signature.

Usually, when composing functions which take more than one parameter, you partially apply them first in order to reduce them to functions which take just one parameter, e.g. (+1) . (*2) applied to 3 will result in (3 * 2) + 1 = 7

Upvotes: 3

Related Questions