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

Remi Turk rturk at science.uva.nl
Sat Feb 12 14:33:00 EST 2005


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.


More information about the Haskell-Cafe mailing list