[GHC] #10514: Generic for existential types
GHC
ghc-devs at haskell.org
Fri Jun 12 09:00:59 UTC 2015
#10514: Generic for existential types
-------------------------------------+-------------------------------------
Reporter: andreas.abel | Owner: ekmett
Type: feature request | Status: new
Priority: normal | Milestone:
Component: Core Libraries | Version: 7.10.1
Resolution: | Keywords:
Operating System: Unknown/Multiple | Architecture:
Type of failure: None/Unknown | Unknown/Multiple
Blocked By: | Test Case:
Related Tickets: | Blocking:
| Differential Revisions:
-------------------------------------+-------------------------------------
Description changed by andreas.abel:
Old description:
> I have some use for Generic for an existential type which is constraint
> to be Generic.
>
> {{{!#hs
>
> {-# LANGUAGE DeriveGeneric #-}
> {-# LANGUAGE ExistentialQuantification #-}
> {-# LANGUAGE StandaloneDeriving #-}
>
> import GHC.Generics
>
> data U = forall a. (Generic a) => U a
> -- deriving (Generic)
> -- Can't make a derived instance of ‘Generic U’:
> -- Constructor ‘U’ has existentials or constraints in its type
> -- Possible fix: use a standalone deriving declaration instead
>
> -- deriving instance Generic U
> -- Can't make a derived instance of ‘Generic U’:
> -- U must be a vanilla data constructor
> -- In the stand-alone deriving instance for ‘Generic U’
>
> data D1Ser
> data C1_0Ser
>
> instance Generic U where
> type Rep U = D D1Ser (C1 C1_0Ser (S1 NoSelector (Rep a)))
> -- Not in scope: type variable ‘a’
>
> -- How to bring the existential type `a' into scope?
>
> }}}
New description:
I have some use for Generic for an existential type which is constraint to
be Generic.
{{{#!hs
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE StandaloneDeriving #-}
import GHC.Generics
data U = forall a. (Generic a) => U a
deriving (Generic) -- TRY 1
-- Can't make a derived instance of ‘Generic U’:
-- Constructor ‘U’ has existentials or constraints in its type
-- Possible fix: use a standalone deriving declaration instead
deriving instance Generic U -- TRY 2
-- Can't make a derived instance of ‘Generic U’:
-- U must be a vanilla data constructor
-- In the stand-alone deriving instance for ‘Generic U’
data D1Ser
data C1_0Ser
instance Generic U where -- TRY 3
type Rep U = D D1Ser (C1 C1_0Ser (S1 NoSelector (Rep a)))
-- Not in scope: type variable ‘a’
-- How to bring the existential type `a' into scope?
}}}
--
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/10514#comment:1>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list