Safe Haskell | None |
---|---|
Language | Haskell2010 |
Low level access to the ghc-mod library.
- type GHCOption = String
- type IncludeDir = FilePath
- newtype GmlT m a = GmlT {}
- class MonadIOC m => MonadIO m where
- class Monad m => GmEnv m where
- ghcLibDir :: FilePath
- ghcModExecutable :: IO FilePath
- withLogger :: (GmGhc m, GmEnv m, GmOut m, GmState m) => (DynFlags -> DynFlags) -> m a -> m (Either String (String, a))
- setNoWarningFlags :: DynFlags -> DynFlags
- setAllWarningFlags :: DynFlags -> DynFlags
- data GhcModEnv = GhcModEnv {}
- data GhcModState
- data GhcModLog
- class Monad m => GmLog m where
- data GmLogLevel
- gmSetLogLevel :: GmLog m => GmLogLevel -> m ()
- runGhcModT' :: IOish m => GhcModEnv -> GhcModState -> GhcModT m a -> GmOutT m (Either GhcModError (a, GhcModState), GhcModLog)
- hoistGhcModT :: IOish m => (Either GhcModError a, GhcModLog) -> GhcModT m a
- runGmlT :: IOish m => [Either FilePath ModuleName] -> GmlT m a -> GhcModT m a
- runGmlT' :: IOish m => [Either FilePath ModuleName] -> (forall gm. GhcMonad gm => DynFlags -> gm DynFlags) -> GmlT m a -> GhcModT m a
- gmlGetSession :: (MonadIO m, MonadBaseControl IO m) => GmlT m HscEnv
- gmlSetSession :: (MonadIO m, MonadBaseControl IO m) => HscEnv -> GmlT m ()
- loadTargets :: IOish m => [GHCOption] -> [FilePath] -> GmlT m ()
- cabalResolvedComponents :: IOish m => GhcModT m (Map ChComponentName (GmComponent GMCResolved (Set ModulePath)))
- options :: GmEnv m => m Options
- cradle :: GmEnv m => m Cradle
- targetGhcOptions :: forall m. IOish m => Cradle -> Set (Either FilePath ModuleName) -> GhcModT m [GHCOption]
- withOptions :: GmEnv m => (Options -> Options) -> m a -> m a
- gmeDoc :: GhcModError -> Doc
- data World
- getCurrentWorld :: IOish m => GhcModT m World
- didWorldChange :: IOish m => World -> GhcModT m Bool
- data ModulePath = ModulePath {
- mpModule :: ModuleName
- mpPath :: FilePath
- data GmComponent t eps = GmComponent {}
- data GmComponentType
- data GmModuleGraph = GmModuleGraph {
- gmgGraph :: Map ModulePath (Set ModulePath)
- prepareCabalHelper :: (IOish m, GmEnv m, GmOut m, GmLog m) => m ()
- data GHandler m a = Exception e => GHandler (e -> m a)
- gcatches :: (MonadIO m, ExceptionMonad m) => m a -> [GHandler m a] -> m a
- module Language.Haskell.GhcMod.FileMapping
Types
type IncludeDir = FilePath Source #
An include directory for modules.
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 # | |
(Monad m, GmEnv (GhcModT m)) => GmEnv (GmlT m) Source # | |
(Monad m, GmLog (GhcModT m)) => GmLog (GmlT m) Source # | |
Monad m => GmOut (GmlT m) Source # | |
(Monad m, GmState (GhcModT m)) => GmState (GmlT m) Source # | |
type StT GmlT a Source # | |
type StM (GmlT m) a Source # | |
Various Paths
ghcModExecutable :: IO FilePath Source #
Returns the path to the currently running ghc-mod executable. With ghc<7.6
this is a guess but >=7.6 uses getExecutablePath
.
Logging
withLogger :: (GmGhc m, GmEnv m, GmOut m, GmState m) => (DynFlags -> DynFlags) -> m a -> m (Either String (String, a)) Source #
Logged messages are returned as String
.
Right is success and Left is failure.
Environment, state and logging
data GhcModState Source #
class Monad m => GmLog m where Source #
(Monad m, GmLog m) => GmLog (MaybeT m) Source # | |
(Monad m, GmLog (GhcModT m)) => GmLog (GmlT m) Source # | |
Monad m => GmLog (GmT m) Source # | |
GmLog m => GmLog (GmOutT m) Source # | |
Monad m => GmLog (LogDiscardT m) Source # | |
Monad m => GmLog (JournalT GhcModLog m) Source # | |
(Monad m, GmLog m, Error e) => GmLog (ErrorT e m) Source # | |
(Monad m, GmLog m) => GmLog (StateT s m) Source # | |
(Monad m, GmLog m) => GmLog (ReaderT * r m) Source # | |
data GmLogLevel Source #
gmSetLogLevel :: GmLog m => GmLogLevel -> m () Source #
Monad utilities
runGhcModT' :: IOish m => GhcModEnv -> GhcModState -> GhcModT m a -> GmOutT m (Either GhcModError (a, GhcModState), GhcModLog) Source #
Run a computation inside GhcModT
providing the RWST environment and
initial state. This is a low level function, use it only if you know what to
do with GhcModEnv
and GhcModState
.
You should probably look at runGhcModT
instead.
hoistGhcModT :: IOish m => (Either GhcModError a, GhcModLog) -> GhcModT m a Source #
hoistGhcModT result
. Embed a GhcModT computation's result into a GhcModT
computation. Note that if the computation that returned result
modified the
state part of GhcModT this cannot be restored.
runGmlT :: IOish m => [Either FilePath ModuleName] -> GmlT m a -> GhcModT m a Source #
Run a GmlT action (i.e. a function in the GhcMonad) in the context of certain files or modules
runGmlT' :: IOish m => [Either FilePath ModuleName] -> (forall gm. GhcMonad gm => DynFlags -> gm DynFlags) -> GmlT m a -> GhcModT m a Source #
Run a GmlT action (i.e. a function in the GhcMonad) in the context of certain files or modules, with updated GHC flags
gmlGetSession :: (MonadIO m, MonadBaseControl IO m) => GmlT m HscEnv Source #
Get the underlying GHC session
gmlSetSession :: (MonadIO m, MonadBaseControl IO m) => HscEnv -> GmlT m () Source #
Set the underlying GHC session
loadTargets :: IOish m => [GHCOption] -> [FilePath] -> GmlT m () Source #
Set the files as targets and load them.
cabalResolvedComponents :: IOish m => GhcModT m (Map ChComponentName (GmComponent GMCResolved (Set ModulePath))) Source #
Accessing GhcModEnv
and GhcModState
targetGhcOptions :: forall m. IOish m => Cradle -> Set (Either FilePath ModuleName) -> GhcModT m [GHCOption] Source #
GhcModError
gmeDoc :: GhcModError -> Doc Source #
World
Cabal Helper
data ModulePath Source #
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 # | |
Binary eps => Binary (GmComponent t eps) Source # | |
type Rep (GmComponent t eps) Source # | |
data GmModuleGraph Source #