Re: [Haskell-cafe] Re: Point-free style (Was: Things to avoid)

2005-02-10 Thread ajb
G'day all.

Quoting Sebastian Sylvan <[EMAIL PROTECTED]>:

> 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
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Point-free style (Was: Things to avoid)

2005-02-10 Thread David Menendez
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 <[EMAIL PROTECTED]> | "In this house, we obey the laws
  |of thermodynamics!"
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Point-free style (Was: Things to avoid)

2005-02-10 Thread Sebastian Sylvan
On Thu, 10 Feb 2005 18:04:26 -0800 (PST), [EMAIL PROTECTED] <[EMAIL PROTECTED]> 
wrote:
> 
> 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
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Point-free style (Was: Things to avoid)

2005-02-10 Thread oleg

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.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Point-free style

2005-02-10 Thread Fritz Ruehr
Jerzy pointed out the utility (well, at least the *possibility*) of 
expressions such as the following when writing points-free code (or 
perhaps per Matthew it should be "pointy code" :) ):

(.) . (.) . (.)
This is the function which composes a 1-argument function with a 
3-argument function (and the pattern generalizes to n in the second 
functional argument). I sometimes itch to use the n=2 case, as in the 
following, but good sense usually gets the better of me:

(.<) = (.) . (.)
(this allows, for example, concat .< replicate).
One gets the impression of some odd kind of Morse code, or perhaps 
"smileys" / "emoticons" ...

The attached file gives some more detail and examples for the 
points-free fans.

  --  Fritz



Comp.hs
Description: application/text
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Point-free style (Was: Things to avoid)

2005-02-10 Thread Matthew Roberts
I have to agree (although I suspect few others will :))
matt
On 11/02/2005, at 1:23 AM, Jan-Willem Maessen wrote:
On Feb 10, 2005, at 6:50 AM, Henning Thielemann wrote:
On Thu, 10 Feb 2005, [ISO-8859-1] Thomas Jäger wrote:
Altogether, the spirit of the page seems to be "use as little
syntactic sugar as possible" which maybe appropriate if it is aimed 
at
newbies, who often overuse syntactic sugar (do-notation).
This overuse is what I observed and what I like to reduce. There are 
many
people advocating Haskell just because of the sugar, which let 
interested
people fail to see what's essential for Haskell. When someone says to 
me
that there is a new language which I should know of because it 
supports
definition of infix operators and list comprehension, I shake my head 
and
wonder why he don't simply stick to Perl, Python, C++ or whatever.
If you're trying to avoid obscurity, why advocate point-free style?
I ask this question to be deliberately provocative; I'm not trying to 
single you out in particular.  So, to everybody: What's so great about 
point-free style?

Is it really clear or obvious what
> map . (+)
means?  Contrast this with
> \n -> map (+n)
or
> \n xs -> map (+n) xs
I submit that, while it is possible to develop a reading knowledge of 
point-free style, non-trivial use of point-free 
computations---compositions of functions with arity greater than 1, as 
above, compositions of sections of composition or application, arrow 
notation without the sugar, and so forth---will always be more 
difficult to read and understand than the direct version.  I submit 
that this is true even if one is familiar with point-free programming 
and skilled in its use.
Even something as simple as eta-reduction (as in the second and third 
functions above) can seriously obscure the meaning of program code by 
concealing the natural arity of a function.

-Jan-Willem Maessen
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Point-free style

2005-02-10 Thread Matthew Roberts
just a few quick observations
comming from an imperative background, I found point free code very 
difficult to understand when learning Haskell.  It is not that it is 
hard to understand the concepts of point-free style, it is that it is 
hard to know when something is point-free.

It is "another option" and I think the best way to make a language 
"readable" is to stick to a few simple rules and clean semantics.  
Since, you can't write all your code point-free, I say write it all 
pointed - consistency is the thing!

also, the term "point free" confused me for quite a while.  Point-free 
code has lots of points (periods) and so I kept thinking it was the 
other way around.

matt
On 11/02/2005, at 7:19 AM, Henning Thielemann wrote:
On 10 Feb 2005, Peter Simons wrote:
Now compare that to the following function, which does the
some thing but without point-free notation:
  incrEach' :: Integer -> [Integer] -> [Integer]
  incrEach' i is = is >>= \i' -> return (i'+i)
point-free again
is >>= return . (i+)
:-]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Things to avoid (Was: Top 20 ``things'' to know in Haskell)

