Safe Haskell | None |
---|---|
Language | Haskell2010 |
Types in CoreHW
- data Type
- data TypeView
- data ConstTy
- data LitTy
- type Kind = Type
- type KindOrType = Type
- type KiName = Name Kind
- type TyName = Name Type
- type TyVar = Var Type
- tyView :: Type -> TypeView
- coreView :: HashMap TyConName TyCon -> Type -> TypeView
- transparentTy :: Type -> Type
- typeKind :: HashMap TyConName TyCon -> Type -> Kind
- mkTyConTy :: TyConName -> Type
- mkFunTy :: Type -> Type -> Type
- mkTyConApp :: TyConName -> [Type] -> Type
- splitFunTy :: HashMap TyConName TyCon -> Type -> Maybe (Type, Type)
- splitFunTys :: HashMap TyConName TyCon -> Type -> ([Type], Type)
- splitFunForallTy :: Type -> ([Either TyVar Type], Type)
- splitTyConAppM :: Type -> Maybe (TyConName, [Type])
- isPolyFunTy :: Type -> Bool
- isPolyFunCoreTy :: HashMap TyConName TyCon -> Type -> Bool
- isPolyTy :: Type -> Bool
- isFunTy :: HashMap TyConName TyCon -> Type -> Bool
- applyFunTy :: HashMap TyConName TyCon -> Type -> Type -> Type
- applyTy :: Fresh m => HashMap TyConName TyCon -> Type -> KindOrType -> m Type
- findFunSubst :: [([Type], Type)] -> [Type] -> Maybe Type
Documentation
Types in CoreHW: function and polymorphic types
VarTy Kind TyName | Type variable |
ConstTy ConstTy | Type constant |
ForAllTy (Bind TyVar Type) | Polymorphic Type |
AppTy Type Type | Type Application |
LitTy LitTy | Type literal |
An easier view on types
Type Constants
Literal Types
type KindOrType = Type Source
Either a Kind or a Type
coreView :: HashMap TyConName TyCon -> Type -> TypeView Source
A view on types in which Signal
types and newtypes are transparent, and
type functions are evaluated when possible.
transparentTy :: Type -> Type Source
A transformation that renders Signal
types transparent
mkTyConApp :: TyConName -> [Type] -> Type Source
Make a TyCon Application out of a TyCon and a list of argument types
splitFunTy :: HashMap TyConName TyCon -> Type -> Maybe (Type, Type) Source
Split a function type in an argument and result type
splitFunForallTy :: Type -> ([Either TyVar Type], Type) Source
Split a poly-function type in a: list of type-binders and argument types, and the result type
splitTyConAppM :: Type -> Maybe (TyConName, [Type]) Source
Split a TyCon Application in a TyCon and its arguments
isPolyFunTy :: Type -> Bool Source
Is a type a polymorphic or function type?
isPolyFunCoreTy :: HashMap TyConName TyCon -> Type -> Bool Source
Is a type a polymorphic or function type under coreView
?
applyFunTy :: HashMap TyConName TyCon -> Type -> Type -> Type Source
Apply a function type to an argument type and get the result type