[GHC] #10514: Generic for existential types

#10514: Generic for existential types -------------------------------------+------------------------------------- Reporter: | Owner: ekmett andreas.abel | Status: new Type: feature | Milestone: request | Version: 7.10.1 Priority: normal | Operating System: Unknown/Multiple Component: Core | Type of failure: None/Unknown Libraries | Blocked By: Keywords: | Related Tickets: Architecture: | Unknown/Multiple | Test Case: | Blocking: | Differential Revisions: | -------------------------------------+------------------------------------- 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? }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10514 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#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

#10514: Generic for existential types -------------------------------------+------------------------------------- Reporter: andreas.abel | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Core Libraries | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Changes (by RyanGlScott): * cc: RyanGlScott, ekmett (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10514#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10514: Generic for existential types -------------------------------------+------------------------------------- Reporter: andreas.abel | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Core Libraries | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by dreixel): I might be wrong, but I don't think there's any hope for supporting existentials with the current approach of `GHC.Generics` (especially when their kind is `*` and they show up as arguments to constructors). -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10514#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10514: Generic for existential types -------------------------------------+------------------------------------- Reporter: andreas.abel | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Core Libraries | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Revisions: -------------------------------------+------------------------------------- Comment (by goldfire): Something tells me this is an open research problem... -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10514#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10514: Generic for existential types -------------------------------------+------------------------------------- Reporter: andreas.abel | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Core Libraries | Version: 7.10.1 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #8560 | Differential Revisions: -------------------------------------+------------------------------------- Changes (by goldfire): * related: => #8560 Comment: See also #8560 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10514#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10514: Generic for existential types -------------------------------------+------------------------------------- Reporter: andreas.abel | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Core Libraries | Version: 7.10.1 Resolution: | Keywords: Generics Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #8560 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * keywords: => Generics -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10514#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10514: Generic for existential types -------------------------------------+------------------------------------- Reporter: andreas.abel | Owner: Type: feature request | Status: new Priority: normal | Milestone: Component: Core Libraries | Version: 7.10.1 Resolution: | Keywords: Generics Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #8560 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): I think that we'd need new language extensions (`QuantifiedConstraints` and `ImplicationConstraints`) to do this properly. See [https://ghc.haskell.org/trac/ghc/ticket/5927#comment:17 my comment] on #5927. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10514#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#10514: Generic for existential types -------------------------------------+------------------------------------- Reporter: andreas.abel | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: Component: Core Libraries | Version: 7.10.1 Resolution: | Keywords: Generics Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #8560 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by Iceland_jack): * cc: Iceland_jack (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/10514#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC