Bugs item #1075259, was opened at 2004-11-29 14:00
Message generated for change (Comment added) made by ginge
You can respond by visiting: 
https://sourceforge.net/tracker/?func=detail&atid=108032&aid=1075259&group_id=8032

Please note that this message will contain a full copy of the comment thread,
including the initial issue submission, for this request,
not just the latest update.
Category: Compiler (Parser)
Group: 6.2.2
Status: Open
Resolution: None
Priority: 2
Submitted By: Nobody/Anonymous (nobody)
Assigned to: Nobody/Anonymous (nobody)
Summary: Wrong overlapped/missing pattern warnings

Initial Comment:
compiling:

  module Overlap where

  f (n+1) = 2
  f 0     = 1

emits wrongly:

    Warning: Pattern match(es) are overlapped
             In the definition of `f': f 0 = ...


The Patterns are disjoint, aren't they? At least  "f 0"
yields "1" when evaluated and negative inputs for f are
rejected. However the warning is not emitted if the two
equations are given in reversed order.

Christian ([EMAIL PROTECTED])


----------------------------------------------------------------------

Comment By: Neil Mitchell (ginge)
Date: 2005-12-03 16:15

Message:
Logged In: YES 
user_id=618575

When adding -fwarn-simple-patterns to the command line, all
3 of the previous examples give an additional 2 warning's,
i.e. ex1 and ex2 give two identical warnings, and ex3 gives
3 identical warnings.

Warning: Pattern match(es) are non-exhaustive
         In a case alternative: Patterns not matched: []


----------------------------------------------------------------------

Comment By: Simon Peyton Jones (simonpj)
Date: 2005-12-02 09:12

Message:
Logged In: YES 
user_id=50165

Another example from Neil Mitchell

I have been playing around with -fwarn-incomplete-patterns 
under GHC
6.4.1 on Windows.

-- no warning
ex1 x = ss
    where (s:ss) = x

-- no warning
ex2 x = let (s:ss) = x in ss

--    Warning: Pattern match(es) are non-exhaustive
--             In a case alternative: Patterns not matched: 
[]
ex3 x = case x of ~(s:ss) -> ss

I have translated all 3 functions using the rules supplied 
in the Haskell 98 report, so they all have the same 
meaning, but only one gives an error. Is it intentional to 
ignore where/let pattern matches?

----------------------------------------------------------------------

Comment By: Simon Peyton Jones (simonpj)
Date: 2004-12-13 09:49

Message:
Logged In: YES 
user_id=50165

Here's another example, from Peter White

When I compile the following module with the -Wall option on 
ghc v6.2.1  
I get warnings:
Warning: Pattern match(es) are non-exhaustive
     In a record-update construct: Patterns not matched D2.
The warnings occur at both of the indicated places in the 
module.
Since the functions both handle all the cases of the data 
type D, it  
seems the warning should not be given.


data D = D1 { f1 :: Int } | D2

-- Use pattern matching in the argument
f :: D -> D
f  d1@(D1 {f1 = n}) = d1 { f1 = f1 d1 + 1 } -- Warning here
f  d = d

-- Use case pattern matching
g :: D -> D
g  d1 = case d1 of
           D1 { f1 = n } -> d1 { f1 = n + 1 } -- Warning here 
also
           D2            -> d1



----------------------------------------------------------------------

You can respond by visiting: 
https://sourceforge.net/tracker/?func=detail&atid=108032&aid=1075259&group_id=8032
_______________________________________________
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to