[GHC] #13272: DeriveAnyClass regression involving a rigid type variable

#13272: DeriveAnyClass regression involving a rigid type variable -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler | Version: 8.1 (Type checker) | Keywords: Generics | Operating System: Unknown/Multiple Architecture: | Type of failure: GHC rejects Unknown/Multiple | valid program Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- I was writing up an example to show off how `DeriveAnyClass` has improved since 639e702b6129f501c539b158b982ed8489e3d09c, and wouldn't you know it, the example doesn't actually compile anymore post- 639e702b6129f501c539b158b982ed8489e3d09c. Oopsie. {{{#!hs module TypeName where import GHC.Generics class TypeName a where typeName :: forall proxy. proxy a -> String default typeName :: forall proxy d f. (Generic a, Rep a ~ D1 d f, Datatype d) => proxy a -> String typeName _ = gtypeName $ from (undefined :: a) gtypeName :: Datatype d => D1 d f p -> String gtypeName = datatypeName data T a = MkT a deriving (Generic, TypeName) }}} This compiles before that commit. After it, however, it fails with the error: {{{ [1 of 1] Compiling TypeName ( Bug.hs, interpreted ) Bug.hs:23:22: error: • Couldn't match type ‘f’ with ‘C1 ('MetaCons "MkT" 'PrefixI 'False) (S1 ('MetaSel 'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a))’ arising from the 'deriving' clause of a data type declaration ‘f’ is a rigid type variable bound by the deriving clause for ‘TypeName (T a)’ at Bug.hs:14:38 • When deriving the instance for (TypeName (T a)) | 23 | deriving (Generic, TypeName) | ^^^^^^^^ }}} I'm not sure why it's complaining only about `f` and not, say, `d`. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13272 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13272: DeriveAnyClass regression involving a rigid type variable -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.1 checker) | Resolution: | Keywords: Generics Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): And it gets worse if you make a slight tweak to the original program by introducing an intermediary type variable: {{{#!hs {-# LANGUAGE DefaultSignatures #-} {-# LANGUAGE DeriveAnyClass #-} {-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeFamilies #-} module TypeName where import GHC.Generics class TypeName a where typeName :: proxy a -> String default typeName :: (Generic a, Rep a ~ gg, gg ~ D1 d f, Datatype d) => proxy a -> String typeName _ = gtypeName $ from (undefined :: a) gtypeName :: Datatype d => D1 d f p -> String gtypeName = datatypeName data T a = MkT a deriving (Generic, TypeName) }}} Then it sends the compiler (presumably the constraint solver) into an infinite loop! I'll attach the portion of `-ddump-tc-trace`'s output that appears to be looping. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13272#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13272: DeriveAnyClass regression involving a rigid type variable -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.1 checker) | Resolution: | Keywords: Generics Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * Attachment "13272-ddump-tc-trace-loop.txt" added. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13272 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13272: DeriveAnyClass regression involving a rigid type variable -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.1 checker) | Resolution: | Keywords: Generics Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Description changed by RyanGlScott: @@ -7,0 +7,6 @@ + {-# LANGUAGE DefaultSignatures #-} + {-# LANGUAGE DeriveAnyClass #-} + {-# LANGUAGE DeriveGeneric #-} + {-# LANGUAGE FlexibleContexts #-} + {-# LANGUAGE ScopedTypeVariables #-} + {-# LANGUAGE TypeFamilies #-} New description: I was writing up an example to show off how `DeriveAnyClass` has improved since 639e702b6129f501c539b158b982ed8489e3d09c, and wouldn't you know it, the example doesn't actually compile anymore post- 639e702b6129f501c539b158b982ed8489e3d09c. Oopsie. {{{#!hs {-# LANGUAGE DefaultSignatures #-} {-# LANGUAGE DeriveAnyClass #-} {-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeFamilies #-} module TypeName where import GHC.Generics class TypeName a where typeName :: forall proxy. proxy a -> String default typeName :: forall proxy d f. (Generic a, Rep a ~ D1 d f, Datatype d) => proxy a -> String typeName _ = gtypeName $ from (undefined :: a) gtypeName :: Datatype d => D1 d f p -> String gtypeName = datatypeName data T a = MkT a deriving (Generic, TypeName) }}} This compiles before that commit. After it, however, it fails with the error: {{{ [1 of 1] Compiling TypeName ( Bug.hs, interpreted ) Bug.hs:23:22: error: • Couldn't match type ‘f’ with ‘C1 ('MetaCons "MkT" 'PrefixI 'False) (S1 ('MetaSel 'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a))’ arising from the 'deriving' clause of a data type declaration ‘f’ is a rigid type variable bound by the deriving clause for ‘TypeName (T a)’ at Bug.hs:14:38 • When deriving the instance for (TypeName (T a)) | 23 | deriving (Generic, TypeName) | ^^^^^^^^ }}} I'm not sure why it's complaining only about `f` and not, say, `d`. -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13272#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13272: DeriveAnyClass regression involving a rigid type variable -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.1 checker) | Resolution: | Keywords: Generics Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * cc: simonpj (added) Comment: FWIW, in the example in comment:1, the loop happens upon the first call to `solveWantedsAndDrop` [http://git.haskell.org/ghc.git/blob/0e7601749d53d59df528ede996d8b54352051498... here]. I'm a bit clueless as to where to begin searching for a place to debug this. Simon, do you have any ideas? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13272#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13272: DeriveAnyClass regression involving a rigid type variable -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.4.1 Component: Compiler (Type | Version: 8.1 checker) | Resolution: | Keywords: Generics Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by bgamari): * milestone: 8.2.1 => 8.4.1 Comment: We discussed this on the call and Simon said that fixing this correctly will be non-trivial. I'm (sadly) going to bump to 8.4 unless something changes. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13272#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13272: DeriveAnyClass regression involving a rigid type variable -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.4.1 Component: Compiler (Type | Version: 8.1 checker) | Resolution: | Keywords: Generics Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): It's still a bit of a bummer that `DeriveAnyClass` has become //worse//. Perhaps we should just revert 639e702b6129f501c539b158b982ed8489e3d09c for now? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13272#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13272: DeriveAnyClass regression involving a rigid type variable -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.4.1 Component: Compiler (Type | Version: 8.1 checker) | Resolution: | Keywords: Generics Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by rwbarton): Isn't it better now in other ways, though? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13272#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13272: DeriveAnyClass regression involving a rigid type variable -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.4.1 Component: Compiler (Type | Version: 8.1 checker) | Resolution: | Keywords: Generics Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott):
Isn't it better now in other ways, though?
That's true. I really don't know how many pieces of code in the wild actually structure their default type signatures in a way that's analogous to the original program, so if not too many folks complain about it during the 8.2 release candidate window, I suppose we could deem 639e702b6129f501c539b158b982ed8489e3d09c a net positive and live with it for now. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13272#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13272: DeriveAnyClass regression involving a rigid type variable -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: new Priority: high | Milestone: 8.4.1 Component: Compiler (Type | Version: 8.1 checker) | Resolution: | Keywords: Generics Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): I thikn I have a fix actually. Wait till tomorrow -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13272#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13272: DeriveAnyClass regression involving a rigid type variable
-------------------------------------+-------------------------------------
Reporter: RyanGlScott | Owner: (none)
Type: bug | Status: new
Priority: high | Milestone: 8.4.1
Component: Compiler (Type | Version: 8.1
checker) |
Resolution: | Keywords: Generics
Operating System: Unknown/Multiple | Architecture:
Type of failure: GHC rejects | Unknown/Multiple
valid program | Test Case:
Blocked By: | Blocking:
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Simon Peyton Jones

