[GHC] #15969: Generic1 deriving should use more coercions

#15969: Generic1 deriving should use more coercions -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.8.1 Component: Compiler | Version: 8.6.2 Keywords: Generics | Operating System: Unknown/Multiple Architecture: | Type of failure: Runtime Unknown/Multiple | performance bug Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Consider {{{#!hs newtype Foo a = Foo (Maybe [a]) deriving (Generic1) }}} This produces some rather unsatisfactory Core: {{{ -- to1 worker Travv.$fGeneric1Foo1 :: forall a. Rep1 Foo a -> Maybe [a] Travv.$fGeneric1Foo1 = \ (@ a_a7RL) (ds_d9dZ :: Rep1 Foo a_a7RL) -> case ds_d9dZ `cast` Co:103 of { Nothing -> GHC.Maybe.Nothing @ [a_a7RL]; Just a1_a9fD -> GHC.Maybe.Just @ [a_a7RL] (a1_a9fD `cast` Co:5) } -- from1 worker Travv.$fGeneric1Foo2 :: forall a. Foo a -> Maybe (Rec1 [] a) Travv.$fGeneric1Foo2 = \ (@ a_a7R6) (x_a7GJ :: Foo a_a7R6) -> case x_a7GJ `cast` Co:2 of { Nothing -> GHC.Maybe.Nothing @ (Rec1 [] a_a7R6); Just a1_a9fD -> GHC.Maybe.Just @ (Rec1 [] a_a7R6) (a1_a9fD `cast` Co:6) } }}} Both of these functions could be implemented as safe coercions, but neither of them is! Similarly, if I define {{{#!hs data Bar a = Bar (Maybe [a]) deriving Generic1 }}} I get a `to1` worker that looks like {{{ Travv.$fGeneric1Bar_$cto1 :: forall a. Rep1 Bar a -> Bar a Travv.$fGeneric1Bar_$cto1 = \ (@ a_a7UA) (ds_d9ho :: Rep1 Bar a_a7UA) -> Travv.Bar @ a_a7UA (case ds_d9ho `cast` Co:103 of { Nothing -> GHC.Maybe.Nothing @ [a_a7UA]; Just a1_a9iK -> GHC.Maybe.Just @ [a_a7UA] (a1_a9iK `cast` Co:5) }) }}} That `case` expression should really just be a cast. I think the basic trick is probably to inspect the role of the type argument of each type in a composition, using that to work out whether to coerce that step. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15969 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15969: Generic1 deriving should use more coercions -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.8.1 Component: Compiler | Version: 8.6.2 Resolution: | Keywords: Generics Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by dfeuer): I think this problem suggests that `Generic1` got composition the wrong way around. Let's take a slightly bigger example: {{{#!hs data Baz a = Baz (Maybe [Either Int a]) }}} We currently derive {{{#!hs Rep1 Baz = ... (Maybe :.: ([] :.: Rec1 (Either Int))) }}} Suppose we did it the other way: {{{#!hs Rep1 Baz = .... ((Rec1 Maybe :.: []) :.: Either Int) }}} then we'd have the `Rec1` "exposed" properly: {{{#!hs from1 (Baz q) = M1 (M1 (M1 (Comp1 (Comp1 (Rec1 q))))) }}} No fanciness required at all! -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15969#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15969: Generic1 deriving should use more coercions -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.8.1 Component: Compiler | Version: 8.6.2 Resolution: | Keywords: Generics Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by dfeuer): * cc: ekmett (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15969#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15969: Generic1 deriving should use more coercions -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.8.1 Component: Compiler | Version: 8.6.2 Resolution: | Keywords: Generics, | Deriving Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by simonpj): * keywords: Generics => Generics, Deriving -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15969#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15969: Generic1 deriving should use more coercions -------------------------------------+------------------------------------- Reporter: dfeuer | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.8.1 Component: Compiler | Version: 8.6.2 Resolution: | Keywords: Generics, | Deriving Operating System: Unknown/Multiple | Architecture: Type of failure: Runtime | Unknown/Multiple performance bug | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by RyanGlScott): This is a very interesting observation. I, too, have been rather annoyed by the fact that `Generic1` requires using `fmap` to implement instances involving `(:.:)`. In fact, I've pondered using `Coercible`-plus-`QuantifiedConstraints` to get replace these `fmap`s in [https://gist.github.com/RyanGlScott/cca1a0605a3b460c4af073cfce3c15fb this gist]. (It comes with its [https://ghc.haskell.org/trac/ghc/ticket/8516#comment:7 own set of problems], which is why I haven't pursued the idea further.) Remarkably, however, this technique bypasses the need to use `fmap` entirely! I'm not sure why `Generic1` didn't pick this convention to start with—perhaps they wanted `(:.:)` to be right-associative as a sort of parallel the function composition operator `(.)`, which is also associative? I can't say. Unfortunately, `(:.:)` being right-associative //is// a well established convention at this point, and switching it to be left-associative would break lots of code in the wild. Most instances of `(:.:)` tend to look like this: {{{#!hs instance (Cls f, GCls g) => GCls (f :.: g) where gmeth = ... class Cls f where meth :: ... default meth :: (Generic1, GCls (Rep1 f)) => ... meth = ... gmeth ... class GCls f where gmeth :: ... }}} That is, you give the outer type `f` an instance of the "base" class (`Cls`) and the inner type `g` an instance of the "generified" class (`GCls`). If we made `(:.:)` left-associative, then we'd have to turn this convention around and instead define: {{{#!hs instance (GCls f, Cls g) => GCls (f :.: g) where gmeth = ... }}} Is the breakage worth it? I'm inclined to say "no", since if we're going to make a backwards-incompatible change to `GHC.Generics`, then our effort might be better spent incorporating a more modern generic programming library into GHC (call it `GHC.Generics2`, perhaps) and slowly deprecating `GHC.Generics` in favor of that one. And thankfully, most modern generic programming frameworks no longer use `(:.:)`, so it's simply a non-issue there. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15969#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC