Safe Haskell | None |
---|---|
Language | Haskell2010 |
Type definitions for the constraint solver
Synopsis
- data WorkList = WL {
- wl_eqs :: [Ct]
- wl_funeqs :: [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
- extendWorkListFunEq :: Ct -> WorkList -> WorkList
- appendWorkList :: WorkList -> WorkList -> WorkList
- selectNextWorkItem :: TcS (Maybe Ct)
- workListSize :: WorkList -> Int
- workListWantedCount :: WorkList -> Int
- getWorkList :: TcS WorkList
- updWorkListTcS :: (WorkList -> WorkList) -> TcS ()
- pushLevelNoWorkList :: SDoc -> TcS a -> TcS (TcLevel, a)
- data TcS a
- runTcS :: TcS a -> TcM (a, EvBindMap)
- runTcSDeriveds :: TcS a -> TcM a
- runTcSWithEvBinds :: EvBindsVar -> TcS a -> TcM a
- failTcS :: SDoc -> TcS a
- warnTcS :: WarningFlag -> SDoc -> TcS ()
- addErrTcS :: SDoc -> TcS ()
- runTcSEqualities :: TcS a -> TcM a
- nestTcS :: TcS a -> TcS a
- nestImplicTcS :: EvBindsVar -> TcLevel -> TcS a -> TcS a
- setEvBindsTcS :: EvBindsVar -> TcS a -> TcS a
- emitImplicationTcS :: TcLevel -> SkolemInfo -> [TcTyVar] -> [EvVar] -> Cts -> TcS TcEvBinds
- emitTvImplicationTcS :: TcLevel -> SkolemInfo -> [TcTyVar] -> Cts -> TcS ()
- runTcPluginTcS :: TcPluginM a -> TcS a
- addUsedGRE :: Bool -> GlobalRdrElt -> TcS ()
- addUsedGREs :: [GlobalRdrElt] -> TcS ()
- keepAlive :: Name -> TcS ()
- matchGlobalInst :: DynFlags -> Bool -> Class -> [Type] -> TcS ClsInstResult
- data ClsInstResult
- = NoInstance
- | OneInst {
- cir_new_theta :: [TcPredType]
- cir_mk_ev :: [EvExpr] -> EvTerm
- cir_what :: InstanceWhat
- | NotSure
- data QCInst = QCI {
- qci_ev :: CtEvidence
- qci_tvs :: [TcTyVar]
- qci_pred :: TcPredType
- qci_pend_sc :: Bool
- panicTcS :: SDoc -> TcS a
- traceTcS :: String -> SDoc -> TcS ()
- traceFireTcS :: CtEvidence -> SDoc -> TcS ()
- bumpStepCountTcS :: TcS ()
- csTraceTcS :: SDoc -> TcS ()
- wrapErrTcS :: TcM a -> TcS a
- wrapWarnTcS :: TcM a -> TcS a
- data MaybeNew
- freshGoals :: [MaybeNew] -> [CtEvidence]
- isFresh :: MaybeNew -> Bool
- getEvExpr :: MaybeNew -> EvExpr
- newTcEvBinds :: TcS EvBindsVar
- newNoTcEvBinds :: TcS EvBindsVar
- newWantedEq :: CtLoc -> Role -> TcType -> TcType -> TcS (CtEvidence, Coercion)
- newWantedEq_SI :: BlockSubstFlag -> ShadowInfo -> CtLoc -> Role -> TcType -> TcType -> TcS (CtEvidence, Coercion)
- emitNewWantedEq :: CtLoc -> Role -> TcType -> TcType -> TcS Coercion
- newWanted :: CtLoc -> PredType -> TcS MaybeNew
- newWanted_SI :: ShadowInfo -> CtLoc -> PredType -> TcS MaybeNew
- newWantedEvVar :: CtLoc -> TcPredType -> TcS MaybeNew
- newWantedNC :: CtLoc -> PredType -> TcS CtEvidence
- newWantedEvVarNC :: CtLoc -> TcPredType -> TcS CtEvidence
- newDerivedNC :: CtLoc -> TcPredType -> TcS CtEvidence
- newBoundEvVarId :: TcPredType -> EvTerm -> TcS EvVar
- unifyTyVar :: TcTyVar -> TcType -> TcS ()
- unflattenFmv :: TcTyVar -> TcType -> TcS ()
- reportUnifications :: TcS a -> TcS (Int, a)
- setEvBind :: EvBind -> TcS ()
- setWantedEq :: TcEvDest -> Coercion -> TcS ()
- setWantedEvTerm :: TcEvDest -> EvTerm -> TcS ()
- setEvBindIfWanted :: CtEvidence -> EvTerm -> TcS ()
- newEvVar :: TcPredType -> TcS EvVar
- newGivenEvVar :: CtLoc -> (TcPredType, EvTerm) -> TcS CtEvidence
- newGivenEvVars :: CtLoc -> [(TcPredType, EvTerm)] -> TcS [CtEvidence]
- emitNewDeriveds :: CtLoc -> [TcPredType] -> TcS ()
- emitNewDerivedEq :: CtLoc -> Role -> TcType -> TcType -> TcS ()
- checkReductionDepth :: CtLoc -> TcType -> TcS ()
- getSolvedDicts :: TcS (DictMap CtEvidence)
- setSolvedDicts :: DictMap CtEvidence -> TcS ()
- getInstEnvs :: TcS InstEnvs
- getFamInstEnvs :: TcS (FamInstEnv, FamInstEnv)
- getTopEnv :: TcS HscEnv
- getGblEnv :: TcS TcGblEnv
- getLclEnv :: TcS TcLclEnv
- getTcEvBindsVar :: TcS EvBindsVar
- getTcLevel :: TcS TcLevel
- getTcEvTyCoVars :: EvBindsVar -> TcS TyCoVarSet
- getTcEvBindsMap :: EvBindsVar -> TcS EvBindMap
- setTcEvBindsMap :: EvBindsVar -> EvBindMap -> TcS ()
- tcLookupClass :: Name -> TcS Class
- tcLookupId :: Name -> TcS Id
- data InertSet = IS {
- inert_cans :: InertCans
- inert_fsks :: [(TcTyVar, TcType)]
- inert_flat_cache :: ExactFunEqMap (TcCoercion, TcType, CtFlavour)
- inert_solved_dicts :: DictMap CtEvidence
- data InertCans = IC {
- inert_eqs :: InertEqs
- inert_funeqs :: FunEqMap Ct
- inert_dicts :: DictMap Ct
- inert_insts :: [QCInst]
- inert_safehask :: DictMap Ct
- inert_irreds :: Cts
- inert_count :: Int
- updInertTcS :: (InertSet -> InertSet) -> TcS ()
- updInertCans :: (InertCans -> InertCans) -> TcS ()
- updInertDicts :: (DictMap Ct -> DictMap Ct) -> TcS ()
- updInertIrreds :: (Cts -> Cts) -> TcS ()
- getNoGivenEqs :: TcLevel -> [TcTyVar] -> TcS (Bool, Cts)
- setInertCans :: InertCans -> TcS ()
- getInertEqs :: TcS (DTyVarEnv EqualCtList)
- getInertCans :: TcS InertCans
- getInertGivens :: TcS [Ct]
- getInertInsols :: TcS Cts
- getTcSInerts :: TcS InertSet
- setTcSInerts :: InertSet -> TcS ()
- matchableGivens :: CtLoc -> PredType -> InertSet -> Cts
- prohibitedSuperClassSolve :: CtLoc -> CtLoc -> Bool
- mightMatchLater :: TcPredType -> CtLoc -> TcPredType -> CtLoc -> Bool
- getUnsolvedInerts :: TcS (Bag Implication, Cts, Cts, Cts)
- removeInertCts :: [Ct] -> InertCans -> InertCans
- getPendingGivenScs :: TcS [Ct]
- addInertCan :: Ct -> TcS ()
- insertFunEq :: FunEqMap a -> TyCon -> [Type] -> a -> FunEqMap a
- addInertForAll :: QCInst -> TcS ()
- emitWorkNC :: [CtEvidence] -> TcS ()
- emitWork :: [Ct] -> TcS ()
- isImprovable :: CtEvidence -> Bool
- kickOutAfterUnification :: TcTyVar -> TcS Int
- addInertSafehask :: InertCans -> Ct -> InertCans
- insertSafeOverlapFailureTcS :: InstanceWhat -> Ct -> TcS ()
- updInertSafehask :: (DictMap Ct -> DictMap Ct) -> TcS ()
- getSafeOverlapFailures :: TcS Cts
- type DictMap a = TcAppMap a
- emptyDictMap :: DictMap a
- lookupInertDict :: InertCans -> CtLoc -> Class -> [Type] -> Maybe CtEvidence
- findDictsByClass :: DictMap a -> Class -> Bag a
- addDict :: DictMap a -> Class -> [Type] -> a -> DictMap a
- addDictsByClass :: DictMap Ct -> Class -> Bag Ct -> DictMap Ct
- delDict :: DictMap a -> Class -> [Type] -> DictMap a
- foldDicts :: (a -> b -> b) -> DictMap a -> b -> b
- filterDicts :: (Ct -> Bool) -> DictMap Ct -> DictMap Ct
- findDict :: DictMap a -> CtLoc -> Class -> [Type] -> Maybe a
- type EqualCtList = [Ct]
- findTyEqs :: InertCans -> TyVar -> EqualCtList
- foldTyEqs :: (Ct -> b -> b) -> InertEqs -> b -> b
- isInInertEqs :: DTyVarEnv EqualCtList -> TcTyVar -> TcType -> Bool
- lookupInertTyVar :: InertEqs -> TcTyVar -> Maybe TcType
- addSolvedDict :: InstanceWhat -> CtEvidence -> Class -> [Type] -> TcS ()
- lookupSolvedDict :: InertSet -> CtLoc -> Class -> [Type] -> Maybe CtEvidence
- foldIrreds :: (Ct -> b -> b) -> Cts -> b -> b
- lookupFlatCache :: TyCon -> [Type] -> TcS (Maybe (TcCoercion, TcType, CtFlavour))
- extendFlatCache :: TyCon -> [Type] -> (TcCoercion, TcType, CtFlavour) -> TcS ()
- newFlattenSkolem :: CtFlavour -> CtLoc -> TyCon -> [TcType] -> TcS (CtEvidence, Coercion, TcTyVar)
- dischargeFunEq :: CtEvidence -> TcTyVar -> TcCoercion -> TcType -> TcS ()
- pprKicked :: Int -> SDoc
- updInertFunEqs :: (FunEqMap Ct -> FunEqMap Ct) -> TcS ()
- findFunEq :: FunEqMap a -> TyCon -> [Type] -> Maybe a
- findFunEqsByTyCon :: FunEqMap a -> TyCon -> [a]
- instDFunType :: DFunId -> [DFunInstType] -> TcS ([TcType], TcThetaType)
- newFlexiTcSTy :: Kind -> TcS TcType
- instFlexi :: [TKVar] -> TcS TCvSubst
- instFlexiX :: TCvSubst -> [TKVar] -> TcS TCvSubst
- cloneMetaTyVar :: TcTyVar -> TcS TcTyVar
- demoteUnfilledFmv :: TcTyVar -> TcS ()
- tcInstSkolTyVarsX :: TCvSubst -> [TyVar] -> TcS (TCvSubst, [TcTyVar])
- data TcLevel
- isFilledMetaTyVar_maybe :: TcTyVar -> TcS (Maybe Type)
- isFilledMetaTyVar :: TcTyVar -> TcS Bool
- zonkTyCoVarsAndFV :: TcTyCoVarSet -> TcS TcTyCoVarSet
- zonkTcType :: TcType -> TcS TcType
- zonkTcTypes :: [TcType] -> TcS [TcType]
- zonkTcTyVar :: TcTyVar -> TcS TcType
- zonkCo :: Coercion -> TcS Coercion
- zonkTyCoVarsAndFVList :: [TcTyCoVar] -> TcS [TcTyCoVar]
- zonkSimples :: Cts -> TcS Cts
- zonkWC :: WantedConstraints -> TcS WantedConstraints
- zonkTyCoVarKind :: TcTyCoVar -> TcS TcTyCoVar
- newTcRef :: a -> TcS (TcRef a)
- readTcRef :: TcRef a -> TcS a
- writeTcRef :: TcRef a -> a -> TcS ()
- updTcRef :: TcRef a -> (a -> a) -> TcS ()
- getDefaultInfo :: TcS ([Type], (Bool, Bool))
- getDynFlags :: HasDynFlags m => m DynFlags
- getGlobalRdrEnvTcS :: TcS GlobalRdrEnv
- matchFam :: TyCon -> [Type] -> TcS (Maybe (CoercionN, TcType))
- matchFamTcM :: TyCon -> [Type] -> TcM (Maybe (CoercionN, TcType))
- checkWellStagedDFun :: CtLoc -> InstanceWhat -> PredType -> TcS ()
- pprEq :: TcType -> TcType -> SDoc
Documentation
WL | |
|
isEmptyWorkList :: WorkList -> Bool Source #
workListSize :: WorkList -> Int Source #
workListWantedCount :: WorkList -> Int Source #
Instances
Monad TcS # | |
Functor TcS # | |
MonadFail TcS # | |
Applicative TcS # | |
MonadUnique TcS # | |
Defined in GHC.Tc.Solver.Monad getUniqueSupplyM :: TcS UniqSupply Source # getUniqueM :: TcS Unique Source # getUniquesM :: TcS [Unique] Source # | |
HasModule TcS # | |
HasDynFlags TcS # | |
Defined in GHC.Tc.Solver.Monad | |
MonadThings TcS # | |
runTcSDeriveds :: TcS a -> TcM a Source #
This variant of runTcS
will keep solving, even when only Deriveds
are left around. It also doesn't return any evidence, as callers won't
need it.
runTcSWithEvBinds :: EvBindsVar -> TcS a -> TcM a Source #
runTcSEqualities :: TcS a -> TcM a Source #
This can deal only with equality constraints.
nestImplicTcS :: EvBindsVar -> TcLevel -> TcS a -> TcS a Source #
setEvBindsTcS :: EvBindsVar -> TcS a -> TcS a Source #
emitImplicationTcS :: TcLevel -> SkolemInfo -> [TcTyVar] -> [EvVar] -> Cts -> TcS TcEvBinds Source #
emitTvImplicationTcS :: TcLevel -> SkolemInfo -> [TcTyVar] -> Cts -> TcS () Source #
runTcPluginTcS :: TcPluginM a -> TcS a Source #
addUsedGRE :: Bool -> GlobalRdrElt -> TcS () Source #
addUsedGREs :: [GlobalRdrElt] -> TcS () Source #
matchGlobalInst :: DynFlags -> Bool -> Class -> [Type] -> TcS ClsInstResult Source #
data ClsInstResult Source #
NoInstance | |
OneInst | |
| |
NotSure |
Instances
Outputable ClsInstResult # | |
Defined in GHC.Tc.Instance.Class |
QCI | |
|
traceFireTcS :: CtEvidence -> SDoc -> TcS () Source #
bumpStepCountTcS :: TcS () Source #
csTraceTcS :: SDoc -> TcS () Source #
wrapErrTcS :: TcM a -> TcS a Source #
wrapWarnTcS :: TcM a -> TcS a Source #
freshGoals :: [MaybeNew] -> [CtEvidence] Source #
newWantedEq :: CtLoc -> Role -> TcType -> TcType -> TcS (CtEvidence, Coercion) Source #
Make a new equality CtEvidence
newWantedEq_SI :: BlockSubstFlag -> ShadowInfo -> CtLoc -> Role -> TcType -> TcType -> TcS (CtEvidence, Coercion) Source #
emitNewWantedEq :: CtLoc -> Role -> TcType -> TcType -> TcS Coercion Source #
Emit a new Wanted equality into the work-list
newWanted_SI :: ShadowInfo -> CtLoc -> PredType -> TcS MaybeNew Source #
newWantedEvVar :: CtLoc -> TcPredType -> TcS MaybeNew Source #
newWantedNC :: CtLoc -> PredType -> TcS CtEvidence Source #
newWantedEvVarNC :: CtLoc -> TcPredType -> TcS CtEvidence Source #
newDerivedNC :: CtLoc -> TcPredType -> TcS CtEvidence Source #
newBoundEvVarId :: TcPredType -> EvTerm -> TcS EvVar Source #
Make a new Id
of the given type, bound (in the monad's EvBinds) to the
given term
setEvBindIfWanted :: CtEvidence -> EvTerm -> TcS () Source #
newGivenEvVar :: CtLoc -> (TcPredType, EvTerm) -> TcS CtEvidence Source #
newGivenEvVars :: CtLoc -> [(TcPredType, EvTerm)] -> TcS [CtEvidence] Source #
emitNewDeriveds :: CtLoc -> [TcPredType] -> TcS () Source #
Checks if the depth of the given location is too much. Fails if it's too big, with an appropriate error message.
setSolvedDicts :: DictMap CtEvidence -> TcS () Source #
getFamInstEnvs :: TcS (FamInstEnv, FamInstEnv) Source #
getTcLevel :: TcS TcLevel Source #
getTcEvBindsMap :: EvBindsVar -> TcS EvBindMap Source #
setTcEvBindsMap :: EvBindsVar -> EvBindMap -> TcS () Source #
IS | |
|
IC | |
|
setInertCans :: InertCans -> TcS () Source #
getInertGivens :: TcS [Ct] Source #
getInertInsols :: TcS Cts Source #
setTcSInerts :: InertSet -> TcS () 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
mightMatchLater :: TcPredType -> CtLoc -> TcPredType -> CtLoc -> Bool Source #
getUnsolvedInerts :: TcS (Bag Implication, Cts, Cts, Cts) Source #
removeInertCts :: [Ct] -> InertCans -> InertCans Source #
Remove inert constraints from the InertCans
, for use when a
typechecker plugin wishes to discard a given.
getPendingGivenScs :: TcS [Ct] Source #
addInertCan :: Ct -> TcS () Source #
insertFunEq :: FunEqMap a -> TyCon -> [Type] -> a -> FunEqMap a Source #
addInertForAll :: QCInst -> TcS () Source #
emitWorkNC :: [CtEvidence] -> TcS () Source #
isImprovable :: CtEvidence -> Bool Source #
insertSafeOverlapFailureTcS :: InstanceWhat -> Ct -> TcS () Source #
emptyDictMap :: DictMap a Source #
lookupInertDict :: InertCans -> CtLoc -> Class -> [Type] -> Maybe CtEvidence Source #
Look up a dictionary inert. NB: the returned CtEvidence
might not
match the input exactly. Note [Use loose types in inert set].
type EqualCtList = [Ct] Source #
isInInertEqs :: DTyVarEnv EqualCtList -> TcTyVar -> TcType -> Bool Source #
addSolvedDict :: InstanceWhat -> CtEvidence -> Class -> [Type] -> TcS () Source #
lookupSolvedDict :: InertSet -> CtLoc -> Class -> [Type] -> Maybe CtEvidence Source #
Look up a solved inert. NB: the returned CtEvidence
might not
match the input exactly. See Note [Use loose types in inert set].
foldIrreds :: (Ct -> b -> b) -> Cts -> b -> b Source #
lookupFlatCache :: TyCon -> [Type] -> TcS (Maybe (TcCoercion, TcType, CtFlavour)) Source #
extendFlatCache :: TyCon -> [Type] -> (TcCoercion, TcType, CtFlavour) -> TcS () Source #
newFlattenSkolem :: CtFlavour -> CtLoc -> TyCon -> [TcType] -> TcS (CtEvidence, Coercion, TcTyVar) Source #
dischargeFunEq :: CtEvidence -> TcTyVar -> TcCoercion -> TcType -> TcS () Source #
findFunEqsByTyCon :: FunEqMap a -> TyCon -> [a] Source #
instDFunType :: DFunId -> [DFunInstType] -> TcS ([TcType], TcThetaType) Source #
demoteUnfilledFmv :: TcTyVar -> TcS () Source #
writeTcRef :: TcRef a -> a -> TcS () Source #
getDynFlags :: HasDynFlags m => m DynFlags Source #
checkWellStagedDFun :: CtLoc -> InstanceWhat -> PredType -> TcS () Source #