ghc-9.8.2: The GHC API
Safe HaskellNone
LanguageHaskell2010

GHC.Tc.Solver.InertSet

Synopsis

The work list

data WorkList Source #

Constructors

WL 

Fields

Instances

Instances details
Outputable WorkList Source # 
Instance details

Defined in GHC.Tc.Solver.InertSet

Methods

ppr :: WorkList -> SDoc Source #

The inert set

data InertCans Source #

Constructors

IC 

Fields

Instances

Instances details
Outputable InertCans Source # 
Instance details

Defined in GHC.Tc.Solver.InertSet

Methods

ppr :: InertCans -> SDoc Source #

noMatchableGivenDicts :: InertSet -> CtLoc -> Class -> [TcType] -> Bool Source #

Returns True iff there are no Given constraints that might, potentially, match the given class consraint. This is used when checking to see if a Given might overlap with an instance. See Note [Instance and Given overlap] in GHC.Tc.Solver.Dict

prohibitedSuperClassSolve Source #

Arguments

:: CtLoc

is it loopy to use this one ...

-> CtLoc

... to solve this one?

-> Bool

True ==> don't solve it

Is it (potentially) loopy to use the first ct1 to solve ct2?

Necessary (but not sufficient) conditions for this function to return True:

  • ct1 and ct2 both arise from superclass expansion,
  • ct1 is a Given and ct2 is a Wanted.

See Note [Solving superclass constraints] in GHC.Tc.TyCl.Instance, (sc2).

Inert equalities

foldTyEqs :: (EqCt -> b -> b) -> InertEqs -> b -> b Source #

partitionFunEqs :: (EqCt -> Bool) -> InertFunEqs -> ([EqCt], InertFunEqs) Source #

foldFunEqs :: (EqCt -> b -> b) -> FunEqMap EqualCtList -> b -> b Source #

Inert Dicts

Inert Irreds

foldIrreds :: (IrredCt -> b -> b) -> InertIrreds -> b -> b Source #

Kick-out

Cycle breaker vars

type CycleBreakerVarStack Source #

Arguments

 = NonEmpty (Bag (TcTyVar, TcType))

a stack of (CycleBreakerTv, original family applications) lists first element in the stack corresponds to current implication; later elements correspond to outer implications used to undo the cycle-breaking needed to handle Note [Type equality cycles] in GHC.Tc.Solver.Equality Why store the outer implications? For the use in mightEqualLater (only)

Why NonEmpty? So there is always a top element to add to

pushCycleBreakerVarStack :: CycleBreakerVarStack -> CycleBreakerVarStack Source #

Push a fresh environment onto the cycle-breaker var stack. Useful when entering a nested implication.

addCycleBreakerBindings Source #

Arguments

:: Bag (TcTyVar, Type)

(cbv,expansion) pairs

-> InertSet 
-> InertSet 

Add a new cycle-breaker binding to the top environment on the stack.

forAllCycleBreakerBindings_ :: Monad m => CycleBreakerVarStack -> (TcTyVar -> TcType -> m ()) -> m () Source #

Perform a monadic operation on all pairs in the top environment in the stack.

Solving one from another

data InteractResult Source #

Constructors

KeepInert 
KeepWork 

Instances

Instances details
Outputable InteractResult Source # 
Instance details

Defined in GHC.Tc.Solver.InertSet