ghc-7.4.1: The GHC API

Safe HaskellSafe-Infered

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

floatOutPartialApplications :: Bool

True = float out partial applications based on arity information.

Plugins

type PluginPass = ModGuts -> CoreM ModGutsSource

A description of the plugin pass itself

data Plugin Source

Plugin is the core compiler plugin data type. Try to avoid constructing one of these directly, and just modify some fields of defaultPlugin instead: this is to try and preserve source-code compatability when we add fields to this.

Nonetheless, this API is preliminary and highly likely to change in the future.

Constructors

Plugin 

Fields

installCoreToDos :: [CommandLineOption] -> [CoreToDo] -> CoreM [CoreToDo]

Modify the Core pipeline that will be used for compilation. This is called as the Core pipeline is built for every module being compiled, and plugins get the opportunity to modify the pipeline in a nondeterministic order.

type CommandLineOption = StringSource

Command line options gathered from the -PModule.Name:stuff syntax are given to you as this type

defaultPlugin :: PluginSource

Default plugin: does nothing at all! For compatability reasons you should base all your plugin definitions on this default value.

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

Reading from the monad

getOrigNameCache :: CoreM OrigNameCacheSource

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 aSource

liftIOWithCount :: IO (SimplCount, a) -> CoreM aSource

Lift an IO operation into CoreM while consuming its SimplCount

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

Lift an IO operation with 1 argument into another monad

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

Lift an IO operation with 2 arguments into another monad

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

Lift an IO operation with 3 arguments into another monad

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

Lift an IO operation with 4 arguments into another monad

Global initialization

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.

Debug output

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

errorMsgS :: String -> CoreM ()Source

Output a string error to the screen

fatalErrorMsg :: SDoc -> CoreM ()Source

Output a fatal error to the screen. Note this does not by itself cause the compiler to die

fatalErrorMsgS :: String -> CoreM ()Source

Output a fatal string error to the screen. Note this does not by itself 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 :: DynFlag -> 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 unqualifed 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.