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

2005-02-12 Thread Daniel Fischer
Am Samstag, 12. Februar 2005 01:42 schrieb [EMAIL PROTECTED]:
 Iavor Diatchki writes in response to Thomas Jger

  Literal patterns need equality:
  f 2 = e
  is like:
  f x | x == 2 = e
 
  These do not force the 'Num' class to be a superclass of 'Ord' or
  'Eq'.  If 'Num' was not a superclass of 'Eq', whenver you used a
  literal pattern there would be an extra constraint that there should
  be equality on the corresponding type.

 You mean of course that Eq is a superclass of Num, not the reverse.

 Anyway, I always hated this, especially working with functional objects
 for which I had some arithmetic defined...


 Jerzy Karczmarczuk


I feel somewhat similarly.
I think it would be nice to have numerical classes where the arithmetic 
operations are provided, so you can naturally add functions c, and then have 
Num a subclass where fromInteger and instances of Eq and Show are added.

Daniel
___
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-12 Thread Remi Turk
On Fri, Feb 11, 2005 at 11:14:40AM +0100, Henning Thielemann wrote:
 
 On Fri, 11 Feb 2005, Remi Turk wrote:
 
  1) It's talking about the compiler having difficulty with some
 warnings when using guards.
 
 http://www.haskell.org//pipermail/haskell-cafe/2005-January/008290.html

Simon Peyton-Jones wrote in 
http://www.haskell.org//pipermail/haskell-cafe/2005-January/008290.html
 GHC has -fwarn-incomplete-patterns and -fwarn-overlapped-patterns.  But
 the code implementing these checks is old and crufty, and the warnings
 are sometimes a bit wrong -- at least when guards and numeric literals
 are involved.  I think they are accurate when you are just using
 ordinary pattern matching.

Does anyone know nice examples where it goes wrong? (And which
could be added to the wiki.) I found the following case where GHC
wrongly gives two warnings, but 1) it's a rather convoluted
example and 2) it's - in general - probably undecidable anyway
(fromInteger might execute arbitrary code):

data Foo = Foo | Bar deriving (Eq, Show)

instance Num Foo where
fromInteger _ = Foo

f   :: Foo - Bool
f 0 = True
f Bar = False

foo.hs:14:
Warning: Pattern match(es) are overlapped
 In the definition of `f': f Bar = ...

foo.hs:14:
Warning: Pattern match(es) are non-exhaustive
 In the definition of `f':
 Patterns not matched: #x with #x `notElem` [0]
   
BTW, what exactly does this mean?

 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.
 
 Yes, your example is better.

If no-one complains I'll remove the isPrime-part (which IMO
doesn't demonstrate any guard-problems) and collapse it with the
factorial-example (which does).

  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.
 
 I have seen it similarly in the example I give below at that page. So I
 found it worth noting that some guards can nicely be replaced by simple
 patterns. More examples are welcome. May be we should replace it by
 
 foo xs | not (null xs) = bar (head xs)
 
 vs.
 
 foo (x:_) = bar x
Done.

 This example might be useful, too:
 
 foo x | x == 0 = blub
 x /= 0 = bla
 
 vs.
 
 foo 0 = blub
 foo _ = bla

I agree, and so did Stephan Hohe, who added the factorial example ;)

  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.
 
 It was given to me as a good example why Guards are invaluable:
  http://www.haskell.org//pipermail/haskell-cafe/2005-January/008320.html

Ouch, that hurts. Though I hope I'm not blaspheming when I say
I'd rather do without if-then-else (which I'm not using all that
often and could easily replace by a function `if') than without
guards.

  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.)
 
 Nice!
Done too.

-- 
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-11 Thread Henning Thielemann

On Fri, 11 Feb 2005, Remi Turk wrote:

 1) It's talking about the compiler having difficulty with some
warnings when using guards.

http://www.haskell.org//pipermail/haskell-cafe/2005-January/008290.html

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.

Yes, your example is better.

 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.

I have seen it similarly in the example I give below at that page. So I
found it worth noting that some guards can nicely be replaced by simple
patterns. More examples are welcome. May be we should replace it by

foo xs | not (null xs) = bar (head xs)

vs.

foo (x:_) = bar x


This example might be useful, too:

foo x | x == 0 = blub
x /= 0 = bla

vs.

foo 0 = blub
foo _ = bla


 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.

It was given to me as a good example why Guards are invaluable:
 http://www.haskell.org//pipermail/haskell-cafe/2005-January/008320.html

 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.)

Nice!

___
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-11 Thread Thomas Jäger
Hi,

On Thu, 10 Feb 2005 16:18:19 -0800, Iavor Diatchki
[EMAIL PROTECTED] wrote:
  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
agreed

 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 '+'.  
IMO, that's not a big problem, because if ambigouties arise, only one
of the possible meanings will compile (e.g. if you use + somewhere
else in the module, ghc will complain about an ambigous occurrence of
`+'). All (rather strange) other cases are caught by ghc -Wall.

I found another disadvantage:
iii) As a side effects of how n+k patterns work, each instance of the
Num class must also be an instance of Eq, which of course doesn't make
sense for all numeric types.

 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.
It's true that their functionality can be easily expressed without them.

I like to see them (well, n+1 patterns) as a special case of views
because they allow numbers to be matched against something that is not
a constructor and involve a computation on pattern matching. An
unambigous replacement using views could look somewhat like
 foo Zero  = 1
 foo (Succ n) = 2 * foo n

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-11 Thread Iavor Diatchki
Hi,

On Fri, 11 Feb 2005 12:02:56 +0100, Thomas Jäger [EMAIL PROTECTED] wrote:

 iii) As a side effects of how n+k patterns work, each instance of the
 Num class must also be an instance of Eq, which of course doesn't make
 sense for all numeric types.

Well this is not entirely true.  I don't think 'n+k' patterns need
equality, but they need ordering
f (n + k) = e
is like:
f x | x  k = let n = x - k in e

Literal patterns need equality:
f 2 = e
is like:
f x | x == 2 = e

These do not force the 'Num' class to be a superclass of 'Ord' or
'Eq'.  If 'Num' was not a superclass of 'Eq', whenver you used a
literal pattern there would be an extra constraint that there should
be equality on the corresponding type. For example:
f 2 = Hello
would get the type:
f :: (Eq a, Num a) = a - String

Hope this helps
-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 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


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 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 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 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 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] 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


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

2005-02-09 Thread Henning Thielemann

On Wed, 9 Feb 2005, Henning Thielemann wrote:

 On Wed, 9 Feb 2005, Bayley, Alistair wrote:

  Were you thinking of something like [n] Things a Java Programmer Should
  Know About Ruby ?
http://jimweirich.tadalist.com/lists/public/14055
 
  Perhaps you'd like to start a page on the wiki. A link from here, maybe?
http://haskell.org/hawiki/FrequentlyAskedQuestions

 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.

___
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-09 Thread Matthew Walton
Henning Thielemann wrote:
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.
Very interesting. It would be nice to have reasoning for the n+k 
patterns thing. Guidelines that say 'don't do this' with no reason are 
far more confusing than no guidelines at all.

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