Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- findValidHoleFits :: TidyEnv -> [Implication] -> [Ct] -> Ct -> TcM (TidyEnv, SDoc)
- tcFilterHoleFits :: Maybe Int -> [Implication] -> [Ct] -> (TcType, [TcTyVar]) -> [HoleFitCandidate] -> TcM (Bool, [HoleFit])
- data HoleFit = HoleFit {}
- data HoleFitCandidate
- tcCheckHoleFit :: Cts -> [Implication] -> TcSigmaType -> TcSigmaType -> TcM (Bool, HsWrapper)
- tcSubsumes :: TcSigmaType -> TcSigmaType -> TcM Bool
- withoutUnification :: FV -> TcM a -> TcM a
Documentation
:: 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.
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 _ _`).
data HoleFitCandidate Source #
HoleFitCandidates are passed to the filter and checked whether they can be made to fit.
Instances
Eq HoleFitCandidate # | |
Defined in TcHoleErrors (==) :: HoleFitCandidate -> HoleFitCandidate -> Bool # (/=) :: HoleFitCandidate -> HoleFitCandidate -> Bool # | |
Outputable HoleFitCandidate # | |
Defined in TcHoleErrors | |
HasOccName HoleFitCandidate # | |
Defined in TcHoleErrors occName :: HoleFitCandidate -> OccName Source # |
:: 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.