[GHC] #13758: Deriving can't find an instance that holds, standalone deriving works

#13758: Deriving can't find an instance that holds, standalone deriving works -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 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: -------------------------------------+------------------------------------- Using [https://hackage.haskell.org/package/generic-deriving-1.11.2/docs /Generics-Deriving-Monoid.html generic-deriving] works {{{#!hs {-# Language ScopedTypeVariables, GeneralizedNewtypeDeriving, DeriveGeneric, UndecidableInstances, StandaloneDeriving, FlexibleContexts #-} import GHC.Generics import Generics.Deriving.Monoid hiding (GMonoid) import Data.Coerce import Data.Constraint import Data.Semigroup newtype GenericMonoid a = GenericMonoid a instance (Generic a, Monoid' (Rep a)) => Semigroup (GenericMonoid a) where (<>) = coerce (mappenddefault :: a -> a -> a) instance (Generic a, Monoid' (Rep a)) => Monoid (GenericMonoid a) where mempty = coerce (memptydefault :: a) mappend = coerce (mappenddefault :: a -> a -> a) data Urls = Urls String String String deriving (Show, Generic) newtype UrlsDeriv = UD (GenericMonoid Urls) deriving instance Semigroup UrlsDeriv deriving instance Monoid UrlsDeriv }}} but changing that to {{{#!hs newtype UrlsDeriv = UD (GenericMonoid Urls) deriving (Semigroup, Monoid) }}} fails {{{ $ ghci -ignore-dot-ghci tWqD.hs GHCi, version 8.0.1: http://www.haskell.org/ghc/ :? for help [1 of 1] Compiling Main ( tWqD.hs, interpreted ) Ok, modules loaded: Main. *Main> :r [1 of 1] Compiling Main ( tWqD.hs, interpreted ) tWqD.hs:26:13: error: • No instance for (Monoid' (Rep Urls)) arising from the 'deriving' clause of a data type declaration Possible fix: use a standalone 'deriving instance' declaration, so you can specify the instance context yourself • When deriving the instance for (Semigroup UrlsDeriv) tWqD.hs:26:24: error: • No instance for (Monoid' (Rep Urls)) arising from the 'deriving' clause of a data type declaration Possible fix: use a standalone 'deriving instance' declaration, so you can specify the instance context yourself • When deriving the instance for (Monoid UrlsDeriv) Failed, modules loaded: none. }}} This feels familiar but I couldn't quickly. I can't recall if this behavior is intended so I'm filing a ticket just in case. It even following proof of `Monoid' (Rep Urls)` and a dummy quasiquote `pure []` separating it them, {{{#!hs {-# Language ..., TemplateHaskell #-} ... doo :: Dict (Monoid' (Rep Urls)) doo = Dict pure [] newtype UrlsDeriv = UD (GenericMonoid Urls) deriving Monoid }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13758 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13758: Deriving can't find an instance that holds, standalone deriving works -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Description changed by Iceland_jack: @@ -1,3 +1,0 @@ - Using [https://hackage.haskell.org/package/generic-deriving-1.11.2/docs - /Generics-Deriving-Monoid.html generic-deriving] works - @@ -10,0 +7,2 @@ + -- https://hackage.haskell.org/package/generic-deriving-1.11.2/docs + /Generics-Deriving-Monoid.html New description: {{{#!hs {-# Language ScopedTypeVariables, GeneralizedNewtypeDeriving, DeriveGeneric, UndecidableInstances, StandaloneDeriving, FlexibleContexts #-} import GHC.Generics -- https://hackage.haskell.org/package/generic-deriving-1.11.2/docs /Generics-Deriving-Monoid.html import Generics.Deriving.Monoid hiding (GMonoid) import Data.Coerce import Data.Constraint import Data.Semigroup newtype GenericMonoid a = GenericMonoid a instance (Generic a, Monoid' (Rep a)) => Semigroup (GenericMonoid a) where (<>) = coerce (mappenddefault :: a -> a -> a) instance (Generic a, Monoid' (Rep a)) => Monoid (GenericMonoid a) where mempty = coerce (memptydefault :: a) mappend = coerce (mappenddefault :: a -> a -> a) data Urls = Urls String String String deriving (Show, Generic) newtype UrlsDeriv = UD (GenericMonoid Urls) deriving instance Semigroup UrlsDeriv deriving instance Monoid UrlsDeriv }}} but changing that to {{{#!hs newtype UrlsDeriv = UD (GenericMonoid Urls) deriving (Semigroup, Monoid) }}} fails {{{ $ ghci -ignore-dot-ghci tWqD.hs GHCi, version 8.0.1: http://www.haskell.org/ghc/ :? for help [1 of 1] Compiling Main ( tWqD.hs, interpreted ) Ok, modules loaded: Main. *Main> :r [1 of 1] Compiling Main ( tWqD.hs, interpreted ) tWqD.hs:26:13: error: • No instance for (Monoid' (Rep Urls)) arising from the 'deriving' clause of a data type declaration Possible fix: use a standalone 'deriving instance' declaration, so you can specify the instance context yourself • When deriving the instance for (Semigroup UrlsDeriv) tWqD.hs:26:24: error: • No instance for (Monoid' (Rep Urls)) arising from the 'deriving' clause of a data type declaration Possible fix: use a standalone 'deriving instance' declaration, so you can specify the instance context yourself • When deriving the instance for (Monoid UrlsDeriv) Failed, modules loaded: none. }}} This feels familiar but I couldn't quickly. I can't recall if this behavior is intended so I'm filing a ticket just in case. It even following proof of `Monoid' (Rep Urls)` and a dummy quasiquote `pure []` separating it them, {{{#!hs {-# Language ..., TemplateHaskell #-} ... doo :: Dict (Monoid' (Rep Urls)) doo = Dict pure [] newtype UrlsDeriv = UD (GenericMonoid Urls) deriving Monoid }}} -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13758#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13758: Deriving can't find an instance that holds, standalone deriving works -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Description changed by Iceland_jack: @@ -0,0 +1,2 @@ + This works: + @@ -70,2 +72,2 @@ - It even following proof of `Monoid' (Rep Urls)` and a dummy quasiquote - `pure []` separating it them, + ---- + '''Magically''' having `pure []` separate them, works: @@ -84,1 +86,1 @@ - deriving Monoid + deriving (Semigroup, Monoid) New description: This works: {{{#!hs {-# Language ScopedTypeVariables, GeneralizedNewtypeDeriving, DeriveGeneric, UndecidableInstances, StandaloneDeriving, FlexibleContexts #-} import GHC.Generics -- https://hackage.haskell.org/package/generic-deriving-1.11.2/docs /Generics-Deriving-Monoid.html import Generics.Deriving.Monoid hiding (GMonoid) import Data.Coerce import Data.Constraint import Data.Semigroup newtype GenericMonoid a = GenericMonoid a instance (Generic a, Monoid' (Rep a)) => Semigroup (GenericMonoid a) where (<>) = coerce (mappenddefault :: a -> a -> a) instance (Generic a, Monoid' (Rep a)) => Monoid (GenericMonoid a) where mempty = coerce (memptydefault :: a) mappend = coerce (mappenddefault :: a -> a -> a) data Urls = Urls String String String deriving (Show, Generic) newtype UrlsDeriv = UD (GenericMonoid Urls) deriving instance Semigroup UrlsDeriv deriving instance Monoid UrlsDeriv }}} but changing that to {{{#!hs newtype UrlsDeriv = UD (GenericMonoid Urls) deriving (Semigroup, Monoid) }}} fails {{{ $ ghci -ignore-dot-ghci tWqD.hs GHCi, version 8.0.1: http://www.haskell.org/ghc/ :? for help [1 of 1] Compiling Main ( tWqD.hs, interpreted ) Ok, modules loaded: Main. *Main> :r [1 of 1] Compiling Main ( tWqD.hs, interpreted ) tWqD.hs:26:13: error: • No instance for (Monoid' (Rep Urls)) arising from the 'deriving' clause of a data type declaration Possible fix: use a standalone 'deriving instance' declaration, so you can specify the instance context yourself • When deriving the instance for (Semigroup UrlsDeriv) tWqD.hs:26:24: error: • No instance for (Monoid' (Rep Urls)) arising from the 'deriving' clause of a data type declaration Possible fix: use a standalone 'deriving instance' declaration, so you can specify the instance context yourself • When deriving the instance for (Monoid UrlsDeriv) Failed, modules loaded: none. }}} This feels familiar but I couldn't quickly. I can't recall if this behavior is intended so I'm filing a ticket just in case. ---- '''Magically''' having `pure []` separate them, works: {{{#!hs {-# Language ..., TemplateHaskell #-} ... doo :: Dict (Monoid' (Rep Urls)) doo = Dict pure [] newtype UrlsDeriv = UD (GenericMonoid Urls) deriving (Semigroup, Monoid) }}} -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13758#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13758: Deriving can't find an instance that holds, standalone deriving works -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #2721, #8165 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * related: => #2721, #8165 Comment: Hah! You tickled a bug that I originally ran into when I was working on the fix for #2721/#8165 (making `GeneralizedNewtypeDeriving` work for classes with associated type families). The issue was that we weren't updating the type family instance environment early enough in type checking, which resulted in the strange staging error you experienced. I had thought that the only way to trigger that bug was with classes with associated type families, but you have just proven me wrong! The fix made it into GHC 8.2.1, and this program does indeed typecheck with that version. However, I'll keep this ticket open for now, as this program makes for a good GHC regression test. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13758#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13758: Deriving can't find an instance that holds, standalone deriving works
-------------------------------------+-------------------------------------
Reporter: Iceland_jack | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.0.1
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking:
Related Tickets: #2721, #8165 | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by Ryan Scott

#13758: Deriving can't find an instance that holds, standalone deriving works -------------------------------------+------------------------------------- Reporter: Iceland_jack | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.2.1 Component: Compiler | Version: 8.0.1 Resolution: fixed | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: | deriving/should_compile/T13758 Blocked By: | Blocking: Related Tickets: #2721, #8165 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * testcase: => deriving/should_compile/T13758 * status: new => closed * resolution: => fixed * milestone: => 8.2.1 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13758#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC