module Optics.TH.Internal.Utils where
import Language.Haskell.TH
import qualified Language.Haskell.TH.Datatype as D
appsT :: TypeQ -> [TypeQ] -> TypeQ
appsT = foldl appT
appsE1 :: ExpQ -> [ExpQ] -> ExpQ
appsE1 = foldl appE
toTupleT :: [TypeQ] -> TypeQ
toTupleT [x] = x
toTupleT xs = appsT (tupleT (length xs)) xs
toTupleE :: [ExpQ] -> ExpQ
toTupleE [x] = x
toTupleE xs = tupE xs
toTupleP :: [PatQ] -> PatQ
toTupleP [x] = x
toTupleP xs = tupP xs
conAppsT :: Name -> [Type] -> Type
conAppsT conName = foldl AppT (ConT conName)
bndrName :: TyVarBndr -> Name
bndrName (PlainTV n ) = n
bndrName (KindedTV n _) = n
newNames :: String -> Int -> Q [Name]
newNames base n = sequence [ newName (base++show i) | i <- [1..n] ]
eqSubst :: Type -> String -> Q (Type, Pred)
eqSubst ty n = do
placeholder <- VarT <$> newName n
pure (placeholder, D.equalPred placeholder ty)
inlinePragma :: Name -> [DecQ]
inlinePragma methodName = [pragInlD methodName Inline FunLike AllPhases]