ghc-9.15: The GHC API
Safe HaskellNone
LanguageGHC2021

GHC.Tc.Solver.Monad

Description

Monadic definitions for the constraint solver

Synopsis

Documentation

newtype TcS a Source #

Constructors

TcS 

Fields

Instances

Instances details
HasDynFlags TcS Source # 
Instance details

Defined in GHC.Tc.Solver.Monad

MonadThings TcS Source # 
Instance details

Defined in GHC.Tc.Solver.Monad

MonadUnique TcS Source # 
Instance details

Defined in GHC.Tc.Solver.Monad

HasModule TcS Source # 
Instance details

Defined in GHC.Tc.Solver.Monad

Applicative TcS Source # 
Instance details

Defined in GHC.Tc.Solver.Monad

Methods

pure :: a -> TcS a Source #

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

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

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

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

Functor TcS Source # 
Instance details

Defined in GHC.Tc.Solver.Monad

Methods

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

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

Monad TcS Source # 
Instance details

Defined in GHC.Tc.Solver.Monad

Methods

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

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

return :: a -> TcS a Source #

MonadFail TcS Source # 
Instance details

Defined in GHC.Tc.Solver.Monad

Methods

fail :: HasCallStack => String -> TcS a Source #

MonadFix TcS Source # 
Instance details

Defined in GHC.Tc.Solver.Monad

Methods

mfix :: (a -> TcS a) -> TcS a Source #

MonadIO TcS Source # 
Instance details

Defined in GHC.Tc.Solver.Monad

Methods

liftIO :: IO a -> TcS a Source #

data TcSEnv Source #

Constructors

TcSEnv 

Fields

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.

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.

wrapTcS :: TcM a -> TcS a Source #

ctLocWarnTcS :: CtLoc -> TcRnMessage -> TcS () Source #

Emit a warning within the TcS monad at the location given by the CtLoc.

runTcSEqualities :: TcS a -> TcM a Source #

This can deal only with equality constraints.

nestTcS :: TcS a -> TcS a Source #

data QCInst Source #

A quantified constraint, also called a "local instance" (a simplified version of ClsInst).

See Note [Quantified constraints] in GHC.Tc.Solver.Solve

Constructors

QCI

A quantified constraint, of type forall tvs. context => ty

Fields

Instances

Instances details
Outputable QCInst Source # 
Instance details

Defined in GHC.Tc.Types.Constraint

Methods

ppr :: QCInst -> SDoc Source #

data TcSMode Source #

The mode for the constraint solving monad.

See Note [TcSMode], where each constructor is documented

Constructors

TcSVanilla

Normal constraint solving

TcSPMCheck

Used when doing patterm match overlap checks

TcSEarlyAbort

Abort early on insoluble constraints

TcSShortCut

Fully solve all constraints, without using local Givens

Instances

Instances details
Outputable TcSMode Source # 
Instance details

Defined in GHC.Tc.Solver.Monad

Methods

ppr :: TcSMode -> SDoc Source #

Eq TcSMode Source # 
Instance details

Defined in GHC.Tc.Solver.Monad

data StopOrContinue a Source #

Instances

Instances details
Functor StopOrContinue Source # 
Instance details

Defined in GHC.Tc.Solver.Monad

Methods

fmap :: (a -> b) -> StopOrContinue a -> StopOrContinue b Source #

(<$) :: a -> StopOrContinue b -> StopOrContinue a Source #

Outputable a => Outputable (StopOrContinue a) Source # 
Instance details

Defined in GHC.Tc.Solver.Monad

Methods

ppr :: StopOrContinue a -> SDoc Source #

newtype SolverStage a Source #

Constructors

Stage 

Instances

Instances details
Applicative SolverStage Source # 
Instance details

Defined in GHC.Tc.Solver.Monad

Functor SolverStage Source # 
Instance details

Defined in GHC.Tc.Solver.Monad

Methods

fmap :: (a -> b) -> SolverStage a -> SolverStage b Source #

(<$) :: a -> SolverStage b -> SolverStage a Source #

Monad SolverStage Source # 
Instance details

Defined in GHC.Tc.Solver.Monad

data CanonicalEvidence Source #

CanonicalEvidence says whether a piece of evidence has a singleton type; For example, given (d1 :: C Int), will any other (d2 :: C Int) do equally well? See Note [Coherence and specialisation: overview] above, and Note [Desugaring non-canonical evidence] in GHC.HsToCore.Binds

Instances

Instances details
Outputable CanonicalEvidence Source # 
Instance details

Defined in GHC.Core.InstEnv

newWantedEq :: CtLoc -> RewriterSet -> Role -> TcType -> TcType -> TcS (WantedCtEvidence, 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 WantedCtEvidence 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 WantedCtEvidence 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

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

Good for both equalities and non-equalities

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.

getInertInsols :: TcS Cts Source #

Retrieves all insoluble constraints from the inert set, specifically including Given constraints.

This consists of:

  • insoluble equalities, such as Int ~# Bool;
  • constraints that are top-level custom type errors, of the form TypeError msg, but not constraints such as Eq (TypeError msg) in which the type error is nested;
  • unsatisfiable constraints, of the form Unsatisfiable msg.

The inclusion of Givens is important for pattern match warnings, as we want to consider a pattern match that introduces insoluble Givens to be redundant (see Note [Pattern match warnings with insoluble Givens] in GHC.Tc.Solver).

removeInertCts :: [Ct] -> InertCans -> InertCans Source #

Remove inert constraints from the InertCans, for use when a typechecker plugin wishes to discard a given.

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

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

Look up a dictionary inert.

lookupSolvedDict :: InertSet -> Class -> [Type] -> Maybe CtEvidence Source #

Look up a solved inert.

foldIrreds :: (IrredCt -> b -> b) -> InertIrreds -> b -> b Source #

lookupFamAppInert :: (CtFlavourRole -> Bool) -> TyCon -> [Type] -> TcS (Maybe EqCt) Source #

Looks up a family application in the inerts.

data TcLevel Source #

Instances

Instances details
Outputable TcLevel Source # 
Instance details

Defined in GHC.Tc.Utils.TcType

Methods

ppr :: TcLevel -> SDoc Source #

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

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

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