Safe Haskell | None |
---|---|
Language | Haskell2010 |
- type FamInstEnvs = (FamInstEnv, FamInstEnv)
- tcGetFamInstEnvs :: TcM FamInstEnvs
- checkFamInstConsistency :: [Module] -> [Module] -> TcM ()
- tcExtendLocalFamInstEnv :: [FamInst] -> TcM a -> TcM a
- tcLookupFamInst :: FamInstEnvs -> TyCon -> [Type] -> Maybe FamInstMatch
- tcLookupDataFamInst :: FamInstEnvs -> TyCon -> [TcType] -> (TyCon, [TcType], TcCoercion)
- tcLookupDataFamInst_maybe :: FamInstEnvs -> TyCon -> [TcType] -> Maybe (TyCon, [TcType], Coercion)
- tcInstNewTyCon_maybe :: TyCon -> [TcType] -> Maybe (TcType, TcCoercion)
- tcTopNormaliseNewTypeTF_maybe :: FamInstEnvs -> GlobalRdrEnv -> Type -> Maybe (TcCoercion, Type)
- newFamInst :: FamFlavor -> CoAxiom Unbranched -> TcRnIf gbl lcl FamInst
Documentation
type FamInstEnvs = (FamInstEnv, FamInstEnv) Source
checkFamInstConsistency :: [Module] -> [Module] -> TcM () Source
tcExtendLocalFamInstEnv :: [FamInst] -> TcM a -> TcM a Source
tcLookupFamInst :: FamInstEnvs -> TyCon -> [Type] -> Maybe FamInstMatch Source
tcLookupDataFamInst :: FamInstEnvs -> TyCon -> [TcType] -> (TyCon, [TcType], TcCoercion) Source
Like tcLookupDataFamInst_maybe
, but returns the arguments back if
there is no data family to unwrap.
tcLookupDataFamInst_maybe :: FamInstEnvs -> TyCon -> [TcType] -> Maybe (TyCon, [TcType], Coercion) Source
Converts a data family type (eg F [a]) to its representation type (eg FList a) and returns a coercion between the two: co :: F [a] ~R FList a
tcInstNewTyCon_maybe :: TyCon -> [TcType] -> Maybe (TcType, TcCoercion) Source
If co :: T ts ~ rep_ty
then:
instNewTyCon_maybe T ts = Just (rep_ty, co)
Checks for a newtype, and for being saturated Just like Coercion.instNewTyCon_maybe, but returns a TcCoercion
tcTopNormaliseNewTypeTF_maybe :: FamInstEnvs -> GlobalRdrEnv -> Type -> Maybe (TcCoercion, Type) Source
Get rid of top-level newtypes, potentially looking through newtype
instances. Only unwraps newtypes that are in scope. This is used
for solving for Coercible
in the solver. This version is careful
not to unwrap data/newtype instances if it can't continue unwrapping.
Such care is necessary for proper error messages.
Does not look through type families. Does not normalise arguments to a tycon.
Always produces a representational coercion.
newFamInst :: FamFlavor -> CoAxiom Unbranched -> TcRnIf gbl lcl FamInst Source