ghc-6.10.3: The GHC APIContentsIndex
Unify
Documentation
tcMatchTy :: TyVarSet -> Type -> Type -> Maybe TvSubst
tcMatchTys :: TyVarSet -> [Type] -> [Type] -> Maybe TvSubst
tcMatchTyX :: TyVarSet -> TvSubst -> Type -> Type -> Maybe TvSubst
ruleMatchTyX :: MatchEnv -> TvSubstEnv -> Type -> Type -> Maybe TvSubstEnv
tcMatchPreds :: [TyVar] -> [PredType] -> [PredType] -> Maybe TvSubstEnv
data MatchEnv
Constructors
ME
me_tmpls :: VarSet
me_env :: RnEnv2
dataConCannotMatch :: [Type] -> DataCon -> Bool
data Refinement
show/hide Instances
emptyRefinement :: Refinement
isEmptyRefinement :: Refinement -> Bool
matchRefine :: [TyVar] -> [Coercion] -> Refinement
refineType :: Refinement -> Type -> Maybe (Coercion, Type)
refinePred :: Refinement -> PredType -> Maybe (Coercion, PredType)
refineResType :: Refinement -> Type -> Maybe (Coercion, Type)
tcUnifyTys :: (TyVar -> BindFlag) -> [Type] -> [Type] -> Maybe TvSubst
data BindFlag
Constructors
BindMe
Skolem
Produced by Haddock version 2.4.2