
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/82aea77ed908fe36bed829c9c4a01ea9.... 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