[GHC] #15650: Add (or document if already exist) ability to derive custom typeclasses via source plugins

#15650: Add (or document if already exist) ability to derive custom typeclasses via source plugins -------------------------------------+------------------------------------- Reporter: chshersh | Owner: (none) Type: feature | Status: new request | Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.6.1-beta1 Keywords: source | Operating System: Unknown/Multiple plugins,deriving,typeclass | Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- == Problem Suppose, I have some custom typeclass `Foo` defined in some library `foo`: {{{#!hs class Foo a where ... some methods ... }}} I would like to be able to derive instances of this typeclass for any possible data type using `deriving` clause just like GHC already does for typeclasses `Eq`, `Ord`, `Show`, `Read`, `Enum`, etc.: {{{#!hs data Bar = Bar | Baz deriving (Eq, Ord, Foo) }}} There're already two possible ways to derive instances of custom typeclasses: 1. `anyclass` deriving strategy (usually involves `Generic`) 2. `-XTemplateHaskell` solution. But I would like to have source-plugin-based solution for this problem so I can just add `-fplugin=Foo.Plugin` and enjoy deriving capabilities. == Advantage over existing approaches Solution with `-XTemplateHaskell` is not that pleasant to write and easy to maintain (you need to use libraries like http://hackage.haskell.org/package/th-abstraction to support multiple GHC versions),involves scoping restriction and is syntactically uglier. Compare: {{{#!hs {-# LANGUAGE TemplateHaskell #-} data Bar = Bar | Baz deriving (Eq, Ord) deriveFoo ''Bar }}} Solution with something like `Generic` introduces performance overhead (required for to/from generic representation conversion). This might not be significant for something like ''parsing CLI arguments'' but it's more important if you want to have efficient binary serialisation. Also, it's known that deriving typeclasses is a relatively slow compilation process (https://github.com/tfausak/tfausak.github.io/issues/127) so there's slight chance that deriving typeclass manually can be slightly faster than deriving `Generic + MyClass`. Especially when maintainers of plugins can experiment with some caching strategies for deriving typeclasses. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15650 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15650: Add (or document if already exist) ability to derive custom typeclasses via source plugins -------------------------------------+------------------------------------- Reporter: chshersh | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.6.1-beta1 Resolution: | Keywords: source | plugins,deriving,typeclass 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 am far from an expert on source plugins, so I can't say whether this is possible or not. But my initial reaction is: sure, why not? I could imagine an API like this: {{{#!hs type Derived a = a class Foo a where ... data Bar deriving (Derived Foo) }}} Here, the use of `Derived` is a syntactic clue to a source plugin to derive this using some custom functionality (instead of just trying to derive `Foo` normally). To make this robust, you'd likely need to borrow some of GHC's own logic for `deriving` type classes. Luckily, GHC already exposes much of this! See the `TcDeriv`, `TcGenDeriv`, and `TcDerivUtils` modules. I certainly don't have the time to try this out myself, but I'd be happy point any volunteers in the right direction. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15650#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15650: Add (or document if already exist) ability to derive custom typeclasses via source plugins -------------------------------------+------------------------------------- Reporter: chshersh | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.6.1-beta1 Resolution: | Keywords: source | plugins,deriving,typeclass Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: #12457 | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * related: => #12457 -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15650#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15650: Add (or document if already exist) ability to derive custom typeclasses via source plugins -------------------------------------+------------------------------------- Reporter: chshersh | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.6.1-beta1 Resolution: | Keywords: source | plugins,deriving,typeclass Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by mpickering): * related: #12457 => Comment: I have been playing around with this problem this morning. There are some engineering issues to do with the phase ordering. Plugins run at the end of the specific phase so you need to at least run a renamer plugin to remove the instances like `Derived Foo` from the deriving list. Then you probably need to also to implement a type checker plugin to solve the instances you are yet to create and finally, actually generate the instances with `TcDeriv` and so on. One way around this might be to implement the deriving all in a renamer plugin as then you can just directly generate the `instance Foo a where..` syntax and pass it into the type checker. Now typing this out, this seems a more robust and easy solution to implement. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15650#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC