Safe Haskell | None |
---|---|
Language | GHC2021 |
Synopsis
- class (Functor m, ExceptionMonad m, HasDynFlags m, HasLogger m) => GhcMonad (m :: Type -> Type) where
- getSession :: m HscEnv
- setSession :: HscEnv -> m ()
- newtype Ghc a = Ghc {}
- newtype GhcT (m :: Type -> Type) a = GhcT {}
- liftGhcT :: m a -> GhcT m a
- reflectGhc :: Ghc a -> Session -> IO a
- reifyGhc :: (Session -> IO a) -> Ghc a
- getSessionDynFlags :: GhcMonad m => m DynFlags
- liftIO :: MonadIO m => IO a -> m a
- data Session = Session !(IORef HscEnv)
- withSession :: GhcMonad m => (HscEnv -> m a) -> m a
- modifySession :: GhcMonad m => (HscEnv -> HscEnv) -> m ()
- modifySessionM :: GhcMonad m => (HscEnv -> m HscEnv) -> m ()
- withTempSession :: GhcMonad m => (HscEnv -> HscEnv) -> m a -> m a
- modifyLogger :: GhcMonad m => (Logger -> Logger) -> m ()
- pushLogHookM :: GhcMonad m => (LogAction -> LogAction) -> m ()
- popLogHookM :: GhcMonad m => m ()
- pushJsonLogHookM :: GhcMonad m => (LogJsonAction -> LogJsonAction) -> m ()
- popJsonLogHookM :: GhcMonad m => m ()
- putLogMsgM :: GhcMonad m => MessageClass -> SrcSpan -> SDoc -> m ()
- putMsgM :: GhcMonad m => SDoc -> m ()
- withTimingM :: GhcMonad m => SDoc -> (b -> ()) -> m b -> m b
- logDiagnostics :: GhcMonad m => Messages GhcMessage -> m ()
- printException :: (HasLogger m, MonadIO m, HasDynFlags m) => SourceError -> m ()
- type WarnErrLogger = forall (m :: Type -> Type). (HasDynFlags m, MonadIO m, HasLogger m) => Maybe SourceError -> m ()
- defaultWarnErrLogger :: WarnErrLogger
Ghc
monad stuff
class (Functor m, ExceptionMonad m, HasDynFlags m, HasLogger m) => GhcMonad (m :: Type -> Type) 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.
getSession :: m HscEnv Source #
setSession :: HscEnv -> m () Source #
Instances
GhcMonad Ghc Source # | |
Defined in GHC.Driver.Monad getSession :: Ghc HscEnv Source # setSession :: HscEnv -> Ghc () Source # | |
ExceptionMonad m => GhcMonad (GhcT m) Source # | |
Defined in GHC.Driver.Monad getSession :: GhcT m HscEnv Source # setSession :: HscEnv -> GhcT m () 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
.
Instances
MonadCatch Ghc Source # | |
Defined in GHC.Driver.Monad | |
MonadMask Ghc Source # | |
Defined in GHC.Driver.Monad mask :: HasCallStack => ((forall a. Ghc a -> Ghc a) -> Ghc b) -> Ghc b Source # uninterruptibleMask :: HasCallStack => ((forall a. Ghc a -> Ghc a) -> Ghc b) -> Ghc b Source # generalBracket :: HasCallStack => Ghc a -> (a -> ExitCase b -> Ghc c) -> (a -> Ghc b) -> Ghc (b, c) Source # | |
MonadThrow Ghc Source # | |
Defined in GHC.Driver.Monad | |
HasDynFlags Ghc Source # | |
Defined in GHC.Driver.Monad | |
GhcMonad Ghc Source # | |
Defined in GHC.Driver.Monad getSession :: Ghc HscEnv Source # setSession :: HscEnv -> Ghc () Source # | |
HasLogger Ghc Source # | |
Applicative Ghc Source # | |
Functor Ghc Source # | |
Monad Ghc Source # | |
MonadFail Ghc Source # | |
Defined in GHC.Driver.Monad | |
MonadFix Ghc Source # | |
Defined in GHC.Driver.Monad | |
MonadIO Ghc Source # | |
Defined in GHC.Driver.Monad |
newtype GhcT (m :: Type -> Type) 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.
Instances
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
getSessionDynFlags :: GhcMonad m => m DynFlags Source #
Grabs the DynFlags from the Session
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.
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.
modifySessionM :: GhcMonad m => (HscEnv -> m 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.
Logger
popLogHookM :: GhcMonad m => m () Source #
Pop a log hook from the stack
pushJsonLogHookM :: GhcMonad m => (LogJsonAction -> LogJsonAction) -> m () Source #
popJsonLogHookM :: GhcMonad m => m () Source #
putLogMsgM :: GhcMonad m => MessageClass -> SrcSpan -> SDoc -> m () Source #
Put a log message
withTimingM :: GhcMonad m => SDoc -> (b -> ()) -> m b -> m b Source #
Time an action
Diagnostics
logDiagnostics :: GhcMonad m => Messages GhcMessage -> m () Source #
A monad that allows logging of diagnostics.
printException :: (HasLogger m, MonadIO m, HasDynFlags m) => SourceError -> m () Source #
Print the all diagnostics in a SourceError
. Useful inside exception
handlers.
type WarnErrLogger = forall (m :: Type -> Type). (HasDynFlags m, MonadIO m, HasLogger m) => Maybe SourceError -> m () Source #
A function called to log warnings and errors.