ghc-7.6.2: The GHC API

Safe HaskellNone

GhcMonad

Contents

Synopsis

Ghc monad stuff

class (Functor m, MonadIO m, ExceptionMonad m, HasDynFlags m) => GhcMonad m whereSource

A monad that has all the features needed by GHC API calls.

In short, a GHC monad

  • allows embedding of IO actions,
  • can log warnings,
  • allows handling of (extensible) exceptions, and
  • maintains a current session.

If you do not use Ghc or GhcT, make sure to call initGhcMonad before any call to the GHC API functions can occur.

Instances

newtype Ghc a Source

A minimal implementation of a GhcMonad. If you need a custom monad, e.g., to maintain additional state consider wrapping this monad or using GhcT.

Constructors

Ghc 

Fields

unGhc :: Session -> IO a
 

newtype GhcT m a Source

A monad transformer to add GHC specific features to another monad.

Note that the wrapped monad must support IO and handling of exceptions.

Constructors

GhcT 

Fields

unGhcT :: Session -> m a
 

liftGhcT :: Monad m => m a -> GhcT m aSource

reflectGhc :: Ghc a -> Session -> IO aSource

Reflect a computation in the Ghc monad into the IO monad.

You can use this to call functions returning an action in the Ghc monad inside an IO action. This is needed for some (too restrictive) callback arguments of some library functions:

 libFunc :: String -> (Int -> IO a) -> IO a
 ghcFunc :: Int -> Ghc a

 ghcFuncUsingLibFunc :: String -> Ghc a -> Ghc a
 ghcFuncUsingLibFunc str =
   reifyGhc $ \s ->
     libFunc $ \i -> do
       reflectGhc (ghcFunc i) s

reifyGhc :: (Session -> IO a) -> Ghc aSource

getSessionDynFlags :: GhcMonad m => m DynFlagsSource

Grabs the DynFlags from the Session

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

data Session Source

The Session is a handle to the complete state of a compilation session. A compilation session consists of a set of modules constituting the current program or library, the context for interactive evaluation, and various caches.

Constructors

Session !(IORef HscEnv) 

withSession :: GhcMonad m => (HscEnv -> m a) -> m aSource

Call the argument with the current session.

modifySession :: GhcMonad m => (HscEnv -> HscEnv) -> m ()Source

Set the current session to the result of applying the current session to the argument.

withTempSession :: GhcMonad m => (HscEnv -> HscEnv) -> m a -> m aSource

Call an action with a temporarily modified Session.

Warnings

logWarnings :: GhcMonad m => WarningMessages -> m ()Source

A monad that allows logging of warnings.

printException :: GhcMonad m => SourceError -> m ()Source

Print the error message and all warnings. Useful inside exception handlers. Clears warnings after printing.

printExceptionAndWarnings :: GhcMonad m => SourceError -> m ()Source

Deprecated: use printException instead

type WarnErrLogger = GhcMonad m => Maybe SourceError -> m ()Source

A function called to log warnings and errors.