
#14322: Simplifying an instance context makes a rewrite rule no longer typecheck -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.2.1 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Here's a simpler example: {{{ {-# LANGUAGE GADTs, FlexibleContexts, NoMonoLocalBinds #-} data T a where MkT :: Eq a => a -> T a f :: T [b] -> Bool f (MkT xs) = g xs g :: Eq [b] => [b] -> Bool g xs = xs == xs }}} We get {{{ T14322.hs:12:6: warning: [-Wsimplifiable-class-constraints] * The constraint `Eq [b]' matches an instance declaration instance Eq a => Eq [a] -- Defined in `GHC.Classes' This makes type inference for inner bindings fragile; either use MonoLocalBinds, or simplify it using the instance }}} But you can't simplify `g`'s type signature, becuase then at the call site in `f` we get a wanted `Eq a` dictionary which we can't get from a given `Eq [a]` dictionary bound by the existential. The exact same thing is happening with your RULE. I don't see a great solution here. Personally I's use `MonoLocalBinds` to suppress the warning. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14322#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler