ghc-lib-0.20201101: The GHC API, decoupled from GHC versions
Safe HaskellNone
LanguageHaskell2010

GHC.Tc.Solver.Monad

Description

Type definitions for the constraint solver

Synopsis

Documentation

data WorkList Source #

Constructors

WL 

Fields

Instances

Instances details
Outputable WorkList Source # 
Instance details

Defined in GHC.Tc.Solver.Monad

Methods

ppr :: WorkList -> SDoc

pushLevelNoWorkList :: SDoc -> TcS a -> TcS (TcLevel, a) Source #

data TcS a Source #

Instances

Instances details
Monad TcS Source # 
Instance details

Defined in GHC.Tc.Solver.Monad

Methods

(>>=) :: TcS a -> (a -> TcS b) -> TcS b #

(>>) :: TcS a -> TcS b -> TcS b #

return :: a -> TcS a #

Functor TcS Source # 
Instance details

Defined in GHC.Tc.Solver.Monad

Methods

fmap :: (a -> b) -> TcS a -> TcS b #

(<$) :: a -> TcS b -> TcS a #

MonadFail TcS Source # 
Instance details

Defined in GHC.Tc.Solver.Monad

Methods

fail :: String -> TcS a #

Applicative TcS Source # 
Instance details

Defined in GHC.Tc.Solver.Monad

Methods

pure :: a -> TcS a #

(<*>) :: TcS (a -> b) -> TcS a -> TcS b #

liftA2 :: (a -> b -> c) -> TcS a -> TcS b -> TcS c #

(*>) :: TcS a -> TcS b -> TcS b #

(<*) :: TcS a -> TcS b -> TcS a #

MonadUnique TcS Source # 
Instance details

Defined in GHC.Tc.Solver.Monad

MonadThings TcS Source # 
Instance details

Defined in GHC.Tc.Solver.Monad

HasDynFlags TcS Source # 
Instance details

Defined in GHC.Tc.Solver.Monad

HasModule TcS Source # 
Instance details

Defined in GHC.Tc.Solver.Monad

Methods

getModule :: TcS Module

runTcS :: TcS a -> TcM (a, EvBindMap) Source #

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 Source #

Arguments

:: EvBindsVar 
-> Bool

Unflatten types afterwards? Don't if you want to reuse the InertSet.

-> TcS a 
-> TcM a 

runTcSInerts :: InertSet -> TcS a -> TcM (a, InertSet) Source #

A variant of runTcS that takes and returns an InertSet for later resumption of the TcS session. Crucially, it doesn't unflattenGivens when done.

failTcS :: SDoc -> TcS a Source #

warnTcS :: WarningFlag -> SDoc -> TcS () Source #

addErrTcS :: SDoc -> TcS () Source #

runTcSEqualities :: TcS a -> TcM a Source #

This can deal only with equality constraints.

nestTcS :: TcS a -> TcS a Source #

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 #

addUsedGRE :: Bool -> GlobalRdrElt -> TcS () Source #

addUsedGREs :: [GlobalRdrElt] -> TcS () Source #

data ClsInstResult Source #

Constructors

NoInstance 
OneInst 

Fields

NotSure 

Instances

Instances details
Outputable ClsInstResult Source # 
Instance details

Defined in GHC.Tc.Instance.Class

Methods

ppr :: ClsInstResult -> SDoc

data QCInst #

Constructors

QCI 

Fields

Instances

Instances details
Outputable QCInst 
Instance details

Defined in GHC.Tc.Types.Constraint

Methods

ppr :: QCInst -> SDoc

panicTcS :: SDoc -> TcS a Source #

traceTcS :: String -> SDoc -> TcS () Source #

traceFireTcS :: CtEvidence -> SDoc -> TcS () Source #

csTraceTcS :: SDoc -> TcS () Source #

wrapErrTcS :: TcM a -> TcS a Source #

wrapWarnTcS :: TcM a -> TcS a Source #

data MaybeNew Source #

Constructors

Fresh CtEvidence 
Cached EvExpr 

freshGoals :: [MaybeNew] -> [CtEvidence] Source #

getEvExpr :: MaybeNew -> EvExpr Source #

newTcEvBinds :: TcS EvBindsVar Source #

newNoTcEvBinds :: TcS EvBindsVar 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

setEvBind :: EvBind -> TcS () Source #

setWantedEq :: TcEvDest -> Coercion -> TcS () Source #

Equalities only

setWantedEvTerm :: TcEvDest -> EvTerm -> TcS () Source #

Good for both equalities and non-equalities

setEvBindIfWanted :: CtEvidence -> EvTerm -> TcS () Source #

newEvVar :: TcPredType -> TcS EvVar Source #

newGivenEvVar :: CtLoc -> (TcPredType, EvTerm) -> TcS CtEvidence Source #