2005-02-10 Thread Iavor Diatchki
Hello,

> ...
> Yeah, as long as it is explained and clearly marked as an opinion (as
> it is now), that's ok. One reason that I got so excited about that is
> because I don't like the current situation with (n+k)-patterns:
> Everybody says they're evil, but hardly anybody can explain why he
> thinks so.

I think 'evil' may be a little too strong.  I think the usual argument
against 'n+k' patterns is that:
i) they are a very special case, and may be confusing as they make it
look as if '+' was a constructor, which it is not
ii) they lead to some weird syntactic complications, e.g.
x + 3 = 5 defines a function called '+', while (x + 3) = 5 defines a
variable 'x' to be equal to 2.
and there is other weirdness like:
x + 2 : xs = ...
does this define '+' or ('x' and 'xs')?  i think it is '+'.  anyways
when used as intended 'n+k' are cute.   it is not clear if the
complications in the language specification and implementaions are
worth the trouble though.
-iavor
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Things to avoid (Was: Top 20 ``things'' to know in Haskell)

2005-02-10 Thread Remi Turk
On Wed, Feb 09, 2005 at 02:54:12PM +0100, Henning Thielemann wrote:
> 
> On Wed, 9 Feb 2005, Henning Thielemann wrote:
> > Is there also a Wiki page about things you should avoid?
> 
> Since I couldn't find one, I started one on my own:
> 
> http://www.haskell.org/hawiki/ThingsToAvoid
> 
> I consider 'length', guards and proper recursion anchors.

Okay, I still definitely have some problems with the part about
guards, and I'm going on bothering you about it because it's The
HaWiki, and not just your site ;)

First of all, I rarely combine multiple-defs with guards, and
even more rarely omit an otherwise- or all-variables-and-no-guard
case, so I may just have avoided all stated problems that way.

Second, I don't have much experience with Haskell-newbies
(besides my own (hopefully) past and the ones on the mailing
lists), so my assumptions about common pitfalls may well be
wrong.

That said, the points I don't agree with:

1) It's talking about the compiler having difficulty with some
   warnings when using guards. In none of the examples given (the
   primes) I got any warnings, and from a quick made up example
   it appears that at least GHC is quite capable of detecting
   non-exhaustive patterns even when combining patterns and
   guards. In case you're talking about something like this:

   f x | odd x  = ...
   | even x = ...

   GHC does complain. I would also call it Bad Code,
   but if it's what you mean, _this_ example should be in the
   wiki. (As in: blahblah, it actually _is_ exhaustive, but in
   general requires solving the halting-problem to prove or
   something like that ;)

   Also, when compiling them (even _without_ optimizations) the
   three examples yield _exactly_ the same code, except for the
   fact that the if-then-else example moves the "n == 2"
   comparision to the RHS of the expression. This move can just
   as easy be done on the guarded version, which removes any
   difference in generated code/warnings.

2) foo xs | length xs == 1 = bar (head xs)
   As already said in "Don't ask for the length of a list, if you
   don't need it", this usage of length is bad in itself, and
   doesn't really help the argument against patterns IMO.

