ghc-lib-0.20201101: The GHC API, decoupled from GHC versions
Safe HaskellNone
LanguageHaskell2010

GHC.Tc.Utils.Monad

Description

Functions for working with the typechecker environment (setters, getters...).

Synopsis

Initialisation

initTc :: HscEnv -> HscSource -> Bool -> Module -> RealSrcSpan -> TcM r -> IO (Messages, Maybe r) Source #

Setup the initial typechecking environment

initTcWithGbl :: HscEnv -> TcGblEnv -> RealSrcSpan -> TcM r -> IO (Messages, Maybe r) Source #

Run a TcM action in the context of an existing GblEnv.

initTcInteractive :: HscEnv -> TcM a -> IO (Messages, Maybe a) Source #

initTcRnIf Source #

Arguments

:: Char

Mask for unique supply

-> HscEnv 
-> gbl 
-> lcl 
-> TcRnIf gbl lcl a 
-> IO a 

Simple accessors

discardResult :: TcM a -> TcM () Source #

getTopEnv :: TcRnIf gbl lcl HscEnv Source #

updTopEnv :: (HscEnv -> HscEnv) -> TcRnIf gbl lcl a -> TcRnIf gbl lcl a Source #

getGblEnv :: TcRnIf gbl lcl gbl Source #

updGblEnv :: (gbl -> gbl) -> TcRnIf gbl lcl a -> TcRnIf gbl lcl a Source #

setGblEnv :: gbl -> TcRnIf gbl lcl a -> TcRnIf gbl lcl a Source #

getLclEnv :: TcRnIf gbl lcl lcl Source #

updLclEnv :: (lcl -> lcl) -> TcRnIf gbl lcl a -> TcRnIf gbl lcl a Source #

setLclEnv :: lcl' -> TcRnIf gbl lcl' a -> TcRnIf gbl lcl a Source #

getEnvs :: TcRnIf gbl lcl (gbl, lcl) Source #

setEnvs :: (gbl', lcl') -> TcRnIf gbl' lcl' a -> TcRnIf gbl lcl a Source #

xoptM :: Extension -> TcRnIf gbl lcl Bool Source #

doptM :: DumpFlag -> TcRnIf gbl lcl Bool Source #

goptM :: GeneralFlag -> TcRnIf gbl lcl Bool Source #

woptM :: WarningFlag -> TcRnIf gbl lcl Bool Source #

setXOptM :: Extension -> TcRnIf gbl lcl a -> TcRnIf gbl lcl a Source #

unsetXOptM :: Extension -> TcRnIf gbl lcl a -> TcRnIf gbl lcl a Source #

unsetGOptM :: GeneralFlag -> TcRnIf gbl lcl a -> TcRnIf gbl lcl a Source #

unsetWOptM :: WarningFlag -> TcRnIf gbl lcl a -> TcRnIf gbl lcl a Source #

whenDOptM :: DumpFlag -> TcRnIf gbl lcl () -> TcRnIf gbl lcl () Source #

Do it flag is true

whenGOptM :: GeneralFlag -> TcRnIf gbl lcl () -> TcRnIf gbl lcl () Source #

whenWOptM :: WarningFlag -> TcRnIf gbl lcl () -> TcRnIf gbl lcl () Source #

whenXOptM :: Extension -> TcRnIf gbl lcl () -> TcRnIf gbl lcl () Source #

unlessXOptM :: Extension -> TcRnIf gbl lcl () -> TcRnIf gbl lcl () Source #

getGhcMode :: TcRnIf gbl lcl GhcMode Source #

withDoDynamicToo :: TcRnIf gbl lcl a -> TcRnIf gbl lcl a Source #

getEpsVar :: TcRnIf gbl lcl (TcRef ExternalPackageState) Source #

getEps :: TcRnIf gbl lcl ExternalPackageState Source #

updateEps :: (ExternalPackageState -> (ExternalPackageState, a)) -> TcRnIf gbl lcl a Source #

Update the external package state. Returns the second result of the modifier function.

This is an atomic operation and forces evaluation of the modified EPS in order to avoid space leaks.

updateEps_ :: (ExternalPackageState -> ExternalPackageState) -> TcRnIf gbl lcl () Source #

Update the external package state.

This is an atomic operation and forces evaluation of the modified EPS in order to avoid space leaks.

getHpt :: TcRnIf gbl lcl HomePackageTable Source #

getEpsAndHpt :: TcRnIf gbl lcl (ExternalPackageState, HomePackageTable) Source #

Arrow scopes

newArrowScope :: TcM a -> TcM a Source #

escapeArrowScope :: TcM a -> TcM a Source #

Unique supply

newUnique :: TcRnIf gbl lcl Unique Source #

newSysName :: OccName -> TcRnIf gbl lcl Name Source #

newSysLocalId :: FastString -> Mult -> TcType -> TcRnIf gbl lcl TcId Source #

newSysLocalIds :: FastString -> [Scaled TcType] -> TcRnIf gbl lcl [TcId] Source #

Accessing input/output

newTcRef :: a -> TcRnIf gbl lcl (TcRef a) Source #

readTcRef :: TcRef a -> TcRnIf gbl lcl a Source #

writeTcRef :: TcRef a -> a -> TcRnIf gbl lcl () Source #

updTcRef :: TcRef a -> (a -> a) -> TcRnIf gbl lcl () Source #

Debugging

traceTc :: String -> SDoc -> TcRn () Source #

traceRn :: String -> SDoc -> TcRn () Source #

traceOptTcRn :: DumpFlag -> SDoc -> TcRn () Source #

dumpOptTcRn :: DumpFlag -> String -> DumpFormat -> SDoc -> TcRn () Source #

Dump if the given DumpFlag is set.

dumpTcRn :: Bool -> DumpOptions -> String -> DumpFormat -> SDoc -> TcRn () Source #

Unconditionally dump some trace output

Certain tests (T3017, Roles3, T12763 etc.) expect part of the output generated by `-ddump-types` to be in PprUser style. However, generally we want all other debugging output to use PprDump style. We PprUser style if useUserStyle is True.

printForUserTcRn :: SDoc -> TcRn () Source #

Like logInfoTcRn, but for user consumption

traceIf :: SDoc -> TcRnIf m n () Source #

traceHiDiffs :: SDoc -> TcRnIf m n () Source #

traceOptIf :: DumpFlag -> SDoc -> TcRnIf m n () Source #

debugTc :: TcM () -> TcM () Source #

Typechecker global environment

tcSelfBootInfo :: TcRn SelfBootInfo Source #

getGlobalRdrEnv :: TcRn GlobalRdrEnv Source #

getRdrEnvs :: TcRn (GlobalRdrEnv, LocalRdrEnv) Source #

getImports :: TcRn ImportAvails Source #

getFixityEnv :: TcRn FixityEnv Source #

extendFixityEnv :: [(Name, FixItem)] -> RnM a -> RnM a Source #

getRecFieldEnv :: TcRn RecFieldEnv Source #

Error management

setSrcSpan :: SrcSpan -> TcRn a -> TcRn a Source #

addLocM :: (a -> TcM b) -> Located a -> TcM b Source #

wrapLocM :: (a -> TcM b) -> Located a -> TcM (Located b) Source #

wrapLocFstM :: (a -> TcM (b, c)) -> Located a -> TcM (Located b, c) Source #

wrapLocSndM :: (a -> TcM (b, c)) -> Located a -> TcM (b, Located c) Source #

wrapLocM_ :: (a -> TcM ()) -> Located a -> TcM () Source #

getErrsVar :: TcRn (TcRef Messages) Source #

setErrsVar :: TcRef Messages -> TcRn a -> TcRn a Source #

addErr :: MsgDoc -> TcRn () Source #

failWith :: MsgDoc -> TcRn a Source #

failAt :: SrcSpan -> MsgDoc -> TcRn a Source #

addErrAt :: SrcSpan -> MsgDoc -> TcRn () Source #

addErrs :: [(SrcSpan, MsgDoc)] -> TcRn () Source #

checkErr :: Bool -> MsgDoc -> TcRn () Source #

addMessages :: Messages -> TcRn () Source #

discardWarnings :: TcRn a -> TcRn a Source #

Usage environment

tcCollectingUsage :: TcM a -> TcM (UsageEnv, a) Source #

tcCollectingUsage thing_inside runs thing_inside and returns the usage information which was collected as part of the execution of thing_inside. Careful: tcCollectingUsage thing_inside itself does not report any usage information, it's up to the caller to incorporate the returned usage information into the larger context appropriately.

tcScalingUsage :: Mult -> TcM a -> TcM a Source #

tcScalingUsage mult thing_inside runs thing_inside and scales all the usage information by mult.

tcEmitBindingUsage :: UsageEnv -> TcM () Source #

Shared error message stuff: renamer and typechecker

mkLongErrAt :: SrcSpan -> MsgDoc -> MsgDoc -> TcRn ErrMsg Source #

mkErrDocAt :: SrcSpan -> ErrDoc -> TcRn ErrMsg Source #

addLongErrAt :: SrcSpan -> MsgDoc -> MsgDoc -> TcRn () Source #

reportErrors :: [ErrMsg] -> TcM () Source #

reportError :: ErrMsg -> TcRn () Source #

reportWarning :: WarnReason -> ErrMsg -> TcRn () Source #

recoverM :: TcRn r -> TcRn r -> TcRn r Source #

mapAndRecoverM :: (a -> TcRn b) -> [a] -> TcRn [b] Source #

Drop elements of the input that fail, so the result list can be shorter than the argument list

mapAndReportM :: (a -> TcRn b) -> [a] -> TcRn [b] Source #

Apply the function to all elements on the input list If all succeed, return the list of results Otherwise fail, propagating all errors

foldAndRecoverM :: (b -> a -> TcRn b) -> b -> [a] -> TcRn b Source #

The accumulator is not updated if the action fails

attemptM :: TcRn r -> TcRn (Maybe r) Source #

tryTc :: TcRn a -> TcRn (Maybe a, Messages) Source #

askNoErrs :: TcRn a -> TcRn (a, Bool) Source #

discardErrs :: TcRn a -> TcRn a Source #

tryTcDiscardingErrs :: TcM r -> TcM r -> TcM r Source #

checkNoErrs :: TcM r -> TcM r Source #

whenNoErrs :: TcM () -> TcM () Source #

ifErrsM :: TcRn r -> TcRn r -> TcRn r Source #

failIfErrsM :: TcRn () Source #

Context management for the type checker

getErrCtxt :: TcM [ErrCtxt] Source #

setErrCtxt :: [ErrCtxt] -> TcM a -> TcM a Source #

addErrCtxt :: MsgDoc -> TcM a -> TcM a Source #

Add a fixed message to the error context. This message should not do any tidying.

addErrCtxtM :: (TidyEnv -> TcM (TidyEnv, MsgDoc)) -> TcM a -> TcM a Source #

Add a message to the error context. This message may do tidying.

addLandmarkErrCtxt :: MsgDoc -> TcM a -> TcM a Source #

Add a fixed landmark message to the error context. A landmark message is always sure to be reported, even if there is a lot of context. It also doesn't count toward the maximum number of contexts reported.

addLandmarkErrCtxtM :: (TidyEnv -> TcM (TidyEnv, MsgDoc)) -> TcM a -> TcM a Source #

Variant of addLandmarkErrCtxt that allows for monadic operations and tidying.

popErrCtxt :: TcM a -> TcM a Source #

getCtLocM :: CtOrigin -> Maybe TypeOrKind -> TcM CtLoc Source #

setCtLocM :: CtLoc -> TcM a -> TcM a Source #

Error message generation (type checker)

addErrTc :: MsgDoc -> TcM () Source #

addErrTcM :: (TidyEnv, MsgDoc) -> TcM () Source #

failWithTc :: MsgDoc -> TcM a Source #

failWithTcM :: (TidyEnv, MsgDoc) -> TcM a Source #

checkTc :: Bool -> MsgDoc -> TcM () Source #

checkTcM :: Bool -> (TidyEnv, MsgDoc) -> TcM () Source #

failIfTc :: Bool -> MsgDoc -> TcM () Source #

failIfTcM :: Bool -> (TidyEnv, MsgDoc) -> TcM () Source #

warnIfFlag :: WarningFlag -> Bool -> MsgDoc -> TcRn () Source #

Display a warning if a condition is met, and the warning is enabled

warnIf :: Bool -> MsgDoc -> TcRn () Source #

Display a warning if a condition is met.

warnTc :: WarnReason -> Bool -> MsgDoc -> TcM () Source #

Display a warning if a condition is met.

warnTcM :: WarnReason -> Bool -> (TidyEnv, MsgDoc) -> TcM () Source #

Display a warning if a condition is met.

addWarnTc :: WarnReason -> MsgDoc -> TcM () Source #

Display a warning in the current context.

addWarnTcM :: WarnReason -> (TidyEnv, MsgDoc) -> TcM () Source #

Display a warning in a given context.

addWarn :: WarnReason -> MsgDoc -> TcRn () Source #

Display a warning for the current source location.

addWarnAt :: WarnReason -> SrcSpan -> MsgDoc -> TcRn () Source #

Display a warning for a given source location.

add_warn :: WarnReason -> MsgDoc -> MsgDoc -> TcRn () Source #

Display a warning, with an optional flag, for the current source location.

mkErrInfo :: TidyEnv -> [ErrCtxt] -> TcM SDoc Source #

Type constraints

newTcEvBinds :: TcM EvBindsVar Source #

newNoTcEvBinds :: TcM EvBindsVar Source #

Creates an EvBindsVar incapable of holding any bindings. It still tracks covar usages (see comments on ebv_tcvs in GHC.Tc.Types.Evidence), thus must be made monadically

cloneEvBindsVar :: EvBindsVar -> TcM EvBindsVar Source #

addTcEvBind :: EvBindsVar -> EvBind -> TcM () Source #

addTopEvBinds :: Bag EvBind -> TcM a -> TcM a Source #

getTcEvTyCoVars :: EvBindsVar -> TcM TyCoVarSet Source #

getTcEvBindsMap :: EvBindsVar -> TcM EvBindMap Source #

setTcEvBindsMap :: EvBindsVar -> EvBindMap -> TcM () Source #

getConstraintVar :: TcM (TcRef WantedConstraints) Source #

setConstraintVar :: TcRef WantedConstraints -> TcM a -> TcM a Source #

emitConstraints :: WantedConstraints -> TcM () Source #

emitStaticConstraints :: WantedConstraints -> TcM () Source #

emitSimple :: Ct -> TcM () Source #

emitSimples :: Cts -> TcM () Source #

emitImplication :: Implication -> TcM () Source #

emitImplications :: Bag Implication -> TcM () Source #

emitInsoluble :: Ct -> TcM () Source #

emitHole :: Hole -> TcM () Source #

emitHoles :: Bag Hole -> TcM () Source #

discardConstraints :: TcM a -> TcM a Source #

Throw out any constraints emitted by the thing_inside

captureConstraints :: TcM a -> TcM (a, WantedConstraints) Source #

tryCaptureConstraints :: TcM a -> TcM (Maybe a, WantedConstraints) Source #

pushLevelAndCaptureConstraints :: TcM a -> TcM (TcLevel, WantedConstraints, a) Source #

The name says it all. The returned TcLevel is the *inner* TcLevel.

pushTcLevelM_ :: TcM a -> TcM a Source #

pushTcLevelM :: TcM a -> TcM (TcLevel, a) Source #

pushTcLevelsM :: Int -> TcM a -> TcM (a, TcLevel) Source #

setTcLevel :: TcLevel -> TcM a -> TcM a Source #

getLclTypeEnv :: TcM TcTypeEnv Source #

setLclTypeEnv :: TcLclEnv -> TcM a -> TcM a Source #

Template Haskell context

recordThUse :: TcM () Source #

keepAlive :: Name -> TcRn () Source #

getStage :: TcM ThStage Source #

getStageAndBindLevel :: Name -> TcRn (Maybe (TopLevelFlag, ThLevel, ThStage)) Source #

setStage :: ThStage -> TcM a -> TcRn a Source #

addModFinalizersWithLclEnv :: ThModFinalizers -> TcM () Source #

Adds the given modFinalizers to the global environment and set them to use the current local environment.

Safe Haskell context

recordUnsafeInfer :: WarningMessages -> TcM () Source #

Mark that safe inference has failed See Note [Safe Haskell Overlapping Instances Implementation] although this is used for more than just that failure case.

finalSafeMode :: DynFlags -> TcGblEnv -> IO SafeHaskellMode Source #

Figure out the final correct safe haskell mode

fixSafeInstances :: SafeHaskellMode -> [ClsInst] -> [ClsInst] Source #

Switch instances to safe instances if we're in Safe mode.

Stuff for the renamer's local env

getLocalRdrEnv :: RnM LocalRdrEnv Source #

setLocalRdrEnv :: LocalRdrEnv -> RnM a -> RnM a Source #

Stuff for interface decls

mkIfLclEnv :: Module -> SDoc -> IsBootInterface -> IfLclEnv Source #

initIfaceTcRn :: IfG a -> TcRn a Source #

Run an IfG (top-level interface monad) computation inside an existing TcRn (typecheck-renaming monad) computation by initializing an IfGblEnv based on TcGblEnv.

initIfaceCheck :: SDoc -> HscEnv -> IfG a -> IO a Source #

initIfaceLcl :: Module -> SDoc -> IsBootInterface -> IfL a -> IfM lcl a Source #

initIfaceLclWithSubst :: Module -> SDoc -> IsBootInterface -> NameShape -> IfL a -> IfM lcl a Source #

Initialize interface typechecking, but with a NameShape to apply when typechecking top-level OccNames (see lookupIfaceTop)

initIfaceLoad :: HscEnv -> IfG a -> IO a Source #

failIfM :: MsgDoc -> IfL a Source #

forkM_maybe :: SDoc -> IfL a -> IfL (Maybe a) Source #

Run thing_inside in an interleaved thread. It shares everything with the parent thread, so this is DANGEROUS.

It returns Nothing if the computation fails

It's used for lazily type-checking interface signatures, which is pretty benign.

See Note [Masking exceptions in forkM_maybe]

forkM :: SDoc -> IfL a -> IfL a Source #

setImplicitEnvM :: TypeEnv -> IfL a -> IfL a Source #

withException :: TcRnIf gbl lcl (MaybeErr MsgDoc a) -> TcRnIf gbl lcl a Source #

A convenient wrapper for taking a MaybeErr MsgDoc a and throwing an exception if it is an error.

Stuff for cost centres.

getCCIndexM :: (gbl -> TcRef CostCentreState) -> FastString -> TcRnIf gbl lcl CostCentreIndex Source #

Get the next cost centre index associated with a given name.

getCCIndexTcM :: FastString -> TcM CostCentreIndex Source #

Types etc.

Orphan instances

MonadUnique (IOEnv (Env gbl lcl)) Source # 
Instance details

Methods

getUniqueSupplyM :: IOEnv (Env gbl lcl) UniqSupply #

getUniqueM :: IOEnv (Env gbl lcl) Unique #

getUniquesM :: IOEnv (Env gbl lcl) [Unique] #