Re: Point-free style (Was: Things to avoid)

Jan-Willem Maessen wrote: ] Is it really clear or obvious what ] ] > map . (+) ] ] means? Perhaps the following two examples might be more convincing:
u=uncurry e=((partition $ u(==)).) . zip f x=(x\\).(x\\)
It is obviously clear what 'e' and 'f x' do. The second example, which even contains the type signature to increase comprehension:
prod:: (MCompose a b (c -> d) e, MCompose f g (b,g) d) => (h -> a) -> (c -> f) -> h -> e
prod = (. ((. (,)) . mcomp)) . mcomp
Here `prod' is indeed the categorical product. The second example is taken from http://pobox.com/~oleg/ftp/Haskell/categorical-maxn.lhs which has the following comment about that code fragment: The constraints in the prod's type are intricately related. The final expression for prod bears some similarity with Unlambda code. Perhaps because both Unlambda and the category theory eschew "elements" in favor of combinations of arrows. Probably there are other similarities.

On Thu, 10 Feb 2005 18:04:26 -0800 (PST), oleg@pobox.com
Jan-Willem Maessen wrote: ] Is it really clear or obvious what ] ] > map . (+) ] ] means?
Perhaps the following two examples might be more convincing:
u=uncurry e=((partition $ u(==)).) . zip f x=(x\\).(x\\)
It is obviously clear what 'e' and 'f x' do.
I would have to disagree there... Show that to someone who's just taken an intro course in Haskell and ask them what they mean and you'll see what I mean. Even if they know how the . operator works it would still take several minutes of reasoning to figure out what it means. Only if you've taken considerable time to get a solid intuition for points-free style by using it extensively would the last two of those example ever be "obvious". I am, like some others, of the opinion that using points-free style almost always makes the code less clear for basically everyone else. Trivial examples such as:
double = 2* can be tolerated, but in general you only stand to gain clarity from exlicitly writing out the parameters to the function.
Points free style is cool in a geeky sort of way, but not really all that useful when you're trying to write clear code that people can actually understand. /S -- Sebastian Sylvan +46(0)736-818655 UIN: 44640862

Sebastian Sylvan writes:
Points free style is cool in a geeky sort of way, but not really all that useful when you're trying to write clear code that people can actually understand.
That's true of badly-written point-free code, certainly. However, anyone
who has spent time doing shell scripting in UNIX should be fairly
comfortable with function composition in principle.
Here's some code I wrote when I was playing around with an RDF
combinator library:
tsArcFwd s p = maybe [] id . Map.lookup (s,p) . store_sp
tsArcBwd p o = maybe [] id . Map.lookup (p,o) . store_po
I suppose a point-wise version of these would look like this:
tsArcFwd s p ts = maybe [] id (Map.lookup (s,p) (store_sp ts))
or this:
tsArcFwd s p ts =
case Map.lookup (s,p) (store_sp ts) of
Just xs -> xs
Nothing -> []
Here's another one:
addTriple (s,p,o) = addArc s p o . addNode s . addNode p . addNode o
I like to think it's pretty straightforward.
I suppose you could argue that these are examples of "semi-point-free"
style, or something. Certainly, I wouldn't want to rewrite tsArcFwd or
addTriple into fully point-free style.
--
David Menendez

David Menendez wrote:
Here's another one:
addTriple (s,p,o) = addArc s p o . addNode s . addNode p . addNode o
I like to think it's pretty straightforward.
I suppose you could argue that these are examples of "semi-point-free" style, or something. Certainly, I wouldn't want to rewrite tsArcFwd or addTriple into fully point-free style.
This is closest to where my code tends to end up. I like some of the implications of point-free style, but I generally tend to avoid point-free stuff involving functions which take more than one argument - in that case, I'll generally make at least one of the arguments explicit. It helps me write the function and makes the code more self-documenting - at least to my mind. Of course, point-free code becomes much clearer with a nice type signature. As does pretty much all other Haskell code.

G'day all.
Quoting Sebastian Sylvan
I am, like some others, of the opinion that using points-free style almost always makes the code less clear for basically everyone else.
Count me among the "some others". There are basically two situations where "pointless style" makes sense for me. 1. Currying, when passing a value to a higher-order function. Compare: map head xss with: map (\xs -> head xs) xss 2. Currying, at the level of a rule. Compare: heads xss = map head xss with: heads = map head Note that "currying" applies to operator sections too. The idiom of "pipelined functions" deserves its own special mention: countlines = length . lines But this is really a shorthand for: countlines cs = length . lines $ cs I pretty much never use any other uses of pointless style. Mind you, I don't do any arrow programming. Mind you, this is probably why I don't do any arrow programming. :-) Cheers, Andrew Bromage

ajb@spamcop.net wrote:
Note that "currying" applies to operator sections too. The idiom of "pipelined functions" deserves its own special mention:
countlines = length . lines
But this is really a shorthand for:
countlines cs = length . lines $ cs
an interesting use of $ (in conjunction with another infix). I usually write: countlines cs = length $ lines cs or more general f = g . h . i becomes f x = g $ h $ i x Christian
participants (6)
-
ajb@spamcop.net
-
Christian Maeder
-
David Menendez
-
Matthew Walton
-
oleg@pobox.com
-
Sebastian Sylvan