Safe Haskell | None |
---|---|
Language | Haskell98 |
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 :: TyVar
- betaTyVar :: TyVar
- gammaTyVar :: TyVar
- deltaTyVar :: TyVar
- alphaTy :: Type
- betaTy :: Type
- gammaTy :: Type
- deltaTy :: Type
- openAlphaTy :: Type
- openBetaTy :: Type
- openAlphaTyVar :: TyVar
- openBetaTyVar :: TyVar
- openAlphaTyVars :: [TyVar]
- kKiVar :: KindVar
- superKindTyCon :: TyCon
- superKind :: Kind
- anyKindTyCon :: TyCon
- liftedTypeKindTyCon :: TyCon
- openTypeKindTyCon :: TyCon
- unliftedTypeKindTyCon :: TyCon
- constraintKindTyCon :: TyCon
- superKindTyConName :: Name
- anyKindTyConName :: Name
- liftedTypeKindTyConName :: Name
- openTypeKindTyConName :: Name
- unliftedTypeKindTyConName :: Name
- constraintKindTyConName :: Name
- anyKind :: Kind
- liftedTypeKind :: Kind
- unliftedTypeKind :: Kind
- openTypeKind :: Kind
- constraintKind :: 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
- voidPrimTyCon :: TyCon
- voidPrimTy :: Type
- statePrimTyCon :: TyCon
- mkStatePrimTy :: Type -> Type
- realWorldTyCon :: TyCon
- realWorldTy :: Type
- realWorldStatePrimTy :: Type
- proxyPrimTyCon :: TyCon
- mkProxyPrimTy :: Type -> Type -> Type
- arrayPrimTyCon :: TyCon
- mkArrayPrimTy :: Type -> Type
- byteArrayPrimTyCon :: TyCon
- byteArrayPrimTy :: Type
- arrayArrayPrimTyCon :: TyCon
- mkArrayArrayPrimTy :: Type
- mutableArrayPrimTyCon :: TyCon
- mkMutableArrayPrimTy :: Type -> Type -> Type
- mutableByteArrayPrimTyCon :: TyCon
- mkMutableByteArrayPrimTy :: Type -> Type
- mutableArrayArrayPrimTyCon :: TyCon
- 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
- eqReprPrimTyCon :: TyCon
- anyTy :: Type
- anyTyCon :: TyCon
- anyTypeOfKind :: Kind -> Type
- int8X16PrimTy :: Type
- int8X16PrimTyCon :: TyCon
- int16X8PrimTy :: Type
- int16X8PrimTyCon :: TyCon
- int32X4PrimTy :: Type
- int32X4PrimTyCon :: TyCon
- int64X2PrimTy :: Type
- int64X2PrimTyCon :: TyCon
- int8X32PrimTy :: Type
- int8X32PrimTyCon :: TyCon
- int16X16PrimTy :: Type
- int16X16PrimTyCon :: TyCon
- int32X8PrimTy :: Type
- int32X8PrimTyCon :: TyCon
- int64X4PrimTy :: Type
- int64X4PrimTyCon :: TyCon
- int8X64PrimTy :: Type
- int8X64PrimTyCon :: TyCon
- int16X32PrimTy :: Type
- int16X32PrimTyCon :: TyCon
- int32X16PrimTy :: Type
- int32X16PrimTyCon :: TyCon
- int64X8PrimTy :: Type
- int64X8PrimTyCon :: TyCon
- word8X16PrimTy :: Type
- word8X16PrimTyCon :: TyCon
- word16X8PrimTy :: Type
- word16X8PrimTyCon :: TyCon
- word32X4PrimTy :: Type
- word32X4PrimTyCon :: TyCon
- word64X2PrimTy :: Type
- word64X2PrimTyCon :: TyCon
- word8X32PrimTy :: Type
- word8X32PrimTyCon :: TyCon
- word16X16PrimTy :: Type
- word16X16PrimTyCon :: TyCon
- word32X8PrimTy :: Type
- word32X8PrimTyCon :: TyCon
- word64X4PrimTy :: Type
- word64X4PrimTyCon :: TyCon
- word8X64PrimTy :: Type
- word8X64PrimTyCon :: TyCon
- word16X32PrimTy :: Type
- word16X32PrimTyCon :: TyCon
- word32X16PrimTy :: Type
- word32X16PrimTyCon :: TyCon
- word64X8PrimTy :: Type
- word64X8PrimTyCon :: TyCon
- floatX4PrimTy :: Type
- floatX4PrimTyCon :: TyCon
- doubleX2PrimTy :: Type
- doubleX2PrimTyCon :: TyCon
- floatX8PrimTy :: Type
- floatX8PrimTyCon :: TyCon
- doubleX4PrimTy :: Type
- doubleX4PrimTyCon :: TyCon
- floatX16PrimTy :: Type
- floatX16PrimTyCon :: TyCon
- doubleX8PrimTy :: Type
- doubleX8PrimTyCon :: TyCon
Documentation
mkPrimTyConName :: FastString -> Unique -> TyCon -> Name Source
alphaTyVars :: [TyVar] Source
betaTyVars :: [TyVar] Source
openBetaTy :: Type Source
openAlphaTyVars :: [TyVar] Source
mkArrowKinds :: [Kind] -> Kind -> Kind Source
Iterated application of mkArrowKind
primTyCons :: [TyCon] Source
charPrimTy :: Type Source
wordPrimTy :: Type Source
addrPrimTy :: Type Source
voidPrimTy :: Type Source
mkStatePrimTy :: Type -> Type Source
mkProxyPrimTy :: Type -> Type -> Type Source
mkArrayPrimTy :: Type -> Type Source
mkMutableArrayPrimTy :: Type -> Type -> Type Source
mkMutVarPrimTy :: Type -> Type -> Type Source
mkMVarPrimTy :: Type -> Type -> Type Source
mkTVarPrimTy :: Type -> Type -> Type Source
mkStablePtrPrimTy :: Type -> Type Source
mkStableNamePrimTy :: Type -> Type Source
mkWeakPrimTy :: Type -> Type Source
Any
anyTypeOfKind :: Kind -> Type Source