Safe Haskell | None |
---|---|
Language | Haskell2010 |
- type GhcModT m = GmT (GmOutT m)
- newtype GmOutT m a = GmOutT {}
- newtype GmT m a = GmT {
- unGmT :: StateT GhcModState (ErrorT GhcModError (JournalT GhcModLog (ReaderT GhcModEnv m))) a
- newtype GmlT m a = GmlT {}
- newtype LightGhc a = LightGhc {
- unLightGhc :: ReaderT (IORef HscEnv) IO a
- type GmGhc m = (IOish m, GhcMonad m)
- type IOish m = (Functor m, MonadIO m, MonadBaseControl IO m, ExceptionMonad m)
- data GhcModEnv = GhcModEnv {}
- data GhcModState = GhcModState {}
- data GhcModCaches = GhcModCaches {
- gmcPackageDbStack :: CacheContents ChCacheData [GhcPkgDb]
- gmcMergedPkgOptions :: CacheContents ChCacheData [GHCOption]
- gmcComponents :: CacheContents ChCacheData [GmComponent GMCRaw ChEntrypoint]
- gmcResolvedComponents :: CacheContents [GmComponent GMCRaw (Set ModulePath)] (Map ChComponentName (GmComponent GMCResolved (Set ModulePath)))
- defaultGhcModState :: GhcModState
- data GmGhcSession = GmGhcSession {
- gmgsOptions :: ![GHCOption]
- gmgsSession :: !(IORef HscEnv)
- data GmComponent t eps = GmComponent {}
- data CompilerMode
- data GmLogLevel
- data GhcModLog = GhcModLog {
- gmLogLevel :: Maybe GmLogLevel
- gmLogVomitDump :: Last Bool
- gmLogMessages :: [(GmLogLevel, String, Doc)]
- data GhcModError
- = GMENoMsg
- | GMEString String
- | GMECabalConfigure GhcModError
- | GMEStackConfigure GhcModError
- | GMEStackBootstrap GhcModError
- | GMECabalCompAssignment [(Either FilePath ModuleName, Set ChComponentName)]
- | GMEProcess String String [String] (Either Int GhcModError)
- | GMENoCabalFile
- | GMETooManyCabalFiles [FilePath]
- | GMEWrongWorkingDirectory FilePath FilePath
- type Gm m = (GmEnv m, GmState m, GmLog m, GmOut m)
- class Monad m => GmEnv m where
- class Monad m => GmState m where
- gmsGet :: m GhcModState
- gmsPut :: GhcModState -> m ()
- gmsState :: (GhcModState -> (a, GhcModState)) -> m a
- class Monad m => GmLog m where
- gmlJournal :: GhcModLog -> m ()
- gmlHistory :: m GhcModLog
- gmlClear :: m ()
- class Monad m => GmOut m where
- cradle :: GmEnv m => m Cradle
- options :: GmEnv m => m Options
- outputOpts :: GmOut m => m OutputOpts
- withOptions :: GmEnv m => (Options -> Options) -> m a -> m a
- getCompilerMode :: GmState m => m CompilerMode
- setCompilerMode :: GmState m => CompilerMode -> m ()
- getMMappedFiles :: GmState m => m FileMappingMap
- setMMappedFiles :: GmState m => FileMappingMap -> m ()
- addMMappedFile :: GmState m => FilePath -> FileMapping -> m ()
- delMMappedFile :: GmState m => FilePath -> m ()
- lookupMMappedFile :: GmState m => FilePath -> m (Maybe FileMapping)
- getMMappedFilePaths :: GmState m => m [FilePath]
- class MonadIOC m => MonadIO m where
- gmlGetSession :: (MonadIO m, MonadBaseControl IO m) => GmlT m HscEnv
- gmlSetSession :: (MonadIO m, MonadBaseControl IO m) => HscEnv -> GmlT m ()
Monad Types
MonadTrans GmOutT Source | |
MonadTransControl GmOutT Source | |
MonadBaseControl IO m => MonadBase IO (GmOutT m) Source | |
MonadBaseControl IO m => MonadBaseControl IO (GmOutT m) Source | |
Monad m => Monad (GmOutT m) Source | |
Functor m => Functor (GmOutT m) Source | |
Applicative m => Applicative (GmOutT m) Source | |
Alternative m => Alternative (GmOutT m) Source | |
MonadPlus m => MonadPlus (GmOutT m) Source | |
(MonadIO m, MonadBaseControl IO m) => ExceptionMonad (GmOutT m) Source | |
MonadIO m => MonadIO (GmOutT m) Source | |
MonadIOC m => MonadIO (GmOutT m) Source | |
Monad m => GmOut (GmOutT m) Source | |
GmLog m => GmLog (GmOutT m) Source | |
GmEnv m => GmEnv (GmOutT m) Source | |
type StT GmOutT a = StT (ReaderT GhcModEnv) a Source | |
type StM (GmOutT m) a = StM (ReaderT GhcModEnv m) a Source |
GmT | |
|
MonadTrans GmlT Source | |
MonadTransControl GmlT Source | |
MonadBaseControl IO m => MonadBase IO (GmlT m) Source | |
MonadBaseControl IO m => MonadBaseControl IO (GmlT m) Source | |
Monad m => MonadError GhcModError (GmlT m) Source | |
Monad m => Monad (GmlT m) Source | |
Functor m => Functor (GmlT m) Source | |
Monad m => Applicative (GmlT m) Source | |
Monad m => Alternative (GmlT m) Source | |
Monad m => MonadPlus (GmlT m) Source | |
(MonadIO m, MonadBaseControl IO m) => GhcMonad (GmlT m) Source | |
(MonadIO m, MonadBaseControl IO m) => HasDynFlags (GmlT m) Source | |
(MonadIO m, MonadBaseControl IO m) => ExceptionMonad (GmlT m) Source | |
MonadIO m => MonadIO (GmlT m) Source | |
MonadIOC m => MonadIO (GmlT m) Source | |
Monad m => GmOut (GmlT m) Source | |
Monad m => GmLog (GmlT m) Source | |
Monad m => GmState (GmlT m) Source | |
Monad m => GmEnv (GmlT m) Source | |
type StT GmlT a = StT GmT a Source | |
type StM (GmlT m) a = StM (GmT m) a Source |
type IOish m = (Functor m, MonadIO m, MonadBaseControl IO m, ExceptionMonad m) Source
A constraint alias (-XConstraintKinds) to make functions dealing with
GhcModT
somewhat cleaner.
Basicially an IOish m => m
is a Monad
supporting arbitrary IO
and
exception handling. Usually this will simply be IO
but we parametrise it in
the exported API so users have the option to use a custom inner monad.
Environment, state and logging
data GhcModState Source
Monad m => GmState (StateT GhcModState m) Source |
data GhcModCaches Source
data GmGhcSession Source
GmGhcSession | |
|
data GmComponent t eps Source
GmComponent | |
|
Functor (GmComponent t) Source | |
Eq eps => Eq (GmComponent t eps) Source | |
Ord eps => Ord (GmComponent t eps) Source | |
Read eps => Read (GmComponent t eps) Source | |
Show eps => Show (GmComponent t eps) Source | |
Generic (GmComponent t eps) Source | |
Serialize eps => Serialize (GmComponent t eps) Source | |
type Rep (GmComponent t eps) Source |
data CompilerMode Source
Accessing GhcModEnv
, GhcModState
and GhcModLog
data GmLogLevel Source
GhcModLog | |
|
data GhcModError Source
GMENoMsg | Unknown error |
GMEString String | Some Error with a message. These are produced mostly by
|
GMECabalConfigure GhcModError | Configuring a cabal project failed. |
GMEStackConfigure GhcModError | Configuring a stack project failed. |
GMEStackBootstrap GhcModError | Bootstrapping |
GMECabalCompAssignment [(Either FilePath ModuleName, Set ChComponentName)] | Could not find a consistent component assignment for modules |
GMEProcess String String [String] (Either Int GhcModError) | Launching an operating system process failed. Fields in order: function, command, arguments, (stdout, stderr, exitcode) |
GMENoCabalFile | No cabal file found. |
GMETooManyCabalFiles [FilePath] | Too many cabal files found. |
GMEWrongWorkingDirectory FilePath FilePath |
Eq GhcModError Source | |
Show GhcModError Source | |
Exception GhcModError Source | |
Error GhcModError Source | |
Monad m => MonadError GhcModError (GmlT m) | |
Monad m => MonadError GhcModError (GmT m) | |
GmEnv m => GmEnv (ErrorT GhcModError m) Source |
class Monad m => GmState m where Source
gmsGet :: m GhcModState Source
gmsPut :: GhcModState -> m () Source
gmsState :: (GhcModState -> (a, GhcModState)) -> m a Source
outputOpts :: GmOut m => m OutputOpts Source
withOptions :: GmEnv m => (Options -> Options) -> m a -> m a Source
getCompilerMode :: GmState m => m CompilerMode Source
setCompilerMode :: GmState m => CompilerMode -> m () Source
getMMappedFiles :: GmState m => m FileMappingMap Source
setMMappedFiles :: GmState m => FileMappingMap -> m () Source
addMMappedFile :: GmState m => FilePath -> FileMapping -> m () Source
delMMappedFile :: GmState m => FilePath -> m () Source
lookupMMappedFile :: GmState m => FilePath -> m (Maybe FileMapping) Source
getMMappedFilePaths :: GmState m => m [FilePath] Source
Re-exporting convenient stuff
gmlGetSession :: (MonadIO m, MonadBaseControl IO m) => GmlT m HscEnv Source
gmlSetSession :: (MonadIO m, MonadBaseControl IO m) => HscEnv -> GmlT m () Source