| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
TcSMonad
- data WorkList = WL {
- wl_eqs :: [Ct]
 - wl_funeqs :: [Ct]
 - wl_rest :: [Ct]
 - wl_deriv :: [CtEvidence]
 - wl_implics :: Bag Implication
 
 - isEmptyWorkList :: WorkList -> Bool
 - emptyWorkList :: WorkList
 - extendWorkListNonEq :: Ct -> WorkList -> WorkList
 - extendWorkListCt :: Ct -> WorkList -> WorkList
 - extendWorkListDerived :: CtLoc -> CtEvidence -> WorkList -> WorkList
 - extendWorkListCts :: [Ct] -> WorkList -> WorkList
 - extendWorkListEq :: Ct -> WorkList -> WorkList
 - extendWorkListFunEq :: Ct -> WorkList -> WorkList
 - appendWorkList :: WorkList -> WorkList -> WorkList
 - selectNextWorkItem :: TcS (Maybe Ct)
 - workListSize :: WorkList -> Int
 - workListWantedCount :: WorkList -> Int
 - updWorkListTcS :: (WorkList -> WorkList) -> TcS ()
 - data TcS a
 - runTcS :: TcS a -> TcM (a, EvBindMap)
 - runTcSDeriveds :: TcS a -> TcM a
 - runTcSWithEvBinds :: Bool -> Maybe EvBindsVar -> TcS a -> TcM a
 - failTcS :: SDoc -> TcS a
 - warnTcS :: WarningFlag -> SDoc -> TcS ()
 - addErrTcS :: SDoc -> TcS ()
 - runTcSEqualities :: TcS a -> TcM a
 - nestTcS :: TcS a -> TcS a
 - nestImplicTcS :: Maybe EvBindsVar -> TyCoVarSet -> TcLevel -> TcS a -> TcS (a, TyCoVarSet)
 - setEvBindsTcS :: Maybe EvBindsVar -> TcS a -> TcS a
 - runTcPluginTcS :: TcPluginM a -> TcS a
 - addUsedGREs :: [GlobalRdrElt] -> TcS ()
 - deferTcSForAllEq :: Role -> CtLoc -> [Coercion] -> ([TyBinder], TcType) -> ([TyBinder], TcType) -> TcS Coercion
 - panicTcS :: SDoc -> TcS a
 - traceTcS :: String -> SDoc -> TcS ()
 - traceFireTcS :: CtEvidence -> SDoc -> TcS ()
 - bumpStepCountTcS :: TcS ()
 - csTraceTcS :: SDoc -> TcS ()
 - wrapErrTcS :: TcM a -> TcS a
 - wrapWarnTcS :: TcM a -> TcS a
 - data MaybeNew
 - freshGoals :: [MaybeNew] -> [CtEvidence]
 - isFresh :: MaybeNew -> Bool
 - getEvTerm :: MaybeNew -> EvTerm
 - newTcEvBinds :: TcS EvBindsVar
 - newWantedEq :: CtLoc -> Role -> TcType -> TcType -> TcS (CtEvidence, Coercion)
 - newWanted :: CtLoc -> PredType -> TcS MaybeNew
 - newWantedEvVar :: CtLoc -> TcPredType -> TcS MaybeNew
 - newWantedEvVarNC :: CtLoc -> TcPredType -> TcS CtEvidence
 - newDerivedNC :: CtLoc -> TcPredType -> TcS CtEvidence
 - newBoundEvVarId :: TcPredType -> EvTerm -> TcS EvVar
 - unifyTyVar :: TcTyVar -> TcType -> TcS ()
 - unflattenFmv :: TcTyVar -> TcType -> TcS ()
 - reportUnifications :: TcS a -> TcS (Int, a)
 - setEvBind :: EvBind -> TcS ()
 - setWantedEq :: TcEvDest -> Coercion -> TcS ()
 - setEqIfWanted :: CtEvidence -> Coercion -> TcS ()
 - setWantedEvTerm :: TcEvDest -> EvTerm -> TcS ()
 - setWantedEvBind :: EvVar -> EvTerm -> TcS ()
 - setEvBindIfWanted :: CtEvidence -> EvTerm -> TcS ()
 - newEvVar :: TcPredType -> TcS EvVar
 - newGivenEvVar :: CtLoc -> (TcPredType, EvTerm) -> TcS CtEvidence
 - newGivenEvVars :: CtLoc -> [(TcPredType, EvTerm)] -> TcS [CtEvidence]
 - emitNewDerived :: CtLoc -> TcPredType -> TcS ()
 - emitNewDeriveds :: CtLoc -> [TcPredType] -> TcS ()
 - emitNewDerivedEq :: CtLoc -> Role -> TcType -> TcType -> TcS ()
 - checkReductionDepth :: CtLoc -> TcType -> TcS ()
 - getInstEnvs :: TcS InstEnvs
 - getFamInstEnvs :: TcS (FamInstEnv, FamInstEnv)
 - getTopEnv :: TcS HscEnv
 - getGblEnv :: TcS TcGblEnv
 - getLclEnv :: TcS TcLclEnv
 - getTcEvBinds :: TcS (Maybe EvBindsVar)
 - getTcEvBindsFromVar :: EvBindsVar -> TcS (Bag EvBind)
 - getTcLevel :: TcS TcLevel
 - getTcEvBindsMap :: TcS EvBindMap
 - tcLookupClass :: Name -> TcS Class
 - data InertSet = IS {
- inert_cans :: InertCans
 - inert_flat_cache :: ExactFunEqMap (TcCoercion, TcType, CtFlavour)
 - inert_solved_dicts :: DictMap CtEvidence
 
 - data InertCans = IC {
- inert_model :: InertModel
 - inert_eqs :: DTyVarEnv EqualCtList
 - inert_funeqs :: FunEqMap Ct
 - inert_dicts :: DictMap Ct
 - inert_safehask :: DictMap Ct
 - inert_irreds :: Cts
 - inert_insols :: Cts
 - inert_count :: Int
 
 - updInertTcS :: (InertSet -> InertSet) -> TcS ()
 - updInertCans :: (InertCans -> InertCans) -> TcS ()
 - updInertDicts :: (DictMap Ct -> DictMap Ct) -> TcS ()
 - updInertIrreds :: (Cts -> Cts) -> TcS ()
 - getNoGivenEqs :: TcLevel -> [TcTyVar] -> Cts -> TcS Bool
 - setInertCans :: InertCans -> TcS ()
 - getInertEqs :: TcS (DTyVarEnv EqualCtList)
 - getInertCans :: TcS InertCans
 - getInertModel :: TcS InertModel
 - getInertGivens :: TcS [Ct]
 - emptyInert :: InertSet
 - getTcSInerts :: TcS InertSet
 - setTcSInerts :: InertSet -> TcS ()
 - takeGivenInsolubles :: TcS Cts
 - matchableGivens :: CtLoc -> PredType -> InertSet -> Cts
 - prohibitedSuperClassSolve :: CtLoc -> CtLoc -> Bool
 - getUnsolvedInerts :: TcS (Bag Implication, Cts, Cts, Cts, Cts)
 - removeInertCts :: [Ct] -> InertCans -> InertCans
 - getPendingScDicts :: TcS [Ct]
 - addInertCan :: Ct -> TcS ()
 - addInertEq :: Ct -> TcS ()
 - insertFunEq :: FunEqMap a -> TyCon -> [Type] -> a -> FunEqMap a
 - emitInsoluble :: Ct -> TcS ()
 - emitWorkNC :: [CtEvidence] -> TcS ()
 - emitWork :: [Ct] -> TcS ()
 - type InertModel = DTyVarEnv Ct
 - kickOutAfterUnification :: TcTyVar -> TcS Int
 - addInertSafehask :: InertCans -> Ct -> InertCans
 - insertSafeOverlapFailureTcS :: Ct -> TcS ()
 - updInertSafehask :: (DictMap Ct -> DictMap Ct) -> TcS ()
 - getSafeOverlapFailures :: TcS Cts
 - lookupInertDict :: InertCans -> Class -> [Type] -> Maybe CtEvidence
 - findDictsByClass :: DictMap a -> Class -> Bag a
 - addDict :: DictMap a -> Class -> [Type] -> a -> DictMap a
 - addDictsByClass :: DictMap Ct -> Class -> Bag Ct -> DictMap Ct
 - delDict :: DictMap a -> Class -> [Type] -> DictMap a
 - partitionDicts :: (Ct -> Bool) -> DictMap Ct -> (Bag Ct, DictMap Ct)
 - foldDicts :: (a -> b -> b) -> DictMap a -> b -> b
 - filterDicts :: (Ct -> Bool) -> DictMap Ct -> DictMap Ct
 - type EqualCtList = [Ct]
 - findTyEqs :: InertCans -> TyVar -> EqualCtList
 - foldTyEqs :: (Ct -> b -> b) -> DTyVarEnv EqualCtList -> b -> b
 - isInInertEqs :: DTyVarEnv EqualCtList -> TcTyVar -> TcType -> Bool
 - addSolvedDict :: CtEvidence -> Class -> [Type] -> TcS ()
 - lookupSolvedDict :: InertSet -> Class -> [Type] -> Maybe CtEvidence
 - foldIrreds :: (Ct -> b -> b) -> Cts -> b -> b
 - lookupFlatCache :: TyCon -> [Type] -> TcS (Maybe (TcCoercion, TcType, CtFlavour))
 - extendFlatCache :: TyCon -> [Type] -> (TcCoercion, TcType, CtFlavour) -> TcS ()
 - newFlattenSkolem :: CtFlavour -> CtLoc -> TcType -> TcS (CtEvidence, Coercion, TcTyVar)
 - updInertFunEqs :: (FunEqMap Ct -> FunEqMap Ct) -> TcS ()
 - findFunEq :: FunEqMap a -> TyCon -> [Type] -> Maybe a
 - sizeFunEqMap :: FunEqMap a -> Int
 - filterFunEqs :: (Ct -> Bool) -> FunEqMap Ct -> FunEqMap Ct
 - findFunEqsByTyCon :: FunEqMap a -> TyCon -> [a]
 - partitionFunEqs :: (Ct -> Bool) -> FunEqMap Ct -> ([Ct], FunEqMap Ct)
 - foldFunEqs :: (a -> b -> b) -> FunEqMap a -> b -> b
 - instDFunType :: DFunId -> [DFunInstType] -> TcS ([TcType], TcThetaType)
 - newFlexiTcSTy :: Kind -> TcS TcType
 - instFlexiTcS :: [TKVar] -> TcS (TCvSubst, [TcType])
 - cloneMetaTyVar :: TcTyVar -> TcS TcTyVar
 - demoteUnfilledFmv :: TcTyVar -> TcS ()
 - data TcLevel
 - isTouchableMetaTyVarTcS :: TcTyVar -> TcS Bool
 - isFilledMetaTyVar_maybe :: TcTyVar -> TcS (Maybe Type)
 - isFilledMetaTyVar :: TcTyVar -> TcS Bool
 - zonkTyCoVarsAndFV :: TcTyCoVarSet -> TcS TcTyCoVarSet
 - zonkTcType :: TcType -> TcS TcType
 - zonkTcTypes :: [TcType] -> TcS [TcType]
 - zonkTcTyVar :: TcTyVar -> TcS TcType
 - zonkCo :: Coercion -> TcS Coercion
 - zonkTyCoVarsAndFVList :: [TcTyCoVar] -> TcS [TcTyCoVar]
 - zonkSimples :: Cts -> TcS Cts
 - zonkWC :: WantedConstraints -> TcS WantedConstraints
 - newTcRef :: a -> TcS (TcRef a)
 - readTcRef :: TcRef a -> TcS a
 - updTcRef :: TcRef a -> (a -> a) -> TcS ()
 - getDefaultInfo :: TcS ([Type], (Bool, Bool))
 - getDynFlags :: HasDynFlags m => m DynFlags
 - getGlobalRdrEnvTcS :: TcS GlobalRdrEnv
 - matchFam :: TyCon -> [Type] -> TcS (Maybe (Coercion, TcType))
 - matchFamTcM :: TyCon -> [Type] -> TcM (Maybe (Coercion, TcType))
 - checkWellStagedDFun :: PredType -> DFunId -> CtLoc -> TcS ()
 - pprEq :: TcType -> TcType -> SDoc
 
Documentation
Constructors
| WL | |
Fields 
  | |
Instances
isEmptyWorkList :: WorkList -> Bool #
extendWorkListNonEq :: Ct -> WorkList -> WorkList #
extendWorkListCt :: Ct -> WorkList -> WorkList #
extendWorkListDerived :: CtLoc -> CtEvidence -> WorkList -> WorkList #
extendWorkListCts :: [Ct] -> WorkList -> WorkList #
extendWorkListEq :: Ct -> WorkList -> WorkList #
extendWorkListFunEq :: Ct -> WorkList -> WorkList #
appendWorkList :: WorkList -> WorkList -> WorkList #
selectNextWorkItem :: TcS (Maybe Ct) #
workListSize :: WorkList -> Int #
workListWantedCount :: WorkList -> Int #
updWorkListTcS :: (WorkList -> WorkList) -> TcS () #
runTcSDeriveds :: TcS a -> TcM a #
This variant of runTcS will keep solving, even when only Deriveds
 are left around. It also doesn't return any evidence, as callers won't
 need it.
Arguments
| :: Bool | keep running even if only Deriveds are left?  | 
| -> Maybe EvBindsVar | |
| -> TcS a | |
| -> TcM a | 
warnTcS :: WarningFlag -> SDoc -> TcS () #
runTcSEqualities :: TcS a -> TcM a #
This can deal only with equality constraints.
nestImplicTcS :: Maybe EvBindsVar -> TyCoVarSet -> TcLevel -> TcS a -> TcS (a, TyCoVarSet) #
setEvBindsTcS :: Maybe EvBindsVar -> TcS a -> TcS a #
runTcPluginTcS :: TcPluginM a -> TcS a #
addUsedGREs :: [GlobalRdrElt] -> TcS () #
deferTcSForAllEq :: Role -> CtLoc -> [Coercion] -> ([TyBinder], TcType) -> ([TyBinder], TcType) -> TcS Coercion #
traceFireTcS :: CtEvidence -> SDoc -> TcS () #
bumpStepCountTcS :: TcS () #
csTraceTcS :: SDoc -> TcS () #
wrapErrTcS :: TcM a -> TcS a #
wrapWarnTcS :: TcM a -> TcS a #
freshGoals :: [MaybeNew] -> [CtEvidence] #
newWantedEq :: CtLoc -> Role -> TcType -> TcType -> TcS (CtEvidence, Coercion) #
Make a new equality CtEvidence
newWantedEvVar :: CtLoc -> TcPredType -> TcS MaybeNew #
newWantedEvVarNC :: CtLoc -> TcPredType -> TcS CtEvidence #
newDerivedNC :: CtLoc -> TcPredType -> TcS CtEvidence #
newBoundEvVarId :: TcPredType -> EvTerm -> TcS EvVar #
Make a new Id of the given type, bound (in the monad's EvBinds) to the
 given term
unifyTyVar :: TcTyVar -> TcType -> TcS () #
unflattenFmv :: TcTyVar -> TcType -> TcS () #
reportUnifications :: TcS a -> TcS (Int, a) #
setWantedEq :: TcEvDest -> Coercion -> TcS () #
Equalities only
setEqIfWanted :: CtEvidence -> Coercion -> TcS () #
Equalities only
setWantedEvTerm :: TcEvDest -> EvTerm -> TcS () #
Good for equalities and non-equalities
setWantedEvBind :: EvVar -> EvTerm -> TcS () #
setEvBindIfWanted :: CtEvidence -> EvTerm -> TcS () #
newEvVar :: TcPredType -> TcS EvVar #
newGivenEvVar :: CtLoc -> (TcPredType, EvTerm) -> TcS CtEvidence #
newGivenEvVars :: CtLoc -> [(TcPredType, EvTerm)] -> TcS [CtEvidence] #
emitNewDerived :: CtLoc -> TcPredType -> TcS () #
emitNewDeriveds :: CtLoc -> [TcPredType] -> TcS () #
Checks if the depth of the given location is too much. Fails if it's too big, with an appropriate error message.
getInstEnvs :: TcS InstEnvs #
getFamInstEnvs :: TcS (FamInstEnv, FamInstEnv) #
getTcEvBinds :: TcS (Maybe EvBindsVar) #
getTcEvBindsFromVar :: EvBindsVar -> TcS (Bag EvBind) #
getTcLevel :: TcS TcLevel #
tcLookupClass :: Name -> TcS Class #
Constructors
| IS | |
Fields 
  | |
Instances
Constructors
| IC | |
Fields 
  | |
Instances
updInertTcS :: (InertSet -> InertSet) -> TcS () #
updInertCans :: (InertCans -> InertCans) -> TcS () #
updInertDicts :: (DictMap Ct -> DictMap Ct) -> TcS () #
updInertIrreds :: (Cts -> Cts) -> TcS () #
setInertCans :: InertCans -> TcS () #
getInertEqs :: TcS (DTyVarEnv EqualCtList) #
getInertGivens :: TcS [Ct] #
emptyInert :: InertSet #
getTcSInerts :: TcS InertSet #
setTcSInerts :: InertSet -> TcS () #
matchableGivens :: CtLoc -> PredType -> InertSet -> Cts #
Returns Given constraints that might, potentially, match the given pred. This is used when checking to see if a Given might overlap with an instance. See Note [Instance and Given overlap] in TcInteract.
prohibitedSuperClassSolve :: CtLoc -> CtLoc -> Bool #
getUnsolvedInerts :: TcS (Bag Implication, Cts, Cts, Cts, Cts) #
removeInertCts :: [Ct] -> InertCans -> InertCans #
Remove inert constraints from the InertCans, for use when a
 typechecker plugin wishes to discard a given.
getPendingScDicts :: TcS [Ct] #
addInertCan :: Ct -> TcS () #
addInertEq :: Ct -> TcS () #
insertFunEq :: FunEqMap a -> TyCon -> [Type] -> a -> FunEqMap a #
emitInsoluble :: Ct -> TcS () #
emitWorkNC :: [CtEvidence] -> TcS () #
type InertModel = DTyVarEnv Ct #
kickOutAfterUnification :: TcTyVar -> TcS Int #
addInertSafehask :: InertCans -> Ct -> InertCans #
insertSafeOverlapFailureTcS :: Ct -> TcS () #
updInertSafehask :: (DictMap Ct -> DictMap Ct) -> TcS () #
lookupInertDict :: InertCans -> Class -> [Type] -> Maybe CtEvidence #
Look up a dictionary inert. NB: the returned CtEvidence might not
 match the input exactly. Note [Use loose types in inert set].
findDictsByClass :: DictMap a -> Class -> Bag a #
type EqualCtList = [Ct] #
findTyEqs :: InertCans -> TyVar -> EqualCtList #
foldTyEqs :: (Ct -> b -> b) -> DTyVarEnv EqualCtList -> b -> b #
isInInertEqs :: DTyVarEnv EqualCtList -> TcTyVar -> TcType -> Bool #
addSolvedDict :: CtEvidence -> Class -> [Type] -> TcS () #
lookupSolvedDict :: InertSet -> Class -> [Type] -> Maybe CtEvidence #
Look up a solved inert. NB: the returned CtEvidence might not
 match the input exactly. See Note [Use loose types in inert set].
foldIrreds :: (Ct -> b -> b) -> Cts -> b -> b #
lookupFlatCache :: TyCon -> [Type] -> TcS (Maybe (TcCoercion, TcType, CtFlavour)) #
extendFlatCache :: TyCon -> [Type] -> (TcCoercion, TcType, CtFlavour) -> TcS () #
newFlattenSkolem :: CtFlavour -> CtLoc -> TcType -> TcS (CtEvidence, Coercion, TcTyVar) #
updInertFunEqs :: (FunEqMap Ct -> FunEqMap Ct) -> TcS () #
sizeFunEqMap :: FunEqMap a -> Int #
findFunEqsByTyCon :: FunEqMap a -> TyCon -> [a] #
foldFunEqs :: (a -> b -> b) -> FunEqMap a -> b -> b #
instDFunType :: DFunId -> [DFunInstType] -> TcS ([TcType], TcThetaType) #
newFlexiTcSTy :: Kind -> TcS TcType #
cloneMetaTyVar :: TcTyVar -> TcS TcTyVar #
demoteUnfilledFmv :: TcTyVar -> TcS () #
isTouchableMetaTyVarTcS :: TcTyVar -> TcS Bool #
isFilledMetaTyVar :: TcTyVar -> TcS Bool #
zonkTcType :: TcType -> TcS TcType #
zonkTcTypes :: [TcType] -> TcS [TcType] #
zonkTcTyVar :: TcTyVar -> TcS TcType #
zonkTyCoVarsAndFVList :: [TcTyCoVar] -> TcS [TcTyCoVar] #
zonkSimples :: Cts -> TcS Cts #
getDynFlags :: HasDynFlags m => m DynFlags #