[Haskell-beginners] Points-free style

Jonas Almström Duregård jonas.duregard at chalmers.se
Sun Jun 5 18:09:38 CEST 2011


Or you could use curry and uncurry:

sumProducts = curry $ sum . uncurry (zipWith (*))

On 5 June 2011 17:40, Daniel Fischer <daniel.is.fischer at googlemail.com>wrote:

> 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 at haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/beginners/attachments/20110605/0d8d6975/attachment.htm>


More information about the Beginners mailing list