[GHC] #10339: PatternSynonyms confuse exhaustiveness check

#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

#10339: PatternSynonyms confuse exhaustiveness check -------------------------------------+------------------------------------- Reporter: hvr | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.1 Resolution: | 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: -------------------------------------+------------------------------------- Changes (by hvr): * version: 7.10.1 => 7.8.1 Comment: This occurs since GHC 7.8 (when pattern synonyms were introduced), up to GHC HEAD -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10339#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10339: PatternSynonyms confuse exhaustiveness check -------------------------------------+------------------------------------- Reporter: hvr | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 7.8.1 Resolution: | 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: -------------------------------------+------------------------------------- Comment (by wrl314): Another example showing same problem with simple unidirectional pattern synonym: {{{ data Foo2 = Foo2 Int String pattern F a <- Foo2 a _ blah :: Foo2 -> Int blah (F a) = a + 1 }}} Result: {{{ Warning: Pattern match(es) are non-exhaustive In an equation for ‘blah’: Patterns not matched: _ }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10339#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10339: PatternSynonyms confuse exhaustiveness check -------------------------------------+------------------------------------- Reporter: hvr | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 7.8.1 Resolution: duplicate | Keywords: | PatternSynonyms Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: #8779 | Differential Revisions: -------------------------------------+------------------------------------- Changes (by cactus): * status: new => closed * keywords: => PatternSynonyms * resolution: => duplicate * related: => #8779 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10339#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC