Safe Haskell | None |
---|---|
Language | Haskell98 |
- voidType :: VM Type
- newLocalVVar :: FastString -> Type -> VM VVar
- mkDataConTag :: DynFlags -> DataCon -> CoreExpr
- dataConTagZ :: DataCon -> Int
- mkWrapType :: Type -> VM Type
- mkClosureTypes :: [Type] -> Type -> VM Type
- mkPReprType :: Type -> VM Type
- mkPDataType :: Type -> VM Type
- mkPDatasType :: Type -> VM Type
- splitPrimTyCon :: Type -> Maybe TyCon
- mkBuiltinCo :: (Builtins -> TyCon) -> VM Coercion
- wrapNewTypeBodyOfWrap :: CoreExpr -> Type -> VM CoreExpr
- unwrapNewTypeBodyOfWrap :: CoreExpr -> Type -> VM CoreExpr
- wrapNewTypeBodyOfPDataWrap :: CoreExpr -> Type -> VM CoreExpr
- unwrapNewTypeBodyOfPDataWrap :: CoreExpr -> Type -> VM CoreExpr
- wrapNewTypeBodyOfPDatasWrap :: CoreExpr -> Type -> VM CoreExpr
- unwrapNewTypeBodyOfPDatasWrap :: CoreExpr -> Type -> VM CoreExpr
- pdataReprTyCon :: Type -> VM (TyCon, [Type])
- pdataReprTyConExact :: TyCon -> VM TyCon
- pdatasReprTyConExact :: TyCon -> VM TyCon
- pdataUnwrapScrut :: VExpr -> VM (CoreExpr, CoreExpr, DataCon)
- preprSynTyCon :: Type -> VM FamInstMatch
Documentation
newLocalVVar :: FastString -> Type -> VM VVar Source
mkDataConTag :: DynFlags -> DataCon -> CoreExpr Source
dataConTagZ :: DataCon -> Int Source
mkWrapType :: Type -> VM Type Source
Make an application of the Wrap
type constructor.
mkClosureTypes :: [Type] -> Type -> VM Type Source
Make an application of the closure type constructor.
mkPReprType :: Type -> VM Type Source
Make an application of the PRepr
type constructor.
mkPDataType :: Type -> VM Type Source
Make an appliction of the PData
tycon to some argument.
mkPDatasType :: Type -> VM Type Source
Make an application of the PDatas
tycon to some argument.
splitPrimTyCon :: Type -> Maybe TyCon Source
Checks if a type constructor is defined in Prim
(e.g., Int#
); if so, returns it.
mkBuiltinCo :: (Builtins -> TyCon) -> VM Coercion Source
Make a representational coersion to some builtin type.
wrapNewTypeBodyOfWrap :: CoreExpr -> Type -> VM CoreExpr Source
Apply the constructor wrapper of the Wrap
newtype.
unwrapNewTypeBodyOfWrap :: CoreExpr -> Type -> VM CoreExpr Source
Strip the constructor wrapper of the Wrap
newtype.
wrapNewTypeBodyOfPDataWrap :: CoreExpr -> Type -> VM CoreExpr Source
Apply the constructor wrapper of the PData
newtype instance of Wrap
.
unwrapNewTypeBodyOfPDataWrap :: CoreExpr -> Type -> VM CoreExpr Source
Strip the constructor wrapper of the PData
newtype instance of Wrap
.
wrapNewTypeBodyOfPDatasWrap :: CoreExpr -> Type -> VM CoreExpr Source
Apply the constructor wrapper of the PDatas
newtype instance of Wrap
.
unwrapNewTypeBodyOfPDatasWrap :: CoreExpr -> Type -> VM CoreExpr Source
Strip the constructor wrapper of the PDatas
newtype instance of Wrap
.
pdataReprTyCon :: Type -> VM (TyCon, [Type]) Source
Get the representation tycon of the PData
data family for a given type.
This tycon does not appear explicitly in the source program — see Note [PData TyCons] in
Description
:
pdataReprTyCon {Sum2} = {PDataSum2}
The type for which we look up a PData
instance may be more specific than the type in the
instance declaration. In that case the second component of the result will be more specific than
a set of distinct type variables.
pdataReprTyConExact :: TyCon -> VM TyCon Source
Get the representation tycon of the PData
data family for a given type constructor.
For example, for a binary type constructor T
, we determine the representation type constructor
for 'PData (T a b)'.
pdatasReprTyConExact :: TyCon -> VM TyCon Source
Get the representation tycon of the PDatas
data family for a given type constructor.
For example, for a binary type constructor T
, we determine the representation type constructor
for 'PDatas (T a b)'.
pdataUnwrapScrut :: VExpr -> VM (CoreExpr, CoreExpr, DataCon) Source
Unwrap a PData
representation scrutinee.
preprSynTyCon :: Type -> VM FamInstMatch Source
Get the representation tycon of the PRepr
type family for a given type.