ghc-8.4.1: The GHC API

Safe HaskellNone
LanguageHaskell2010

CoreMonad

Contents

Synopsis

Configuration of the 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 SetLevels

  • floatToTopLevelOnly :: Bool

    Allow floating to the top level only.

Plugins

type PluginPass = 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 access common state, register simplification statistics and so on

Instances
Monad CoreM Source # 
Instance details

Methods

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

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

return :: a -> CoreM a #

fail :: String -> CoreM a #

Functor CoreM Source # 
Instance details

Methods

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

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

Applicative CoreM Source # 
Instance details

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 #

MonadIO CoreM Source # 
Instance details

Methods

liftIO :: IO a -> CoreM a #

Alternative CoreM Source # 
Instance details

Methods

empty :: CoreM a #

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

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

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

MonadPlus CoreM Source # 
Instance details

Methods

mzero :: CoreM a #

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

MonadUnique CoreM Source # 
Instance details
HasModule CoreM Source # 
Instance details
HasDynFlags CoreM Source # 
Instance details
MonadThings CoreM Source # 
Instance details

Reading from the monad

getOrigNameCache :: CoreM OrigNameCache Source #

The original name cache is the current mapping from Module and OccName to a compiler-wide unique Name

Writing to the monad

Lifting into the monad

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

Lift a computation from the IO monad.

liftIOWithCount :: IO (SimplCount, a) -> CoreM a Source #

Lift an IO operation into CoreM while consuming its SimplCount

liftIO1 :: MonadIO m => (a -> IO b) -> a -> m b Source #

Lift an IO operation with 1 argument into another monad

liftIO2 :: MonadIO m => (a -> b -> IO c) -> a -> b -> m c Source #

Lift an IO operation with 2 arguments into another monad

liftIO3 :: MonadIO m => (a -> b -> c -> IO d) -> a -> b -> c -> m d Source #

Lift an IO operation with 3 arguments into another monad

liftIO4 :: MonadIO m => (a -> b -> c -> d -> IO e) -> a -> b -> c -> d -> m e Source #

Lift an IO operation with 4 arguments into another monad

Global initialization

reinitializeGlobals :: CoreM () Source #

Deprecated: It is not necessary to call reinitializeGlobals. Since GHC 8.2, this function is a no-op and will be removed in GHC 8.4

Dealing with annotations

getAnnotations :: Typeable a => ([Word8] -> a) -> ModGuts -> CoreM (UniqFM [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 (UniqFM a) Source #

Get at most one annotation of a given type per Unique.

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 -> SDoc -> CoreM () Source #

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

Getting Names

thNameToGhcName :: Name -> CoreM (Maybe Name) Source #

Attempt to convert a Template Haskell name to one that GHC can understand. Original TH names such as those you get when you use the 'foo syntax will be translated to their equivalent GHC name exactly. Qualified or unqualified TH names will be dynamically bound to names in the module being compiled, if possible. Exact TH names will be bound to the name they represent, exactly.