ghc-9.2.5: The GHC API
Safe HaskellSafe-Inferred
LanguageHaskell2010

GHC.Core.Opt.Monad

Synopsis

Configuration of the core-to-core passes

data SimplMode Source #

Constructors

SimplMode 

Fields

Instances

Instances details
Outputable SimplMode Source # 
Instance details

Defined in GHC.Core.Opt.Monad

Methods

ppr :: SimplMode -> SDoc Source #

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.

Instances

Instances details
Outputable FloatOutSwitches Source # 
Instance details

Defined in GHC.Core.Opt.Monad

Plugins

type CorePluginPass = ModGuts -> CoreM ModGuts Source #

A description of the plugin pass itself

Counting

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
MonadIO CoreM Source # 
Instance details

Defined in GHC.Core.Opt.Monad

Methods

liftIO :: IO a -> CoreM a Source #

Alternative CoreM Source # 
Instance details

Defined in GHC.Core.Opt.Monad

Methods

empty :: CoreM a Source #

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

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

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

Applicative CoreM Source # 
Instance details

Defined in GHC.Core.Opt.Monad

Methods

pure :: a -> CoreM a Source #

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

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

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

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

Functor CoreM Source # 
Instance details

Defined in GHC.Core.Opt.Monad

Methods

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

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

Monad CoreM Source # 
Instance details

Defined in GHC.Core.Opt.Monad

Methods

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

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

return :: a -> CoreM a Source #

MonadPlus CoreM Source # 
Instance details

Defined in GHC.Core.Opt.Monad

Methods

mzero :: CoreM a Source #

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

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

runCoreM Source #

Arguments

:: HscEnv 
-> RuleBase 
-> Char

Mask

-> Module 
-> ModuleSet 
-> PrintUnqualified 
-> SrcSpan 
-> CoreM a 
-> IO (a, SimplCount) 

Reading from the monad

Writing to the monad

Lifting into the monad

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

Lift a computation from the IO monad. This allows us to run IO computations in any monadic stack, so long as it supports these kinds of operations (i.e. IO is the base monad for the stack).

Example

Expand
import Control.Monad.Trans.State -- from the "transformers" library

printState :: Show s => StateT s IO ()
printState = do
  state <- get
  liftIO $ print state

Had we omitted liftIO, we would have ended up with this error:

• Couldn't match type ‘IO’ with ‘StateT s IO’
 Expected type: StateT s IO ()
   Actual type: IO ()

The important part here is the mismatch between StateT s IO () and IO ().

Luckily, we know of a function that takes an IO a and returns an (m a): liftIO, enabling us to run the program and see the expected results:

> evalStateT printState "hello"
"hello"

> evalStateT printState 3
3

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.

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

dumpIfSet_dyn :: DumpFlag -> String -> DumpFormat -> SDoc -> CoreM () Source #

Show some labelled SDoc if a particular flag is set or at a verbosity level of -v -ddump-most or higher