ghc-9.4.4: The GHC API
Safe HaskellSafe-Inferred
LanguageHaskell2010

GHC.Tc.Instance.Family

Contents

Description

The FamInst type: family instance heads

Synopsis

Documentation

tcLookupDataFamInst :: FamInstEnvs -> TyCon -> [TcType] -> (TyCon, [TcType], Coercion) Source #

Like tcLookupDataFamInst_maybe, but returns the arguments back if there is no data family to unwrap. Returns a Representational coercion

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 ((Bag GlobalRdrElt, TcCoercion), Type) Source #

tcTopNormaliseNewTypeTF_maybe gets rid of top-level newtypes, potentially looking through newtype instances.

It is only used by the type inference engine (specifically, when solving representational equality), and hence it is careful to unwrap only if the relevant data constructor is in scope. That's why it gets a GlobalRdrEnv argument.

It is careful not to unwrap data/newtype instances if it can't continue unwrapping. Such care is necessary for proper error messages.

It does not look through type families. It does not normalise arguments to a tycon.

If the result is Just ((gres, co), rep_ty), then co : ty ~R rep_ty gres are the GREs for the data constructors that had to be in scope

Injectivity

reportInjectivityErrors Source #

Arguments

:: DynFlags 
-> CoAxiom br

Type family for which we generate errors

-> CoAxBranch

Currently checked equation (represented by axiom)

-> [Bool]

Injectivity annotation

-> TcM () 

Report a list of injectivity errors together with their source locations. Looks only at one equation; does not look for conflicts *among* equations.

reportConflictingInjectivityErrs :: TyCon -> [CoAxBranch] -> CoAxBranch -> TcM () Source #

Report error message for a pair of equations violating an injectivity annotation. No error message if there are no branches.