Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- appsT :: TypeQ -> [TypeQ] -> TypeQ
- appsE1 :: ExpQ -> [ExpQ] -> ExpQ
- toTupleT :: [TypeQ] -> TypeQ
- toTupleE :: [ExpQ] -> ExpQ
- toTupleP :: [PatQ] -> PatQ
- conAppsT :: Name -> [Type] -> Type
- newNames :: String -> Int -> Q [Name]
- eqSubst :: Type -> String -> Q (Type, Pred)
- addKindInfo :: DatatypeInfo -> Type -> Type
- addKindInfo' :: [Type] -> DatatypeInfo -> Type -> Type
- quantifyType :: [TyVarBndrSpec] -> Cxt -> Type -> Type
- quantifyType' :: Set Name -> [TyVarBndrSpec] -> Cxt -> Type -> Type
- tyVarBndrToType :: TyVarBndr_ flag -> Type
- requireExtensions :: String -> [[Extension]] -> Q ()
- requireExtensionsForLabels :: Q ()
- requireExtensionsForFields :: Q ()
- inlinePragma :: Name -> [DecQ]
Documentation
Generate many new names from a given base name.
addKindInfo :: DatatypeInfo -> Type -> Type Source #
addKindInfo' :: [Type] -> DatatypeInfo -> Type -> Type Source #
Fill in kind variables using info from datatype type parameters.
quantifyType :: [TyVarBndrSpec] -> Cxt -> Type -> Type Source #
Template Haskell wants type variables declared in a forall, so we find all free type variables in a given type and declare them.
quantifyType' :: Set Name -> [TyVarBndrSpec] -> Cxt -> Type -> Type Source #
This function works like quantifyType
except that it takes
a list of variables to exclude from quantification.
tyVarBndrToType :: TyVarBndr_ flag -> Type Source #
requireExtensions :: String -> [[Extension]] -> Q () Source #
Pass in a list of lists of extensions, where any of the given extensions will satisfy it. For example, you might need either GADTs or ExistentialQuantification, so you'd write:
requireExtensions [[GADTs, ExistentialQuantification]]
But if you need TypeFamilies and MultiParamTypeClasses, then you'd write:
requireExtensions [[TypeFamilies], [MultiParamTypeClasses]]
requireExtensionsForLabels :: Q () Source #
requireExtensionsForFields :: Q () Source #
inlinePragma :: Name -> [DecQ] Source #