{-# LANGUAGE TemplateHaskell #-}
module Language.Haskell.TH.Extra
where
import Language.Haskell.TH hiding ( tupP, tupE )
import qualified Language.Haskell.TH as TH
tupT :: [TypeQ] -> TypeQ
tupT :: [TypeQ] -> TypeQ
tupT [TypeQ
t] = TypeQ
t
tupT [TypeQ]
tup =
let n :: Int
n = [TypeQ] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [TypeQ]
tup
in (TypeQ -> TypeQ -> TypeQ) -> TypeQ -> [TypeQ] -> TypeQ
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl (\TypeQ
ts TypeQ
t -> [t| $ts $t |]) (Int -> TypeQ
tupleT Int
n) [TypeQ]
tup
tupP :: [PatQ] -> PatQ
tupP :: [PatQ] -> PatQ
tupP [PatQ
p] = PatQ
p
tupP [PatQ]
ps = [PatQ] -> PatQ
TH.tupP [PatQ]
ps
tupE :: [ExpQ] -> ExpQ
tupE :: [ExpQ] -> ExpQ
tupE [ExpQ
t] = ExpQ
t
tupE [ExpQ]
ts = [ExpQ] -> ExpQ
TH.tupE [ExpQ]
ts
tyVarBndrName :: TyVarBndr -> Name
tyVarBndrName :: TyVarBndr -> Name
tyVarBndrName (PlainTV Name
n) = Name
n
tyVarBndrName (KindedTV Name
n Kind
_) = Name
n