Cross-posted from StackOverflow: http://stackoverflow.com/questions/44107336/how-to-define-a-type-in-a-templatehaskell-function-and-use-it-in-the-same-functi

Is there any way to have as single TH function, define a type, and use the type, as well? Relevant code below. `PersonPoly2` is being defined by `makeRecordSplice` and then being passed to `makeAdaptorAndInstance` (provided by Opalaye), which is also a TH function.

Relevant code given below:


    {-# LANGUAGE FlexibleContexts       #-}
    {-# LANGUAGE FlexibleInstances      #-}
    {-# LANGUAGE FunctionalDependencies #-}
    {-# LANGUAGE MultiParamTypeClasses  #-}
    {-# LANGUAGE OverloadedStrings      #-}
    {-# LANGUAGE TemplateHaskell        #-}
    
    module Lib where
    
    import           Data.Profunctor.Product.TH             (makeAdaptorAndInstance)
    import Language.Haskell.TH
    
    makeRecordSplice :: Q [Dec]
    makeRecordSplice = [d|
      data PersonPoly2 a b = Person2
        { id :: a 
        , name :: b
        }
      |]
    
    makeRecordAndAdapter :: Q [Dec]
    makeRecordAndAdapter = do
      record <- makeRecordSplice
      adapter <- makeAdaptorAndInstance "pPerson2" (mkName "PersonPoly2")
      return $ record ++ adapter
    
    
    -------------
    
    /home/Projects/scratch/app/Main.hs:26:1: error:
        ‘PersonPoly2’ is not in scope at a reify
    Failed, modules loaded: Lib.



-- Saurabh.