[GHC] #13314: StandaloneDeriving and DeriveAnyClass don't work together

#13314: StandaloneDeriving and DeriveAnyClass don't work together -------------------------------------+------------------------------------- Reporter: chris-martin | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Keywords: | 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'm starting with the `SPretty` example from the `DeriveAnyClass` section in the GHC users guide: {{{#!hs #!/usr/bin/env stack -- stack --resolver lts-8.0 {-# LANGUAGE DefaultSignatures, DeriveAnyClass, StandaloneDeriving #-} import Prelude import Numeric.Natural (Natural) class SPretty a where sPpr :: a -> String default sPpr :: Show a => a -> String sPpr = show }}} I can write an empty instance for `Natural`: {{{#!hs instance SPretty Natural where }}} So then I would expect to be able to write an equivalent definition using standalone deriving: {{{#!hs deriving instance SPretty Natural }}} But instead it fails with this error: {{{ error: • Can't make a derived instance of ‘SPretty Natural’: The data constructors of ‘Natural’ are not all in scope so you cannot derive an instance for it • In the stand-alone deriving instance for ‘SPretty Natural’ }}} It seems like this ought to work; I'm not sure why the constructors should need to be in scope, given that the instance can be derived trivially without defining any methods. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13314 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13314: StandaloneDeriving and DeriveAnyClass don't work together -------------------------------------+------------------------------------- Reporter: chris-martin | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Resolution: | Keywords: 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 chris-martin: Old description:
I'm starting with the `SPretty` example from the `DeriveAnyClass` section in the GHC users guide:
{{{#!hs #!/usr/bin/env stack -- stack --resolver lts-8.0 {-# LANGUAGE DefaultSignatures, DeriveAnyClass, StandaloneDeriving #-}
import Prelude import Numeric.Natural (Natural)
class SPretty a where sPpr :: a -> String default sPpr :: Show a => a -> String sPpr = show }}}
I can write an empty instance for `Natural`:
{{{#!hs instance SPretty Natural where }}}
So then I would expect to be able to write an equivalent definition using standalone deriving:
{{{#!hs deriving instance SPretty Natural }}}
But instead it fails with this error:
{{{ error: • Can't make a derived instance of ‘SPretty Natural’: The data constructors of ‘Natural’ are not all in scope so you cannot derive an instance for it • In the stand-alone deriving instance for ‘SPretty Natural’ }}}
It seems like this ought to work; I'm not sure why the constructors should need to be in scope, given that the instance can be derived trivially without defining any methods.
New description: I'm starting with the `SPretty` example from the `DeriveAnyClass` section in the GHC users guide: {{{#!hs #!/usr/bin/env stack -- stack --resolver lts-8.0 {-# LANGUAGE DefaultSignatures, DeriveAnyClass, StandaloneDeriving #-} import Prelude import Numeric.Natural (Natural) class SPretty a where sPpr :: a -> String default sPpr :: Show a => a -> String sPpr = show }}} I can write an empty instance for `Natural`: {{{#!hs instance SPretty Natural where }}} So then I would expect to be able to write an equivalent definition using standalone deriving: {{{#!hs deriving instance SPretty Natural }}} But instead it fails with this error: {{{ error: • Can't make a derived instance of ‘SPretty Natural’: The data constructors of ‘Natural’ are not all in scope so you cannot derive an instance for it • In the stand-alone deriving instance for ‘SPretty Natural’ }}} It seems like this ought to work; I'm not sure why the constructors should need to be in scope, given that the instance can be derived trivially without defining any methods. -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13314#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13314: StandaloneDeriving and DeriveAnyClass don't work together -------------------------------------+------------------------------------- Reporter: chris-martin | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Resolution: | Keywords: 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 chris-martin: Old description:
I'm starting with the `SPretty` example from the `DeriveAnyClass` section in the GHC users guide:
{{{#!hs #!/usr/bin/env stack -- stack --resolver lts-8.0 {-# LANGUAGE DefaultSignatures, DeriveAnyClass, StandaloneDeriving #-}
import Prelude import Numeric.Natural (Natural)
class SPretty a where sPpr :: a -> String default sPpr :: Show a => a -> String sPpr = show }}}
I can write an empty instance for `Natural`:
{{{#!hs instance SPretty Natural where }}}
So then I would expect to be able to write an equivalent definition using standalone deriving:
{{{#!hs deriving instance SPretty Natural }}}
But instead it fails with this error:
{{{ error: • Can't make a derived instance of ‘SPretty Natural’: The data constructors of ‘Natural’ are not all in scope so you cannot derive an instance for it • In the stand-alone deriving instance for ‘SPretty Natural’ }}}
It seems like this ought to work; I'm not sure why the constructors should need to be in scope, given that the instance can be derived trivially without defining any methods.
New description: I'm starting with the `SPretty` example from the `DeriveAnyClass` section in the GHC users guide: {{{#!hs #!/usr/bin/env stack -- stack --resolver lts-8.0 {-# LANGUAGE DefaultSignatures, DeriveAnyClass, StandaloneDeriving #-} import Prelude import Numeric.Natural (Natural) class SPretty a where sPpr :: a -> String default sPpr :: Show a => a -> String sPpr = show }}} I can write an empty instance for `Natural`: {{{#!hs instance SPretty Natural where }}} So then I would expect to be able to write an equivalent definition using standalone-deriving and derive-and-class: {{{#!hs deriving instance SPretty Natural }}} But instead it fails with this error: {{{ error: • Can't make a derived instance of ‘SPretty Natural’: The data constructors of ‘Natural’ are not all in scope so you cannot derive an instance for it • In the stand-alone deriving instance for ‘SPretty Natural’ }}} It seems like this ought to work; I'm not sure why the constructors should need to be in scope, given that the instance can be derived trivially without defining any methods. -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13314#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13314: StandaloneDeriving and DeriveAnyClass don't work together -------------------------------------+------------------------------------- Reporter: chris-martin | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Resolution: | Keywords: 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 chris-martin: Old description:
I'm starting with the `SPretty` example from the `DeriveAnyClass` section in the GHC users guide:
{{{#!hs #!/usr/bin/env stack -- stack --resolver lts-8.0 {-# LANGUAGE DefaultSignatures, DeriveAnyClass, StandaloneDeriving #-}
import Prelude import Numeric.Natural (Natural)
class SPretty a where sPpr :: a -> String default sPpr :: Show a => a -> String sPpr = show }}}
I can write an empty instance for `Natural`:
{{{#!hs instance SPretty Natural where }}}
So then I would expect to be able to write an equivalent definition using standalone-deriving and derive-and-class:
{{{#!hs deriving instance SPretty Natural }}}
But instead it fails with this error:
{{{ error: • Can't make a derived instance of ‘SPretty Natural’: The data constructors of ‘Natural’ are not all in scope so you cannot derive an instance for it • In the stand-alone deriving instance for ‘SPretty Natural’ }}}
It seems like this ought to work; I'm not sure why the constructors should need to be in scope, given that the instance can be derived trivially without defining any methods.
New description: I'm starting with the `SPretty` example from the `DeriveAnyClass` section in the GHC users guide: {{{#!hs #!/usr/bin/env stack -- stack --resolver lts-8.0 {-# LANGUAGE DefaultSignatures, DeriveAnyClass, StandaloneDeriving #-} import Prelude import Numeric.Natural (Natural) class SPretty a where sPpr :: a -> String default sPpr :: Show a => a -> String sPpr = show }}} I can write an empty instance for `Natural`: {{{#!hs instance SPretty Natural where }}} So then I would expect to be able to write an equivalent definition using `StandaloneDeriving` and `DeriveAnyClass`: {{{#!hs deriving instance SPretty Natural }}} But instead it fails with this error: {{{ error: • Can't make a derived instance of ‘SPretty Natural’: The data constructors of ‘Natural’ are not all in scope so you cannot derive an instance for it • In the stand-alone deriving instance for ‘SPretty Natural’ }}} It seems like this ought to work; I'm not sure why the constructors should need to be in scope, given that the instance can be derived trivially without defining any methods. -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13314#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13314: StandaloneDeriving and DeriveAnyClass don't work together -------------------------------------+------------------------------------- Reporter: chris-martin | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Resolution: fixed | Keywords: 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 rwbarton): * status: new => closed * cc: RyanGlScott (added) * resolution: => fixed Comment: Happily this works with the revamped `DeriveAnyClass` logic in HEAD. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13314#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13314: StandaloneDeriving and DeriveAnyClass don't work together -------------------------------------+------------------------------------- Reporter: chris-martin | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Resolution: fixed | Keywords: Generics Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #11509 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * keywords: => Generics * related: => #11509 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13314#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13314: StandaloneDeriving and DeriveAnyClass don't work together -------------------------------------+------------------------------------- Reporter: chris-martin | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Resolution: fixed | Keywords: Generics, | deriving Operating System: Unknown/Multiple | Architecture: Type of failure: GHC rejects | Unknown/Multiple valid program | Test Case: Blocked By: | Blocking: Related Tickets: #11509 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * keywords: Generics => Generics, deriving -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13314#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC