Safe Haskell | None |
---|---|
Language | Haskell2010 |
GHC.Tc.Solver.InertSet
Synopsis
- data WorkList = WL {
- wl_eqs :: [Ct]
- wl_rest :: [Ct]
- wl_implics :: Bag Implication
- isEmptyWorkList :: WorkList -> Bool
- emptyWorkList :: WorkList
- extendWorkListNonEq :: Ct -> WorkList -> WorkList
- extendWorkListCt :: Ct -> WorkList -> WorkList
- extendWorkListCts :: [Ct] -> WorkList -> WorkList
- extendWorkListEq :: Ct -> WorkList -> WorkList
- extendWorkListDeriveds :: [CtEvidence] -> WorkList -> WorkList
- appendWorkList :: WorkList -> WorkList -> WorkList
- extendWorkListImplic :: Implication -> WorkList -> WorkList
- workListSize :: WorkList -> Int
- selectWorkItem :: WorkList -> Maybe (Ct, WorkList)
- data InertSet = IS {}
- data InertCans = IC {}
- type InertEqs = DTyVarEnv EqualCtList
- emptyInert :: InertSet
- addInertItem :: TcLevel -> InertCans -> Ct -> InertCans
- matchableGivens :: CtLoc -> PredType -> InertSet -> Cts
- mightEqualLater :: InertSet -> TcPredType -> CtLoc -> TcPredType -> CtLoc -> Bool
- prohibitedSuperClassSolve :: CtLoc -> CtLoc -> Bool
- foldTyEqs :: (Ct -> b -> b) -> InertEqs -> b -> b
- delEq :: InertCans -> CanEqLHS -> TcType -> InertCans
- findEq :: InertCans -> CanEqLHS -> [Ct]
- kickOutRewritableLHS :: CtFlavourRole -> CanEqLHS -> InertCans -> (WorkList, InertCans)
The work list
Constructors
WL | |
Fields
|
Instances
isEmptyWorkList :: WorkList -> Bool Source #
extendWorkListDeriveds :: [CtEvidence] -> WorkList -> WorkList Source #
extendWorkListImplic :: Implication -> WorkList -> WorkList Source #
workListSize :: WorkList -> Int Source #
The inert set
Constructors
IS | |
Fields |
Instances
Constructors
IC | |
Fields
|
Instances
type InertEqs = DTyVarEnv EqualCtList Source #
matchableGivens :: CtLoc -> PredType -> InertSet -> Cts Source #
Returns Given constraints that might, potentially, match the given pred. 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.Interact
mightEqualLater :: InertSet -> TcPredType -> CtLoc -> TcPredType -> CtLoc -> Bool Source #
Inert equalities
Kick-out
kickOutRewritableLHS :: CtFlavourRole -> CanEqLHS -> InertCans -> (WorkList, InertCans) Source #