<div dir="ltr"><div>Hi Sebastian,<br></div><div><br></div><div>This is exciting! I haven't taken a close look at the implementation, but here are my initial reactions:</div><div><ul><li>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...</li><li>...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.<br></li><li>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.</li><li>
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 <i>just</i> 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.)</li><li>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.</li></ul><div>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.<br></div><div><br></div><div>Best,</div><div><br></div><div>Ryan<br></div></div></div><br><div class="gmail_quote"><div dir="ltr" class="gmail_attr">On Wed, Jun 19, 2024 at 4:52 AM Sebastian Graf <<a href="mailto:sgraf1337@gmail.com">sgraf1337@gmail.com</a>> wrote:<br></div><blockquote class="gmail_quote" style="margin:0px 0px 0px 0.8ex;border-left:1px solid rgb(204,204,204);padding-left:1ex"><div class="msg-1438398085486069382">



<div>Hi Ryan and GHC devs,<div><br></div><div>I'm working on-and-off on a prototype that enables use of TemplateHaskell as a deriving strategy: <a href="https://gitlab.haskell.org/ghc/ghc/-/commit/82aea77ed908fe36bed829c9c4a01ea9b30a0181" style="font-size:12pt" target="_blank">https://gitlab.haskell.org/ghc/ghc/-/commit/82aea77ed908fe36bed829c9c4a01ea9b30a0181</a>.</div><div><span>My current working example is:</span></div><div><br></div><div>```</div><div>{-# LANGUAGE TemplateHaskell #-}
</div><div>{-# LANGUAGE TypeFamilies #-}
</div><div><br></div><div>module T12457A where
</div><div><br></div><div>import GHC.Internal.TH.Lib
</div><div>import GHC.Internal.TH.Syntax
</div><div><br></div><div>class C a where
</div><div>  type Assoc a
</div><div>  m :: a -> Int
</div><div>  n :: a -> Int
</div><div><br></div><div>instance DeriveTH C where
</div><div>  deriveTH _p head = do
</div><div>    let AppT (ConT t) (VarT a) = head
</div><div>    x <- newName "x"
</div><div>    x2 <- newName "x"
</div><div>    addTopDecls =<< [d|
</div><div>      $(varP x) = 12
</div><div>      $(varP x2) = 23 |]
</div><div>    [d|
</div><div>      instance C $(varT a) => C ($(conT t) $(varT a)) where
</div><div>        type Assoc <span>($(conT t) $(varT a)) </span><span>= Char </span></div><div>        m :: Eq a => a -> Int
</div><div>        m _ = $(varE x) + 42
</div><div>        {-# INLINE m #-}
</div><div>        n :: Show a => a -> Int
</div><div>        n _ = $(varE x2) + 13 |]
</div><div><br></div><div>---</div><div><br></div><div>{-# LANGUAGE TemplateHaskell #-}
</div><div>{-# LANGUAGE ConstraintKinds #-}
</div><div>{-# LANGUAGE DerivingStrategies #-}
</div><div><br></div><div>module T12457 where
</div><div><br></div><div>import <a href="http://Language.Haskell.TH" target="_blank">Language.Haskell.TH</a>
</div><div>import GHC.Internal.TH.Lib
</div><div>import T12457A
</div><div><br></div><div>newtype T a = T [a] deriving th C
</div><div>```</div><div><br></div><div>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`.</div><div>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.</div><div>That leaves me wondering: Is it a good idea to integrate this new deriving strategy so tightly with the existing deriving framework?</div><div>I would rather just call `tcClsInstDecl`, do a bit of sanity checking for specified constraints in standalone deriving declarations and call it a day.</div><div><br></div><div>Given that you are the architect of our current deriving code, I hope you are the right person to ask for input.</div><div><br></div><div>Thanks,</div><div>Sebastian</div></div></div></blockquote></div>