3) the pattern guards extension.
   I have two objections against this one. First, I don't think
   it's a good idea to talk about a non-standard extension like
   pattern guards in a wiki about newbie-problems. (Unless in the
   sense of "there are some compiler extensions which you
   probably won't need anytime soon.") Second, it's just horrible
   code: A useless violation of DRY (Don't Repeat Yourself).
   
Groeten,
Remi


P.S.   I _do_ agree with most of the other points ;)

P.P.S. Does a piece about "Avoid explicit lambda's" stand any
   chance of not being removed?
   (Basically about "\x y -> x + y" vs "(+)", and "when it
   gets more complicated it probably deserves a name.")

-- 
Nobody can be exactly like me. Even I have trouble doing it.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Getting an attribute of an object

2005-02-10 Thread Tomasz Zielonka
On Thu, Feb 10, 2005 at 09:17:17PM +0100, Dmitri Pissarenko wrote:
> Hello!

Hello!

> I have a list of instances of the ClassifiedImage class, which is defined as
> follows.
> 
> data ClassifiedImage = ClassifiedImage {imageFileName :: String, subjectID ::
> String}
> deriving Show

ClassifiedImage is not a class. You use ClassifiedImage both as a type
constructor (before =) and as a data constructor (after =).

> Attribute imageFileName contains a file name of a certain image. I want
> to "transform" the list [ClassifiedImage] into a list [(ClassifiedImage,
> Image)], where Image is content of the file with name imageFileName.

You've used labelled fields. The label imageFileName automatically
introduces function imageFileName into scope, with type:

imageFileName :: ClassifiedImage -> String

> That is, I want to have a routine, which iterates through the list of
> ClassifiedImages, reads each file (with filename contained in the attribute
> ClassifiedImage.imageFileName) and stores its content in a variable.
> 
> I have already a function, which reads the content of a file.
> 
> My idea is to use map for this task:

> readClassifiedImages :: [ClassifiedImage] -> [(ClassifiedImage, Image)]

You'll probably have to use a subtly different type for this function:

  readClassifiedImages :: [ClassifiedImage] -> IO [(ClassifiedImage, Image)]

> readClassifiedImages classifiedImages = do
> return map readerFunc classifiedImages

Note that here you use return with 3 arguments. Most probably not what
you want. More about using "map" later.

> readerFunc denotes some function, which takes the attribute imageFileName of a
> ClassifiedImage instance.
> 
> I suppose that this readerFunc looks like shown below.

> readerFunc :: ClassifiedImage -> (ClassifiedImage, Image)
> readerFunc classifiedImage = (classifiedImage, fileContent)
> where   fileName = classifiedImageFileName classifiedImage
> fileContent = readImage fileName
 
If you wan't to load an image from disk, etc, you'll have to use the
IO monad. Thus readerFunc will have an IO type. Also, there is no need
to return the ClassifiedImage from readerFunc, unless readerFunc should
return a different ClassifiedImage.

  readerFunc :: ClassifiedImage -> IO Image
  readerFunc classifiedImage = readFile fileName
where   fileName = imageFileName classifiedImage

> classifiedImageFileName :: ClassifiedImage -> String

classifiedImageFileName = imageFileName

> Can I use map for readImage function, which is in the IO domain? If not, what
> tutorial can help me?

Assuming you have 

readerFunc :: ClassifiedImage -> IO Image

you can use map to construct readClassifiedImages, like this:

readClassifiedImages :: [ClassifiedImage] -> IO [(ClassifiedImage, Image)]
readClassifiedImages classifiedImages =
sequence $ map (\ci -> readerFunc ci >>= \i -> return (ci, i)) 
classifiedImages

but there is already mapM, which can be defined as:

mapM f l = sequence (map f l)

so you can:

readClassifiedImages :: [ClassifiedImage] -> IO [(ClassifiedImage, Image)]
readClassifiedImages classifiedImages =
mapM (\ci -> readerFunc ci >>= \i -> return (ci, i)) classifiedImages

you can also use some syntactic sugar:

readClassifiedImages :: [ClassifiedImage] -> IO [(ClassifiedImage, Image)]
readClassifiedImages classifiedImages =
sequence $ [ do i <- readerFunc ci
return (ci, i)
   | ci <- classifiedImages ]

or this way (my preferred notation):

readClassifiedImages :: [ClassifiedImage] -> IO [(ClassifiedImage, Image)]
readClassifiedImages classifiedImages =
(`mapM` classifiedImages) $ \ci -> do
i <- readerFunc ci
return (ci, i)

HTH

Best regards
Tomasz

-- 
Szukamy programisty C++ i Haskell'a: http://tinyurl.com/5mw4e
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Getting an attribute of an object

2005-02-10 Thread Jules Bean
On 10 Feb 2005, at 20:17, Dmitri Pissarenko wrote:
Hello!
I have a list of instances of the ClassifiedImage class, which is 
defined as
follows.

data ClassifiedImage = ClassifiedImage {imageFileName :: String, 
subjectID ::
String}
deriving Show

Attribute imageFileName contains a file name of a certain image. I want
to "transform" the list [ClassifiedImage] into a list 
[(ClassifiedImage,
Image)], where Image is content of the file with name imageFileName.

That is, I want to have a routine, which iterates through the list of
ClassifiedImages, reads each file (with filename contained in the 
attribute
ClassifiedImage.imageFileName) and stores its content in a variable.

I have already a function, which reads the content of a file.
My idea is to use map for this task:
readClassifiedImages :: [ClassifiedImage] -> [(ClassifiedImage, Image)]
readClassifiedImages classifiedImages = do
return map readerFunc classifiedImages
readerFunc denotes some function, which takes the attribute 
imageFileName of a
ClassifiedImage instance.

I suppose that this readerFunc looks like shown below.
readerFunc :: ClassifiedImage -> (ClassifiedImage, Image)
readerFunc classifiedImage = (classifiedImage, fileContent)
where   fileName = classifiedImageFileName classifiedImage
fileContent = readImage fileName
classifiedImageFileName :: ClassifiedImage -> String
In order for this function to work, I need to define 
classifiedImageFileName,
which "returns" the imageFileName attribute of an instance of 
ClassifiedImage
class.
This is called a selector function. Haskell defines one automatically 
with the same name as the field. imageFileName is a function 
ClassifiedImage -> String.

(ClassifiedImage is not a class, it's a datatype, by the way)
How can I define this function?
Can I use map for readImage function, which is in the IO domain? If 
not, what
tutorial can help me?

If you're happy to replace Image with IO image, then that will be fine.
Jules
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Point-free style

2005-02-10 Thread Henning Thielemann

On 10 Feb 2005, Peter Simons wrote:

> Now compare that to the following function, which does the
> some thing but without point-free notation:
>
>   incrEach' :: Integer -> [Integer] -> [Integer]
>   incrEach' i is = is >>= \i' -> return (i'+i)

point-free again

is >>= return . (i+)

:-]

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Getting an attribute of an object

2005-02-10 Thread Dmitri Pissarenko
Can I use map for readImage function, which is in the IO domain? If not, what
tutorial can help me?
Sorry, by "IO domain" I mean "IO monad".
Dmitri Pissarenko
--
Dmitri Pissarenko
Software Engineer
http://dapissarenko.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Getting an attribute of an object

2005-02-10 Thread Dmitri Pissarenko
Hello!

I have a list of instances of the ClassifiedImage class, which is defined as
follows.

data ClassifiedImage = ClassifiedImage {imageFileName :: String, subjectID ::
String}
deriving Show

Attribute imageFileName contains a file name of a certain image. I want
to "transform" the list [ClassifiedImage] into a list [(ClassifiedImage,
Image)], where Image is content of the file with name imageFileName.

That is, I want to have a routine, which iterates through the list of
ClassifiedImages, reads each file (with filename contained in the attribute
ClassifiedImage.imageFileName) and stores its content in a variable.

I have already a function, which reads the content of a file.

My idea is to use map for this task:

readClassifiedImages :: [ClassifiedImage] -> [(ClassifiedImage, Image)]
readClassifiedImages classifiedImages = do
return map readerFunc classifiedImages

readerFunc denotes some function, which takes the attribute imageFileName of a
ClassifiedImage instance.

I suppose that this readerFunc looks like shown below.

readerFunc :: ClassifiedImage -> (ClassifiedImage, Image)
readerFunc classifiedImage = (classifiedImage, fileContent)
where   fileName = classifiedImageFileName classifiedImage
fileContent = readImage fileName

classifiedImageFileName :: ClassifiedImage -> String

In order for this function to work, I need to define classifiedImageFileName,
which "returns" the imageFileName attribute of an instance of ClassifiedImage
class.

How can I define this function?

Can I use map for readImage function, which is in the IO domain? If not, what
tutorial can help me?

Thanks in advance

Dmitri Pissarenko

--
Dmitri Pissarenko
Software Engineer
http://dapissarenko.com
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Point-free style

2005-02-10 Thread Hal Daume III
> >   incrEach' i is = is >>= \i' -> return (i'+i)
> 
> Ugh, but I think the natural way to write it looks more like
> 
> incrAll :: Integer -> [Integer] -> [Integer]
> incrAll n ks = map (+n) ks
> 
> which is no less readable than map . (+).

I tend to like point-freeing only the last argument, which gives something 
like:

> incrAll n = map (+n)

which I think (personally) is the most readable.

-- 
 Hal Daume III   | [EMAIL PROTECTED]
 "Arrest this man, he talks in maths."   | www.isi.edu/~hdaume

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Point-free style

2005-02-10 Thread Daniel Fischer
Am Donnerstag, 10. Februar 2005 16:53 schrieb Peter Simons:
> Jan-Willem Maessen writes:
>  > Is it really clear or obvious what
>  >
>  >map . (+)
>  >
>  > means?
>
> Yes, it is perfectly obvious once you write it like this:
>
>   incrEach :: Integer -> [Integer] -> [Integer]
>   incrEach = map . (+)

Yes, but without the type signature it isn't really (to a beginner, at least).
>
> Now compare that to the following function, which does the
> some thing but without point-free notation:
>
>   incrEach' :: Integer -> [Integer] -> [Integer]
>   incrEach' i is = is >>= \i' -> return (i'+i)

Ugh, but I think the natural way to write it looks more like

incrAll :: Integer -> [Integer] -> [Integer]
incrAll n ks = map (+n) ks

which is no less readable than map . (+).
>
> Which one is harder to read? ;-)
>
> Peter
>
Daniel
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Point-free style

2005-02-10 Thread Peter Simons
Jan-Willem Maessen writes:

 > Is it really clear or obvious what
 >
 >map . (+)
 >
 > means?

Yes, it is perfectly obvious once you write it like this:

  incrEach :: Integer -> [Integer] -> [Integer]
  incrEach = map . (+)

Now compare that to the following function, which does the
some thing but without point-free notation:

  incrEach' :: Integer -> [Integer] -> [Integer]
  incrEach' i is = is >>= \i' -> return (i'+i)

Which one is harder to read? ;-)

Peter

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Top 20 ``things'' to know in Haskell

2005-02-10 Thread Graham Klyne
It's not exactly what you ask for, but I wrote down some of the things I 
learned in my early days with Haskell:
  http://www.ninebynine.org/Software/Learning-Haskell-Notes.html

#g
--
At 10:31 07/02/05 -0500, Jacques Carette wrote:
The recent post of Graham Klyne (below) reminds me that I have meant to ask:
is there a ``top 20'' things a serious programmer should know when writing
code in Haskell?  Of course there is a lot of programming language theory
that would be great to know, but I mean really down-to-earth things like the
2 items below (module Maybe, the 'maybe' function).
The Haskell libraries are quite large, and it is unrealistic to try to get
familiar with all of them right away.  But getting a ``small'' list would be
very useful - I think of this as step 2 after one learns to get comfortable
with a language.  I had done this (for Maple) for training new hires at
Maplesoft, and I definitely noticed that they became more idiomatic
programmers faster this way.
Jacques
PS: of course, this could already exist on haskell.org and/or the Wiki, but
not in an 'obvious' enough place as I missed it...
-Original Message-
From: [EMAIL PROTECTED]
[mailto:[EMAIL PROTECTED] On Behalf Of Graham Klyne
Sent: February 7, 2005 10:09 AM
To: Yuri D'Elia; haskell-cafe@haskell.org
Subject: [Haskell-cafe] Re: [Haskell] [newbye] 'Just a'
You might also be interested in the library function 'maybe':
   http://www.haskell.org/onlinereport/standard-prelude.html#$vmaybe
or maybe (sic) Maybe.fromMaybe in:
   http://www.haskell.org/onlinereport/maybe.html
#g
--
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Graham Klyne
For email:
http://www.ninebynine.org/#Contact
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Point-free style (Was: Things to avoid)

2005-02-10 Thread Jan-Willem Maessen
On Feb 10, 2005, at 6:50 AM, Henning Thielemann wrote:
On Thu, 10 Feb 2005, [ISO-8859-1] Thomas Jäger wrote:
Altogether, the spirit of the page seems to be "use as little
syntactic sugar as possible" which maybe appropriate if it is aimed at
newbies, who often overuse syntactic sugar (do-notation).
This overuse is what I observed and what I like to reduce. There are 
many
people advocating Haskell just because of the sugar, which let 
interested
people fail to see what's essential for Haskell. When someone says to 
me
that there is a new language which I should know of because it supports
definition of infix operators and list comprehension, I shake my head 
and
wonder why he don't simply stick to Perl, Python, C++ or whatever.
If you're trying to avoid obscurity, why advocate point-free style?
I ask this question to be deliberately provocative; I'm not trying to 
single you out in particular.  So, to everybody: What's so great about 
point-free style?

Is it really clear or obvious what
> map . (+)
means?  Contrast this with
> \n -> map (+n)
or
> \n xs -> map (+n) xs
I submit that, while it is possible to develop a reading knowledge of 
point-free style, non-trivial use of point-free 
computations---compositions of functions with arity greater than 1, as 
above, compositions of sections of composition or application, arrow 
notation without the sugar, and so forth---will always be more 
difficult to read and understand than the direct version.  I submit 
that this is true even if one is familiar with point-free programming 
and skilled in its use.
Even something as simple as eta-reduction (as in the second and third 
functions above) can seriously obscure the meaning of program code by 
concealing the natural arity of a function.

-Jan-Willem Maessen
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Things to avoid (Was: Top 20 ``things'' to know in Haskell)

2005-02-10 Thread Thomas Jäger
On Thu, 10 Feb 2005 12:50:16 +0100 (MET), Henning Thielemann
<[EMAIL PROTECTED]> wrote:
> 
> On Thu, 10 Feb 2005, [ISO-8859-1] Thomas Jäger wrote:
> 
> > Altogether, the spirit of the page seems to be "use as little
> > syntactic sugar as possible" which maybe appropriate if it is aimed at
> > newbies, who often overuse syntactic sugar (do-notation).
> 
> This overuse is what I observed and what I like to reduce. There are many
> people advocating Haskell just because of the sugar, which let interested
> people fail to see what's essential for Haskell. When someone says to me
> that there is a new language which I should know of because it supports
> definition of infix operators and list comprehension, I shake my head and
> wonder why he don't simply stick to Perl, Python, C++ or whatever.
I don't believe that Haskell advocacy usually happens on such a
superficial level, in fact most users of curly-braced languages hate
Haskell's syntax, so that won't be an argument for Haskell anyway.
Looking at it closer, syntax often makes a huge difference. Haskell is
an many ways similar to mathematical notation, which allows to express
complicated concepts in a concise way and happens to use a lot of
syntactic sugar. There should be no doubt about that 1 + 2 + 3 is
easier for humans to parse than (+ (+ 1 2)).
This becomes especially important when you are embedding a domain
specific language into Haskell. Allowing combinators to be used infix
make code more readable, better understandable, reduces parenthesis,
and sometimes resolves the question in which order the arguments of
the functions appear. It's not strictly necessary, but is a big
advantage over postfix-languages.

> What I forgot: Each new syntactic sugar is something more, a reader must
> know, a compiler and debugger developer must implement and test, a source
> code formatter, highlighter, documentation extractor or code transformer
> must respect. We should try harder to reduce these extensions rather than
> inventing new ones.  Leave the award for the most complicated syntax for
> C++! :-]
Ideally, new syntactic sugar is self-explanatory, and this is the case
for most of Haskell's sugar (maybe in contrast to C++). The fact that
some tools get a little more complicated doesn't bother me much if it
helps me write my program in a more concise way.

> That's why I want to stress that the syntactic sugar is much less
> important or even necessary than generally believed. I hope that the
> examples clarify that.
Yeah, as long as it is explained and clearly marked as an opinion (as
it is now), that's ok. One reason that I got so excited about that is
because I don't like the current situation with (n+k)-patterns:
Everybody says they're evil, but hardly anybody can explain why he
thinks so.

Thomas
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Things to avoid (Was: Top 20 ``things'' to know in Haskell)

2005-02-10 Thread Henning Thielemann

On Thu, 10 Feb 2005, [ISO-8859-1] Thomas Jäger wrote:

> Altogether, the spirit of the page seems to be "use as little
> syntactic sugar as possible" which maybe appropriate if it is aimed at
> newbies, who often overuse syntactic sugar (do-notation).

What I forgot: Each new syntactic sugar is something more, a reader must
know, a compiler and debugger developer must implement and test, a source
code formatter, highlighter, documentation extractor or code transformer
must respect. We should try harder to reduce these extensions rather than
inventing new ones.  Leave the award for the most complicated syntax for
C++! :-]

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Things to avoid (Was: Top 20 ``things'' to know in Haskell)

2005-02-10 Thread Henning Thielemann

On Thu, 10 Feb 2005, [ISO-8859-1] Thomas Jäger wrote:

> Altogether, the spirit of the page seems to be "use as little
> syntactic sugar as possible" which maybe appropriate if it is aimed at
> newbies, who often overuse syntactic sugar (do-notation).

This overuse is what I observed and what I like to reduce. There are many
people advocating Haskell just because of the sugar, which let interested
people fail to see what's essential for Haskell. When someone says to me
that there is a new language which I should know of because it supports
definition of infix operators and list comprehension, I shake my head and
wonder why he don't simply stick to Perl, Python, C++ or whatever.

For me it was the same with LaTeX: Someone who was very convinced about
LaTeX tried to convince me. He loved the nice type setting of formulas,
but the way he worked with LaTeX (trying around centi-meter measures,
adding \skip here and boldface there) didn't convince me and I stuck to a
WYSIWYG text processor. Today I'm using LaTeX all the time, because I like
the easy extensibility, the simple work with large documents, the
programmability, the possibility to generate LaTeX code automatically.

That's why I want to stress that the syntactic sugar is much less
important or even necessary than generally believed. I hope that the
examples clarify that.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Things to avoid (Was: Top 20 ``things'' to know in Haskell)

2005-02-10 Thread Remi Turk
On Wed, Feb 09, 2005 at 02:54:12PM +0100, Henning Thielemann wrote:
> On Wed, 9 Feb 2005, Henning Thielemann wrote:
> > Is there also a Wiki page about things you should avoid?
> 
> Since I couldn't find one, I started one on my own:
> 
> http://www.haskell.org/hawiki/ThingsToAvoid
> 
> I consider 'length', guards and proper recursion anchors.

Oops, I just forgot a comment to my latest update: I added an
example to illustrate the fromInteger-in-a-pattern case.

-- 
Nobody can be exactly like me. Even I have trouble doing it.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Things to avoid (Was: Top 20 ``things'' to know in Haskell)

2005-02-10 Thread Thomas Jäger
> > Is there also a Wiki page about things you should avoid?
> 
> Since I couldn't find one, I started one on my own:
> 
> http://www.haskell.org/hawiki/ThingsToAvoid
> 
> I consider 'length', guards and proper recursion anchors.

[Moving the discussion from the wiki to the mailing list until we've
reached some kind of consensus]

ad n+k-patterns
This old discussion seems kind of relevant.
http://www.dcs.gla.ac.uk/mail-www/haskell/msg01131.html

In my opinion, there's no reason to avoid (n+1)-patterns. Recursion is
the natural definition of many functions on the natural numbers, just
like on lists, trees or any other ADT. There just happens to be a more
efficient representation of naturals than as Peano numbers. There are
indeed circumstances where
> foo (n+1) = ... n ... n ... n ...
is much clearer than
> foo n = let n' = n + 1 in n' `seq` ... n' ... n' ... n' ...
On the wiki, you claim
> data Natural = Zero | Successor Natural
> They are implemented using binary numbers and it is not even tried to 
> simulate the behaviour of Natural (e.g. laziness). Thus I wouldn't state, 
> that 3 > matches the pattern 2+1.
If however, you had defined
> data Nat = Zero | Succ !Nat,
pattern matching would still be possible, but Nat would behave exactly
as the (n+1) - pattern.

ad guards
I agree that guards are not always the right way to do it (as in the
example you mentioned on the wiki which was bad Haskell code anyway).
However, they have valid uses that can't be easily/naturally expressed
without them. A typical example might be
> foo (App e1 e2) | e1 `myGuard` e2 = App (foo e1) (foo e2)
> foo (Lambda v e) = Lambda v (foo e)
> foo (App e1 e2) = App (bar e1) (bar e2)
> ... 

So instead of saying "guards are bad", i think there should rather be
an explanation when guards are appropriate.

Altogether, the spirit of the page seems to be "use as little
syntactic sugar as possible" which maybe appropriate if it is aimed at
newbies, who often overuse syntactic sugar (do-notation). However, I
like most of the syntactic sugar provided by Haskell/Ghc, and it is
one reason why Haskell is such nice language, so I don't think we
should advocate unsugaring all our programs.

Thomas
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe