Safe Haskell | None |
---|---|
Language | Haskell98 |
Synopsis
- data SessionType
- data SessionConfig = SessionConfig SessionType PackageDbStack
- type GhcM a = MGhcT SessionConfig (First DynFlags) (LogT IO) a
- type GhcWorker = Worker (MGhcT SessionConfig (First DynFlags) (LogT IO))
- newtype MGhcT s d m a = MGhcT {}
- runGhcM :: MonadLog m => Maybe FilePath -> GhcM a -> m a
- ghcWorker :: MonadLog m => m GhcWorker
- workerSession :: SessionType -> PackageDbStack -> [String] -> GhcM ()
- ghcSession :: PackageDbStack -> [String] -> GhcM ()
- ghciSession :: GhcM ()
- haddockSession :: PackageDbStack -> [String] -> GhcM ()
- tmpSession :: PackageDbStack -> [String] -> GhcM ()
- data Ghc a
- newtype LogT (m :: Type -> Type) a = LogT {}
- module HsDev.Tools.Ghc.Base
- module HsDev.Tools.Ghc.Repl
- module HsDev.Tools.Ghc.MGhc
- module Control.Concurrent.Worker
Workers
data SessionType Source #
Instances
Eq SessionType Source # | |
Defined in HsDev.Tools.Ghc.Worker (==) :: SessionType -> SessionType -> Bool # (/=) :: SessionType -> SessionType -> Bool # | |
Ord SessionType Source # | |
Defined in HsDev.Tools.Ghc.Worker compare :: SessionType -> SessionType -> Ordering # (<) :: SessionType -> SessionType -> Bool # (<=) :: SessionType -> SessionType -> Bool # (>) :: SessionType -> SessionType -> Bool # (>=) :: SessionType -> SessionType -> Bool # max :: SessionType -> SessionType -> SessionType # min :: SessionType -> SessionType -> SessionType # | |
Show SessionType Source # | |
Defined in HsDev.Tools.Ghc.Worker showsPrec :: Int -> SessionType -> ShowS # show :: SessionType -> String # showList :: [SessionType] -> ShowS # | |
Formattable SessionType Source # | |
Defined in HsDev.Tools.Ghc.Worker formattable :: SessionType -> FormatFlags -> Formatted # |
data SessionConfig Source #
Instances
Eq SessionConfig Source # | |
Defined in HsDev.Tools.Ghc.Worker (==) :: SessionConfig -> SessionConfig -> Bool # (/=) :: SessionConfig -> SessionConfig -> Bool # | |
Ord SessionConfig Source # | |
Defined in HsDev.Tools.Ghc.Worker compare :: SessionConfig -> SessionConfig -> Ordering # (<) :: SessionConfig -> SessionConfig -> Bool # (<=) :: SessionConfig -> SessionConfig -> Bool # (>) :: SessionConfig -> SessionConfig -> Bool # (>=) :: SessionConfig -> SessionConfig -> Bool # max :: SessionConfig -> SessionConfig -> SessionConfig # min :: SessionConfig -> SessionConfig -> SessionConfig # | |
Show SessionConfig Source # | |
Defined in HsDev.Tools.Ghc.Worker showsPrec :: Int -> SessionConfig -> ShowS # show :: SessionConfig -> String # showList :: [SessionConfig] -> ShowS # | |
Formattable SessionConfig Source # | |
Defined in HsDev.Tools.Ghc.Worker formattable :: SessionConfig -> FormatFlags -> Formatted # |
newtype MGhcT s d m a Source #
Multi-session ghc monad
Instances
workerSession :: SessionType -> PackageDbStack -> [String] -> GhcM () Source #
Create session with options
ghcSession :: PackageDbStack -> [String] -> GhcM () Source #
Get ghc session
ghciSession :: GhcM () Source #
Get ghci session
haddockSession :: PackageDbStack -> [String] -> GhcM () Source #
Get haddock session with flags
tmpSession :: PackageDbStack -> [String] -> GhcM () Source #
Get haddock session with flags
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
Monad Ghc | |
Functor Ghc | |
MonadFix Ghc | |
Applicative Ghc | |
MonadIO Ghc | |
MonadThrow Ghc Source # | |
Defined in HsDev.Tools.Ghc.Worker | |
GhcMonad Ghc | |
Defined in GhcMonad getSession :: Ghc HscEnv # setSession :: HscEnv -> Ghc () # | |
HasDynFlags Ghc | |
Defined in GhcMonad getDynFlags :: Ghc DynFlags # | |
ExceptionMonad Ghc | |
newtype LogT (m :: Type -> Type) a #
Instances
MonadTrans LogT | |
Defined in System.Log.Simple.Monad | |
Monad m => MonadReader Log (LogT m) | |
Monad m => Monad (LogT m) | |
Functor m => Functor (LogT m) | |
MonadFail m => MonadFail (LogT m) | |
Defined in System.Log.Simple.Monad | |
Applicative m => Applicative (LogT m) | |
MonadIO m => MonadIO (LogT m) | |
Defined in System.Log.Simple.Monad | |
MonadThrow m => MonadThrow (LogT m) | |
Defined in System.Log.Simple.Monad | |
MonadCatch m => MonadCatch (LogT m) | |
MonadMask m => MonadMask (LogT m) | |
ExceptionMonad m => ExceptionMonad (LogT m) Source # | |
(MonadIO m, MonadMask m) => MonadLog (LogT m) | |
module HsDev.Tools.Ghc.Base
module HsDev.Tools.Ghc.Repl
module HsDev.Tools.Ghc.MGhc
module Control.Concurrent.Worker
Orphan instances
MonadThrow Ghc Source # | |
ExceptionMonad m => ExceptionMonad (LogT m) Source # | |
(Monad m, GhcMonad m) => GhcMonad (ReaderT r m) Source # | |
getSession :: ReaderT r m HscEnv # setSession :: HscEnv -> ReaderT r m () # |