| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
GHC.Tc.Solver
Synopsis
- data InferMode
 - simplifyInfer :: TcLevel -> InferMode -> [TcIdSigInst] -> [(Name, TcTauType)] -> WantedConstraints -> TcM ([TcTyVar], [EvVar], TcEvBinds, Bool)
 - findInferredDiff :: TcThetaType -> TcThetaType -> TcM TcThetaType
 - growThetaTyVars :: ThetaType -> TyCoVarSet -> TyCoVarSet
 - simplifyAmbiguityCheck :: Type -> WantedConstraints -> TcM ()
 - simplifyDefault :: ThetaType -> TcM Bool
 - simplifyTop :: WantedConstraints -> TcM (Bag EvBind)
 - simplifyTopImplic :: Bag Implication -> TcM ()
 - simplifyInteractive :: WantedConstraints -> TcM (Bag EvBind)
 - solveEqualities :: String -> TcM a -> TcM a
 - pushLevelAndSolveEqualities :: SkolemInfoAnon -> [TyConBinder] -> TcM a -> TcM a
 - pushLevelAndSolveEqualitiesX :: String -> TcM a -> TcM (TcLevel, WantedConstraints, a)
 - reportUnsolvedEqualities :: SkolemInfo -> [TcTyVar] -> TcLevel -> WantedConstraints -> TcM ()
 - simplifyWantedsTcM :: [CtEvidence] -> TcM WantedConstraints
 - tcCheckGivens :: InertSet -> Bag EvVar -> TcM (Maybe InertSet)
 - tcCheckWanteds :: InertSet -> ThetaType -> TcM Bool
 - tcNormalise :: InertSet -> Type -> TcM Type
 - captureTopConstraints :: TcM a -> TcM (a, WantedConstraints)
 - simplifyTopWanteds :: WantedConstraints -> TcS WantedConstraints
 - promoteTyVarSet :: HasDebugCallStack => TcTyVarSet -> TcM Bool
 - simplifyAndEmitFlatConstraints :: WantedConstraints -> TcM ()
 - solveWanteds :: WantedConstraints -> TcS WantedConstraints
 - approximateWC :: Bool -> WantedConstraints -> Cts
 
Documentation
How should we choose which constraints to quantify over?
Constructors
| ApplyMR | Apply the monomorphism restriction, never quantifying over any constraints  | 
| EagerDefaulting | See Note [TcRnExprMode] in GHC.Tc.Module, the :type +d case; this mode refuses to quantify over any defaultable constraint  | 
| NoRestrictions | Quantify over any constraint that satisfies pickQuantifiablePreds  | 
Instances
simplifyInfer :: TcLevel -> InferMode -> [TcIdSigInst] -> [(Name, TcTauType)] -> WantedConstraints -> TcM ([TcTyVar], [EvVar], TcEvBinds, Bool) Source #
findInferredDiff :: TcThetaType -> TcThetaType -> TcM TcThetaType Source #
growThetaTyVars :: ThetaType -> TyCoVarSet -> TyCoVarSet Source #
simplifyAmbiguityCheck :: Type -> WantedConstraints -> TcM () Source #
simplifyTop :: WantedConstraints -> TcM (Bag EvBind) Source #
simplifyTopImplic :: Bag Implication -> TcM () Source #
simplifyInteractive :: WantedConstraints -> TcM (Bag EvBind) Source #
solveEqualities :: String -> TcM a -> TcM a Source #
Type-check a thing that emits only equality constraints, solving any constraints we can and re-emitting constraints that we can't. Use this variant only when we'll get another crack at it later See Note [Failure in local type signatures]
Panics if we solve any non-equality constraints. (In runTCSEqualities we use an error thunk for the evidence bindings.)
pushLevelAndSolveEqualities :: SkolemInfoAnon -> [TyConBinder] -> TcM a -> TcM a Source #
pushLevelAndSolveEqualitiesX :: String -> TcM a -> TcM (TcLevel, WantedConstraints, a) Source #
reportUnsolvedEqualities :: SkolemInfo -> [TcTyVar] -> TcLevel -> WantedConstraints -> TcM () Source #
tcCheckGivens :: InertSet -> Bag EvVar -> TcM (Maybe InertSet) Source #
Return (Just new_inerts) if the Givens are satisfiable, Nothing if definitely contradictory.
See Note [Pattern match warnings with insoluble Givens] above.
tcCheckWanteds :: InertSet -> ThetaType -> TcM Bool Source #
Return True if the Wanteds are soluble, False if not
tcNormalise :: InertSet -> Type -> TcM Type Source #
Normalise a type as much as possible using the given constraints.
 See Note [tcNormalise].
captureTopConstraints :: TcM a -> TcM (a, WantedConstraints) Source #
simplifyTopWanteds :: WantedConstraints -> TcS WantedConstraints Source #
Simplify top-level constraints, but without reporting any unsolved constraints nor unsafe overlapping.
promoteTyVarSet :: HasDebugCallStack => TcTyVarSet -> TcM Bool Source #
approximateWC :: Bool -> WantedConstraints -> Cts Source #