Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- findValidHoleFits :: TidyEnv -> [Implication] -> [Ct] -> Hole -> TcM (TidyEnv, SDoc)
- tcCheckHoleFit :: TypedHole -> TcSigmaType -> TcSigmaType -> TcM (Bool, HsWrapper)
- withoutUnification :: FV -> TcM a -> TcM a
- tcSubsumes :: TcSigmaType -> TcSigmaType -> TcM Bool
- isFlexiTyVar :: TcTyVar -> TcM Bool
- tcFilterHoleFits :: Maybe Int -> TypedHole -> (TcType, [TcTyVar]) -> [HoleFitCandidate] -> TcM (Bool, [HoleFit])
- getLocalBindings :: TidyEnv -> CtLoc -> TcM [Id]
- pprHoleFit :: HoleFitDispConfig -> HoleFit -> SDoc
- addHoleFitDocs :: [HoleFit] -> TcM [HoleFit]
- getHoleFitSortingAlg :: TcM HoleFitSortingAlg
- getHoleFitDispConfig :: TcM HoleFitDispConfig
- data HoleFitDispConfig = HFDC {
- showWrap :: Bool
- showWrapVars :: Bool
- showType :: Bool
- showProv :: Bool
- showMatches :: Bool
- data HoleFitSortingAlg
- relevantCts :: Type -> [Ct] -> [Ct]
- zonkSubs :: TidyEnv -> [HoleFit] -> TcM (TidyEnv, [HoleFit])
- sortHoleFitsByGraph :: [HoleFit] -> TcM [HoleFit]
- sortHoleFitsBySize :: [HoleFit] -> TcM [HoleFit]
- data HoleFitPlugin = HoleFitPlugin {}
- data HoleFitPluginR = forall s.HoleFitPluginR {
- hfPluginInit :: TcM (TcRef s)
- hfPluginRun :: TcRef s -> HoleFitPlugin
- hfPluginStop :: TcRef s -> TcM ()
Documentation
:: TypedHole | The hole to check against |
-> TcSigmaType | The type to check against (possibly modified, e.g. refined) |
-> 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.
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.
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.
:: Maybe Int | How many we should output, if limited |
-> TypedHole | The hole to filter against |
-> (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.
pprHoleFit :: HoleFitDispConfig -> HoleFit -> SDoc Source #
data HoleFitDispConfig Source #
data HoleFitSortingAlg Source #
Instances
Eq HoleFitSortingAlg Source # | |
Defined in GHC.Tc.Errors.Hole (==) :: HoleFitSortingAlg -> HoleFitSortingAlg -> Bool # (/=) :: HoleFitSortingAlg -> HoleFitSortingAlg -> Bool # | |
Ord HoleFitSortingAlg Source # | |
Defined in GHC.Tc.Errors.Hole compare :: HoleFitSortingAlg -> HoleFitSortingAlg -> Ordering # (<) :: HoleFitSortingAlg -> HoleFitSortingAlg -> Bool # (<=) :: HoleFitSortingAlg -> HoleFitSortingAlg -> Bool # (>) :: HoleFitSortingAlg -> HoleFitSortingAlg -> Bool # (>=) :: HoleFitSortingAlg -> HoleFitSortingAlg -> Bool # max :: HoleFitSortingAlg -> HoleFitSortingAlg -> HoleFitSortingAlg # min :: HoleFitSortingAlg -> HoleFitSortingAlg -> HoleFitSortingAlg # |
sortHoleFitsBySize :: [HoleFit] -> TcM [HoleFit] Source #
Sort by size uses as a measure for relevance the sizes of the different types needed to instantiate the fit to the type of the hole. This is much quicker than sorting by subsumption, and gives reasonable results in most cases.
data HoleFitPlugin Source #
A HoleFitPlugin is a pair of candidate and fit plugins.
data HoleFitPluginR Source #
HoleFitPluginR adds a TcRef to hole fit plugins so that plugins can track internal state. Note the existential quantification, ensuring that the state cannot be modified from outside the plugin.
forall s. HoleFitPluginR | |
|