[GHC] #12810: -Wredundant-constraints doesn't factor in associated type families

#12810: -Wredundant-constraints doesn't factor in associated type families -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 (Type checker) | Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Incorrect Unknown/Multiple | error/warning at compile-time Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- If I compile this code: {{{#!hs {-# LANGUAGE TypeFamilies #-} module M where class C a where type T a instance C a => C [a] where type T [a] = T a }}} with `-Wredundant-constraints` enabled, it complains: {{{ $ /opt/ghc/head/bin/ghc -Wredundant-constraints M.hs [1 of 1] Compiling M ( M.hs, M.o ) M.hs:7:10: warning: [-Wredundant-constraints] • Redundant constraint: C a • In the instance declaration for ‘C [a]’ }}} I don't think this is right. The RHS of `T [a]` won't be able to reduce unless there's a `T a` instance available–that is, unless there's a `C a` instance available, which is what the context provides, making it non- redundant. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12810 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12810: -Wredundant-constraints doesn't factor in associated type families -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple error/warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): This also came up in Phab:D2636 (the fix for #2721 and #8165), since you can now use `GeneralizedNewtypeDeriving` to derive an instance for a class with an associated type family on a newtype. But in [https://phabricator.haskell.org/D2636#77793 this example]: {{{#!hs {-# LANGUAGE GeneralizedNewtypeDeriving, TypeFamilies #-} class C a where type T a newtype Identity a = Identity a deriving C }}} If you compile this with `-Wredundant-constraints`, GHC will look at the derived instance: {{{#!hs instance C a => C (Identity a) where type T (Identity a) = T a }}} And it will emit a warning! {{{ • Redundant constraint: C a • In the instance declaration for ‘C (Identity a)’ }}} This might be even worse that the original example, because now it's //GHC// that's providing the redundant constraint, not the programmer. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12810#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12810: -Wredundant-constraints doesn't factor in associated type families -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple error/warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by rwbarton): Well type families are allowed to not reduce. For example {{{ *M> :t undefined :: T Int undefined :: T Int :: T Int }}} there's nothing stopping you from writing `T Int`, regardless of whether there is an instance `C Int`. So GHC's warning is consistent with that. In your comment, the problem doesn't seem to be the type family, but rather the lack of any methods. An empty class body gives the same warning. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12810#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12810: -Wredundant-constraints doesn't factor in associated type families -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple error/warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): Bah, my mental model of associated families has tripped me up once again. I would have sworn that this code would have been a counterexample to your claim: {{{#!hs {-# LANGUAGE TypeFamilies #-} module M where class C a where type T a instance C Int where type T Int = Bool instance {- C a => -} C [a] where type T [a] = T a f :: T [Int] -> Bool f x = x }}} But to my surprise, that typechecks even in the absence of that `C a` constraint on the `C [a]` instance. So I can see your point. I suppose then that this is actually subsumed under #11369? Or is the presence of associated type families enough to make a class no longer "empty"? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12810#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12810: -Wredundant-constraints doesn't factor in associated type families -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple error/warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by goldfire): I agree with rwbarton in that you do not need the constraint. I think this is just #11369. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12810#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12810: -Wredundant-constraints doesn't factor in associated type families -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Resolution: duplicate | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple error/warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: #11369 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => closed * resolution: => duplicate * related: => #11369 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12810#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12810: -Wredundant-constraints doesn't factor in associated type families -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Resolution: duplicate | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple error/warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: #11369 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Associated types are completely equivalent to top-level type families. Really the only difference is that you are prompted to provide a type instance at the same time as a class instances; and perhaps that the two "logically belong together". But there is no runtime evidence needed, and hence no class constraint is needed in function definitions. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12810#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12810: -Wredundant-constraints doesn't factor in associated type families -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Resolution: duplicate | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple error/warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: #11369 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): I've opened #12814 to discuss the matter of comment:1. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12810#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC