GHC.Tc.Solver.Monad
Monadic definitions for the constraint solver
Documentation
Instances
MonadFail TcS Source # | |
MonadIO TcS Source # | |
Applicative TcS Source # | |
Functor TcS Source # | |
Monad TcS Source # | |
HasDynFlags TcS Source # | |
Defined in GHC.Tc.Solver.Monad Methods | |
MonadThings TcS Source # | |
MonadUnique TcS Source # | |
Defined in GHC.Tc.Solver.Monad Methods getUniqueSupplyM :: TcS UniqSupply Source # getUniqueM :: TcS Unique Source # getUniquesM :: TcS [Unique] Source # | |
HasModule TcS Source # | |
runTcSEarlyAbort :: TcS a -> TcM a Source #
This variant of runTcS
will immediatley fail upon encountering an
insoluble ct. See Note [Speeding up valid hole-fits]. Its one usage
site does not need the ev_binds, so we do not return them.
runTcSWithEvBinds :: EvBindsVar -> TcS a -> TcM a Source #
failTcS :: TcRnMessage -> TcS a Source #
warnTcS :: TcRnMessage -> TcS () Source #
addErrTcS :: TcRnMessage -> TcS () 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 -> SkolemInfoAnon -> [TcTyVar] -> [EvVar] -> Cts -> TcS TcEvBinds Source #
emitTvImplicationTcS :: TcLevel -> SkolemInfoAnon -> [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 #
Constructors
NoInstance | |
OneInst | |
Fields
| |
NotSure |
Instances
Outputable ClsInstResult Source # | |
Defined in GHC.Tc.Instance.Class Methods ppr :: ClsInstResult -> SDoc Source # |
Constructors
QCI | |
Fields
|
Instances
traceFireTcS :: CtEvidence -> SDoc -> TcS () Source #
bumpStepCountTcS :: TcS () Source #
csTraceTcS :: SDoc -> TcS () Source #
wrapErrTcS :: TcM a -> TcS a Source #
wrapWarnTcS :: TcM a -> TcS a Source #
setUnificationFlag :: TcLevel -> TcS () Source #
freshGoals :: [MaybeNew] -> [CtEvidence] Source #
newWantedEq :: CtLoc -> RewriterSet -> Role -> TcType -> TcType -> TcS (CtEvidence, Coercion) Source #
Create a new Wanted constraint holding a coercion hole
for an equality between the two types at the given Role
.
emitNewWantedEq :: CtLoc -> RewriterSet -> Role -> TcType -> TcType -> TcS Coercion Source #
Emit a new Wanted equality into the work-list
newWanted :: CtLoc -> RewriterSet -> PredType -> TcS MaybeNew Source #
Create a new Wanted constraint, potentially looking up non-equality constraints in the cache instead of creating a new one from scratch.
Deals with both equality and non-equality constraints.
newWantedNC :: CtLoc -> RewriterSet -> PredType -> TcS CtEvidence Source #
Create a new Wanted constraint.
Deals with both equality and non-equality constraints.
Does not attempt to re-use non-equality constraints that already exist in the inert set.
newWantedEvVarNC :: CtLoc -> RewriterSet -> TcPredType -> TcS CtEvidence Source #
Create a new Wanted constraint holding an evidence variable.
Don't use this for equality constraints: use newWantedEq
instead.
newBoundEvVarId :: TcPredType -> EvTerm -> TcS EvVar Source #
Make a new Id
of the given type, bound (in the monad's EvBinds) to the
given term
touchabilityTest :: CtFlavour -> TcTyVar -> TcType -> TcS (TouchabilityTestResult, TcType) Source #
This is the key test for untouchability: See Note [Unification preconditions] in GHC.Tc.Utils.Unify and Note [Solve by unification] in GHC.Tc.Solver.Interact
Returns a new rhs type, as this function can turn make some metavariables concrete.
data TouchabilityTestResult Source #
Constructors
TouchableSameLevel | |
TouchableOuterLevel [TcTyVar] TcLevel | |
Untouchable |
Instances
Outputable TouchabilityTestResult Source # | |
Defined in GHC.Tc.Solver.Monad Methods ppr :: TouchabilityTestResult -> SDoc Source # |
setWantedEq :: HasDebugCallStack => TcEvDest -> Coercion -> TcS () Source #
Equalities only
setEvBindIfWanted :: CtEvidence -> EvTerm -> TcS () Source #
newGivenEvVar :: CtLoc -> (TcPredType, EvTerm) -> TcS CtEvidence Source #
newGivenEvVars :: CtLoc -> [(TcPredType, EvTerm)] -> TcS [CtEvidence] 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 #
getHasGivenEqs :: TcLevel -> TcS (HasGivenEqs, Cts) Source #
setInertCans :: InertCans -> TcS () Source #
getInertGivens :: TcS [Ct] Source #
getInertInsols :: TcS Cts Source #
setTcSInerts :: InertSet -> TcS () Source #
getUnsolvedInerts :: TcS (Bag Implication, 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 #
addInertForAll :: QCInst -> TcS () Source #
emitWorkNC :: [CtEvidence] -> TcS () Source #
lookupInertDict :: InertCans -> CtLoc -> Class -> [Type] -> Maybe Ct Source #
Look up a dictionary inert.
insertSafeOverlapFailureTcS :: InstanceWhat -> Ct -> TcS () Source #
addSolvedDict :: InstanceWhat -> CtEvidence -> Class -> [Type] -> TcS () Source #
lookupSolvedDict :: InertSet -> CtLoc -> Class -> [Type] -> Maybe CtEvidence Source #
Look up a solved inert.
foldIrreds :: (Ct -> b -> b) -> Cts -> b -> b Source #
lookupFamAppInert :: (CtFlavourRole -> Bool) -> TyCon -> [Type] -> TcS (Maybe (Reduction, CtFlavourRole)) Source #
Looks up a family application in the inerts.
instDFunType :: DFunId -> [DFunInstType] -> TcS ([TcType], TcThetaType) Source #
tcInstSkolTyVarsX :: SkolemInfo -> TCvSubst -> [TyVar] -> TcS (TCvSubst, [TcTyVar]) Source #
writeTcRef :: TcRef a -> a -> TcS () Source #
getDynFlags :: HasDynFlags m => m DynFlags Source #
matchFamTcM :: TyCon -> [Type] -> TcM (Maybe ReductionN) Source #
checkWellStagedDFun :: CtLoc -> InstanceWhat -> PredType -> TcS () Source #
breakTyEqCycle_maybe :: CtEvidence -> CheckTyEqResult -> CanEqLHS -> TcType -> TcS (Maybe ReductionN) Source #
Conditionally replace all type family applications in the RHS with fresh variables, emitting givens that relate the type family application to the variable. See Note [Type equality cycles] in GHC.Tc.Solver.Canonical. This only works under conditions as described in the Note; otherwise, returns Nothing.