
#11474: incorrect redundant-constraints warning -------------------------------------+------------------------------------- Reporter: hvr | Owner: Type: bug | Status: new Priority: highest | Milestone: 8.0.1 Component: Compiler | Version: 8.0.1-rc1 (Type checker) | Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Incorrect Unknown/Multiple | warning at compile-time Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- The following code when compiled with GHC 8 {{{#!hs {-# LANGUAGE Haskell2010, FunctionalDependencies, KindSignatures, ScopedTypeVariables, TypeOperators, UndecidableInstances #-} import GHC.Generics data Options data Value newtype Tagged s b = Tagged {unTagged :: b} class GToJSON f where gToJSON :: Options -> f a -> Value class SumToJSON f allNullary where sumToJSON :: Options -> f a -> Tagged allNullary Value class AllNullary (f :: * -> *) allNullary | f -> allNullary instance ( AllNullary (a :+: b) allNullary, -- <- removing this line causes a compile error SumToJSON (a :+: b) allNullary ) => GToJSON (a :+: b) where gToJSON opts = (unTagged :: Tagged allNullary Value -> Value) . sumToJSON opts }}} emits a warning {{{ bug.hs:19:10: warning: • Redundant constraint: AllNullary (a :+: b) allNullary • In the instance declaration for ‘GToJSON (a :+: b)’ }}} when commenting out the `AllNullary` constraint, this however results the compile error {{{ bug.hs:19:10: error: • Could not deduce (SumToJSON (a :+: b) allNullary0) from the context: SumToJSON (a :+: b) allNullary bound by an instance declaration: SumToJSON (a :+: b) allNullary => GToJSON (a :+: b) at redconstr.hs:(19,10)-(22,24) The type variable ‘allNullary0’ is ambiguous • In the ambiguity check for an instance declaration To defer the ambiguity check to use sites, enable AllowAmbiguousTypes In the instance declaration for ‘GToJSON (a :+: b)’ }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11474 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler