
#15713: Bogus -Woverlapping-patterns warning with OverloadedStrings -------------------------------------+------------------------------------- Reporter: | Owner: (none) quasicomputational | Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.6.1 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- {{{ $ cat Test.hs {-# LANGUAGE OverloadedStrings, LambdaCase #-} import Data.String data Expr = App Expr Expr | Var String deriving (Eq) instance IsString Expr where fromString = Var . fromString go = \case App ( App ( App "refWithFile" identM ) filenameM) exceptionMayM -> Just 2 App ( App "and" a ) b -> Just 3 App ( App "or" a ) b -> Just 4 _ -> Nothing go' = \case App ( App ( App "refWithFile" identM ) filenameM) exceptionMayM -> Just 2 App ( App "and" a ) b -> Just 3 _ -> Nothing go'' = \case App ( App ( App (Var "refWithFile") identM ) filenameM) exceptionMayM -> Just 2 App ( App (Var "and") a ) b -> Just 3 App ( App (Var "or") a ) b -> Just 4 _ -> Nothing main = do let expr = App (App "or" "a") "b" print (go expr) print (go' expr) $ runghc-8.4.3 Test.hs Test.hs:13:3: warning: [-Woverlapping-patterns] Pattern match is redundant In a case alternative: App (App "or" a) b -> ... | 13 | App ( App "or" a ) b -> Just 4 | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ Just 4 Nothing $ runghc-8.6.1 Test.hs Test.hs:13:3: warning: [-Woverlapping-patterns] Pattern match is redundant In a case alternative: App (App "or" a) b -> ... | 13 | App ( App "or" a ) b -> Just 4 | ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^ Just 4 Nothing }}} The pattern match checker complains about the `"or"` case of `go` being redundant, but, when it is removed (as it is in `go'`) the output is different. `go''` demonstrates that `OverloadedStrings` is relevant, as that is *not* generating a warning. Removing either of the other two cases of `go` also suppresses the warning: all three are necessary. As seen in the transcript, this is happening on both 8.4.3 and 8.6.1. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15713 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler