Deriving via TH (#12457)

Sebastian Graf sgraf1337 at gmail.com
Mon Jun 24 10:14:34 UTC 2024


Hi Ryan and devs,

I opened https://gitlab.haskell.org/ghc/ghc/-/merge_requests/12941 with 
my progress, which seems to work for reasonable examples.
No documentation yet and almost no test coverage, though.

Cheers,
Sebastian


------ Originalnachricht ------
Von "Sebastian Graf" <sgraf1337 at gmail.com>
An "Ryan Scott" <ryan.gl.scott at gmail.com>
Cc "GHC developers" <ghc-devs at haskell.org>
Datum 19.06.2024 17:21:33
Betreff Re[2]: Deriving via TH (#12457)

>Hi Ryan,
>
>Thank you for such a detailed reply!
>What you wrote gave me confidence in just duplicating code from 
>`tcClsInstDecl`.
>The code is a bit of mess now because the tyvars chosen for the 
>`deriving` instance head might not match with the tyvars used returned 
>in the splice, but I think we can sort this out during review once we 
>have a running prototype.
>
>Sebastian
>
>------ Originalnachricht ------
>Von "Ryan Scott" <ryan.gl.scott at gmail.com>
>An "Sebastian Graf" <sgraf1337 at gmail.com>
>Cc "GHC developers" <ghc-devs at haskell.org>
>Datum 19.06.2024 15:07:47
>Betreff Re: Deriving via TH (#12457)
>
>>Hi Sebastian,
>>
>>This is exciting! I haven't taken a close look at the implementation, 
>>but here are my initial reactions:
>>The implementation of `deriving` proceeds in a somewhat unusual way: 
>>you first typecheck the `deriving` clause and use the resulting Core 
>>types to figure out what the instance head should be. Then, you 
>>generate the method bindings for the instance as parsed code, then 
>>proceed to rename and typecheck the bindings. As such, `deriving` goes 
>>from typechecking -> renaming -> typechecking, which is somewhat 
>>odd...
>>...and derived type family instances work in an even more odd way. 
>>Rather than generating parsed type family instance declarations (and 
>>then renaming/typechecking them), `deriving` directly generates Core 
>>axioms for the instances. As such, derived associated type family 
>>instances go through a rather different code path than derived method 
>>bindings. (There are technical reasons why this is the case, but I 
>>won't get into them here.) This asymmetry means that the existing 
>>`deriving` machinery has to do some odd things to make everything fit 
>>together.
>>I think part of the difficulty you're encountering is that the `th` 
>>deriving strategy is attempting to produce associated type family 
>>instances from TH quotes (i.e., parsed code), rather than from 
>>typechecked code. Every other deriving strategy produces its 
>>associated type family instances from Core types, however, so they are 
>>able to generate instances without renaming or typechecking. You don't 
>>have that luxury. As such, I agree that you'll need to reuse other 
>>parts of the renamer and typechecker (e.g., the `tcClsInstDecl` 
>>function) in order to turn your TH-quoted type family instances into 
>>Core axioms.
>>Is it a good idea to integrate this new deriving strategy so tightly 
>>with the existing deriving framework? I think it's at least worth 
>>trying. The `deriving` code path is just different enough from the 
>>code path for ordinary class instances where I think you'll encounter 
>>some oddities if you try to implement the `th` deriving strategy out 
>>of band. For example, you'll want to be able to dump `th`-derived code 
>>that you generate using -ddump-deriv, which currently only happens in 
>>the `deriving` code path. I suppose you could change things so that 
>>-ddump-deriv does things in multiple places in the code, but I worry 
>>that that may lead to an uncomfortable amount of code duplication. 
>>(Not to mention that you'll have to be careful to actually emulate 
>>everything that the `deriving` code path does, because if you forget 
>>something, then that can lead to confusing bugs down the road.)
>>Of course, I won't claim that the current design of the `deriving` 
>>code path is perfect by any means. If there are ways we could clean 
>>things up that would make it easier to implement the `th` deriving 
>>strategy, then we should consider doing that.
>>I'm not sure if I fully answered the spirit of your question, so feel 
>>free to ask follow-up questions with specifics if I missed the mark.
>>
>>Best,
>>
>>Ryan
>>
>>On Wed, Jun 19, 2024 at 4:52 AM Sebastian Graf <sgraf1337 at gmail.com> 
>>wrote:
>>>Hi Ryan and GHC devs,
>>>
>>>I'm working on-and-off on a prototype that enables use of 
>>>TemplateHaskell as a deriving strategy: 
>>>https://gitlab.haskell.org/ghc/ghc/-/commit/82aea77ed908fe36bed829c9c4a01ea9b30a0181.
>>>My current working example is:
>>>
>>>```
>>>{-# LANGUAGE TemplateHaskell #-}
>>>{-# LANGUAGE TypeFamilies #-}
>>>
>>>module T12457A where
>>>
>>>import GHC.Internal.TH.Lib
>>>import GHC.Internal.TH.Syntax
>>>
>>>class C a where
>>>   type Assoc a
>>>   m :: a -> Int
>>>   n :: a -> Int
>>>
>>>instance DeriveTH C where
>>>   deriveTH _p head = do
>>>     let AppT (ConT t) (VarT a) = head
>>>     x <- newName "x"
>>>     x2 <- newName "x"
>>>     addTopDecls =<< [d|
>>>       $(varP x) = 12
>>>       $(varP x2) = 23 |]
>>>     [d|
>>>       instance C $(varT a) => C ($(conT t) $(varT a)) where
>>>         type Assoc ($(conT t) $(varT a)) = Char
>>>         m :: Eq a => a -> Int
>>>         m _ = $(varE x) + 42
>>>         {-# INLINE m #-}
>>>         n :: Show a => a -> Int
>>>         n _ = $(varE x2) + 13 |]
>>>
>>>---
>>>
>>>{-# LANGUAGE TemplateHaskell #-}
>>>{-# LANGUAGE ConstraintKinds #-}
>>>{-# LANGUAGE DerivingStrategies #-}
>>>
>>>module T12457 where
>>>
>>>import Language.Haskell.TH
>>>import GHC.Internal.TH.Lib
>>>import T12457A
>>>
>>>newtype T a = T [a] deriving th C
>>>```
>>>
>>>I just managed to implement `GHC.Tc.Deriv.Infer.inferConstraints` for 
>>>this mechanism (still hacky and broken in many ways) and am now stuck 
>>>in `Deriv.genFamInst`.
>>>I realised I would need to replicate the first half of 
>>>`tcClsInstDecl` to implement it. Before long, I will probably also 
>>>need to replicate the other half to check method bindings.
>>>That leaves me wondering: Is it a good idea to integrate this new 
>>>deriving strategy so tightly with the existing deriving framework?
>>>I would rather just call `tcClsInstDecl`, do a bit of sanity checking 
>>>for specified constraints in standalone deriving declarations and 
>>>call it a day.
>>>
>>>Given that you are the architect of our current deriving code, I hope 
>>>you are the right person to ask for input.
>>>
>>>Thanks,
>>>Sebastian
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-devs/attachments/20240624/4d4aae02/attachment.html>


More information about the ghc-devs mailing list