ghc-6.12.1: The GHC APISource codeContentsIndex
CoreMonad
Contents
The monad
Reading from the monad
Writing to the monad
Lifting into the monad
Dealing with annotations
Screen output
Getting Names
Synopsis
data CoreM a
runCoreM :: HscEnv -> AnnEnv -> RuleBase -> UniqSupply -> Module -> CoreM a -> IO (a, SimplCount)
getHscEnv :: CoreM HscEnv
getAnnEnv :: CoreM AnnEnv
getRuleBase :: CoreM RuleBase
getModule :: CoreM Module
getDynFlags :: CoreM DynFlags
getOrigNameCache :: CoreM OrigNameCache
addSimplCount :: SimplCount -> CoreM ()
liftIO :: MonadIO m => IO a -> m a
liftIOWithCount :: IO (SimplCount, a) -> CoreM a
liftIO1 :: MonadIO m => (a -> IO b) -> a -> m b
liftIO2 :: MonadIO m => (a -> b -> IO c) -> a -> b -> m c
liftIO3 :: MonadIO m => (a -> b -> c -> IO d) -> a -> b -> c -> m d
liftIO4 :: MonadIO m => (a -> b -> c -> d -> IO e) -> a -> b -> c -> d -> m e
findAnnotations :: Typeable a => ([Word8] -> a) -> CoreAnnTarget -> CoreM [a]
addAnnotation :: Typeable a => (a -> [Word8]) -> CoreAnnTarget -> a -> CoreM ()
putMsg :: SDoc -> CoreM ()
putMsgS :: String -> CoreM ()
errorMsg :: SDoc -> CoreM ()
errorMsgS :: String -> CoreM ()
fatalErrorMsg :: SDoc -> CoreM ()
fatalErrorMsgS :: String -> CoreM ()
debugTraceMsg :: SDoc -> CoreM ()
debugTraceMsgS :: String -> CoreM ()
dumpIfSet_dyn :: DynFlag -> String -> SDoc -> CoreM ()
thNameToGhcName :: Name -> CoreM (Maybe Name)
The monad
data CoreM a Source
The monad used by Core-to-Core passes to access common state, register simplification statistics and so on
show/hide Instances
runCoreM :: HscEnv -> AnnEnv -> RuleBase -> UniqSupply -> Module -> CoreM a -> IO (a, SimplCount)Source
Reading from the monad
getHscEnv :: CoreM HscEnvSource
getAnnEnv :: CoreM AnnEnvSource
getRuleBase :: CoreM RuleBaseSource
getModule :: CoreM ModuleSource
getDynFlags :: CoreM DynFlagsSource
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
addSimplCount :: SimplCount -> CoreM ()Source
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
Dealing with annotations
findAnnotations :: Typeable a => ([Word8] -> a) -> CoreAnnTarget -> CoreM [a]Source

Find all the annotations we currently know about for the given target. Note that no annotations will be returned if we haven't loaded information about the particular target you are inquiring about: by default, only those modules that have been imported by the program being compiled will have been loaded in this way.

To load the information from additional modules, you can use the functions DynamicLoading.forceLoadModuleInterfaces and DynamicLoading.forceLoadNameModuleInterface, but be aware that doing this indiscriminantly will impose a performance penalty.

If no deserialization function is supplied, only transient annotations will be returned.

addAnnotation :: Typeable a => (a -> [Word8]) -> CoreAnnTarget -> a -> CoreM ()Source
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.
Produced by Haddock version 2.6.0