[GHC] #15310: Derive Generic1 instances for types of kind (k -> *) -> * that include applications of the parameter

#15310: Derive Generic1 instances for types of kind (k -> *) -> * that include applications of the parameter -------------------------------------+------------------------------------- Reporter: cedricshock | Owner: (none) Type: feature | Status: new request | Priority: low | Milestone: Component: Compiler | Version: (Type checker) | Keywords: DeriveGeneric | Operating System: Unknown/Multiple Generic1 | Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- The `Generic1` class is polykinded. The `DeriveGeneric` extension can derive `Generic1` instances for types of kind `k -> *` parameterized over a parameter with a kind other than `k ~ *`, but only if they don't apply the parameter to other types. It currently cannot derive an instance for {{{#!hs newtype Fix f = In (f (Fix f)) deriving (Generic1) }}} or for {{{#!hs data Child f = Child { ordinal :: Int, nickname :: f String } deriving (Generic1) }}} It's possible to represent these types generically, either with composition that can include occurrences of the parameter or with new types that represent applications of the parameter. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15310 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15310: Derive Generic1 instances for types of kind (k -> *) -> * that include applications of the parameter -------------------------------------+------------------------------------- Reporter: cedricshock | Owner: (none) Type: feature request | Status: new Priority: low | Milestone: Component: Compiler (Type | Version: checker) | Keywords: DeriveGeneric Resolution: | Generic1 Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by cedricshock): These types can represent applications of the parameter in `Generic1` instances {{{#!hs newtype ParAp0 c p = ParAp0 { unParAp0 :: p c } -- applications of the parameter newtype ParAp1 f p = ParAp1 { unParAp1 :: p (f p) } -- recursive applications of the parameter }}} For example the `f (Fix f)` in `Fix` can be represented by `ParAp1 Fix` {{{#!hs type Rep1 Fix = D1 ('MetaData "Fix" "CanDoRep1Model_0" "main" 'GHC.Types.False) (C1 ('MetaCons "In" 'PrefixI 'GHC.Types.False) (S1 ('MetaSel 'GHC.Maybe.Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (ParAp1 Fix))) }}} and the `f String` in `Child` can be represented by `ParAp0 String` {{{#!hs type Rep1 Child = D1 ('MetaData "Child" "CanDoRep1Model_0" "main" 'GHC.Types.False) (C1 ('MetaCons "Child" 'PrefixI 'GHC.Types.True) (S1 ('MetaSel ('Just "ordinal") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 GHC.Types.Int) :*: S1 ('MetaSel ('Just "nickname") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (ParAp0 GHC.Base.String))) }}} Problems arise when attempting to represent a type that contains the parameter applied to the composition of other types. This type contains an application of the parameter to the composition of `[]` and `D` {{{#!hs data Compose2 f = Comp2 (f (Maybe (D f))) deriving Generic1 data D f = D deriving Generic1 }}} `ParAp1 (Maybe :*: D)` can represent `f (Maybe (D f))`, but the resulting `ParAp1` holds an `f ((Maybe :*: D) f))`, which, while representationally equivalent to `f (Maybe (D f))`, isn't nominally equivalent to `f (Maybe (D f))`. This prevents the `to1` and `from1` methods from being written, even with the help of `coerce`. Multiple compositions can be refactored to have `Generic1` instances. {{{#!hs data Compose2 f = Comp2 (f (MaybeD f)) deriving Generic1 newtype MaybeD f = MaybeD (Maybe (D f)) deriving Generic1 data D f = D deriving Generic1 }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15310#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15310: Derive Generic1 instances for types of kind (k -> *) -> * that include applications of the parameter -------------------------------------+------------------------------------- Reporter: cedricshock | Owner: (none) Type: feature request | Status: new Priority: low | Milestone: Component: Compiler (Type | Version: checker) | Keywords: DeriveGeneric Resolution: | Generic1 Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by cedricshock): I wrote an implementation of `Generic1` deriving using `ParAp0` and `ParAp1`. You can preview it in this PR: https://github.com/Cedev/ghc/pull/1 I could use some practical advice and help on what to do next 1. I don't have a test case for a kind `(k -> *) -> *` where `k` isn't `*`. If you have any ideas, especially for a test case where `k ~ Constraint`, I'd appreciate them. 2. There are types in `base` that can now have `Generic1` instances derived for them, starting with `ParAp0` and `ParAp1` themselves. How do I add `Generic1` instances to base without breaking the compiler building, since an old compiler won't be able to derive those `Generic1` instances? 3. What other typeclasses should `ParAp0` and `ParAp1` have instances for? 4. What do I do next? Get feedback from both `ghc-devs` and `glasgow- haskell-users`? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15310#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15310: Derive Generic1 instances for types of kind (k -> *) -> * that include applications of the parameter -------------------------------------+------------------------------------- Reporter: cedricshock | Owner: (none) Type: feature request | Status: new Priority: low | Milestone: Component: Compiler (Type | Version: checker) | Keywords: DeriveGeneric Resolution: | Generic1 Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): I have to admit that I'm not fond of this approach, as it feels terribly //ad hoc//. These new representation types "fix" the issue by wiring in two very particular ways that the last parameter can appear in a data type. But there are an infinite numbers of ways that the last parameter can appear in a data type. What about: * `newtype A a = MkA (Either a a)` * `newtype B f = MkB (WrappedMonad f (Maybe f))` * etc. For every representation type that you cook up to fix one particular use case, one can always come up with another example that can't be represented neatly with the existing machinery. In my view, this reflects a weakness of `Generic1` approach in general. Namely, that one has to go through incredible contortions to bend data types to a certain shape just to be able to have a derived instance. Moreover, the contortions that one must do become even wilder if you start thinking about what it would take to support hypothetical `Generic2`, `Generic3`, etc. classes. My inclination is to not pursue this line of thinking, and instead recommend that you try an alternative generic programming library that's better suited to what you're trying to accomplish. The paper [http://dreixel.net/research/pdf/gpmp_colour.pdf Generic Programming with Multiple Parameters], which is authored by the same person who originally developed `Generic1`, was written to address this concern. In the paper, the author demonstrates a variant of `Generic` that works for any number of parameters (thus subsuming `Generic1`, `Generic2`, `Generic3`, etc.), and allows occurrences of these parameters wherever one desires. Bottom line: while `Generic1` is unfortunately restricted in what it's capable of, its capabilities are also quite predictable. I'm inclined to favor a predictable and limited approach over an approach which covers slightly more data types but adds unwarranted complexity. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15310#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC