Safe Haskell | None |
---|
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 :: Type -> TypeView
- transparentTy :: Type -> Type
- typeKind :: Type -> Kind
- mkTyConTy :: TyCon -> Type
- mkFunTy :: Type -> Type -> Type
- mkTyConApp :: TyCon -> [Type] -> Type
- splitFunTy :: Type -> Maybe (Type, Type)
- splitFunForallTy :: Type -> ([Either TyVar Type], Type)
- splitTyConAppM :: Type -> Maybe (TyCon, [Type])
- isPolyTy :: Type -> Bool
- isFunTy :: Type -> Bool
- applyFunTy :: Type -> Type -> Type
- applyTy :: Fresh m => Type -> KindOrType -> m 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 |
Eq Type | |
Ord Type | |
Show Type | |
Rep Type | |
Alpha Type | |
Pretty Type | |
(Sat (ctx0 Kind), Sat (ctx0 TyName), Sat (ctx0 ConstTy), Sat (ctx0 (Bind TyVar Type)), Sat (ctx0 Type), Sat (ctx0 LitTy)) => Rep1 ctx0 Type | |
Subst Term Type | |
Subst Term TyVar | |
Subst Type TyCon | |
Subst Type Term | |
Subst Type Type | |
Subst Type TyVar | |
Subst Type Id | |
Subst Type DataCon | |
Subst Type PrimRep | |
Subst Type AlgTyConRhs | |
Subst Type Literal | |
Subst Type Pat | |
Subst Type LitTy | |
Subst Type ConstTy | |
Pretty (Var Type) |
An easier view on types
Type Constants
Literal Types
type KindOrType = TypeSource
Either a Kind or a Type
coreView :: Type -> TypeViewSource
A view on types in which Signal
types and newtypes are transparent
transparentTy :: Type -> TypeSource
A transformation that renders Signal
types transparent
mkTyConApp :: TyCon -> [Type] -> TypeSource
Make a TyCon Application out of a TyCon and a list of argument types
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 (TyCon, [Type])Source
Split a TyCon Application in a TyCon and its arguments
applyFunTy :: Type -> Type -> TypeSource
Apply a function type to an argument type and get the result type