| Copyright | (c) 2019-2024 Rudy Matela | 
|---|---|
| License | 3-Clause BSD (see the file LICENSE) | 
| Maintainer | Rudy Matela <rudy@matela.com.br> | 
| Safe Haskell | Safe-Inferred | 
| Language | Haskell2010 | 
Data.Express.Utils.TH
Description
Template Haskell utilities.
Synopsis
- reallyDeriveCascading :: Name -> (Name -> DecsQ) -> Name -> DecsQ
- deriveWhenNeeded :: Name -> (Name -> DecsQ) -> Name -> DecsQ
- deriveWhenNeededOrWarn :: Name -> (Name -> DecsQ) -> Name -> DecsQ
- typeConArgs :: Name -> Q [Name]
- typeConArgsThat :: Name -> (Name -> Q Bool) -> Q [Name]
- typeConCascadingArgsThat :: Name -> (Name -> Q Bool) -> Q [Name]
- normalizeType :: Name -> Q (Type, [Type])
- normalizeTypeUnits :: Name -> Q Type
- isInstanceOf :: Name -> Name -> Q Bool
- isntInstanceOf :: Name -> Name -> Q Bool
- typeArity :: Name -> Q Int
- typeConstructors :: Name -> Q [(Name, [Type])]
- isTypeSynonym :: Name -> Q Bool
- typeSynonymType :: Name -> Q Type
- mergeIFns :: DecsQ -> DecsQ
- mergeI :: DecsQ -> DecsQ -> DecsQ
- lookupValN :: String -> Q Name
- showJustName :: Name -> String
- typeConstructorsArgNames :: Name -> Q [(Name, [Name])]
- (|=>|) :: Cxt -> DecsQ -> DecsQ
- (|++|) :: DecsQ -> DecsQ -> DecsQ
- whereI :: DecsQ -> [Dec] -> DecsQ
- unboundVars :: Type -> [Name]
- toBounded :: Type -> Type
- toBoundedQ :: TypeQ -> TypeQ
- module Language.Haskell.TH
Documentation
normalizeType :: Name -> Q (Type, [Type]) Source #
Normalizes a type by applying it to necessary type variables making it accept zero type parameters. The normalized type is paired with a list of necessary type variables.
> putStrLn $(stringE . show =<< normalizeType ''Int) (ConT ''Int, [])
> putStrLn $(stringE . show =<< normalizeType ''Maybe) (AppT (ConT ''Maybe) (VarT ''a),[VarT ''a])
> putStrLn $(stringE . show =<< normalizeType ''Either) (AppT (AppT (ConT ''Either) (VarT ''a)) (VarT ''b),[VarT ''a,VarT ''b])
> putStrLn $(stringE . show =<< normalizeType ''[]) (AppT (ConT ''[]) (VarT a),[VarT a])
normalizeTypeUnits :: Name -> Q Type Source #
Normalizes a type by applying it to units to make it star-kinded.
 (cf. normalizeType)
normalizeTypeUnits ''Int === [t| Int |] normalizeTypeUnits ''Maybe === [t| Maybe () |] normalizeTypeUnits ''Either === [t| Either () () |]
isInstanceOf :: Name -> Name -> Q Bool Source #
Given a type name and a class name,
 returns whether the type is an instance of that class.
 The given type must be star-kinded ( * )
 and the given class double-star-kinded ( * -> * .
> putStrLn $(stringE . show =<< ''Int `isInstanceOf` ''Num) True
> putStrLn $(stringE . show =<< ''Int `isInstanceOf` ''Fractional) False
isntInstanceOf :: Name -> Name -> Q Bool Source #
The negation of isInstanceOf.
typeArity :: Name -> Q Int Source #
Given a type name, return the number of arguments taken by that type. Examples in partially broken TH:
> putStrLn $(stringE . show =<< typeArity ''Int) 0
> putStrLn $(stringE . show =<< typeArity ''Maybe) 1
> putStrLn $(stringE . show =<< typeArity ''Either) 2
> putStrLn $(stringE . show =<< typeArity ''[]) 1
> putStrLn $(stringE . show =<< typeArity ''(,)) 2
> putStrLn $(stringE . show =<< typeArity ''(,,)) 3
> putStrLn $(stringE . show =<< typeArity ''String) 0
This works for data and newtype declarations and it is useful when generating typeclass instances.
typeConstructors :: Name -> Q [(Name, [Type])] Source #
Given a type Name,
 returns a list of its type constructor Names
 paired with the type arguments they take.
 the type arguments they take.
> putStrLn $(stringE . show =<< typeConstructors ''Bool)
[ ('False, [])
, ('True, [])
]> putStrLn $(stringE . show =<< typeConstructors ''[])
[ ('[], [])
, ('(:), [VarT ''a, AppT ListT (VarT ''a)])
]> putStrLn $(stringE . show =<< typeConstructors ''(,))
[('(,), [VarT (mkName "a"), VarT (mkName "b")])]> data Point  =  Pt Int Int
> putStrLn $(stringE . show =<< typeConstructors ''Point)
[('Pt,[ConT ''Int, ConT ''Int])]isTypeSynonym :: Name -> Q Bool Source #
Is the given Name a type synonym?
> putStrLn $(stringE . show =<< isTypeSynonym 'show) False
> putStrLn $(stringE . show =<< isTypeSynonym ''Char) False
> putStrLn $(stringE . show =<< isTypeSynonym ''String) True
typeSynonymType :: Name -> Q Type Source #
Resolves a type synonym.
> putStrLn $(stringE . show =<< typeSynonymType ''String) AppT ListT (ConT ''Char)
lookupValN :: String -> Q Name Source #
Lookups the name of a value throwing an error when it is not found.
> putStrLn $(stringE . show =<< lookupValN "show") 'show
showJustName :: Name -> String Source #
unboundVars :: Type -> [Name] Source #
Lists all unbound variables in a type.
   This intentionally excludes the ForallT constructor.
toBounded :: Type -> Type Source #
Binds all unbound variables using a ForallT constructor.
   (cf. unboundVars)
module Language.Haskell.TH