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

GHC.Driver.Monad

Synopsis

Ghc monad stuff

class (Functor m, ExceptionMonad m, HasDynFlags m) => GhcMonad m where Source #

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

Instances details
GhcMonad Ghc Source # 
Instance details

Defined in GHC.Driver.Monad

ExceptionMonad m => GhcMonad (GhcT m) Source # 
Instance details

Defined in GHC.Driver.Monad

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

Instances

Instances details
MonadFix Ghc Source # 
Instance details

Defined in GHC.Driver.Monad

Methods

mfix :: (a -> Ghc a) -> Ghc a Source #

MonadIO Ghc Source # 
Instance details

Defined in GHC.Driver.Monad

Methods

liftIO :: IO a -> Ghc a Source #

Applicative Ghc Source # 
Instance details

Defined in GHC.Driver.Monad

Methods

pure :: a -> Ghc a Source #

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

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

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

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

Functor Ghc Source # 
Instance details

Defined in GHC.Driver.Monad

Methods

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

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

Monad Ghc Source # 
Instance details

Defined in GHC.Driver.Monad

Methods

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

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

return :: a -> Ghc a Source #

MonadCatch Ghc Source # 
Instance details

Defined in GHC.Driver.Monad

Methods

catch :: Exception e => Ghc a -> (e -> Ghc a) -> Ghc a Source #

MonadMask Ghc Source # 
Instance details

Defined in GHC.Driver.Monad

Methods

mask :: ((forall a. Ghc a -> Ghc a) -> Ghc b) -> Ghc b Source #

uninterruptibleMask :: ((forall a. Ghc a -> Ghc a) -> Ghc b) -> Ghc b Source #

generalBracket :: Ghc a -> (a -> ExitCase b -> Ghc c) -> (a -> Ghc b) -> Ghc (b, c) Source #

MonadThrow Ghc Source # 
Instance details

Defined in GHC.Driver.Monad

Methods

throwM :: Exception e => e -> Ghc a Source #

GhcMonad Ghc Source # 
Instance details

Defined in GHC.Driver.Monad

HasDynFlags Ghc Source # 
Instance details

Defined in GHC.Driver.Monad

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

Instances

Instances details
MonadIO m => MonadIO (GhcT m) Source # 
Instance details

Defined in GHC.Driver.Monad

Methods

liftIO :: IO a -> GhcT m a Source #

Applicative m => Applicative (GhcT m) Source # 
Instance details

Defined in GHC.Driver.Monad

Methods

pure :: a -> GhcT m a Source #

(<*>) :: GhcT m (a -> b) -> GhcT m a -> GhcT m b Source #

liftA2 :: (a -> b -> c) -> GhcT m a -> GhcT m b -> GhcT m c Source #

(*>) :: GhcT m a -> GhcT m b -> GhcT m b Source #

(<*) :: GhcT m a -> GhcT m b -> GhcT m a Source #

Functor m => Functor (GhcT m) Source # 
Instance details

Defined in GHC.Driver.Monad

Methods

fmap :: (a -> b) -> GhcT m a -> GhcT m b Source #

(<$) :: a -> GhcT m b -> GhcT m a Source #

Monad m => Monad (GhcT m) Source # 
Instance details

Defined in GHC.Driver.Monad

Methods

(>>=) :: GhcT m a -> (a -> GhcT m b) -> GhcT m b Source #

(>>) :: GhcT m a -> GhcT m b -> GhcT m b Source #

return :: a -> GhcT m a Source #

MonadCatch m => MonadCatch (GhcT m) Source # 
Instance details

Defined in GHC.Driver.Monad

Methods

catch :: Exception e => GhcT m a -> (e -> GhcT m a) -> GhcT m a Source #

MonadMask m => MonadMask (GhcT m) Source # 
Instance details

Defined in GHC.Driver.Monad

Methods

mask :: ((forall a. GhcT m a -> GhcT m a) -> GhcT m b) -> GhcT m b Source #

uninterruptibleMask :: ((forall a. GhcT m a -> GhcT m a) -> GhcT m b) -> GhcT m b Source #

generalBracket :: GhcT m a -> (a -> ExitCase b -> GhcT m c) -> (a -> GhcT m b) -> GhcT m (b, c) Source #

MonadThrow m => MonadThrow (GhcT m) Source # 
Instance details

Defined in GHC.Driver.Monad

Methods

throwM :: Exception e => e -> GhcT m a Source #

ExceptionMonad m => GhcMonad (GhcT m) Source # 
Instance details

Defined in GHC.Driver.Monad

MonadIO m => HasDynFlags (GhcT m) Source # 
Instance details

Defined in GHC.Driver.Monad

liftGhcT :: m a -> GhcT m a Source #

reflectGhc :: Ghc a -> Session -> IO a Source #

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 a Source #

getSessionDynFlags :: GhcMonad m => m DynFlags Source #

Grabs the DynFlags from the Session

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

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 a Source #

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 a Source #

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.

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

A function called to log warnings and errors.