Safe Haskell | Safe-Infered |
---|
This module defines TyCons that can't be expressed in Haskell. They are all, therefore, wired-in TyCons. C.f module TysWiredIn
- mkPrimTyConName :: FastString -> Unique -> TyCon -> Name
- tyVarList :: Kind -> [TyVar]
- alphaTyVars :: [TyVar]
- betaTyVars :: [TyVar]
- alphaTyVar, deltaTyVar, gammaTyVar, betaTyVar :: TyVar
- alphaTy, deltaTy, gammaTy, betaTy :: Type
- openAlphaTy, openBetaTy :: Type
- openAlphaTyVar, openBetaTyVar :: TyVar
- openAlphaTyVars :: [TyVar]
- argAlphaTy, argBetaTy :: Type
- argAlphaTyVar, argBetaTyVar :: TyVar
- argAlphaTyVars :: [TyVar]
- kKiVar :: KindVar
- tySuperKindTyCon, constraintKindTyCon, argTypeKindTyCon, ubxTupleKindTyCon, unliftedTypeKindTyCon, openTypeKindTyCon, liftedTypeKindTyCon, anyKindTyCon :: TyCon
- tySuperKind :: SuperKind
- tySuperKindTyConName, constraintKindTyConName, argTypeKindTyConName, ubxTupleKindTyConName, unliftedTypeKindTyConName, openTypeKindTyConName, liftedTypeKindTyConName, anyKindTyConName :: Name
- anyKind, constraintKind, ubxTupleKind, argTypeKind, openTypeKind, unliftedTypeKind, liftedTypeKind :: Kind
- mkArrowKind :: Kind -> Kind -> Kind
- mkArrowKinds :: [Kind] -> Kind -> Kind
- funTyCon :: TyCon
- funTyConName :: Name
- primTyCons :: [TyCon]
- charPrimTyCon :: TyCon
- charPrimTy :: Type
- intPrimTyCon :: TyCon
- intPrimTy :: Type
- wordPrimTyCon :: TyCon
- wordPrimTy :: Type
- addrPrimTyCon :: TyCon
- addrPrimTy :: Type
- floatPrimTyCon :: TyCon
- floatPrimTy :: Type
- doublePrimTyCon :: TyCon
- doublePrimTy :: Type
- statePrimTyCon :: TyCon
- mkStatePrimTy :: Type -> Type
- realWorldTyCon :: TyCon
- realWorldTy :: Type
- realWorldStatePrimTy :: Type
- arrayPrimTyCon, mutableArrayArrayPrimTyCon, arrayArrayPrimTyCon, byteArrayPrimTyCon, mutableByteArrayPrimTyCon, mutableArrayPrimTyCon :: TyCon
- mkArrayPrimTy :: Type -> Type
- byteArrayPrimTy :: Type
- mkArrayArrayPrimTy :: Type
- mkMutableArrayPrimTy :: Type -> Type -> Type
- mkMutableByteArrayPrimTy :: Type -> Type
- mkMutableArrayArrayPrimTy :: Type -> Type
- mutVarPrimTyCon :: TyCon
- mkMutVarPrimTy :: Type -> Type -> Type
- mVarPrimTyCon :: TyCon
- mkMVarPrimTy :: Type -> Type -> Type
- tVarPrimTyCon :: TyCon
- mkTVarPrimTy :: Type -> Type -> Type
- stablePtrPrimTyCon :: TyCon
- mkStablePtrPrimTy :: Type -> Type
- stableNamePrimTyCon :: TyCon
- mkStableNamePrimTy :: Type -> Type
- bcoPrimTyCon :: TyCon
- bcoPrimTy :: Type
- weakPrimTyCon :: TyCon
- mkWeakPrimTy :: Type -> Type
- threadIdPrimTyCon :: TyCon
- threadIdPrimTy :: Type
- int32PrimTyCon :: TyCon
- int32PrimTy :: Type
- word32PrimTyCon :: TyCon
- word32PrimTy :: Type
- int64PrimTyCon :: TyCon
- int64PrimTy :: Type
- word64PrimTyCon :: TyCon
- word64PrimTy :: Type
- eqPrimTyCon :: TyCon
- anyTy :: Type
- anyTyCon :: TyCon
- anyTypeOfKind :: Kind -> Type
Documentation
mkPrimTyConName :: FastString -> Unique -> TyCon -> NameSource
alphaTyVars :: [TyVar]Source
betaTyVars :: [TyVar]Source
tySuperKindTyCon, constraintKindTyCon, argTypeKindTyCon, ubxTupleKindTyCon, unliftedTypeKindTyCon, openTypeKindTyCon, liftedTypeKindTyCon, anyKindTyCon :: TyConSource
tySuperKind :: SuperKindSource
tySuperKindTyConName, constraintKindTyConName, argTypeKindTyConName, ubxTupleKindTyConName, unliftedTypeKindTyConName, openTypeKindTyConName, liftedTypeKindTyConName, anyKindTyConName :: NameSource
anyKind, constraintKind, ubxTupleKind, argTypeKind, openTypeKind, unliftedTypeKind, liftedTypeKind :: KindSource
mkArrowKinds :: [Kind] -> Kind -> KindSource
Iterated application of mkArrowKind
primTyCons :: [TyCon]Source
mkStatePrimTy :: Type -> TypeSource
arrayPrimTyCon, mutableArrayArrayPrimTyCon, arrayArrayPrimTyCon, byteArrayPrimTyCon, mutableByteArrayPrimTyCon, mutableArrayPrimTyCon :: TyConSource
mkArrayPrimTy :: Type -> TypeSource
mkMutableArrayPrimTy :: Type -> Type -> TypeSource
mkMutVarPrimTy :: Type -> Type -> TypeSource
mkMVarPrimTy :: Type -> Type -> TypeSource
mkTVarPrimTy :: Type -> Type -> TypeSource
mkStablePtrPrimTy :: Type -> TypeSource
mkStableNamePrimTy :: Type -> TypeSource
mkWeakPrimTy :: Type -> TypeSource
Any
anyTypeOfKind :: Kind -> TypeSource