Safe Haskell | None |
---|---|
Language | Haskell2010 |
- data FamInst = FamInst {}
- data FamFlavor
- famInstAxiom :: FamInst -> CoAxiom Unbranched
- famInstTyCon :: FamInst -> TyCon
- famInstRHS :: FamInst -> Type
- famInstsRepTyCons :: [FamInst] -> [TyCon]
- famInstRepTyCon_maybe :: FamInst -> Maybe TyCon
- dataFamInstRepTyCon :: FamInst -> TyCon
- pprFamInst :: FamInst -> SDoc
- pprFamInsts :: [FamInst] -> SDoc
- mkImportedFamInst :: Name -> [Maybe Name] -> CoAxiom Unbranched -> 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
- identicalFamInstHead :: FamInst -> FamInst -> Bool
- famInstEnvElts :: FamInstEnv -> [FamInst]
- familyInstances :: (FamInstEnv, FamInstEnv) -> TyCon -> [FamInst]
- orphNamesOfFamInst :: FamInst -> NameSet
- mkCoAxBranch :: [TyVar] -> [Type] -> Type -> SrcSpan -> CoAxBranch
- mkBranchedCoAxiom :: Name -> TyCon -> [CoAxBranch] -> CoAxiom Branched
- mkUnbranchedCoAxiom :: Name -> TyCon -> CoAxBranch -> CoAxiom Unbranched
- mkSingleCoAxiom :: Name -> [TyVar] -> TyCon -> [Type] -> Type -> CoAxiom Unbranched
- computeAxiomIncomps :: CoAxiom br -> CoAxiom br
- data FamInstMatch = FamInstMatch {
- fim_instance :: FamInst
- fim_tys :: [Type]
- lookupFamInstEnv :: FamInstEnvs -> TyCon -> [Type] -> [FamInstMatch]
- lookupFamInstEnvConflicts :: FamInstEnvs -> FamInst -> [FamInstMatch]
- isDominatedBy :: CoAxBranch -> [CoAxBranch] -> Bool
- topNormaliseType :: FamInstEnvs -> Type -> Type
- topNormaliseType_maybe :: FamInstEnvs -> Type -> Maybe (Coercion, Type)
- normaliseType :: FamInstEnvs -> Role -> Type -> (Coercion, Type)
- normaliseTcApp :: FamInstEnvs -> Role -> TyCon -> [Type] -> (Coercion, Type)
- reduceTyFamApp_maybe :: FamInstEnvs -> Role -> TyCon -> [Type] -> Maybe (Coercion, Type)
- chooseBranch :: CoAxiom Branched -> [Type] -> Maybe (BranchIndex, [Type])
- flattenTys :: InScopeSet -> [Type] -> [Type]
Documentation
famInstTyCon :: FamInst -> TyCon Source
famInstRHS :: FamInst -> Type Source
famInstsRepTyCons :: [FamInst] -> [TyCon] Source
pprFamInst :: FamInst -> SDoc Source
pprFamInsts :: [FamInst] -> SDoc Source
mkImportedFamInst :: Name -> [Maybe Name] -> CoAxiom Unbranched -> FamInst Source
type FamInstEnvs = (FamInstEnv, FamInstEnv) Source
type FamInstEnv = UniqFM FamilyInstEnv Source
extendFamInstEnv :: FamInstEnv -> FamInst -> FamInstEnv Source
extendFamInstEnvList :: FamInstEnv -> [FamInst] -> FamInstEnv Source
identicalFamInstHead :: FamInst -> FamInst -> Bool Source
True when the LHSs are identical Used for overriding in GHCi
famInstEnvElts :: FamInstEnv -> [FamInst] Source
familyInstances :: (FamInstEnv, FamInstEnv) -> TyCon -> [FamInst] Source
orphNamesOfFamInst :: FamInst -> NameSet Source
Collects the names of the concrete types and type constructors that make up the LHS of a type family instance, including the family name itself.
For instance, given `type family Foo a b`: `type instance Foo (F (G (H a))) b = ...` would yield [Foo,F,G,H]
Used in the implementation of ":info" in GHCi.
CoAxioms
mkCoAxBranch :: [TyVar] -> [Type] -> Type -> SrcSpan -> CoAxBranch Source
mkBranchedCoAxiom :: Name -> TyCon -> [CoAxBranch] -> CoAxiom Branched Source
mkUnbranchedCoAxiom :: Name -> TyCon -> CoAxBranch -> CoAxiom Unbranched Source
mkSingleCoAxiom :: Name -> [TyVar] -> TyCon -> [Type] -> Type -> CoAxiom Unbranched Source
computeAxiomIncomps :: CoAxiom br -> CoAxiom br Source
data FamInstMatch Source
FamInstMatch | |
|
lookupFamInstEnv :: FamInstEnvs -> TyCon -> [Type] -> [FamInstMatch] Source
isDominatedBy :: CoAxBranch -> [CoAxBranch] -> Bool Source
topNormaliseType :: FamInstEnvs -> Type -> Type Source
topNormaliseType_maybe :: FamInstEnvs -> Type -> Maybe (Coercion, Type) Source
Get rid of *outermost* (or toplevel) * type function redex * newtypes using appropriate coercions. Specifically, if topNormaliseType_maybe env ty = Maybe (co, ty') then (a) co :: ty ~ ty' (b) ty' is not a newtype, and is not a type-family redex
However, ty' can be something like (Maybe (F ty)), where (F ty) is a redex.
Its a bit like Type.repType, but handles type families too The coercion returned is always an R coercion
normaliseType :: FamInstEnvs -> Role -> Type -> (Coercion, Type) Source
normaliseTcApp :: FamInstEnvs -> Role -> TyCon -> [Type] -> (Coercion, Type) Source
reduceTyFamApp_maybe :: FamInstEnvs -> Role -> TyCon -> [Type] -> Maybe (Coercion, Type) Source
chooseBranch :: CoAxiom Branched -> [Type] -> Maybe (BranchIndex, [Type]) Source
flattenTys :: InScopeSet -> [Type] -> [Type] Source