Saurabh Nanda
Saurabh Nanda

Reputation: 6793

How to define a type in a TemplateHaskell function and use it in the same function?

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 (from Opalaye), which is also a TH function.

{-# 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.

Upvotes: 1

Views: 281

Answers (1)

basile-henry
basile-henry

Reputation: 1365

The problem you are having is that makeRecordSplice needs to be in a different module than the one it is instantiated in. This Template-Haskell limitation ensures non-circular dependencies at compile time. It is an annoying limitation but not too difficult to go around. Here is one way you could do it:

{-# LANGUAGE FlexibleContexts       #-}
{-# LANGUAGE FlexibleInstances      #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE MultiParamTypeClasses  #-}
{-# LANGUAGE OverloadedStrings      #-}
{-# LANGUAGE TemplateHaskell        #-}

module Main where

import           Data.Profunctor.Product.TH (makeAdaptorAndInstance)
import           Language.Haskell.TH
import           Lib                        (makeRecordSplice)


$(makeRecordSplice)
$(makeAdaptorAndInstance "pPerson2" (mkName "PersonPoly2"))

main :: IO ()
main = undefined
{-# 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
    }
  |]

You can obviously create an alias for makeAdaptorAndInstance "pPerson2" (mkName "PersonPoly2") and hide it in Lib, you just can't have a splice dependent on another one in the same module.

Hope this helps! :-)

Upvotes: 1

Related Questions