ghc-6.12.1: The GHC APIContentsIndex
TcRnMonad
Synopsis
initTc :: HscEnv -> HscSource -> Bool -> Module -> TcM r -> IO (Messages, Maybe r)
initTcPrintErrors :: HscEnv -> Module -> TcM r -> IO (Messages, Maybe r)
initTcRnIf :: Char -> HscEnv -> gbl -> lcl -> TcRnIf gbl lcl a -> IO a
getTopEnv :: TcRnIf gbl lcl HscEnv
getGblEnv :: TcRnIf gbl lcl gbl
updGblEnv :: (gbl -> gbl) -> TcRnIf gbl lcl a -> TcRnIf gbl lcl a
setGblEnv :: gbl -> TcRnIf gbl lcl a -> TcRnIf gbl lcl a
getLclEnv :: TcRnIf gbl lcl lcl
updLclEnv :: (lcl -> lcl) -> TcRnIf gbl lcl a -> TcRnIf gbl lcl a
setLclEnv :: lcl' -> TcRnIf gbl lcl' a -> TcRnIf gbl lcl a
getEnvs :: TcRnIf gbl lcl (gbl, lcl)
setEnvs :: (gbl', lcl') -> TcRnIf gbl' lcl' a -> TcRnIf gbl lcl a
getDOpts :: TcRnIf gbl lcl DynFlags
doptM :: DynFlag -> TcRnIf gbl lcl Bool
setOptM :: DynFlag -> TcRnIf gbl lcl a -> TcRnIf gbl lcl a
unsetOptM :: DynFlag -> TcRnIf gbl lcl a -> TcRnIf gbl lcl a
ifOptM :: DynFlag -> TcRnIf gbl lcl () -> TcRnIf gbl lcl ()
getGhcMode :: TcRnIf gbl lcl GhcMode
getEpsVar :: TcRnIf gbl lcl (TcRef ExternalPackageState)
getEps :: TcRnIf gbl lcl ExternalPackageState
updateEps :: (ExternalPackageState -> (ExternalPackageState, a)) -> TcRnIf gbl lcl a
updateEps_ :: (ExternalPackageState -> ExternalPackageState) -> TcRnIf gbl lcl ()
getHpt :: TcRnIf gbl lcl HomePackageTable
getEpsAndHpt :: TcRnIf gbl lcl (ExternalPackageState, HomePackageTable)
newUnique :: TcRnIf gbl lcl Unique
newUniqueSupply :: TcRnIf gbl lcl UniqSupply
newLocalName :: Name -> TcRnIf gbl lcl Name
newSysLocalIds :: FastString -> [TcType] -> TcRnIf gbl lcl [TcId]
traceRn :: SDoc -> TcRn ()
traceSplice :: SDoc -> TcRn ()
traceTc :: SDoc -> TcRn ()
traceHiDiffs :: SDoc -> TcRnIf m n ()
traceIf :: SDoc -> TcRnIf m n ()
traceOptIf :: DynFlag -> SDoc -> TcRnIf m n ()
traceOptTcRn :: DynFlag -> SDoc -> TcRn ()
dumpTcRn :: SDoc -> TcRn ()
debugDumpTcRn :: SDoc -> TcRn ()
dumpOptTcRn :: DynFlag -> SDoc -> TcRn ()
getModule :: TcRn Module
setModule :: Module -> TcRn a -> TcRn a
tcIsHsBoot :: TcRn Bool
getGlobalRdrEnv :: TcRn GlobalRdrEnv
getRdrEnvs :: TcRn (GlobalRdrEnv, LocalRdrEnv)
getImports :: TcRn ImportAvails
getFixityEnv :: TcRn FixityEnv
extendFixityEnv :: [(Name, FixItem)] -> RnM a -> RnM a
getRecFieldEnv :: TcRn RecFieldEnv
getDeclaredDefaultTys :: TcRn (Maybe [Type])
getSrcSpanM :: TcRn SrcSpan
setSrcSpan :: SrcSpan -> TcRn a -> TcRn a
addLocM :: (a -> TcM b) -> Located a -> TcM b
wrapLocM :: (a -> TcM b) -> Located a -> TcM (Located b)
wrapLocFstM :: (a -> TcM (b, c)) -> Located a -> TcM (Located b, c)
wrapLocSndM :: (a -> TcM (b, c)) -> Located a -> TcM (b, Located c)
getErrsVar :: TcRn (TcRef Messages)
setErrsVar :: TcRef Messages -> TcRn a -> TcRn a
addErr :: Message -> TcRn ()
failWith :: Message -> TcRn a
addErrAt :: SrcSpan -> Message -> TcRn ()
addErrs :: [(SrcSpan, Message)] -> TcRn ()
addWarn :: Message -> TcRn ()
addWarnAt :: SrcSpan -> Message -> TcRn ()
checkErr :: Bool -> Message -> TcRn ()
warnIf :: Bool -> Message -> TcRn ()
addMessages :: Messages -> TcRn ()
discardWarnings :: TcRn a -> TcRn a
addReport :: Message -> Message -> TcRn ()
addReportAt :: SrcSpan -> Message -> Message -> TcRn ()
addLongErrAt :: SrcSpan -> Message -> Message -> TcRn ()
try_m :: TcRn r -> TcRn (Either IOEnvFailure r)
recoverM :: TcRn r -> TcRn r -> TcRn r
mapAndRecoverM :: (a -> TcRn b) -> [a] -> TcRn [b]
tryTc :: TcRn a -> TcRn (Messages, Maybe a)
tryTcErrs :: TcRn a -> TcRn (Messages, Maybe a)
tryTcLIE :: TcM a -> TcM (Messages, Maybe a)
tryTcLIE_ :: TcM r -> TcM r -> TcM r
checkNoErrs :: TcM r -> TcM r
ifErrsM :: TcRn r -> TcRn r -> TcRn r
failIfErrsM :: TcRn ()
getErrCtxt :: TcM [ErrCtxt]
setErrCtxt :: [ErrCtxt] -> TcM a -> TcM a
addErrCtxt :: Message -> TcM a -> TcM a
addErrCtxtM :: (TidyEnv -> TcM (TidyEnv, Message)) -> TcM a -> TcM a
addLandmarkErrCtxt :: Message -> TcM a -> TcM a
updCtxt :: ([ErrCtxt] -> [ErrCtxt]) -> TcM a -> TcM a
maybeAddErrCtxt :: Maybe Message -> TcM a -> TcM a
popErrCtxt :: TcM a -> TcM a
getInstLoc :: InstOrigin -> TcM InstLoc
setInstCtxt :: InstLoc -> TcM a -> TcM a
addErrTc :: Message -> TcM ()
addErrsTc :: [Message] -> TcM ()
addErrTcM :: (TidyEnv, Message) -> TcM ()
failWithTc :: Message -> TcM a
failWithTcM :: (TidyEnv, Message) -> TcM a
checkTc :: Bool -> Message -> TcM ()
addWarnTc :: Message -> TcM ()
addWarnTcM :: (TidyEnv, Message) -> TcM ()
warnTc :: Bool -> Message -> TcM ()
tcInitTidyEnv :: TcM TidyEnv
add_err_tcm :: TidyEnv -> Message -> SrcSpan -> [ErrCtxt] -> TcM ()
mkErrInfo :: TidyEnv -> [ErrCtxt] -> TcM SDoc
mAX_CONTEXTS :: Int
debugTc :: TcM () -> TcM ()
chooseUniqueOccTc :: (OccSet -> OccName) -> TcM OccName
getLIEVar :: TcM (TcRef LIE)
setLIEVar :: TcRef LIE -> TcM a -> TcM a
getLIE :: TcM a -> TcM (a, [Inst])
extendLIE :: Inst -> TcM ()
extendLIEs :: [Inst] -> TcM ()
setLclTypeEnv :: TcLclEnv -> TcM a -> TcM a
getTcTyVarBindsVar :: TcM (TcRef TcTyVarBinds)
getTcTyVarBinds :: TcM a -> TcM (a, TcTyVarBinds)
bindMetaTyVar :: TcTyVar -> TcType -> TcM ()
getTcTyVarBindsRelation :: TcM [(TcTyVar, TcTyVarSet)]
recordThUse :: TcM ()
keepAliveTc :: Id -> TcM ()
keepAliveSetTc :: NameSet -> TcM ()
getStage :: TcM ThStage
setStage :: ThStage -> TcM a -> TcM a
getLocalRdrEnv :: RnM LocalRdrEnv
setLocalRdrEnv :: LocalRdrEnv -> RnM a -> RnM a
mkIfLclEnv :: Module -> SDoc -> IfLclEnv
initIfaceTcRn :: IfG a -> TcRn a
initIfaceExtCore :: IfL a -> TcRn a
initIfaceCheck :: HscEnv -> IfG a -> IO a
initIfaceTc :: ModIface -> (TcRef TypeEnv -> IfL a) -> TcRnIf gbl lcl a
initIfaceRules :: HscEnv -> ModGuts -> IfG a -> IO a
initIfaceLcl :: Module -> SDoc -> IfL a -> IfM lcl a
getIfModule :: IfL Module
failIfM :: Message -> IfL a
forkM_maybe :: SDoc -> IfL a -> IfL (Maybe a)
forkM :: SDoc -> IfL a -> IfL a
module TcRnTypes
module IOEnv
Documentation
initTc :: HscEnv -> HscSource -> Bool -> Module -> TcM r -> IO (Messages, Maybe r)
initTcPrintErrors :: HscEnv -> Module -> TcM r -> IO (Messages, Maybe r)
initTcRnIf :: Char -> HscEnv -> gbl -> lcl -> TcRnIf gbl lcl a -> IO a
getTopEnv :: TcRnIf gbl lcl HscEnv
getGblEnv :: TcRnIf gbl lcl gbl
updGblEnv :: (gbl -> gbl) -> TcRnIf gbl lcl a -> TcRnIf gbl lcl a
setGblEnv :: gbl -> TcRnIf gbl lcl a -> TcRnIf gbl lcl a
getLclEnv :: TcRnIf gbl lcl lcl
updLclEnv :: (lcl -> lcl) -> TcRnIf gbl lcl a -> TcRnIf gbl lcl a
setLclEnv :: lcl' -> TcRnIf gbl lcl' a -> TcRnIf gbl lcl a
getEnvs :: TcRnIf gbl lcl (gbl, lcl)
setEnvs :: (gbl', lcl') -> TcRnIf gbl' lcl' a -> TcRnIf gbl lcl a
getDOpts :: TcRnIf gbl lcl DynFlags
doptM :: DynFlag -> TcRnIf gbl lcl Bool
setOptM :: DynFlag -> TcRnIf gbl lcl a -> TcRnIf gbl lcl a
unsetOptM :: DynFlag -> TcRnIf gbl lcl a -> TcRnIf gbl lcl a
ifOptM :: DynFlag -> TcRnIf gbl lcl () -> TcRnIf gbl lcl ()
Do it flag is true
getGhcMode :: TcRnIf gbl lcl GhcMode
getEpsVar :: TcRnIf gbl lcl (TcRef ExternalPackageState)
getEps :: TcRnIf gbl lcl ExternalPackageState
updateEps :: (ExternalPackageState -> (ExternalPackageState, a)) -> TcRnIf gbl lcl a

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 ()

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
getEpsAndHpt :: TcRnIf gbl lcl (ExternalPackageState, HomePackageTable)
newUnique :: TcRnIf gbl lcl Unique
newUniqueSupply :: TcRnIf gbl lcl UniqSupply
newLocalName :: Name -> TcRnIf gbl lcl Name
newSysLocalIds :: FastString -> [TcType] -> TcRnIf gbl lcl [TcId]
traceRn :: SDoc -> TcRn ()
traceSplice :: SDoc -> TcRn ()
traceTc :: SDoc -> TcRn ()
traceHiDiffs :: SDoc -> TcRnIf m n ()
traceIf :: SDoc -> TcRnIf m n ()
traceOptIf :: DynFlag -> SDoc -> TcRnIf m n ()
traceOptTcRn :: DynFlag -> SDoc -> TcRn ()
dumpTcRn :: SDoc -> TcRn ()
debugDumpTcRn :: SDoc -> TcRn ()
dumpOptTcRn :: DynFlag -> SDoc -> TcRn ()
getModule :: TcRn Module
setModule :: Module -> TcRn a -> TcRn a
tcIsHsBoot :: TcRn Bool
getGlobalRdrEnv :: TcRn GlobalRdrEnv
getRdrEnvs :: TcRn (GlobalRdrEnv, LocalRdrEnv)
getImports :: TcRn ImportAvails
getFixityEnv :: TcRn FixityEnv
extendFixityEnv :: [(Name, FixItem)] -> RnM a -> RnM a
getRecFieldEnv :: TcRn RecFieldEnv
getDeclaredDefaultTys :: TcRn (Maybe [Type])
getSrcSpanM :: TcRn SrcSpan
setSrcSpan :: SrcSpan -> TcRn a -> TcRn a
addLocM :: (a -> TcM b) -> Located a -> TcM b
wrapLocM :: (a -> TcM b) -> Located a -> TcM (Located b)
wrapLocFstM :: (a -> TcM (b, c)) -> Located a -> TcM (Located b, c)
wrapLocSndM :: (a -> TcM (b, c)) -> Located a -> TcM (b, Located c)
getErrsVar :: TcRn (TcRef Messages)
setErrsVar :: TcRef Messages -> TcRn a -> TcRn a
addErr :: Message -> TcRn ()
failWith :: Message -> TcRn a
addErrAt :: SrcSpan -> Message -> TcRn ()
addErrs :: [(SrcSpan, Message)] -> TcRn ()
addWarn :: Message -> TcRn ()
addWarnAt :: SrcSpan -> Message -> TcRn ()
checkErr :: Bool -> Message -> TcRn ()
warnIf :: Bool -> Message -> TcRn ()
addMessages :: Messages -> TcRn ()
discardWarnings :: TcRn a -> TcRn a
addReport :: Message -> Message -> TcRn ()
addReportAt :: SrcSpan -> Message -> Message -> TcRn ()
addLongErrAt :: SrcSpan -> Message -> Message -> TcRn ()
try_m :: TcRn r -> TcRn (Either IOEnvFailure r)
recoverM :: TcRn r -> TcRn r -> TcRn r
mapAndRecoverM :: (a -> TcRn b) -> [a] -> TcRn [b]
tryTc :: TcRn a -> TcRn (Messages, Maybe a)
tryTcErrs :: TcRn a -> TcRn (Messages, Maybe a)
tryTcLIE :: TcM a -> TcM (Messages, Maybe a)
tryTcLIE_ :: TcM r -> TcM r -> TcM r
checkNoErrs :: TcM r -> TcM r
ifErrsM :: TcRn r -> TcRn r -> TcRn r
failIfErrsM :: TcRn ()
getErrCtxt :: TcM [ErrCtxt]
setErrCtxt :: [ErrCtxt] -> TcM a -> TcM a
addErrCtxt :: Message -> TcM a -> TcM a
addErrCtxtM :: (TidyEnv -> TcM (TidyEnv, Message)) -> TcM a -> TcM a
addLandmarkErrCtxt :: Message -> TcM a -> TcM a
updCtxt :: ([ErrCtxt] -> [ErrCtxt]) -> TcM a -> TcM a
maybeAddErrCtxt :: Maybe Message -> TcM a -> TcM a
popErrCtxt :: TcM a -> TcM a
getInstLoc :: InstOrigin -> TcM InstLoc
setInstCtxt :: InstLoc -> TcM a -> TcM a
addErrTc :: Message -> TcM ()
addErrsTc :: [Message] -> TcM ()
addErrTcM :: (TidyEnv, Message) -> TcM ()
failWithTc :: Message -> TcM a
failWithTcM :: (TidyEnv, Message) -> TcM a
checkTc :: Bool -> Message -> TcM ()
addWarnTc :: Message -> TcM ()
addWarnTcM :: (TidyEnv, Message) -> TcM ()
warnTc :: Bool -> Message -> TcM ()
tcInitTidyEnv :: TcM TidyEnv
add_err_tcm :: TidyEnv -> Message -> SrcSpan -> [ErrCtxt] -> TcM ()
mkErrInfo :: TidyEnv -> [ErrCtxt] -> TcM SDoc
mAX_CONTEXTS :: Int
debugTc :: TcM () -> TcM ()
chooseUniqueOccTc :: (OccSet -> OccName) -> TcM OccName
getLIEVar :: TcM (TcRef LIE)
setLIEVar :: TcRef LIE -> TcM a -> TcM a
getLIE :: TcM a -> TcM (a, [Inst])
extendLIE :: Inst -> TcM ()
extendLIEs :: [Inst] -> TcM ()
setLclTypeEnv :: TcLclEnv -> TcM a -> TcM a
getTcTyVarBindsVar :: TcM (TcRef TcTyVarBinds)
getTcTyVarBinds :: TcM a -> TcM (a, TcTyVarBinds)
bindMetaTyVar :: TcTyVar -> TcType -> TcM ()
getTcTyVarBindsRelation :: TcM [(TcTyVar, TcTyVarSet)]
recordThUse :: TcM ()
keepAliveTc :: Id -> TcM ()
keepAliveSetTc :: NameSet -> TcM ()
getStage :: TcM ThStage
setStage :: ThStage -> TcM a -> TcM a
getLocalRdrEnv :: RnM LocalRdrEnv
setLocalRdrEnv :: LocalRdrEnv -> RnM a -> RnM a
mkIfLclEnv :: Module -> SDoc -> IfLclEnv
initIfaceTcRn :: IfG a -> TcRn a
initIfaceExtCore :: IfL a -> TcRn a
initIfaceCheck :: HscEnv -> IfG a -> IO a
initIfaceTc :: ModIface -> (TcRef TypeEnv -> IfL a) -> TcRnIf gbl lcl a
initIfaceRules :: HscEnv -> ModGuts -> IfG a -> IO a
initIfaceLcl :: Module -> SDoc -> IfL a -> IfM lcl a
getIfModule :: IfL Module
failIfM :: Message -> IfL a
forkM_maybe :: SDoc -> IfL a -> IfL (Maybe a)
forkM :: SDoc -> IfL a -> IfL a
module TcRnTypes
module IOEnv
Produced by Haddock version 2.6.0