[GHC] #13314: StandaloneDeriving and DeriveAnyClass don't work together
GHC
ghc-devs at haskell.org
Wed Feb 22 01:42:51 UTC 2017
#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
More information about the ghc-tickets
mailing list