Safe Haskell | None |
---|---|
Language | GHC2021 |
Synopsis
- data FloatOutSwitches = FloatOutSwitches {}
- data CoreM a
- runCoreM :: HscEnv -> RuleBase -> Char -> Module -> NamePprCtx -> SrcSpan -> CoreM a -> IO (a, SimplCount)
- mapDynFlagsCoreM :: (DynFlags -> DynFlags) -> CoreM a -> CoreM a
- dropSimplCount :: CoreM a -> CoreM a
- getHscEnv :: CoreM HscEnv
- getModule :: HasModule m => m Module
- initRuleEnv :: ModGuts -> CoreM RuleEnv
- getExternalRuleBase :: CoreM RuleBase
- getDynFlags :: HasDynFlags m => m DynFlags
- getPackageFamInstEnv :: CoreM PackageFamInstEnv
- getInteractiveContext :: CoreM InteractiveContext
- getUniqTag :: CoreM Char
- getNamePprCtx :: CoreM NamePprCtx
- getSrcSpanM :: CoreM SrcSpan
- addSimplCount :: SimplCount -> CoreM ()
- liftIO :: MonadIO m => IO a -> m a
- liftIOWithCount :: IO (SimplCount, a) -> CoreM a
- getAnnotations :: Typeable a => ([Word8] -> a) -> ModGuts -> CoreM (ModuleEnv [a], NameEnv [a])
- getFirstAnnotations :: Typeable a => ([Word8] -> a) -> ModGuts -> CoreM (ModuleEnv a, NameEnv a)
- putMsg :: SDoc -> CoreM ()
- putMsgS :: String -> CoreM ()
- errorMsg :: SDoc -> CoreM ()
- msg :: MessageClass -> SDoc -> CoreM ()
- fatalErrorMsg :: SDoc -> CoreM ()
- fatalErrorMsgS :: String -> CoreM ()
- debugTraceMsg :: SDoc -> CoreM ()
- debugTraceMsgS :: String -> CoreM ()
Types used in core-to-core passes
data FloatOutSwitches Source #
FloatOutSwitches | |
|
Instances
Outputable FloatOutSwitches Source # | |
Defined in GHC.Core.Opt.Monad ppr :: FloatOutSwitches -> SDoc Source # |
The monad
The monad used by Core-to-Core passes to register simplification statistics. Also used to have common state (in the form of UniqueSupply) for generating Uniques.
Instances
HasDynFlags CoreM Source # | |
Defined in GHC.Core.Opt.Monad | |
MonadThings CoreM Source # | |
MonadUnique CoreM Source # | |
Defined in GHC.Core.Opt.Monad | |
HasModule CoreM Source # | |
HasLogger CoreM Source # | |
Alternative CoreM Source # | |
Applicative CoreM Source # | |
Functor CoreM Source # | |
Monad CoreM Source # | |
MonadPlus CoreM Source # | |
MonadIO CoreM Source # | |
Defined in GHC.Core.Opt.Monad |
:: HscEnv | |
-> RuleBase | |
-> Char | Mask |
-> Module | |
-> NamePprCtx | |
-> SrcSpan | |
-> CoreM a | |
-> IO (a, SimplCount) |
mapDynFlagsCoreM :: (DynFlags -> DynFlags) -> CoreM a -> CoreM a Source #
Adjust the dyn flags passed to the argument action
dropSimplCount :: CoreM a -> CoreM a Source #
Drop the single count of the argument action so it doesn't effect the total.
Reading from the monad
getDynFlags :: HasDynFlags m => m DynFlags Source #
getUniqTag :: CoreM Char Source #
Writing to the monad
addSimplCount :: SimplCount -> CoreM () Source #
Lifting into the monad
liftIOWithCount :: IO (SimplCount, a) -> CoreM a Source #
Lift an IO
operation into CoreM
while consuming its SimplCount
Dealing with annotations
getAnnotations :: Typeable a => ([Word8] -> a) -> ModGuts -> CoreM (ModuleEnv [a], NameEnv [a]) Source #
Get all annotations of a given type. This happens lazily, that is no deserialization will take place until the [a] is actually demanded and the [a] can also be empty (the UniqFM is not filtered).
This should be done once at the start of a Core-to-Core pass that uses annotations.
See Note [Annotations]
getFirstAnnotations :: Typeable a => ([Word8] -> a) -> ModGuts -> CoreM (ModuleEnv a, NameEnv a) Source #
Get at most one annotation of a given type per annotatable item.
Screen output
errorMsg :: SDoc -> CoreM () Source #
Output an error to the screen. Does not cause the compiler to die.
fatalErrorMsg :: SDoc -> CoreM () Source #
Output a fatal error to the screen. Does not cause the compiler to die.
fatalErrorMsgS :: String -> CoreM () Source #
Output a fatal error to the screen. Does not cause the compiler to die.
debugTraceMsg :: SDoc -> CoreM () Source #
Outputs a debugging message at verbosity level of -v
or higher
debugTraceMsgS :: String -> CoreM () Source #
Output a string debugging message at verbosity level of -v
or higher