<html><head>

<style id="css_styles"> 
blockquote.cite { margin-left: 5px; margin-right: 0px; padding-left: 10px; padding-right:0px; border-left: 1px solid #cccccc }
blockquote.cite2 {margin-left: 5px; margin-right: 0px; padding-left: 10px; padding-right:0px; border-left: 1px solid #cccccc; margin-top: 3px; padding-top: 0px; }
a img { border: 0px; }
table { border-collapse: collapse; }
li[style='text-align: center;'], li[style='text-align: center; '], li[style='text-align: right;'], li[style='text-align: right; '] {  list-style-position: inside;}
body { font-family: 'Segoe UI'; font-size: 12pt; }
.quote { margin-left: 1em; margin-right: 1em; border-left: 5px #ebebeb solid; padding-left: 0.3em; }

 </style>
</head>
<body>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;">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 Language.Haskell.TH
</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></body></html>