Safe Haskell | None |
---|
- data FamInst = FamInst {}
- data FamFlavor
- famInstAxiom :: FamInst -> CoAxiom
- famInstsRepTyCons :: [FamInst] -> [TyCon]
- famInstRepTyCon_maybe :: FamInst -> Maybe TyCon
- dataFamInstRepTyCon :: FamInst -> TyCon
- famInstLHS :: FamInst -> (TyCon, [Type])
- pprFamInst :: FamInst -> SDoc
- pprFamInstHdr :: FamInst -> SDoc
- pprFamInsts :: [FamInst] -> SDoc
- mkSynFamInst :: Name -> [TyVar] -> TyCon -> [Type] -> Type -> FamInst
- mkDataFamInst :: Name -> [TyVar] -> TyCon -> [Type] -> TyCon -> FamInst
- mkImportedFamInst :: Name -> [Maybe Name] -> CoAxiom -> FamInst
- type FamInstEnvs = (FamInstEnv, FamInstEnv)
- type FamInstEnv = UniqFM FamilyInstEnv
- emptyFamInstEnv :: FamInstEnv
- emptyFamInstEnvs :: (FamInstEnv, FamInstEnv)
- extendFamInstEnv :: FamInstEnv -> FamInst -> FamInstEnv
- deleteFromFamInstEnv :: FamInstEnv -> FamInst -> FamInstEnv
- extendFamInstEnvList :: FamInstEnv -> [FamInst] -> FamInstEnv
- identicalFamInst :: FamInst -> FamInst -> Bool
- famInstEnvElts :: FamInstEnv -> [FamInst]
- familyInstances :: (FamInstEnv, FamInstEnv) -> TyCon -> [FamInst]
- lookupFamInstEnv :: FamInstEnvs -> TyCon -> [Type] -> [FamInstMatch]
- lookupFamInstEnvConflicts :: FamInstEnvs -> FamInst -> [TyVar] -> [FamInstMatch]
- lookupFamInstEnvConflicts' :: FamInstEnv -> FamInst -> [TyVar] -> [FamInstMatch]
- topNormaliseType :: FamInstEnvs -> Type -> Maybe (Coercion, Type)
- normaliseType :: FamInstEnvs -> Type -> (Coercion, Type)
- normaliseTcApp :: FamInstEnvs -> TyCon -> [Type] -> (Coercion, Type)
Documentation
famInstAxiom :: FamInst -> CoAxiomSource
famInstsRepTyCons :: [FamInst] -> [TyCon]Source
famInstLHS :: FamInst -> (TyCon, [Type])Source
pprFamInst :: FamInst -> SDocSource
pprFamInstHdr :: FamInst -> SDocSource
pprFamInsts :: [FamInst] -> SDocSource
:: Name | Unique name for the coercion tycon |
-> [TyVar] | Type parameters of the coercion ( |
-> TyCon | Family tycon ( |
-> [Type] | Type instance ( |
-> Type | Representation tycon ( |
-> FamInst |
Create a coercion identifying a type
family instance.
It has the form Co tvs :: F ts ~ R
, where Co
is
the coercion constructor built here, F
the family tycon and R
the
right-hand side of the type family instance.
:: Name | Unique name for the coercion tycon |
-> [TyVar] | Type parameters of the coercion ( |
-> TyCon | Family tycon ( |
-> [Type] | Type instance ( |
-> TyCon | Representation tycon ( |
-> FamInst |
Create a coercion identifying a data
or newtype
representation type
and its family instance. It has the form Co tvs :: F ts ~ R tvs
,
where Co
is the coercion constructor built here, F
the family tycon
and R
the (derived) representation tycon.
type FamInstEnvs = (FamInstEnv, FamInstEnv)Source
type FamInstEnv = UniqFM FamilyInstEnvSource
extendFamInstEnvList :: FamInstEnv -> [FamInst] -> FamInstEnvSource
identicalFamInst :: FamInst -> FamInst -> BoolSource
famInstEnvElts :: FamInstEnv -> [FamInst]Source
familyInstances :: (FamInstEnv, FamInstEnv) -> TyCon -> [FamInst]Source
lookupFamInstEnv :: FamInstEnvs -> TyCon -> [Type] -> [FamInstMatch]Source
lookupFamInstEnvConflicts :: FamInstEnvs -> FamInst -> [TyVar] -> [FamInstMatch]Source
lookupFamInstEnvConflicts' :: FamInstEnv -> FamInst -> [TyVar] -> [FamInstMatch]Source
topNormaliseType :: FamInstEnvs -> Type -> Maybe (Coercion, Type)Source
normaliseType :: FamInstEnvs -> Type -> (Coercion, Type)Source
normaliseTcApp :: FamInstEnvs -> TyCon -> [Type] -> (Coercion, Type)Source