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
- updTopEnv :: (HscEnv -> HscEnv) -> TcRnIf gbl lcl a -> TcRnIf gbl lcl a
- 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 :: Extension -> TcRnIf gbl lcl Bool
- doptM :: DumpFlag -> TcRnIf gbl lcl Bool
- goptM :: GeneralFlag -> TcRnIf gbl lcl Bool
- woptM :: WarningFlag -> TcRnIf gbl lcl Bool
- setXOptM :: Extension -> 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 :: Extension -> 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 -> TcRnIf gbl lcl 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
- tcSelfBootInfo :: TcRn SelfBootInfo
- 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
- failAt :: SrcSpan -> MsgDoc -> TcRn a
- addErrAt :: SrcSpan -> MsgDoc -> TcRn ()
- addErrs :: [(SrcSpan, MsgDoc)] -> TcRn ()
- checkErr :: Bool -> MsgDoc -> TcRn ()
- warnIf :: WarnReason -> Bool -> MsgDoc -> TcRn ()
- addMessages :: Messages -> TcRn ()
- discardWarnings :: TcRn a -> TcRn a
- mkLongErrAt :: SrcSpan -> MsgDoc -> MsgDoc -> TcRn ErrMsg
- mkErrDocAt :: SrcSpan -> ErrDoc -> TcRn ErrMsg
- addLongErrAt :: SrcSpan -> MsgDoc -> MsgDoc -> TcRn ()
- reportErrors :: [ErrMsg] -> TcM ()
- reportError :: ErrMsg -> TcRn ()
- reportWarning :: WarnReason -> 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)
- askNoErrs :: TcRn a -> TcRn (a, Bool)
- discardErrs :: TcRn a -> TcRn 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 :: 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
- addLandmarkErrCtxtM :: (TidyEnv -> TcM (TidyEnv, MsgDoc)) -> TcM a -> TcM a
- updCtxt :: ([ErrCtxt] -> [ErrCtxt]) -> TcM a -> TcM a
- popErrCtxt :: TcM a -> TcM a
- getCtLocM :: CtOrigin -> Maybe TypeOrKind -> TcM CtLoc
- setCtLocM :: 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 ()
- checkTcM :: Bool -> (TidyEnv, MsgDoc) -> TcM ()
- failIfTc :: Bool -> MsgDoc -> TcM ()
- failIfTcM :: Bool -> (TidyEnv, MsgDoc) -> TcM ()
- warnTc :: WarnReason -> Bool -> MsgDoc -> TcM ()
- warnTcM :: WarnReason -> Bool -> (TidyEnv, MsgDoc) -> TcM ()
- addWarnTc :: WarnReason -> MsgDoc -> TcM ()
- addWarnTcM :: WarnReason -> (TidyEnv, MsgDoc) -> TcM ()
- addWarn :: WarnReason -> MsgDoc -> TcRn ()
- addWarnAt :: WarnReason -> SrcSpan -> MsgDoc -> TcRn ()
- add_warn :: WarnReason -> MsgDoc -> MsgDoc -> TcRn ()
- add_warn_at :: WarnReason -> SrcSpan -> MsgDoc -> MsgDoc -> TcRn ()
- tcInitTidyEnv :: TcM TidyEnv
- tcInitOpenTidyEnv :: TyCoVarSet -> 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 -> EvBind -> TcM ()
- getTcEvBinds :: EvBindsVar -> TcM (Bag EvBind)
- getTcEvBindsMap :: EvBindsVar -> TcM EvBindMap
- 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 ()
- discardConstraints :: TcM a -> TcM a
- captureConstraints :: TcM a -> TcM (a, WantedConstraints)
- pushLevelAndCaptureConstraints :: TcM a -> TcM (TcLevel, WantedConstraints, a)
- pushTcLevelM_ :: TcM a -> TcM a
- pushTcLevelM :: TcM a -> TcM (a, TcLevel)
- 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 ()
- recordTopLevelSpliceLoc :: SrcSpan -> TcM ()
- getTopLevelSpliceLocs :: TcM (Set RealSrcSpan)
- keepAlive :: Name -> TcRn ()
- getStage :: TcM ThStage
- getStageAndBindLevel :: Name -> TcRn (Maybe (TopLevelFlag, ThLevel, ThStage))
- setStage :: ThStage -> TcM a -> TcRn a
- recordUnsafeInfer :: WarningMessages -> TcM ()
- finalSafeMode :: DynFlags -> TcGblEnv -> IO SafeHaskellMode
- fixSafeInstances :: SafeHaskellMode -> [ClsInst] -> [ClsInst]
- 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
discardResult :: TcM a -> TcM () Source #
unsetGOptM :: GeneralFlag -> TcRnIf gbl lcl a -> TcRnIf gbl lcl a Source #
unsetWOptM :: WarningFlag -> TcRnIf gbl lcl a -> TcRnIf gbl lcl a Source #
getGhcMode :: TcRnIf gbl lcl GhcMode Source #
withDoDynamicToo :: TcRnIf gbl lcl a -> TcRnIf gbl lcl a 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 #
newSysLocalId :: FastString -> TcType -> TcRnIf gbl lcl TcId Source #
newSysLocalIds :: FastString -> [TcType] -> TcRnIf gbl lcl [TcId] Source #
writeTcRef :: TcRef a -> a -> TcRnIf gbl lcl () 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 #
getGHCiMonad :: TcRn Name Source #
getRdrEnvs :: TcRn (GlobalRdrEnv, LocalRdrEnv) Source #
addDependentFiles :: [FilePath] -> TcRn () Source #
addMessages :: Messages -> TcRn () Source #
discardWarnings :: TcRn a -> TcRn a Source #
reportErrors :: [ErrMsg] -> TcM () Source #
reportError :: ErrMsg -> TcRn () Source #
reportWarning :: WarnReason -> 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.
discardErrs :: TcRn a -> TcRn a Source #
checkNoErrs :: TcM r -> TcM r Source #
whenNoErrs :: TcM () -> TcM () Source #
failIfErrsM :: TcRn () Source #
getErrCtxt :: TcM [ErrCtxt] 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 #
failWithTc :: MsgDoc -> TcM a Source #
warnTcM :: WarnReason -> Bool -> (TidyEnv, MsgDoc) -> TcM () Source #
Display a warning if a condition is met.
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.
add_warn_at :: WarnReason -> SrcSpan -> MsgDoc -> MsgDoc -> TcRn () Source #
Display a warning, with an optional flag, for a given location.
tcInitOpenTidyEnv :: TyCoVarSet -> TcM TidyEnv Source #
Get a TidyEnv
that includes mappings for all vars free in the given
type. Useful when tidying open types.
mAX_CONTEXTS :: Int Source #
addTcEvBind :: EvBindsVar -> EvBind -> TcM () Source #
getTcEvBinds :: EvBindsVar -> TcM (Bag EvBind) Source #
getTcEvBindsMap :: EvBindsVar -> TcM EvBindMap 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 #
discardConstraints :: TcM a -> TcM a Source #
Throw out any constraints emitted by the thing_inside
captureConstraints :: TcM a -> TcM (a, WantedConstraints) Source #
pushLevelAndCaptureConstraints :: TcM a -> TcM (TcLevel, WantedConstraints, a) Source #
pushTcLevelM_ :: TcM a -> TcM a Source #
getTcLevel :: TcM TcLevel Source #
traceTcConstraints :: String -> TcM () Source #
recordThUse :: TcM () Source #
recordThSpliceUse :: TcM () Source #
recordTopLevelSpliceLoc :: SrcSpan -> TcM () Source #
When generating an out-of-scope error message for a variable matching a binding in a later inter-splice group, the typechecker uses the splice locations to provide details in the message about the scope of that binding.
getStageAndBindLevel :: Name -> TcRn (Maybe (TopLevelFlag, ThLevel, ThStage)) Source #
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.
setLocalRdrEnv :: LocalRdrEnv -> RnM a -> RnM a Source #
initIfaceTcRn :: IfG a -> TcRn a Source #
getIfModule :: IfL Module Source #
module TcRnTypes
module IOEnv
Orphan instances
MonadUnique (IOEnv (Env gbl lcl)) # | |