{-# LANGUAGE CPP #-}
module Language.Haskell.TH.Compat where
import Language.Haskell.TH.Syntax
mkTySynInstD :: Name -> [Type] -> Type -> Dec
mkTySynInstD tyConNm tyArgs rhs =
#if MIN_VERSION_template_haskell(2,15,0)
TySynInstD (TySynEqn Nothing
(foldl AppT (ConT tyConNm) tyArgs)
rhs)
#else
TySynInstD tyConNm
(TySynEqn tyArgs
rhs)
#endif
mkTupE :: [Exp] -> Exp
mkTupE = TupE
#if MIN_VERSION_template_haskell(2,16,0)
. map Just
#endif
#if MIN_VERSION_template_haskell(2,17,0)
liftTypedFromUntyped :: (Lift a, Quote m) => a -> Code m a
liftTypedFromUntyped = unsafeCodeCoerce . lift
#elif MIN_VERSION_template_haskell(2,16,0)
liftTypedFromUntyped :: Lift a => a -> Q (TExp a)
liftTypedFromUntyped = unsafeTExpCoerce . lift
#endif