Understanding function composition with negate - haskell

After reading through a page on Higher Order Functions from an awesome site I am still having trouble understanding the negate function paired with function composition.
to be more specific, take this piece of code:
ghci> map (negate . sum . tail) [[1..5],[3..6],[1..7]]
which yields:
[-14,-15,-27]
I re-read the page again, but to be honest, I still have no idea how that line of code produced this answer, if someone could walk me through the process of this I would really appreciate it!

map f [a,b,c] = [f a, f b, f c]
because map f (x:xs) = f x:map f xs - apply f to each element of the list.
So
map (negate.sum.tail) [[1..5],[3..6],[1..7]]
= [(negate.sum.tail) [1..5], (negate.sum.tail) [3..6], (negate.sum.tail) [1..7]]
now
(negate . sum . tail) [1..5]
= negate (sum (tail [1,2,3,4,5]))
= negate (sum [2,3,4,5])
= negate 14
= -14
because (f.g) x = f (g x) and . is right associative, so (negate.sum.tail) xs = (negate.(sum.tail)) xs which in turn is negate ((sum.tail) xs) = negate (sum (tail xs)).
tail gives you everything except the first element of a list: tail (x:xs) = xs, for example tail "Hello" = "ello"
sum adds them up as you expect, and
negate x = -x.
The others work similarly, giving minus the sum of the tail of each list.

To add a different perspective to AndrewC's excellent answer I usually think about these types of problems in terms of the functor laws and fmap. Since map can be thought of as a specialization of fmap to lists we can replace map with the more general fmap and keep the same functionality:
ghci> fmap (negate . sum . tail) [[1..5],[3..6],[1..7]]
Now we can apply the composition functor law using algebraic substitution to shift where the composition is happening and then map each function individually over the list:
fmap (f . g) == fmap f . fmap g -- Composition functor law
fmap (negate . sum . tail) $ [[1..5],[3..6],[1..7]]
== fmap negate . fmap (sum . tail) $ [[1..5],[3..6],[1..7]]
== fmap negate . fmap sum . fmap tail $ [[1..5],[3..6],[1..7]]
== fmap negate . fmap sum $ fmap tail [[1..5],[3..6],[1..7]]
== fmap negate . fmap sum $ [tail [1..5],tail [3..6],tail [1..7]] -- As per AndrewC's explanation
== fmap negate . fmap sum $ [[2..5],[4..6],[2..7]]
== fmap negate $ [14, 15, 27]
== [-14, -15, -27]

Related

Haskell dot operator with sort and (++) [duplicate]

This question already has answers here:
Haskell function composition operator of type (c→d) → (a→b→c) → (a→b→d)
(6 answers)
Closed last year.
I am learning haskell at the moment and trying to figure out all the rules of prefix, infix, precedence, etc.
While trying to implement a function which appends two lists and sorts them I started with:
appendAndSort :: [a] -> [a] -> [a]
appendAndSort = sort . (++)
which does no compile.
Following:
appendAndSort :: Ord a => [a] -> [a] -> [a]
appendAndSort = (sort .) . (++)
on the other hand does work.
Why do I have to add a second dot at sort and parentheses around it?
Let's start with a version that uses explicit parameters.
appendAndSort x y = sort (x ++ y)
Writing ++ as a prefix function rather than an operator yields
appendAndSort x y = sort ((++) x y)
Knowing that (f . g) x == f (g x), we can identify f == sort and g == (++) x to get
appendAndSort x y = (sort . (++) x) y
which lets us drop y as an explicit parameter via eta conversion:
appendAndSort x = sort . (++) x
The next step is to repeat the process above, this time with (.) as the top most operator to write as a prefix function,
appendAndSort x = (.) sort ((++) x)
then apply the definition of . again with f == (.) sort and g == (++):
appendAndSort x = (((.) sort) . (++)) x
and eliminate x via eta conversion
appendAndSort = ((.) sort) . (++)
The last step is to write (.) sort as an operator section, and we're done with our derivation.
appendAndSort = (sort .) . (++)
The expression (f . g) x means f (g x).
Coherently, (f . g) x y means f (g x) y.
Note how y is passed as a second parameter to f, not to g. The result is not f (g x y).
In your case, (sort . (++)) x y would mean sort ((++) x) y, which would call sort with first argument (++) x (the function which prepends the list x to its list argument), and with second argument y. Alas, this is ill-typed since sort only takes one argument.
Consequently, this is also invalid
appendAndSort x y = (sort . (++)) x y
hence so is this
appendAndSort = sort . (++)
By contrast, ((f .) . g) x y does work as expected. Let's compute:
((f .) . g) x y
= -- same reasoning as above, y is passed to (f.), not g
(f .) (g x) y
= -- application associates on the left
((f .) (g x)) y
= -- definition of `(f.)`
(f . (g x)) y
= -- definition of .
f ((g x) y)
= -- application associates on the left
f (g x y)
So this really makes y to be passed to g (and not f).
In my opinion the "idiom" (f .) . g isn't worth using. The pointful \x y -> f (g x y) is much simpler to read, and not terribly longer.
If you really want, you can define a custom composition operator to handle the two-argument case.
(.:) f g = \x y -> f (g x y)
Then, you can write
appendAndSort = sort .: (++)

Haskell point-free style with no functions in the expression

I've been trying to take some simple functions and convert them to point-free style for practice.
I started with something like this:
zipSorted x y = (zip . sort) y $ sort x --zipSorted(x, y) = zip(sort(y), sort(x))
and eventually converted it to
zipSorted = flip (zip . sort) . sort
(I'm not sure if this is even the best way to do it but it works)
Now I'm trying to further reduce this expression by not having it depend on zip and sort at all. In other words, I'm looking for this function: (I think its a combinator if my vocabulary isn't mistaken)
P(f, g, x, y) = f(g(y), g(x))
The fact that sort is present twice but only passed in once hinted to me that I should use the applicative functor operator <*> but I can't figure out how for some reason.
From my understanding, (f <*> g)(x) = f(x, g(x)), so I've tried re-writing the first point-free expression in this form:
flip (zip . sort) . sort
(.) (flip $ zip . sort) sort
(flip (.)) sort $ flip (zip . sort)
(flip (.)) sort $ flip $ (zip .) sort
It seems that sort should be x, (flip (.)) should be f, and flip . (zip .) should be g.
p = (flip (.)) <*> (flip . (zip .))
p sort [2, 1, 3] [4, 1, 5]
yields [(1, 1), (4, 2), (5, 3)] as expected, but now I'm lost on how to pull the zip out. I've tried
p = (flip (.)) <*> (flip . (.))
p zip sort [2, 1, 3] [4, 1, 5]
but this doesn't work. Is there a way to convert that expression to a combinator that factors out zip?
Let's start from the beginning:
zipSort x y = zip (sort y) (sort x)
It's slightly weird that it uses its arguments in the opposite order, but we can fix that later with flip.
Here we have a general pattern of a "combining" function of two arguments (here: zip) being passed two values transformed by another function. If we had the same base argument but different transformers, this would have been a liftA2 pattern:
c (f x) (g x)
==
liftA2 c f g x
But here it's the opposite: We have the same transform function on both sides (here: sort), but different arguments (x and y). That's on:
c (f x) (f y)
==
(c `on` f) x y
In your case we get:
zip (sort y) (sort x)
(zip `on` sort) y x
flip (zip `on` sort) x y
So
zipSort = flip (zip `on` sort) -- or: flip (on zip sort)
We can further pull out zip and sort by recognizing the standard two-argument-into-one-argument-function composition:
(\x y -> f (g x y)) == (f .) . g
giving
zipSort = ((flip .) . on) zip sort
Note that this function is less general than the pointful version, however. The original function has type
(Ord a, Ord b) => [a] -> [b] -> [(b, a)]
but the pointfree version has type
(Ord a) => [a] -> [a] -> [(a, a)]
because unifying the two sorts forces them to have the same type.
I just asked lambdabot for the answer, rather than trying to work it out by hand:
<amalloy> #pl \zip sort x y -> (zip . sort) y $ sort x
<lambdabot> join . (((.) . flip) .) . (.)

What is a "applicative transformation" in naturality of traversability?

The traverse and sequenceA function in Traversable class must satisfy the following 'naturality' laws:
t . traverse f == traverse (t . f)
t . sequenceA == sequenceA . fmap t
for every 'applicative transformation' t. But what is it?
It doesn't seem to work for instance Traversable [] for t = tail:
Prelude> tail . sequenceA $ [[1],[2,3]]
[[1,3]]
Prelude> sequenceA . fmap tail $ [[1],[2,3]]
[]
Nor for t = join (++) (repeat the list twice):
Prelude Control.Monad> join (++) . sequenceA $ [[1],[2,3]]
[[1,2],[1,3],[1,2],[1,3]]
Prelude Control.Monad> sequenceA . fmap (join (++)) $ [[1],[2,3]]
[[1,2],[1,3],[1,2],[1,3],[1,2],[1,3],[1,2],[1,3]]
So for what t they are satisfied?
The Hackage page for Data.Traversable defines an applicative transformation as follows.
[A]n applicative transformation is a function
t :: (Applicative f, Applicative g) => f a -> g a
preserving the Applicative operations, i.e.
t (pure x) = pure x
t (x <*> y) = t x <*> t y
The simplest example of this would be the identity function. id is an applicative transformation. A more specific example for lists would be reverse.
reverse (pure x) = reverse [x] = [x] = pure x
-- (the (<*>) law is more difficult to show)
And you can verify in GHCi that the laws you reference do hold for reverse.
Prelude> reverse . sequenceA $ [[1], [2,3]]
[[1,3],[1,2]]
Prelude> sequenceA . fmap reverse $ [[1], [2,3]]
[[1,3],[1,2]]
Source: Data.Traversable

How do I re-write a Haskell function of two argument to point-free style

I have the following function in Haskell
agreeLen :: (Eq a) => [a] -> [a] -> Int
agreeLen x y = length $ takeWhile (\(a,b) -> a == b) (zip x y)
I'm trying to learn how to write 'idiomatic' Haskell, which seem to prefer using . and $ instead of parenthesis, and also to prefer pointfree code where possible. I just can't seem to get rid of mentioning x and y explicitly. Any ideas?
I think I'd have the same issue with pointfreeing any function of two arguments.
BTW, this is just in pursuit of writing good code; not some "use whatever it takes to make it pointfree" homework exercise.
Thanks.
(Added comment)
Thanks for the answers. You've convinced me this function doesn't benefit from pointfree. And you've also given me some great examples for practicing transforming expressions. It's still difficult for me, and they seem to be as essential to Haskell as pointers are to C.
and also to prefer pointfree code where possible.
Not "where possible", but "where it improves readability (or has other manifest advantages)".
To point-free your
agreeLen x y = length $ takeWhile (\(a,b) -> a == b) (zip x y)
A first step would be to move the ($) right, and replace the one you have with a (.):
agreeLen x y = length . takeWhile (\(a,b) -> a == b) $ zip x y
Now, you can move it even further right:
agreeLen x y = length . takeWhile (uncurry (==)) . zip x $ y
and there you can immediately chop off one argument,
agreeLen x = length . takeWhile (uncurry (==)) . zip x
Then you can rewrite that as a prefix application of the composition operator,
agreeLen x = (.) (length . takeWhile (uncurry (==))) (zip x)
and you can write
f (g x)
as
f . g $ x
generally, here with
f = (.) (length . takeWhile (uncurry (==)))
and g = zip, giving
agreeLen x = ((.) (length . takeWhile (uncurry (==)))) . zip $ x
from which the argument x is easily removed. Then you can transform the prefix application of (.) into a section and get
agreeLen = ((length . takeWhile (uncurry (==))) .) . zip
But, that is less readable than the original, so I don't recommend doing that except for practicing the transformation of expressions into point-free style.
You could also use:
agreeLen :: (Eq a) => [a] -> [a] -> Int
agreeLen x y = length $ takeWhile id $ zipWith (==) x y
Idiomatic Haskell is whatever is easier to read, not necessarily what is most point-free.
As pointed out in Daniel's excellent answer, your problem is to compose f and g when f as one argument and g two. this could be written f ??? g with the correct operator (and with a type signature of (c -> d) -> (a -> b -> c) -> a -> b -> d.
This correspond to the (.).(.) operator (see there) which is sometimes defines as .:. In that case your expression becomes
length . takeWhile (uncurry (==)) .: zip
If you are used to the .: operator, then this point free version is perfectly readable. I can also instead use (<$$$>) = fmap fmap fmap and get
length . takeWhile (uncurry (==)) <$$$> zip
Another concise, point-free solution:
agreeLen = ((length . takeWhile id) .) . zipWith (==)
Equivalently:
agreeLen = (.) (length . takeWhile id) . zipWith (==)

Why does the pointfree version of this function look like this?

I've been playing around with Haskell a fair bit, including practising writing functions in point-free form. Here is an example function:
dotProduct :: (Num a) => [a] -> [a] -> a
dotProduct xs ys = sum (zipWith (*) xs ys)
I would like to write this function in point-free form. Here is an example I found elsewhere:
dotProduct = (sum .) . zipWith (*)
However, I don't understand why the point-free form looks like (sum .) . zipWith (*) instead of sum . zipWith (*). Why is sum in brackets and have 2 composition operators?
dotProduct xs ys = sum (zipWith (*) xs ys) -- # definition
dotProduct xs = \ys -> sum (zipWith (*) xs ys) -- # f x = g <=> f = \x -> g
= \ys -> (sum . (zipWith (*) xs)) ys -- # f (g x) == (f . g) x
= sum . (zipWith (*) xs) -- # \x -> f x == f
= sum . zipWith (*) xs -- # Precedence rule
dotProduct = \xs -> sum . zipWith (*) xs -- # f x = g <=> f = \x -> g
= \xs -> (sum .) (zipWith (*) xs) -- # f * g == (f *) g
= \xs -> ((sum .) . zipWith (*)) xs -- # f (g x) == (f . g) x
= (sum .) . zipWith (*) -- # \x -> f x == f
The (sum .) is a section. It is defined as
(sum .) f = sum . f
Any binary operators can be written like this, e.g. map (7 -) [1,2,3] == [7-1, 7-2, 7-3].
KennyTM's answer is excellent, but still I'd like to offer another perspective:
dotProduct = (.) (.) (.) sum (zipWith (*))
(.) f g applies f on the result of g given one argument
(.) (.) (.) f g applies f on the result of g given two arguments
(.) (.) ((.) (.) (.)) f g applies f on the result of g given three arguments
...
Can do (.~) = (.) (.) (.), (.~~) = (.) (.) (.~), (.~~~) = (.) (.) (.~~) and now let foo a b c d = [1..5]; (.~~~) sum foo 0 0 0 0 results in 15.
But I wouldn't do it. It will probably make code unreadable. Just be point-full.
Conal's TypeCompose provides a synonym for (.) called result. Perhaps this name is more helpful for understanding what's going on.
fmap also works instead of (.), if importing the relevant instances (import Control.Applicative would do it) but its type is more general and thus perhaps more confusing.
Conal's concept of "fusion" (not to be confused with other usages of "fusion") is kind of related and imho offers a nice way to compose functions. More details in this long Google Tech Talk that Conal gave

Resources