[GHC] #12700: Don't warn about redundant constraints for type equalities

#12700: Don't warn about redundant constraints for type equalities -------------------------------------+------------------------------------- Reporter: crockeea | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.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 Rev(s): | Wiki Page: -------------------------------------+------------------------------------- With `-Wall`, the following code {{{ {-# LANGUAGE TypeFamilies #-} type family Foo x where Foo Double = Int foo :: (RealFrac a, Integral b, b ~ Foo a) => a -> b foo = round }}} produces the warning {{{ • Redundant constraint: b ~ Foo a • In the type signature for: foo :: (RealFrac a, Integral b, b ~ Foo a) => a -> b }}} Technically, I suppose this is correct in the sense that if we remove the constraint `b ~ Foo a`, `foo` still compiles. However, the ''meaning'' changes without the type equality, because the function I wrote is equivalent to `foo :: (RealFrac a, Integral (Foo a)) => a -> Foo a` (which requires `-XFlexibleContexts`), while the function it suggests is the much more general `foo :: (RealFrac a, Integral b) => a -> b`. Since this is the case, I think the warning is invalid. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12700 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12700: Don't warn about redundant constraints for type equalities -------------------------------------+------------------------------------- Reporter: crockeea | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.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 Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): I don't get what you mean by "the meaning changes". I understand that writing {{{ foo :: (RealFrac a, Integral (Foo a)) => a -> Foo a }}} requires `FlexibleContexts` whereas the version you wrote does not; but that's not too terrible is it? Maybe putting equalities in contexts should require `FlexibleContexts` too, since it's just as flexible. You say that "the function it suggests is the much more general...". But the two are fully equivalent, so I don't know what you have in mind by "suggests" here. Would you care to elaborate? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12700#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12700: Don't warn about redundant constraints for type equalities -------------------------------------+------------------------------------- Reporter: crockeea | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.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 Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by crockeea): Sorry if I was unclear, Simon. GHC says the constraint `b ~ Foo a` is redundant. To me, this warning means that GHC is suggesting it would be better to write `foo :: (RealFrac a, Integral b) => a -> b`. I disagree with GHC's suggestion: I meant to write the original signature (which is equivalent to the one which requires `FlexibleContexts`), because it is more specific and can help with type inference elsewhere in my program. Moreover, if I wrote the original signature in a different form (the `FlexibleContexts` version), GHC does ''not'' suggest it would be better to write `foo :: (RealFrac a, Integral b) => a -> b`. In that case it notices that the type restriction is meaningful. What I'm getting at here is: if A and B are equivalent (as my two signatures are), then GHC should have the same behavior when I do either one. Maybe it's difficult for GHC to realize that my particular A and B are equivalent, and I suppose that would be a valid reason to close the ticket. As to why I chose to write the signature I did instead of the `FlexibleContexts` version, it can be save some space in type signatures when some type variables are equivalent to long expressions. I don't give a whit about using `FlexibleContexts`, in fact it is enabled almost everywhere in my code already. As to whether putting type equalities in contexts should require `FlexibleContexts`: that misses the point, since I get the same warning with the original signature when the extension is enabled. GHC still behaves differently on equivalent inputs. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12700#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12700: Don't warn about redundant constraints for type equalities -------------------------------------+------------------------------------- Reporter: crockeea | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.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 Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): I see * `foo` really does have the type `(RealFrac a, Integral b) => a -> b`. That is, as GHC claims, the constraint can simply be omitted. * But you specifically want to write a less-polymorphic type than the most general type. Another example might be {{{ f :: Ord a => a -> a f x = x }}} The `Ord a` is not needed, but you might want to require it for some software engineering reason. That's your situation here, I believe. * It's worth noting that you can certainly say {{{ f :: [a] -> [a] f x = x }}} thus specifying a less polymorphic type than the most general one, without causing a warning of any kind. This is one of the reasons that `-Wredundant-constraints` is no longer on by default, and is not even enabled by `-Wall`. I'm a bit sad, but the annoyance was too great. The real solution would be a per-function pragma to say "I intend to have a redundant constraint here". If I've understood aright, then we need take no action, except add it as another use-case for the per-function pragma See #11370, #10635 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12700#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12700: Don't warn about redundant constraints for type equalities -------------------------------------+------------------------------------- Reporter: crockeea | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.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 Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by hsyl20): Could we allow local type alias declarations into contexts? E.g., {{{ foo :: (RealFrac a, Integral b, let b ~ Foo a) => a -> b }}} This would be equivalent to: {{{ foo :: forall a. (RealFrac a, Integral b, let b ~ Foo a) => a -> b }}} i.e., b doesn't leak and isn't reported as redundant. Still ideally "b" should be accessible in the function code (with ScopedTypeVariable, TypeApplications, etc.). It would be useful to me to avoid redundancy into contexts such as the following where "zs" is the type alias: {{{ xxx :: forall x xs ys zs m. ( Monad m , zs ~ Union (Filter x xs) ys , Catchable x xs , Liftable (Filter x xs) zs , Liftable ys zs ) => Variant xs -> (x -> Flow m ys) -> Flow m zs }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12700#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12700: Don't warn about redundant constraints for type equalities -------------------------------------+------------------------------------- Reporter: crockeea | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.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 Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by hsyl20): * cc: hsyl20 (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12700#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12700: Don't warn about redundant constraints for type equalities -------------------------------------+------------------------------------- Reporter: crockeea | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.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 Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by crockeea): I'm not sure why the extra syntax is needed, i.e. how is `let b ~ Foo a` different from `b ~ Foo a`? I'm intending, as hsyl20 indicated, to do the former, but apparently using the `b ~ Foo a` implies, and is more general than, `let b ~ Foo a`. Is there no way for GHC to turn the signature `forall a b . (b ~ Foo a) => a -> b` into `forall a . (let b ~ Foo a) => a -> b` or even `forall a . a -> Foo a`? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12700#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12700: Don't warn about redundant constraints for type equalities -------------------------------------+------------------------------------- Reporter: crockeea | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.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: #14237 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * related: => #14237 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12700#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC