[GHC] #10339: PatternSynonyms confuse exhaustiveness check
GHC
ghc-devs at haskell.org
Tue Apr 21 14:08:38 UTC 2015
#10339: PatternSynonyms confuse exhaustiveness check
-------------------------------------+-------------------------------------
Reporter: hvr | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 7.10.1
Keywords: | Operating System: Unknown/Multiple
Architecture: | Type of failure: Incorrect
Unknown/Multiple | warning at compile-time
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Revisions: |
-------------------------------------+-------------------------------------
I just noticed some odd behaviour when (ab)using pattern synonyms in the
following code (whose style I don't really endorse):
{{{#!hs
{-# LANGUAGE PatternSynonyms, LambdaCase #-}
module PatSyn1 where
import System.Directory (doesFileExist)
pattern Found = True
pattern NotFound = False
readConfigFile :: FilePath -> IO ()
readConfigFile filePath = doesFileExist filePath >>= \case
Found -> putStrLn =<< readFile filePath
NotFound -> putStrLn "File does not exist."
pattern Void = ()
foo :: () -> ()
foo Void = ()
}}}
Results in
{{{
/home/hvr/Haskell/PatSyn1.hs:(11,54)-(13,47): Warning:
Pattern match(es) are non-exhaustive
In a case alternative: Patterns not matched: _
/home/hvr/Haskell/PatSyn1.hs:19:1-13: Warning:
Pattern match(es) are non-exhaustive
In an equation for ‘foo’: Patterns not matched: _
}}}
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/10339>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list