Safe Haskell | None |
---|---|
Language | GHC2021 |
This module defines TyCons that can't be expressed in Haskell. They are all, therefore, wired-in TyCons. C.f module GHC.Builtin.Types
Synopsis
- mkTemplateKindVar :: Kind -> TyVar
- mkTemplateKindVars :: [Kind] -> [TyVar]
- mkTemplateTyVars :: [Kind] -> [TyVar]
- mkTemplateTyVarsFrom :: Int -> [Kind] -> [TyVar]
- mkTemplateKiTyVars :: [Kind] -> ([Kind] -> [Kind]) -> [TyVar]
- mkTemplateKiTyVar :: Kind -> (Kind -> [Kind]) -> [TyVar]
- mkTemplateTyConBinders :: [Kind] -> ([Kind] -> [Kind]) -> [TyConBinder]
- mkTemplateKindTyConBinders :: [Kind] -> [TyConBinder]
- mkTemplateAnonTyConBinders :: [Kind] -> [TyConBinder]
- alphaTyVars :: [TyVar]
- alphaTyVar :: TyVar
- betaTyVar :: TyVar
- gammaTyVar :: TyVar
- deltaTyVar :: TyVar
- alphaTyVarSpec :: TyVarBinder
- betaTyVarSpec :: TyVarBinder
- gammaTyVarSpec :: TyVarBinder
- deltaTyVarSpec :: TyVarBinder
- alphaTys :: [Type]
- alphaTy :: Type
- betaTy :: Type
- gammaTy :: Type
- deltaTy :: Type
- alphaTyVarsUnliftedRep :: [TyVar]
- alphaTyVarUnliftedRep :: TyVar
- alphaTysUnliftedRep :: [Type]
- alphaTyUnliftedRep :: Type
- runtimeRep1TyVar :: TyVar
- runtimeRep2TyVar :: TyVar
- runtimeRep3TyVar :: TyVar
- runtimeRep1TyVarInf :: TyVarBinder
- runtimeRep2TyVarInf :: TyVarBinder
- runtimeRep1Ty :: RuntimeRepType
- runtimeRep2Ty :: RuntimeRepType
- runtimeRep3Ty :: RuntimeRepType
- levity1TyVar :: TyVar
- levity2TyVar :: TyVar
- levity1TyVarInf :: TyVarBinder
- levity2TyVarInf :: TyVarBinder
- levity1Ty :: Type
- levity2Ty :: Type
- alphaConstraintTyVar :: TyVar
- alphaConstraintTy :: Type
- openAlphaTyVar :: TyVar
- openBetaTyVar :: TyVar
- openGammaTyVar :: TyVar
- openAlphaTyVarSpec :: TyVarBinder
- openBetaTyVarSpec :: TyVarBinder
- openGammaTyVarSpec :: TyVarBinder
- openAlphaTy :: Type
- openBetaTy :: Type
- openGammaTy :: Type
- levPolyAlphaTyVar :: TyVar
- levPolyBetaTyVar :: TyVar
- levPolyAlphaTyVarSpec :: TyVarBinder
- levPolyBetaTyVarSpec :: TyVarBinder
- levPolyAlphaTy :: Type
- levPolyBetaTy :: Type
- multiplicityTyVar1 :: TyVar
- multiplicityTyVar2 :: TyVar
- tYPETyCon :: TyCon
- tYPETyConName :: Name
- tYPEKind :: Type
- cONSTRAINTTyCon :: TyCon
- cONSTRAINTTyConName :: Name
- cONSTRAINTKind :: Type
- funTyFlagTyCon :: FunTyFlag -> TyCon
- isArrowTyCon :: TyCon -> Bool
- fUNTyCon :: TyCon
- fUNTyConName :: Name
- ctArrowTyCon :: TyCon
- ctArrowTyConName :: Name
- ccArrowTyCon :: TyCon
- ccArrowTyConName :: Name
- tcArrowTyCon :: TyCon
- tcArrowTyConName :: Name
- unexposedPrimTyCons :: [TyCon]
- exposedPrimTyCons :: [TyCon]
- primTyCons :: [TyCon]
- charPrimTyCon :: TyCon
- charPrimTy :: Type
- charPrimTyConName :: Name
- intPrimTyCon :: TyCon
- intPrimTy :: Type
- intPrimTyConName :: Name
- wordPrimTyCon :: TyCon
- wordPrimTy :: Type
- wordPrimTyConName :: Name
- addrPrimTyCon :: TyCon
- addrPrimTy :: Type
- addrPrimTyConName :: Name
- floatPrimTyCon :: TyCon
- floatPrimTy :: Type
- floatPrimTyConName :: Name
- doublePrimTyCon :: TyCon
- doublePrimTy :: Type
- doublePrimTyConName :: Name
- 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
- smallArrayPrimTyCon :: TyCon
- mkSmallArrayPrimTy :: Type -> Type
- mutableArrayPrimTyCon :: TyCon
- mkMutableArrayPrimTy :: Type -> Type -> Type
- mutableByteArrayPrimTyCon :: TyCon
- mkMutableByteArrayPrimTy :: Type -> Type
- smallMutableArrayPrimTyCon :: TyCon
- mkSmallMutableArrayPrimTy :: Type -> Type -> Type
- mutVarPrimTyCon :: TyCon
- mkMutVarPrimTy :: Type -> Type -> Type
- mVarPrimTyCon :: TyCon
- mkMVarPrimTy :: Type -> Type -> Type
- ioPortPrimTyCon :: TyCon
- mkIOPortPrimTy :: Type -> Type -> Type
- tVarPrimTyCon :: TyCon
- mkTVarPrimTy :: Type -> Type -> Type
- stablePtrPrimTyCon :: TyCon
- mkStablePtrPrimTy :: Type -> Type
- stableNamePrimTyCon :: TyCon
- mkStableNamePrimTy :: Type -> Type
- compactPrimTyCon :: TyCon
- compactPrimTy :: Type
- bcoPrimTyCon :: TyCon
- bcoPrimTy :: Type
- weakPrimTyCon :: TyCon
- mkWeakPrimTy :: Type -> Type
- threadIdPrimTyCon :: TyCon
- threadIdPrimTy :: Type
- stackSnapshotPrimTyCon :: TyCon
- stackSnapshotPrimTy :: Type
- promptTagPrimTyCon :: TyCon
- mkPromptTagPrimTy :: Type -> Type
- int8PrimTyCon :: TyCon
- int8PrimTy :: Type
- int8PrimTyConName :: Name
- word8PrimTyCon :: TyCon
- word8PrimTy :: Type
- word8PrimTyConName :: Name
- int16PrimTyCon :: TyCon
- int16PrimTy :: Type
- int16PrimTyConName :: Name
- word16PrimTyCon :: TyCon
- word16PrimTy :: Type
- word16PrimTyConName :: Name
- int32PrimTyCon :: TyCon
- int32PrimTy :: Type
- int32PrimTyConName :: Name
- word32PrimTyCon :: TyCon
- word32PrimTy :: Type
- word32PrimTyConName :: Name
- int64PrimTyCon :: TyCon
- int64PrimTy :: Type
- int64PrimTyConName :: Name
- word64PrimTyCon :: TyCon
- word64PrimTy :: Type
- word64PrimTyConName :: Name
- eqPrimTyCon :: TyCon
- eqReprPrimTyCon :: TyCon
- eqPhantPrimTyCon :: TyCon
- equalityTyCon :: Role -> TyCon
- 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
mkTemplateKindVar :: Kind -> TyVar Source #
mkTemplateKindVars :: [Kind] -> [TyVar] Source #
mkTemplateTyVars :: [Kind] -> [TyVar] Source #
mkTemplateTyConBinders :: [Kind] -> ([Kind] -> [Kind]) -> [TyConBinder] Source #
mkTemplateKindTyConBinders :: [Kind] -> [TyConBinder] Source #
mkTemplateAnonTyConBinders :: [Kind] -> [TyConBinder] Source #
alphaTyVars :: [TyVar] Source #
alphaTyVar :: TyVar Source #
gammaTyVar :: TyVar Source #
deltaTyVar :: TyVar Source #
alphaTysUnliftedRep :: [Type] Source #
levity1TyVar :: TyVar Source #
levity2TyVar :: TyVar Source #
openAlphaTy :: Type Source #
openBetaTy :: Type Source #
openGammaTy :: Type Source #
levPolyBetaTy :: Type Source #
tYPETyConName :: Name Source #
funTyFlagTyCon :: FunTyFlag -> TyCon Source #
isArrowTyCon :: TyCon -> Bool Source #
The FUN
type constructor.
FUN :: forall (m :: Multiplicity) -> forall {rep1 :: RuntimeRep} {rep2 :: RuntimeRep}. TYPE rep1 -> TYPE rep2 -> Type
The runtime representations quantification is left inferred. This
means they cannot be specified with -XTypeApplications
.
This is a deliberate choice to allow future extensions to the function arrow.
fUNTyConName :: Name Source #
ctArrowTyCon :: TyCon Source #
ccArrowTyCon :: TyCon Source #
tcArrowTyCon :: TyCon Source #
unexposedPrimTyCons :: [TyCon] Source #
Primitive TyCon
s that are defined in GHC.Prim but not "exposed".
See Note [Unexposed TyCons]
exposedPrimTyCons :: [TyCon] Source #
Primitive TyCon
s that are defined in, and exported from, GHC.Prim.
primTyCons :: [TyCon] Source #
charPrimTy :: Type Source #
intPrimTyCon :: TyCon Source #
wordPrimTy :: Type Source #
addrPrimTy :: Type Source #
floatPrimTy :: Type Source #
doublePrimTy :: Type Source #
mkStatePrimTy :: Type -> Type Source #
realWorldTy :: Type Source #
mkArrayPrimTy :: Type -> Type Source #
mkSmallArrayPrimTy :: Type -> Type Source #
mkMutableByteArrayPrimTy :: Type -> Type Source #
mkStablePtrPrimTy :: Type -> Type Source #
mkStableNamePrimTy :: Type -> Type Source #
compactPrimTy :: Type Source #
bcoPrimTyCon :: TyCon Source #
mkWeakPrimTy :: Type -> Type Source #
mkPromptTagPrimTy :: Type -> Type Source #
int8PrimTy :: Type Source #
word8PrimTy :: Type Source #
int16PrimTy :: Type Source #
word16PrimTy :: Type Source #
int32PrimTy :: Type Source #
word32PrimTy :: Type Source #
int64PrimTy :: Type Source #
word64PrimTy :: Type Source #
eqPrimTyCon :: TyCon Source #
equalityTyCon :: Role -> TyCon Source #
Given a Role, what TyCon is the type of equality predicates at that role?
SIMD
int8X16PrimTy :: Type Source #
int16X8PrimTy :: Type Source #
int32X4PrimTy :: Type Source #
int64X2PrimTy :: Type Source #
int8X32PrimTy :: Type Source #
int32X8PrimTy :: Type Source #
int64X4PrimTy :: Type Source #
int8X64PrimTy :: Type Source #
int64X8PrimTy :: Type Source #
floatX4PrimTy :: Type Source #
floatX8PrimTy :: Type Source #