Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- simplifyInfer :: TcLevel -> InferMode -> [TcIdSigInst] -> [(Name, TcTauType)] -> WantedConstraints -> TcM ([TcTyVar], [EvVar], TcEvBinds, WantedConstraints, Bool)
- data InferMode
- growThetaTyVars :: ThetaType -> TyCoVarSet -> TyCoVarSet
- simplifyAmbiguityCheck :: Type -> WantedConstraints -> TcM ()
- simplifyDefault :: ThetaType -> TcM ()
- simplifyTop :: WantedConstraints -> TcM (Bag EvBind)
- simplifyTopImplic :: Bag Implication -> TcM ()
- simplifyInteractive :: WantedConstraints -> TcM (Bag EvBind)
- solveEqualities :: TcM a -> TcM a
- solveLocalEqualities :: String -> TcM a -> TcM a
- solveLocalEqualitiesX :: String -> TcM a -> TcM (WantedConstraints, a)
- simplifyWantedsTcM :: [CtEvidence] -> TcM WantedConstraints
- tcCheckSatisfiability :: Bag EvVar -> TcM Bool
- tcNormalise :: Bag EvVar -> Type -> TcM Type
- captureTopConstraints :: TcM a -> TcM (a, WantedConstraints)
- simpl_top :: WantedConstraints -> TcS WantedConstraints
- promoteTyVarSet :: TcTyVarSet -> TcM Bool
- emitFlatConstraints :: WantedConstraints -> TcM ()
- solveWanteds :: WantedConstraints -> TcS WantedConstraints
- solveWantedsAndDrop :: WantedConstraints -> TcS WantedConstraints
- approximateWC :: Bool -> WantedConstraints -> Cts
- runTcSDeriveds :: TcS a -> TcM a
Documentation
simplifyInfer :: TcLevel -> InferMode -> [TcIdSigInst] -> [(Name, TcTauType)] -> WantedConstraints -> TcM ([TcTyVar], [EvVar], TcEvBinds, WantedConstraints, Bool) Source #
How should we choose which constraints to quantify over?
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 |
growThetaTyVars :: ThetaType -> TyCoVarSet -> TyCoVarSet Source #
simplifyAmbiguityCheck :: Type -> WantedConstraints -> TcM () Source #
simplifyDefault :: ThetaType -> TcM () Source #
simplifyTop :: WantedConstraints -> TcM (Bag EvBind) Source #
simplifyTopImplic :: Bag Implication -> TcM () Source #
simplifyInteractive :: WantedConstraints -> TcM (Bag EvBind) Source #
solveEqualities :: TcM a -> TcM a Source #
Type-check a thing that emits only equality constraints, then solve those constraints. Fails outright if there is trouble. Use this if you're not going to get another crack at solving (because, e.g., you're checking a datatype declaration)
solveLocalEqualities :: 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. The thing_inside should generally bump the TcLevel to make sure that this run of the solver doesn't affect anything lying around.
solveLocalEqualitiesX :: String -> TcM a -> TcM (WantedConstraints, a) Source #
tcNormalise :: Bag EvVar -> 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 #
simpl_top :: WantedConstraints -> TcS WantedConstraints Source #
Simplify top-level constraints, but without reporting any unsolved constraints nor unsafe overlapping.
promoteTyVarSet :: TcTyVarSet -> TcM Bool Source #
emitFlatConstraints :: WantedConstraints -> TcM () Source #
approximateWC :: Bool -> WantedConstraints -> Cts Source #