#13272: DeriveAnyClass regression involving a rigid type variable -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: closed Priority: high | Milestone: 8.4.1 Component: Compiler (Type | Version: 8.1 checker) | Resolution: fixed | Keywords: Generics Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: GHC rejects | Test Case: valid program | deriving/should_compile/T13272, | T13272a Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * status: new => closed * testcase: => deriving/should_compile/T13272, T13272a * resolution: => fixed -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13272#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13272: DeriveAnyClass regression involving a rigid type variable -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: closed Priority: high | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.1 checker) | Resolution: fixed | Keywords: Generics Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: GHC rejects | Test Case: valid program | deriving/should_compile/T13272, | T13272a Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * milestone: 8.4.1 => 8.2.1 Comment: Many thanks Simon, you're a lifesaver. For my edification, which part in particular was causing the reported error? Was it the fact that we were creating new variables in `inferConstraintsDAC` without using `pushTcLevelM`? Or was it due to not using explicit unification variables (via `newMetaTyVarsX`)? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13272#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13272: DeriveAnyClass regression involving a rigid type variable -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: closed Priority: high | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.1 checker) | Resolution: fixed | Keywords: Generics Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: GHC rejects | Test Case: valid program | deriving/should_compile/T13272, | T13272a Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by simonpj): The latter! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13272#comment:12 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13272: DeriveAnyClass regression involving a rigid type variable -------------------------------------+------------------------------------- Reporter: RyanGlScott | Owner: (none) Type: bug | Status: closed Priority: high | Milestone: 8.2.1 Component: Compiler (Type | Version: 8.1 checker) | Keywords: Generics, Resolution: fixed | deriving Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: GHC rejects | Test Case: valid program | deriving/should_compile/T13272, | T13272a Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * keywords: Generics => Generics, deriving -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13272#comment:13 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC