ghc-8.0.0.20160204: The GHC API

Safe HaskellNone
LanguageHaskell2010

TcRnMonad

Contents

Synopsis

Documentation

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

Setup the initial typechecking environment

initTcRnIf :: Char -> HscEnv -> gbl -> lcl -> TcRnIf gbl lcl a -> IO a 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

setXOptM :: 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

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.

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

updTcRefX :: TcRef a -> (a -> a) -> TcRnIf gbl lcl a Source

traceTcN :: Int -> SDoc -> TcRn () Source

Typechecker trace

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

Output a doc if the given DumpFlag is set.

By default this logs to stdout However, if the `-ddump-to-file` flag is set, then this will dump output to a file

Just a wrapper for dumpSDoc

traceTcRn :: DumpFlag -> SDoc -> TcRn () Source

Unconditionally dump some trace output

The DumpFlag is used only to set the output filename for --dump-to-file, not to decide whether or not to output That part is done by the caller

printForUserTcRn :: SDoc -> TcRn () Source

Like logInfoTcRn, but for user consumption

debugDumpTcRn :: SDoc -> TcRn () Source

Typechecker debug

traceIf :: SDoc -> TcRnIf m n () 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

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

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

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

Succeeds if applying the argument to all members of the lists succeeds, but nevertheless runs it on all arguments, to collect all errors.

tryTcLIE_ :: TcM r -> TcM r -> TcM r Source

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

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

checkTH :: a -> String -> TcRn () Source

failTH :: Outputable a => a -> String -> TcRn x 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.

updCtxt :: ([ErrCtxt] -> [ErrCtxt]) -> TcM a -> TcM a Source

tcInitOpenTidyEnv :: TyCoVarSet -> TcM TidyEnv Source

Get a TidyEnv that includes mappings for all vars free in the given type. Useful when tidying open types.

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

discardConstraints :: TcM a -> TcM a Source

Throw out any constraints emitted by the thing_inside

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.

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.

initIfaceTc :: ModIface -> (TcRef TypeEnv -> IfL a) -> TcRnIf gbl lcl a Source

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

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

module TcRnTypes

module IOEnv

Orphan instances