Safe Haskell | None |
---|---|
Language | Haskell2010 |
- initTc :: HscEnv -> HscSource -> Bool -> Module -> RealSrcSpan -> TcM r -> IO (Messages, Maybe r)
- initTcInteractive :: HscEnv -> TcM a -> IO (Messages, Maybe a)
- initTcForLookup :: HscEnv -> TcM a -> IO a
- initTcRnIf :: Char -> HscEnv -> gbl -> lcl -> TcRnIf gbl lcl a -> IO a
- discardResult :: TcM a -> TcM ()
- 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
- xoptM :: ExtensionFlag -> TcRnIf gbl lcl Bool
- doptM :: DumpFlag -> TcRnIf gbl lcl Bool
- goptM :: GeneralFlag -> TcRnIf gbl lcl Bool
- woptM :: WarningFlag -> TcRnIf gbl lcl Bool
- setXOptM :: ExtensionFlag -> TcRnIf gbl lcl a -> TcRnIf gbl lcl a
- unsetGOptM :: GeneralFlag -> TcRnIf gbl lcl a -> TcRnIf gbl lcl a
- unsetWOptM :: WarningFlag -> TcRnIf gbl lcl a -> TcRnIf gbl lcl a
- whenDOptM :: DumpFlag -> TcRnIf gbl lcl () -> TcRnIf gbl lcl ()
- whenGOptM :: GeneralFlag -> TcRnIf gbl lcl () -> TcRnIf gbl lcl ()
- whenWOptM :: WarningFlag -> TcRnIf gbl lcl () -> TcRnIf gbl lcl ()
- whenXOptM :: ExtensionFlag -> TcRnIf gbl lcl () -> TcRnIf gbl lcl ()
- getGhcMode :: TcRnIf gbl lcl GhcMode
- withDoDynamicToo :: TcRnIf gbl lcl a -> TcRnIf gbl lcl a
- 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)
- newArrowScope :: TcM a -> TcM a
- escapeArrowScope :: TcM a -> TcM a
- newUnique :: TcRnIf gbl lcl Unique
- newUniqueSupply :: TcRnIf gbl lcl UniqSupply
- newLocalName :: Name -> TcM Name
- newName :: OccName -> TcM Name
- newSysName :: OccName -> TcM Name
- newSysLocalId :: FastString -> TcType -> TcRnIf gbl lcl TcId
- newSysLocalIds :: FastString -> [TcType] -> TcRnIf gbl lcl [TcId]
- newTcRef :: a -> TcRnIf gbl lcl (TcRef a)
- readTcRef :: TcRef a -> TcRnIf gbl lcl a
- writeTcRef :: TcRef a -> a -> TcRnIf gbl lcl ()
- updTcRef :: TcRef a -> (a -> a) -> TcRnIf gbl lcl ()
- updTcRefX :: TcRef a -> (a -> a) -> TcRnIf gbl lcl a
- traceTc :: String -> SDoc -> TcRn ()
- traceTcN :: Int -> SDoc -> TcRn ()
- traceRn :: SDoc -> TcRn ()
- traceOptTcRn :: DumpFlag -> SDoc -> TcRn ()
- traceTcRn :: DumpFlag -> SDoc -> TcRn ()
- getPrintUnqualified :: DynFlags -> TcRn PrintUnqualified
- printForUserTcRn :: SDoc -> TcRn ()
- debugDumpTcRn :: SDoc -> TcRn ()
- traceIf :: SDoc -> TcRnIf m n ()
- traceHiDiffs :: SDoc -> TcRnIf m n ()
- traceOptIf :: DumpFlag -> SDoc -> TcRnIf m n ()
- setModule :: Module -> TcRn a -> TcRn a
- getIsGHCi :: TcRn Bool
- getGHCiMonad :: TcRn Name
- getInteractivePrintName :: TcRn Name
- tcIsHsBootOrSig :: 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])
- addDependentFiles :: [FilePath] -> TcRn ()
- 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 :: MsgDoc -> TcRn ()
- failWith :: MsgDoc -> TcRn a
- addErrAt :: SrcSpan -> MsgDoc -> TcRn ()
- addErrs :: [(SrcSpan, MsgDoc)] -> TcRn ()
- checkErr :: Bool -> MsgDoc -> TcRn ()
- warnIf :: Bool -> MsgDoc -> TcRn ()
- addMessages :: Messages -> TcRn ()
- discardWarnings :: TcRn a -> TcRn a
- mkLongErrAt :: SrcSpan -> MsgDoc -> MsgDoc -> TcRn ErrMsg
- addLongErrAt :: SrcSpan -> MsgDoc -> MsgDoc -> TcRn ()
- reportErrors :: [ErrMsg] -> TcM ()
- reportError :: ErrMsg -> TcRn ()
- reportWarning :: ErrMsg -> TcRn ()
- try_m :: TcRn r -> TcRn (Either IOEnvFailure r)
- recoverM :: TcRn r -> TcRn r -> TcRn r
- mapAndRecoverM :: (a -> TcRn b) -> [a] -> TcRn [b]
- mapAndReportM :: (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
- whenNoErrs :: TcM () -> TcM ()
- ifErrsM :: TcRn r -> TcRn r -> TcRn r
- failIfErrsM :: TcRn ()
- checkTH :: Outputable a => a -> String -> TcRn ()
- failTH :: Outputable a => a -> String -> TcRn x
- getErrCtxt :: TcM [ErrCtxt]
- setErrCtxt :: [ErrCtxt] -> TcM a -> TcM a
- addErrCtxt :: MsgDoc -> TcM a -> TcM a
- addErrCtxtM :: (TidyEnv -> TcM (TidyEnv, MsgDoc)) -> TcM a -> TcM a
- addLandmarkErrCtxt :: MsgDoc -> TcM a -> TcM a
- updCtxt :: ([ErrCtxt] -> [ErrCtxt]) -> TcM a -> TcM a
- popErrCtxt :: TcM a -> TcM a
- getCtLoc :: CtOrigin -> TcM CtLoc
- setCtLoc :: CtLoc -> TcM a -> TcM a
- addErrTc :: MsgDoc -> TcM ()
- addErrsTc :: [MsgDoc] -> TcM ()
- addErrTcM :: (TidyEnv, MsgDoc) -> TcM ()
- mkErrTcM :: (TidyEnv, MsgDoc) -> TcM ErrMsg
- failWithTc :: MsgDoc -> TcM a
- failWithTcM :: (TidyEnv, MsgDoc) -> TcM a
- checkTc :: Bool -> MsgDoc -> TcM ()
- warnTc :: Bool -> MsgDoc -> TcM ()
- addWarnTc :: MsgDoc -> TcM ()
- addWarnTcM :: (TidyEnv, MsgDoc) -> TcM ()
- addWarn :: MsgDoc -> TcRn ()
- addWarnAt :: SrcSpan -> MsgDoc -> TcRn ()
- add_warn :: MsgDoc -> MsgDoc -> TcRn ()
- add_warn_at :: SrcSpan -> MsgDoc -> MsgDoc -> TcRn ()
- tcInitTidyEnv :: TcM TidyEnv
- add_err_tcm :: TidyEnv -> MsgDoc -> SrcSpan -> [ErrCtxt] -> TcM ()
- mkErrInfo :: TidyEnv -> [ErrCtxt] -> TcM SDoc
- mAX_CONTEXTS :: Int
- debugTc :: TcM () -> TcM ()
- newTcEvBinds :: TcM EvBindsVar
- addTcEvBind :: EvBindsVar -> EvVar -> EvTerm -> TcM ()
- getTcEvBinds :: EvBindsVar -> TcM (Bag EvBind)
- chooseUniqueOccTc :: (OccSet -> OccName) -> TcM OccName
- getConstraintVar :: TcM (TcRef WantedConstraints)
- setConstraintVar :: TcRef WantedConstraints -> TcM a -> TcM a
- emitConstraints :: WantedConstraints -> TcM ()
- emitSimple :: Ct -> TcM ()
- emitSimples :: Cts -> TcM ()
- emitImplication :: Implication -> TcM ()
- emitImplications :: Bag Implication -> TcM ()
- emitInsoluble :: Ct -> TcM ()
- captureConstraints :: TcM a -> TcM (a, WantedConstraints)
- captureTcLevel :: TcM a -> TcM (a, TcLevel)
- pushTcLevelM :: TcM a -> TcM a
- getTcLevel :: TcM TcLevel
- setTcLevel :: TcLevel -> TcM a -> TcM a
- isTouchableTcM :: TcTyVar -> TcM Bool
- getLclTypeEnv :: TcM TcTypeEnv
- setLclTypeEnv :: TcLclEnv -> TcM a -> TcM a
- traceTcConstraints :: String -> TcM ()
- emitWildcardHoleConstraints :: [(Name, TcTyVar)] -> TcM ()
- recordThUse :: TcM ()
- recordThSpliceUse :: TcM ()
- keepAlive :: Name -> TcRn ()
- getStage :: TcM ThStage
- getStageAndBindLevel :: Name -> TcRn (Maybe (TopLevelFlag, ThLevel, ThStage))
- setStage :: ThStage -> TcM a -> TcRn a
- recordUnsafeInfer :: TcM ()
- finalSafeMode :: DynFlags -> TcGblEnv -> IO SafeHaskellMode
- getLocalRdrEnv :: RnM LocalRdrEnv
- setLocalRdrEnv :: LocalRdrEnv -> RnM a -> RnM a
- mkIfLclEnv :: Module -> SDoc -> IfLclEnv
- initIfaceTcRn :: IfG a -> TcRn a
- initIfaceCheck :: HscEnv -> IfG a -> IO a
- initIfaceTc :: ModIface -> (TcRef TypeEnv -> IfL a) -> TcRnIf gbl lcl a
- initIfaceLcl :: Module -> SDoc -> IfL a -> IfM lcl a
- getIfModule :: IfL Module
- failIfM :: MsgDoc -> 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 -> RealSrcSpan -> TcM r -> IO (Messages, Maybe r) Source
Setup the initial typechecking environment
initTcForLookup :: HscEnv -> TcM a -> IO a Source
discardResult :: TcM a -> TcM () Source
xoptM :: ExtensionFlag -> TcRnIf gbl lcl Bool Source
goptM :: GeneralFlag -> TcRnIf gbl lcl Bool Source
woptM :: WarningFlag -> TcRnIf gbl lcl Bool Source
setXOptM :: ExtensionFlag -> 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
whenGOptM :: GeneralFlag -> TcRnIf gbl lcl () -> TcRnIf gbl lcl () Source
whenWOptM :: WarningFlag -> TcRnIf gbl lcl () -> TcRnIf gbl lcl () Source
whenXOptM :: ExtensionFlag -> 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
newArrowScope :: TcM a -> TcM a Source
escapeArrowScope :: TcM a -> TcM a Source
newUniqueSupply :: TcRnIf gbl lcl UniqSupply Source
newLocalName :: Name -> TcM Name Source
newSysName :: OccName -> TcM Name Source
newSysLocalId :: FastString -> TcType -> TcRnIf gbl lcl TcId Source
newSysLocalIds :: FastString -> [TcType] -> TcRnIf gbl lcl [TcId] Source
writeTcRef :: TcRef a -> a -> TcRnIf gbl lcl () Source
traceOptTcRn :: DumpFlag -> SDoc -> TcRn () Source
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
traceHiDiffs :: SDoc -> TcRnIf m n () Source
traceOptIf :: DumpFlag -> SDoc -> TcRnIf m n () Source
getDeclaredDefaultTys :: TcRn (Maybe [Type]) Source
addDependentFiles :: [FilePath] -> TcRn () Source
setSrcSpan :: SrcSpan -> TcRn a -> TcRn a Source
getErrsVar :: TcRn (TcRef Messages) Source
addMessages :: Messages -> TcRn () Source
discardWarnings :: TcRn a -> TcRn a Source
reportErrors :: [ErrMsg] -> TcM () Source
reportError :: ErrMsg -> TcRn () Source
reportWarning :: ErrMsg -> TcRn () 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.
checkNoErrs :: TcM r -> TcM r Source
whenNoErrs :: TcM () -> TcM () Source
failIfErrsM :: TcRn () Source
checkTH :: Outputable a => a -> String -> TcRn () Source
failTH :: Outputable a => a -> String -> TcRn x Source
getErrCtxt :: TcM [ErrCtxt] Source
setErrCtxt :: [ErrCtxt] -> TcM a -> TcM a Source
addErrCtxt :: MsgDoc -> TcM a -> TcM a Source
addLandmarkErrCtxt :: MsgDoc -> TcM a -> TcM a Source
popErrCtxt :: TcM a -> TcM a Source
failWithTc :: MsgDoc -> TcM a Source
failWithTcM :: (TidyEnv, MsgDoc) -> TcM a Source
addWarnTcM :: (TidyEnv, MsgDoc) -> TcM () Source
addTcEvBind :: EvBindsVar -> EvVar -> EvTerm -> TcM () Source
getTcEvBinds :: EvBindsVar -> TcM (Bag EvBind) Source
setConstraintVar :: TcRef WantedConstraints -> TcM a -> TcM a Source
emitConstraints :: WantedConstraints -> TcM () Source
emitSimple :: Ct -> TcM () Source
emitSimples :: Cts -> TcM () Source
emitImplication :: Implication -> TcM () Source
emitImplications :: Bag Implication -> TcM () Source
emitInsoluble :: Ct -> TcM () Source
captureConstraints :: TcM a -> TcM (a, WantedConstraints) Source
captureTcLevel :: TcM a -> TcM (a, TcLevel) Source
pushTcLevelM :: TcM a -> TcM a Source
setTcLevel :: TcLevel -> TcM a -> TcM a Source
isTouchableTcM :: TcTyVar -> TcM Bool Source
setLclTypeEnv :: TcLclEnv -> TcM a -> TcM a Source
traceTcConstraints :: String -> TcM () Source
emitWildcardHoleConstraints :: [(Name, TcTyVar)] -> TcM () Source
recordThUse :: TcM () Source
recordThSpliceUse :: TcM () Source
getStageAndBindLevel :: Name -> TcRn (Maybe (TopLevelFlag, ThLevel, ThStage)) Source
recordUnsafeInfer :: TcM () Source
Mark that safe inference has failed
finalSafeMode :: DynFlags -> TcGblEnv -> IO SafeHaskellMode Source
Figure out the final correct safe haskell mode
setLocalRdrEnv :: LocalRdrEnv -> RnM a -> RnM a Source
mkIfLclEnv :: Module -> SDoc -> IfLclEnv Source
initIfaceTcRn :: IfG a -> TcRn a Source
initIfaceCheck :: HscEnv -> IfG a -> IO a Source
module TcRnTypes
module IOEnv