ghc-lib-0.20190402: The GHC API, decoupled from GHC versions

Safe HaskellNone
LanguageHaskell2010

TcHoleErrors

Synopsis

Documentation

findValidHoleFits Source #

Arguments

:: TidyEnv

The tidy_env for zonking

-> [Implication]

Enclosing implications for givens

-> [Ct]

The unsolved simple constraints in the implication for the hole.

-> Ct

The hole constraint itself

-> TcM (TidyEnv, SDoc) 

tcFilterHoleFits Source #

Arguments

:: Maybe Int

How many we should output, if limited

-> [Implication]

Enclosing implications for givens

-> [Ct]

Any relevant unsolved simple constraints

-> (TcType, [TcTyVar])

The type to check for fits and a list of refinement variables (free type variables in the type) for emulating additional holes.

-> [HoleFitCandidate]

The candidates to check whether fit.

-> TcM (Bool, [HoleFit])

We return whether or not we stopped due to hitting the limit and the fits we found.

tcFilterHoleFits filters the candidates by whether, given the implications and the relevant constraints, they can be made to match the type by running the type checker. Stops after finding limit matches.

data HoleFit Source #

HoleFit is the type we use for valid hole fits. It contains the element that was checked, the Id of that element as found by tcLookup, and the refinement level of the fit, which is the number of extra argument holes that this fit uses (e.g. if hfRefLvl is 2, the fit is for `Id _ _`).

Instances
Eq HoleFit Source # 
Instance details

Defined in TcHoleErrors

Methods

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

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

Ord HoleFit Source # 
Instance details

Defined in TcHoleErrors

Outputable HoleFit Source # 
Instance details

Defined in TcHoleErrors

Methods

ppr :: HoleFit -> SDoc #

pprPrec :: Rational -> HoleFit -> SDoc #

data HoleFitCandidate Source #

HoleFitCandidates are passed to the filter and checked whether they can be made to fit.

tcCheckHoleFit Source #

Arguments

:: Cts

Any relevant Cts to the hole.

-> [Implication]

The nested implications of the hole with the innermost implication first.

-> TcSigmaType

The type of the hole.

-> TcSigmaType

The type to check whether fits.

-> TcM (Bool, HsWrapper)

Whether it was a match, and the wrapper from hole_ty to ty.

A tcSubsumes which takes into account relevant constraints, to fix trac #14273. This makes sure that when checking whether a type fits the hole, the type has to be subsumed by type of the hole as well as fulfill all constraints on the type of the hole. Note: The simplifier may perform unification, so make sure to restore any free type variables to avoid side-effects.

tcSubsumes :: TcSigmaType -> TcSigmaType -> TcM Bool Source #

Reports whether first type (ty_a) subsumes the second type (ty_b), discarding any errors. Subsumption here means that the ty_b can fit into the ty_a, i.e. `tcSubsumes a b == True` if b is a subtype of a.

withoutUnification :: FV -> TcM a -> TcM a Source #

Takes a list of free variables and restores any Flexi type variables in free_vars after the action is run.