Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Monadic definitions for the constraint solver
Synopsis
- data TcS a
- runTcS :: TcS a -> TcM (a, EvBindMap)
- runTcSEarlyAbort :: TcS a -> TcM a
- runTcSWithEvBinds :: EvBindsVar -> TcS a -> TcM a
- runTcSInerts :: InertSet -> TcS a -> TcM (a, InertSet)
- failTcS :: TcRnMessage -> TcS a
- warnTcS :: TcRnMessage -> TcS ()
- addErrTcS :: TcRnMessage -> TcS ()
- wrapTcS :: TcM a -> TcS a
- ctLocWarnTcS :: CtLoc -> TcRnMessage -> 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 -> SkolemInfoAnon -> [TcTyVar] -> [EvVar] -> Cts -> TcS TcEvBinds
- emitTvImplicationTcS :: TcLevel -> SkolemInfoAnon -> [TcTyVar] -> Cts -> TcS ()
- selectNextWorkItem :: TcS (Maybe Ct)
- getWorkList :: TcS WorkList
- updWorkListTcS :: (WorkList -> WorkList) -> TcS ()
- pushLevelNoWorkList :: SDoc -> TcS a -> TcS (TcLevel, a)
- runTcPluginTcS :: TcPluginM a -> TcS a
- recordUsedGREs :: Bag GlobalRdrElt -> 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
- resetUnificationFlag :: TcS Bool
- setUnificationFlag :: TcLevel -> TcS ()
- data MaybeNew
- freshGoals :: [MaybeNew] -> [CtEvidence]
- isFresh :: MaybeNew -> Bool
- getEvExpr :: MaybeNew -> EvExpr
- newTcEvBinds :: TcS EvBindsVar
- newNoTcEvBinds :: TcS EvBindsVar
- newWantedEq :: CtLoc -> RewriterSet -> Role -> TcType -> TcType -> TcS (CtEvidence, Coercion)
- emitNewWantedEq :: CtLoc -> RewriterSet -> Role -> TcType -> TcType -> TcS Coercion
- newWanted :: CtLoc -> RewriterSet -> PredType -> TcS MaybeNew
- newWantedNC :: CtLoc -> RewriterSet -> PredType -> TcS CtEvidence
- newWantedEvVarNC :: CtLoc -> RewriterSet -> TcPredType -> TcS CtEvidence
- newBoundEvVarId :: TcPredType -> EvTerm -> TcS EvVar
- unifyTyVar :: TcTyVar -> TcType -> TcS ()
- reportUnifications :: TcS a -> TcS (Int, a)
- touchabilityTest :: CtFlavour -> TcTyVar -> TcType -> TcS (TouchabilityTestResult, TcType)
- data TouchabilityTestResult
- setEvBind :: EvBind -> TcS ()
- setWantedEq :: HasDebugCallStack => 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]
- 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
- setLclEnv :: TcLclEnv -> TcS a -> TcS a
- 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
- updInertTcS :: (InertSet -> InertSet) -> TcS ()
- updInertCans :: (InertCans -> InertCans) -> TcS ()
- updInertDicts :: (DictMap Ct -> DictMap Ct) -> TcS ()
- updInertIrreds :: (Cts -> Cts) -> TcS ()
- getHasGivenEqs :: TcLevel -> TcS (HasGivenEqs, Cts)
- setInertCans :: InertCans -> TcS ()
- getInertEqs :: TcS InertEqs
- getInertCans :: TcS InertCans
- getInertGivens :: TcS [Ct]
- getInertInsols :: TcS Cts
- getInnermostGivenEqLevel :: TcS TcLevel
- getTcSInerts :: TcS InertSet
- setTcSInerts :: InertSet -> TcS ()
- getUnsolvedInerts :: TcS (Bag Implication, 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 ()
- lookupInertDict :: InertCans -> CtLoc -> Class -> [Type] -> Maybe Ct
- kickOutAfterUnification :: TcTyVar -> TcS Int
- addInertSafehask :: InertCans -> Ct -> InertCans
- insertSafeOverlapFailureTcS :: InstanceWhat -> Ct -> TcS ()
- updInertSafehask :: (DictMap Ct -> DictMap Ct) -> TcS ()
- getSafeOverlapFailures :: TcS Cts
- addSolvedDict :: InstanceWhat -> CtEvidence -> Class -> [Type] -> TcS ()
- lookupSolvedDict :: InertSet -> CtLoc -> Class -> [Type] -> Maybe CtEvidence
- foldIrreds :: (Ct -> b -> b) -> Cts -> b -> b
- lookupFamAppInert :: (CtFlavourRole -> Bool) -> TyCon -> [Type] -> TcS (Maybe (Reduction, CtFlavourRole))
- lookupFamAppCache :: TyCon -> [Type] -> TcS (Maybe Reduction)
- extendFamAppCache :: TyCon -> [Type] -> Reduction -> TcS ()
- pprKicked :: Int -> SDoc
- instDFunType :: DFunId -> [DFunInstType] -> TcS ([TcType], TcThetaType)
- newFlexiTcSTy :: Kind -> TcS TcType
- instFlexiX :: Subst -> [TKVar] -> TcS Subst
- cloneMetaTyVar :: TcTyVar -> TcS TcTyVar
- tcInstSkolTyVarsX :: SkolemInfo -> Subst -> [TyVar] -> TcS (Subst, [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 ReductionN)
- matchFamTcM :: TyCon -> [Type] -> TcM (Maybe ReductionN)
- checkWellStagedDFun :: CtLoc -> InstanceWhat -> PredType -> TcS ()
- pprEq :: TcType -> TcType -> SDoc
- breakTyEqCycle_maybe :: CtEvidence -> CheckTyEqResult -> CanEqLHS -> TcType -> TcS (Maybe ReductionN)
- rewriterView :: TcType -> Maybe TcType
Documentation
Instances
MonadFail TcS Source # | |
MonadFix TcS Source # | |
MonadIO TcS Source # | |
Applicative TcS Source # | |
Functor TcS Source # | |
Monad TcS Source # | |
HasDynFlags TcS Source # | |
Defined in GHC.Tc.Solver.Monad | |
MonadThings TcS Source # | |
MonadUnique TcS Source # | |
Defined in GHC.Tc.Solver.Monad 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 immediately 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 #
ctLocWarnTcS :: CtLoc -> 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 #
recordUsedGREs :: Bag GlobalRdrElt -> TcS () Source #
matchGlobalInst :: DynFlags -> Bool -> Class -> [Type] -> TcS ClsInstResult Source #
data ClsInstResult Source #
NoInstance | |
OneInst | |
| |
NotSure |
Instances
Outputable ClsInstResult Source # | |
Defined in GHC.Tc.Instance.Class ppr :: ClsInstResult -> SDoc Source # |
QCI | |
|
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 #
Instances
Outputable TouchabilityTestResult Source # | |
Defined in GHC.Tc.Solver.Monad 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 -> Subst -> [TyVar] -> TcS (Subst, [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.