ghc-9.11: The GHC API
Safe HaskellNone
LanguageGHC2021

GHC.Core.Opt.Monad

Synopsis

Types used in core-to-core passes

data FloatOutSwitches Source #

Constructors

FloatOutSwitches 

Fields

  • floatOutLambdas :: Maybe Int

    Just n = float lambdas to top level, if doing so will abstract over n or fewer value variables Nothing = float all lambdas to top level, regardless of how many free variables Just 0 is the vanilla case: float a lambda iff it has no free vars

  • floatOutConstants :: Bool

    True = float constants to top level, even if they do not escape a lambda

  • floatOutOverSatApps :: Bool

    True = float out over-saturated applications based on arity information. See Note [Floating over-saturated applications] in GHC.Core.Opt.SetLevels

  • floatToTopLevelOnly :: Bool

    Allow floating to the top level only.

  • floatJoinsToTop :: Bool

    Float join points to top level if possible See Note [Floating join point bindings] in GHC.Core.Opt.SetLevels

Instances

Instances details
Outputable FloatOutSwitches Source # 
Instance details

Defined in GHC.Core.Opt.Monad

The monad

data CoreM a Source #

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

Instances details
HasDynFlags CoreM Source # 
Instance details

Defined in GHC.Core.Opt.Monad

MonadThings CoreM Source # 
Instance details

Defined in GHC.Plugins

MonadUnique CoreM Source # 
Instance details

Defined in GHC.Core.Opt.Monad

HasModule CoreM Source # 
Instance details

Defined in GHC.Core.Opt.Monad

HasLogger CoreM Source # 
Instance details

Defined in GHC.Core.Opt.Monad

Alternative CoreM Source # 
Instance details

Defined in GHC.Core.Opt.Monad

Methods

empty :: CoreM a #

(<|>) :: CoreM a -> CoreM a -> CoreM a #

some :: CoreM a -> CoreM [a] #

many :: CoreM a -> CoreM [a] #

Applicative CoreM Source # 
Instance details

Defined in GHC.Core.Opt.Monad

Methods

pure :: a -> CoreM a #

(<*>) :: CoreM (a -> b) -> CoreM a -> CoreM b #

liftA2 :: (a -> b -> c) -> CoreM a -> CoreM b -> CoreM c #

(*>) :: CoreM a -> CoreM b -> CoreM b #

(<*) :: CoreM a -> CoreM b -> CoreM a #

Functor CoreM Source # 
Instance details

Defined in GHC.Core.Opt.Monad

Methods

fmap :: (a -> b) -> CoreM a -> CoreM b #

(<$) :: a -> CoreM b -> CoreM a #

Monad CoreM Source # 
Instance details

Defined in GHC.Core.Opt.Monad

Methods

(>>=) :: CoreM a -> (a -> CoreM b) -> CoreM b #

(>>) :: CoreM a -> CoreM b -> CoreM b #

return :: a -> CoreM a #

MonadPlus CoreM Source # 
Instance details

Defined in GHC.Core.Opt.Monad

Methods

mzero :: CoreM a #

mplus :: CoreM a -> CoreM a -> CoreM a #

MonadIO CoreM Source # 
Instance details

Defined in GHC.Core.Opt.Monad

Methods

liftIO :: IO a -> CoreM a #

runCoreM Source #

Arguments

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

Writing to the monad

Lifting into the monad

liftIO :: MonadIO m => IO a -> m a #

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

putMsg :: SDoc -> CoreM () Source #

Output a message to the screen

putMsgS :: String -> CoreM () Source #

Output a String message to the screen

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