newGivenEvVars :: CtLoc -> [(TcPredType, EvTerm)] -> TcS [CtEvidence] Source #

emitNewDeriveds :: CtLoc -> [TcPredType] -> TcS () Source #

emitNewDerivedEq :: CtLoc -> Role -> TcType -> TcType -> TcS () Source #

checkReductionDepth Source #

Arguments

:: CtLoc 
-> TcType

type being reduced

-> TcS () 

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 #

getInstEnvs :: TcS InstEnvs Source #

getFamInstEnvs :: TcS (FamInstEnv, FamInstEnv) Source #

getGblEnv :: TcS TcGblEnv Source #

getLclEnv :: TcS TcLclEnv Source #

getTcEvBindsVar :: TcS EvBindsVar Source #

getTcEvTyCoVars :: EvBindsVar -> TcS TyCoVarSet Source #

getTcEvBindsMap :: EvBindsVar -> TcS EvBindMap Source #

setTcEvBindsMap :: EvBindsVar -> EvBindMap -> TcS () Source #

data InertSet Source #

Constructors

IS 

Fields

Instances

Instances details
Outputable InertSet Source # 
Instance details

Defined in GHC.Tc.Solver.Monad

Methods

ppr :: InertSet -> SDoc

data InertCans Source #

Constructors

IC 

Fields

Instances

Instances details
Outputable InertCans Source # 
Instance details

Defined in GHC.Tc.Solver.Monad

Methods

ppr :: InertCans -> SDoc

updInertDicts :: (DictMap Ct -> DictMap Ct) -> TcS () Source #

updInertIrreds :: (Cts -> Cts) -> 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

prohibitedSuperClassSolve :: CtLoc -> CtLoc -> Bool Source #

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.

addInertCan :: Ct -> TcS () Source #

insertFunEq :: FunEqMap a -> TyCon -> [Type] -> a -> FunEqMap a Source #

emitWorkNC :: [CtEvidence] -> TcS () Source #

emitWork :: [Ct] -> TcS () Source #

isImprovable :: CtEvidence -> Bool Source #

type DictMap a = TcAppMap a Source #

lookupInertDict :: InertCans -> CtLoc -> Class -> [Type] -> Maybe CtEvidence Source #

Look up a dictionary inert.

addDict :: DictMap a -> Class -> [Type] -> a -> DictMap a Source #

addDictsByClass :: DictMap Ct -> Class -> Bag Ct -> DictMap Ct Source #

foldDicts :: (a -> b -> b) -> DictMap a -> b -> b Source #

filterDicts :: (Ct -> Bool) -> DictMap Ct -> DictMap Ct Source #

findDict :: DictMap a -> CtLoc -> Class -> [Type] -> Maybe a Source #

type EqualCtList = [Ct] Source #

foldTyEqs :: (Ct -> b -> b) -> InertEqs -> b -> b 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 #

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 #

pprKicked :: Int -> SDoc Source #

updInertFunEqs :: (FunEqMap Ct -> FunEqMap Ct) -> TcS () Source #

findFunEq :: FunEqMap a -> TyCon -> [Type] -> Maybe a Source #

findFunEqsByTyCon :: FunEqMap a -> TyCon -> [a] Source #

instDFunType :: DFunId -> [DFunInstType] -> TcS ([TcType], TcThetaType) Source #

instFlexi :: [TKVar] -> TcS TCvSubst Source #

data TcLevel #

Instances

Instances details
Eq TcLevel 
Instance details

Defined in GHC.Tc.Utils.TcType

Methods

(==) :: TcLevel -> TcLevel -> Bool #

(/=) :: TcLevel -> TcLevel -> Bool #

Ord TcLevel 
Instance details

Defined in GHC.Tc.Utils.TcType

Outputable TcLevel 
Instance details

Defined in GHC.Tc.Utils.TcType

Methods

ppr :: TcLevel -> SDoc

zonkTyCoVarsAndFV :: TcTyCoVarSet -> TcS TcTyCoVarSet Source #

zonkTyCoVarsAndFVList :: [TcTyCoVar] -> TcS [TcTyCoVar] Source #

zonkSimples :: Cts -> TcS Cts Source #

zonkWC :: WantedConstraints -> TcS WantedConstraints Source #

zonkTyCoVarKind :: TcTyCoVar -> TcS TcTyCoVar Source #

newTcRef :: a -> TcS (TcRef a) Source #

readTcRef :: TcRef a -> TcS a Source #

writeTcRef :: TcRef a -> a -> TcS () Source #

updTcRef :: TcRef a -> (a -> a) -> TcS () Source #

getDynFlags :: HasDynFlags m => m DynFlags #

getGlobalRdrEnvTcS :: TcS GlobalRdrEnv Source #

pprEq :: TcType -> TcType -> SDoc Source #