[GHC] #11947: GHC mistakenly warns about type defaulting in the presence of -XTypeApplications

#11947: GHC mistakenly warns about type defaulting in the presence of -XTypeApplications -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 (Type checker) | Keywords: | Operating System: Unknown/Multiple TypeApplications | Architecture: | Type of failure: Incorrect Unknown/Multiple | warning at compile-time Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- This code: {{{#!hs {-# LANGUAGE RankNTypes #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeApplications #-} module Main (main) where theFloatDigits :: forall a. RealFloat a => Int theFloatDigits = floatDigits (undefined @_ @a) main :: IO () main = print (theFloatDigits @Double, theFloatDigits @Float) }}} erroneously produces this warning: {{{ $ /opt/ghc/8.0.1/bin/runghc -Wall TheFloatDigits.hs TheFloatDigits.hs:6:19: warning: [-Wtype-defaults] • Defaulting the following constraint to type ‘Double’ RealFloat a0 • In the ambiguity check for ‘theFloatDigits’ To defer the ambiguity check to use sites, enable AllowAmbiguousTypes In the type signature: theFloatDigits :: forall a. RealFloat a => Int (53,24) }}} GHC's claim that `a0` was defaulted to `Double` is clearly bogus, since `theFloatDigits` outputs different answers for `Double` and `Float`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11947 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11947: GHC mistakenly warns about type defaulting in the presence of -XTypeApplications -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Keywords: Resolution: | TypeApplications 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 goldfire): This is correct behavior. As described [http://downloads.haskell.org/~ghc/8.0.1-rc2/docs/html/users_guide/glasgow_ex... #ambiguous-types-and-the-ambiguity-check here], the ambiguity check for `theFloatDigits` does precisely this: {{{ check :: forall a. RealFloat a => Int -- type copied from theFloatDigits check = theFloatDigits }}} When checking this declaration, `a` is indeed defaulted to `Double`, as reported. This is a consequence of the fact that `theFloatDigits`'s type is indeed ambiguous. A few ways forward here: 1. Clarify the mechanism behind the ambiguity check in the manual. It's stated in there now, but we could make this more prominent and describe that GHC really does type-check a binding as above. 2. Disable type defaulting in an ambiguity check. 3. Do nothing. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11947#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11947: GHC mistakenly warns about type defaulting in the presence of -XTypeApplications -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Keywords: Resolution: | TypeApplications 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 RyanGlScott): I suppose this is correct, but it hardly feels intuitive to me. The definition of `theFloatDigits`, as written above, doesn't seem ambiguous at all, given that we are explicitly applying the type `a` to `undefined`. The fact that GHC is emitting a warning at all appears to be byproduct of the particular implementation it uses to check for ambiguity. That being said, it looks like option 2 would be the most sensible option? I can't envision a scenario in which not defaulting types in an ambiguity check would make a difference. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11947#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11947: GHC mistakenly warns about type defaulting in the presence of -XTypeApplications -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Keywords: Resolution: | TypeApplications 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 goldfire): `theFloatDigits` isn't the thing that's ambiguous or not; it's `theFloatDigits`'s type, `forall a. RealFloat a => Int`, which certainly is ambiguous, mentioning a type variable only in a constraint and not the type head. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11947#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11947: GHC mistakenly warns about type defaulting in the presence of -XTypeApplications -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Keywords: Resolution: | TypeApplications 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 RyanGlScott): Replying to [comment:3 goldfire]:
`theFloatDigits` isn't the thing that's ambiguous or not; it's `theFloatDigits`'s type, `forall a. RealFloat a => Int`, which certainly is ambiguous, mentioning a type variable only in a constraint and not the type head.
Sorry, I was confused. You're absolutely right in that `theFloatDigits`'s type signature is ambiguous. That is apparent if you try to typecheck something similar without defaulting rules like: {{{#!hs theIsSigned :: forall a. Bits a => Bool theIsSigned = isSigned (undefined @_ @a) }}} This fails to compile without `-XAllowAmbiguousTypes` enabled, which makes sense. `theFloatDigits`, on the other hand, compiles both with and without `-XAllowAmbiguousTypes`! This adds another wrinkle to the bug—should it require `-XAllowAmbiguousTypes`, or should it type defaulting make certain otherwise-ambiguous type signatures permissible? I'm not sure what the answer is, but I do believe that we should at least have some way to write `theFloatDigits` without needing to disable `-Wtype-defaults` altogether. Would it make sense to disable type defaulting in ambiguity checks when `-XAllowAmbiguousTypes` is enabled? After all, the warning message already suggests turning it on. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11947#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11947: GHC mistakenly warns about type defaulting in the presence of -XTypeApplications -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Keywords: Resolution: | TypeApplications 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 goldfire): But you should get no warning with `-XAllowAmbiguousTypes`, as that skips the ambiguity check that causes the warning. Or am I mistaken here? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11947#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11947: GHC mistakenly warns about type defaulting in the presence of -XTypeApplications -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Keywords: Resolution: | TypeApplications 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 RyanGlScott): Replying to [comment:5 goldfire]:
But you should get no warning with `-XAllowAmbiguousTypes`, as that skips the ambiguity check that causes the warning. Or am I mistaken here?
You do get a warning, it seems: {{{ $ /opt/ghc/8.0.1/bin/runghc -Wall -XAllowAmbiguousTypes TheFloatDigits.hs TheFloatDigits.hs:6:19: warning: [-Wtype-defaults] • Defaulting the following constraint to type ‘Double’ RealFloat a0 • In the ambiguity check for ‘theFloatDigits’ In the type signature: theFloatDigits :: forall a. RealFloat a => Int (53,24) }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11947#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11947: GHC mistakenly warns about type defaulting in the presence of -XTypeApplications -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Keywords: Resolution: | TypeApplications 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 goldfire): That is a solid bug. GHC should do no such thing. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11947#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11947: GHC mistakenly warns about type defaulting in the presence of -XTypeApplications -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Keywords: Resolution: | TypeApplications 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 think that the solution here is fairly simple: `simplifyAmbiguityCheck` should not do defaulting. Should not be hard to try this out. Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11947#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11947: GHC mistakenly warns about type defaulting in the presence of
-XTypeApplications
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner:
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler (Type | Version: 8.0.1
checker) | Keywords:
Resolution: | TypeApplications
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 Simon Peyton Jones

#11947: GHC mistakenly warns about type defaulting in the presence of -XTypeApplications -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Keywords: Resolution: fixed | TypeApplications Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Incorrect | Test Case: warning at compile-time | typecheck/should_compile/T11947 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * status: new => closed * testcase: => typecheck/should_compile/T11947 * resolution: => fixed Comment: Yes, that worked. The change is small and non-invasive, so could be merged; but it's also a corner case so I think I'll suggest leaving for 8.2 unless anyone yells. Simon -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11947#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11947: GHC mistakenly warns about type defaulting in the presence of -XTypeApplications -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: merge Priority: normal | Milestone: 8.0.2 Component: Compiler (Type | Version: 8.0.1 checker) | Keywords: Resolution: fixed | TypeApplications Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Incorrect | Test Case: warning at compile-time | typecheck/should_compile/T11947 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: closed => merge * milestone: => 8.0.2 Comment: It'd be nice to have this in 8.0.2, since this bug currently requires me to disable `-Wall` in one of my projects. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11947#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#11947: GHC mistakenly warns about type defaulting in the presence of -XTypeApplications -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: closed Priority: normal | Milestone: 8.0.2 Component: Compiler (Type | Version: 8.0.1 checker) | Keywords: Resolution: fixed | TypeApplications Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: Incorrect | Test Case: warning at compile-time | typecheck/should_compile/T11947 Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: merge => closed Comment: Merged to `ghc-8.0` as 7a69acc846e19562a0e07f8f5f9a5c01f8084e83. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/11947#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC