ghc-9.0.2: The GHC API
Safe HaskellSafe-Inferred
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.

initTcRnIf Source #

Arguments

:: Char

Mask for unique supply

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

Simple accessors

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 #

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 #

withDoDynamicToo :: TcRnIf gbl lcl a -> TcRnIf gbl lcl a 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.

Arrow scopes

Unique supply

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

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 #

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

Typechecker global environment

Error management

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 #

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.

Shared error message stuff: renamer and typechecker

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

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

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

Context management for the type checker

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.

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

Error message generation (type checker)

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.

Type constraints

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

discardConstraints :: TcM a -> TcM a Source #

Throw out any constraints emitted by the thing_inside

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

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

Template Haskell context

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

Stuff for interface decls

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.

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)

forkM :: SDoc -> 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 :: ContainsCostCentreState gbl => FastString -> TcRnIf gbl lcl CostCentreIndex Source #

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

Types etc.

Orphan instances

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