[GHC] #12441: Conflicting definitions error does not print explicit quantifiers when necessary

#12441: Conflicting definitions error does not print explicit quantifiers when necessary -------------------------------------+------------------------------------- Reporter: ezyang | 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: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- {{{ -- Y.hs-boot {-# LANGUAGE ScopedTypeVariables #-} module Y where f :: forall a b. (a, b) -- YY.hs module YY where import {-# SOURCE #-} Y -- Y.hs {-# LANGUAGE ScopedTypeVariables #-} module Y where import YY f :: forall b a. (a, b) f = undefined }}} I get the following unhelpful error: {{{ ezyang@sabre:~$ ghc-8.0 --make Y.hs -fforce-recomp [1 of 3] Compiling Y[boot] ( Y.hs-boot, Y.o-boot ) [2 of 3] Compiling YY ( YY.hs, YY.o ) [3 of 3] Compiling Y ( Y.hs, Y.o ) Y.hs-boot:3:1: error: Identifier ‘f’ has conflicting definitions in the module and its hs-boot file Main module: f :: (a, b) Boot file: f :: (a, b) The two types are different }}} Yes this example is purposely shooting itself in the foot, but in the wild I encountered an un-annotated type which inferred a different quantifier ordering than what I expected, and I subsequently spent a while puzzling over the error message. `-fprint-explicit-foralls` is a sufficient workaround. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12441 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12441: Conflicting definitions error does not print explicit quantifiers when necessary -------------------------------------+------------------------------------- Reporter: ezyang | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Resolution: | Keywords: newcomers 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 bgamari): * keywords: => newcomers * failure: None/Unknown => Incorrect warning at compile-time @@ -1,1 +1,1 @@ - {{{ + {{{#!hs @@ -6,0 +6,1 @@ + @@ -9,0 +10,1 @@ + New description: {{{#!hs -- Y.hs-boot {-# LANGUAGE ScopedTypeVariables #-} module Y where f :: forall a b. (a, b) -- YY.hs module YY where import {-# SOURCE #-} Y -- Y.hs {-# LANGUAGE ScopedTypeVariables #-} module Y where import YY f :: forall b a. (a, b) f = undefined }}} I get the following unhelpful error: {{{ ezyang@sabre:~$ ghc-8.0 --make Y.hs -fforce-recomp [1 of 3] Compiling Y[boot] ( Y.hs-boot, Y.o-boot ) [2 of 3] Compiling YY ( YY.hs, YY.o ) [3 of 3] Compiling Y ( Y.hs, Y.o ) Y.hs-boot:3:1: error: Identifier ‘f’ has conflicting definitions in the module and its hs-boot file Main module: f :: (a, b) Boot file: f :: (a, b) The two types are different }}} Yes this example is purposely shooting itself in the foot, but in the wild I encountered an un-annotated type which inferred a different quantifier ordering than what I expected, and I subsequently spent a while puzzling over the error message. `-fprint-explicit-foralls` is a sufficient workaround. -- Comment: I think this would be a reasonable thing for a newcomer to knock off. Just check whether the two types are equivalent up to quantifiers and render them with quantifiers if so. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12441#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12441: Conflicting definitions error does not print explicit quantifiers when necessary -------------------------------------+------------------------------------- Reporter: ezyang | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Resolution: | Keywords: newcomer 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 bgamari): * keywords: newcomers => newcomer -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12441#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12441: Conflicting definitions error does not print explicit quantifiers when necessary -------------------------------------+------------------------------------- Reporter: ezyang | Owner: philderbeast Type: bug | Status: new Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Resolution: | Keywords: newcomer 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 philderbeast): * owner: => philderbeast -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12441#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12441: Conflicting definitions error does not print explicit quantifiers when necessary -------------------------------------+------------------------------------- Reporter: ezyang | Owner: philderbeast Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Resolution: | Keywords: newcomer 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): Phab:D2734 Wiki Page: | -------------------------------------+------------------------------------- Changes (by philderbeast): * status: new => patch * differential: => Phab:D2734 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12441#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12441: Conflicting definitions error does not print explicit quantifiers when necessary -------------------------------------+------------------------------------- Reporter: ezyang | Owner: philderbeast Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Resolution: | Keywords: newcomer 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): Phab:D2734 Wiki Page: | -------------------------------------+------------------------------------- Comment (by philderbeast): Found these failures ... {{{ Unexpected results from: TEST="T3468 tcfail072 T8119 KindInvariant" }}} Of those, only T3468 is showing forall in the diff ... {{{ Actual stderr output differs from expected: and its hs-boot file Main module: type role Tool phantom data Tool d where - F :: a -> Tool d + F :: forall d a r. a -> Tool d Boot file: abstract Tool The types have different kinds *** unexpected failure for T3468(normal) }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12441#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12441: Conflicting definitions error does not print explicit quantifiers when necessary -------------------------------------+------------------------------------- Reporter: ezyang | Owner: philderbeast Type: bug | Status: patch Priority: normal | Milestone: Component: Compiler (Type | Version: 8.0.1 checker) | Resolution: | Keywords: newcomer 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): Phab:D2734 Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): Thanks for doing this patch. To me the extra-code to extra-benefit ratio feels a bit low. My suggestion: always print foralls when displaying the results from hi-boot- file mis-matches. * It's a relatively corner case that few people encounter, and those that do are probably not going to be puzzled by a forall. * If we start getting complaints that the foralls are cluttering things up for someone we can consider elaborating. In short, let's not solve a problem we don't yet have. Even with the "always print foralls" idea, the whole ppr-iface stuff is getting a bit baroque. We have * The print-foralls flag * The `ShowSub` info * Sometimes `hdr_only` flag goo Could we combine all three into a single record with three fields? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12441#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12441: Conflicting definitions error does not print explicit quantifiers when
necessary
-------------------------------------+-------------------------------------
Reporter: ezyang | Owner: philderbeast
Type: bug | Status: patch
Priority: normal | Milestone:
Component: Compiler (Type | Version: 8.0.1
checker) |
Resolution: | Keywords: newcomer
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): Phab:D2734
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ben Gamari

#12441: Conflicting definitions error does not print explicit quantifiers when necessary -------------------------------------+------------------------------------- Reporter: ezyang | Owner: Type: bug | Status: new Priority: normal | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.0.1 checker) | Resolution: | Keywords: newcomer 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): Phab:D2734 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * owner: philderbeast => * status: patch => new * milestone: => 8.2.1 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12441#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#12441: Conflicting definitions error does not print explicit quantifiers when necessary -------------------------------------+------------------------------------- Reporter: ezyang | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.0.1 checker) | Resolution: fixed | Keywords: newcomer 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): Phab:D2734 Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * status: new => closed * resolution: => fixed Comment: Thanks to philderbeast for taking care of this! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12441#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC