
Hi folks, I am working my way through "Learn You a Haskell for Great Good" and have reached page 84, where the book recommends that you define your functions in a "points-free style", using the "." and "$" operators. Now I have: sumProducts' :: Num a => [a] -> [a] -> a sumProducts' x y = sum (zipWith (*) x y) I would like to eliminate the "x" and the "y" in the definition, but all I have managed to contrive is: sumProducts :: Num a => [a] -> [a] -> a sumProducts x = sum . zipWith (*) x How do I proceed from here? Any advice is welcome :) Many thanks in advance, /Alexander

You can use the fun (.).(.) operator :D
sumProducts :: Num a => [a] -> [a] -> a
sumProducts = ((.).(.)) sum (zipWith (*))
In all seriousness though, points-free isn't always the most readable way to go.
On Sun, Jun 5, 2011 at 11:09 PM, Alexander Shendi
Hi folks,
I am working my way through "Learn You a Haskell for Great Good" and have reached page 84, where the book recommends that you define your functions in a "points-free style", using the "." and "$" operators.
Now I have:
sumProducts' :: Num a => [a] -> [a] -> a sumProducts' x y = sum (zipWith (*) x y)
I would like to eliminate the "x" and the "y" in the definition, but all I have managed to contrive is:
sumProducts :: Num a => [a] -> [a] -> a sumProducts x = sum . zipWith (*) x
How do I proceed from here? Any advice is welcome :)
Many thanks in advance,
/Alexander
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

On Sonntag, 5. Juni 2011, 17:09, Alexander Shendi wrote:
Hi folks,
I am working my way through "Learn You a Haskell for Great Good" and have reached page 84, where the book recommends that you define your functions in a "points-free style", using the "." and "$" operators.
Now I have:
sumProducts' :: Num a => [a] -> [a] -> a sumProducts' x y = sum (zipWith (*) x y)
I would like to eliminate the "x" and the "y" in the definition, but all I have managed to contrive is:
sumProducts :: Num a => [a] -> [a] -> a sumProducts x = sum . zipWith (*) x
How do I proceed from here? Any advice is welcome :)
Many thanks in advance,
/Alexander
First, (mentally) insert parentheses: sumProducts x = sum . (zipWith (*) x) Now, write the composition as a prefix application of (.), sumProducts x = (.) sum (zipWith (*) x) = ((.) sum) (zipWith (*) x) which has the form f (g x), with f = (.) sum and g = zipWith (*), so it's (f . g) x, which expands to (((.) sum) . (zipWith (*))) x and now the argument can easily be dropped, giving sumProducts = ((.) sum) . (zipWith (*)) now to make it look a little nicer, we can remove unnecessary parentheses and write (.) sum as a section, sumProducts = (sum .) . zipWith (*) Generally, pointfreeing goes f (g x) ~> f . g f (g x y) ~> (f .) . g f (g x y z) ~> ((f .) .) . g Play with it and get a little experience, but don't overuse it. Nobody really wants to come across a pointfree version of \a b c d e f g h -> foo (bar a b) (baz c d e) f (quux g h) (and that's not even repeating or flipping arguments)

On 5 June 2011 16:40, Daniel Fischer
\a b c d e f g h -> foo (bar a b) (baz c d e) f (quux g h)
Just for the fun of it: $ pointfree "\a b c d e f g h -> foo (bar a b) (baz c d e) f (quux g h)" flip flip quux . ((flip . ((flip . ((flip . ((flip . (((.) . (.)) .)) .)) .)) .)) .) . flip flip baz . (((.) . (.) . (.) . foo) .) . bar using: http://hackage.haskell.org/package/pointfree Cheers, Ozgur

Or you could use curry and uncurry:
sumProducts = curry $ sum . uncurry (zipWith (*))
On 5 June 2011 17:40, Daniel Fischer
On Sonntag, 5. Juni 2011, 17:09, Alexander Shendi wrote:
Hi folks,
I am working my way through "Learn You a Haskell for Great Good" and have reached page 84, where the book recommends that you define your functions in a "points-free style", using the "." and "$" operators.
Now I have:
sumProducts' :: Num a => [a] -> [a] -> a sumProducts' x y = sum (zipWith (*) x y)
I would like to eliminate the "x" and the "y" in the definition, but all I have managed to contrive is:
sumProducts :: Num a => [a] -> [a] -> a sumProducts x = sum . zipWith (*) x
How do I proceed from here? Any advice is welcome :)
Many thanks in advance,
/Alexander
First, (mentally) insert parentheses:
sumProducts x = sum . (zipWith (*) x)
Now, write the composition as a prefix application of (.),
sumProducts x = (.) sum (zipWith (*) x) = ((.) sum) (zipWith (*) x)
which has the form f (g x), with f = (.) sum and g = zipWith (*), so it's
(f . g) x, which expands to
(((.) sum) . (zipWith (*))) x
and now the argument can easily be dropped, giving
sumProducts = ((.) sum) . (zipWith (*))
now to make it look a little nicer, we can remove unnecessary parentheses and write (.) sum as a section,
sumProducts = (sum .) . zipWith (*)
Generally, pointfreeing goes
f (g x) ~> f . g f (g x y) ~> (f .) . g f (g x y z) ~> ((f .) .) . g
Play with it and get a little experience, but don't overuse it. Nobody really wants to come across a pointfree version of
\a b c d e f g h -> foo (bar a b) (baz c d e) f (quux g h)
(and that's not even repeating or flipping arguments)
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

Alexander Shendi
I am working my way through "Learn You a Haskell for Great Good" and have reached page 84, where the book recommends that you define your functions in a "points-free style", using the "." and "$" operators.
Now I have:
sumProducts' :: Num a => [a] -> [a] -> a sumProducts' x y = sum (zipWith (*) x y)
I would like to eliminate the "x" and the "y" in the definition, but all I have managed to contrive is:
sumProducts :: Num a => [a] -> [a] -> a sumProducts x = sum . zipWith (*) x
How do I proceed from here? Any advice is welcome :)
Honestly, don't! The definition you have there is perfectly fine. Please remember: If the point-free style isn't easy to write, it's probably also not easy to read. In general, I would refrain from removing the points from functions with more than one argument. But the rule I use is a bit more complicated: When I have a function with two arguments and both arguments have the same "subjectness" or are combined in a "monoidic" way, then I don't remove the points, unless the point-free style is really trivial to derive. Examples: -- Good (because trivial): add = (+) -- Good (very readable, point-free would be pointless): hypot x y = sqrt (x^2 + y^2) -- Bad (I don't even want to derive this by hand): hypot = undefined However, in many cases the two arguments of a binary function have a different "subjectness". The last argument is the subject to be transformed and the earlier argument modifies the transformation, but is not itself a subject to be transformed. In these cases I remove only the last point: -- Bad: chunksOf n xs = takeWhile (not . null) (map (take n) (iterate (drop n) xs)) -- Good: chunksOf n = takeWhile (not . null) . map (take n) . iterate (drop n) -- Bad: chunksOf = liftA2 ((.) . (takeWhile (not . null) .)) (map . take) (iterate . drop) Use point-free style, when it actually makes your code more readable! Point-free style is used to give definitions in terms of data flow instead of function applications. Then there are the many cases, where an argument is just passed to multiple functions and then the results of the individual functions are combined. In this case you can use the fact that (e ->) is an applicative functor. Simple example: Calculating the average value of a list. -- Good: average xs = sum xs / fromIntegral (length xs) -- Perhaps better: average = liftA2 (/) sum (fromIntegral . length) To get back to your example: The two arguments your function has have the same "subjectness". They are combined in a "monoidic" way and thus what you really have is a mathematical formula. Though not always it's often difficult to get rid of the points in a formula. Also even if it's easy, it doesn't always improve the readability in any way. Example: -- Good: \x -> 2*x + 1 -- Bad: (+1) . (2*) -- Matter of taste (I still don't like it): let double = (2*) in succ . double Greets, Ertugrul -- nightmare = unsafePerformIO (getWrongWife >>= sex) http://ertes.de/
participants (6)
-
Alexander Shendi
-
Daniel Fischer
-
Ertugrul Soeylemez
-
Jonas Almström Duregård
-
Lyndon Maydwell
-
Ozgur Akgun