Safe Haskell | None |
---|---|
Language | Haskell2010 |
The ghc-mod library.
- data Cradle = Cradle {}
- data Project
- findCradle :: (IOish m, GmOut m) => m Cradle
- data Options = Options {
- optOutput :: OutputOpts
- optPrograms :: Programs
- optGhcUserOptions :: [GHCOption]
- optOperators :: Bool
- optDetailed :: Bool
- optQualified :: Bool
- optHlintOpts :: [String]
- optFileMappings :: [(FilePath, Maybe FilePath)]
- newtype LineSeparator = LineSeparator String
- data OutputStyle
- data FileMapping = FileMapping {}
- defaultOptions :: Options
- data GmLogLevel
- increaseLogLevel :: GmLogLevel -> GmLogLevel
- decreaseLogLevel :: GmLogLevel -> GmLogLevel
- gmSetLogLevel :: GmLog m => GmLogLevel -> m ()
- gmLog :: (MonadIO m, GmLog m, GmOut m) => GmLogLevel -> String -> Doc -> m ()
- data ModuleString
- newtype Expression = Expression {}
- data GhcPkgDb
- type Symbol = String
- data SymbolDb
- 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 GhcModT m = GmT (GmOutT m)
- type IOish m = (Functor m, MonadIO m, MonadBaseControl IO m, ExceptionMonad m)
- runGhcModT :: (IOish m, GmOut m) => Options -> GhcModT m a -> m (Either GhcModError a, GhcModLog)
- withOptions :: GmEnv m => (Options -> Options) -> m a -> m a
- dropSession :: IOish m => GhcModT m ()
- boot :: IOish m => GhcModT m String
- browse :: forall m. IOish m => String -> GhcModT m String
- check :: IOish m => [FilePath] -> GhcModT m (Either String String)
- checkSyntax :: IOish m => [FilePath] -> GhcModT m String
- debugInfo :: IOish m => GhcModT m String
- componentInfo :: IOish m => [String] -> GhcModT m String
- expandTemplate :: IOish m => [FilePath] -> GhcModT m String
- info :: IOish m => FilePath -> Expression -> GhcModT m String
- lint :: IOish m => FilePath -> GhcModT m String
- pkgDoc :: IOish m => String -> GhcModT m String
- rootInfo :: (IOish m, GmOut m) => m String
- types :: IOish m => FilePath -> Int -> Int -> GhcModT m String
- splits :: IOish m => FilePath -> Int -> Int -> GhcModT m String
- sig :: IOish m => FilePath -> Int -> Int -> GhcModT m String
- refine :: IOish m => FilePath -> Int -> Int -> Expression -> GhcModT m String
- auto :: IOish m => FilePath -> Int -> Int -> GhcModT m String
- modules :: (IOish m, Gm m) => m String
- languages :: IOish m => GhcModT m String
- flags :: IOish m => GhcModT m String
- findSymbol :: IOish m => Symbol -> GhcModT m String
- lookupSymbol :: IOish m => Symbol -> SymbolDb -> GhcModT m String
- dumpSymbol :: IOish m => FilePath -> GhcModT m String
- loadSymbolDb :: IOish m => FilePath -> GhcModT m SymbolDb
- isOutdated :: IOish m => SymbolDb -> GhcModT m Bool
- gmPutStr :: (MonadIO m, GmOut m) => String -> m ()
- gmErrStr :: (MonadIO m, GmOut m) => String -> m ()
- gmPutStrLn :: (MonadIO m, GmOut m) => String -> m ()
- gmErrStrLn :: (MonadIO m, GmOut m) => String -> m ()
- loadMappedFile :: IOish m => FilePath -> FilePath -> GhcModT m ()
- loadMappedFileSource :: IOish m => FilePath -> String -> GhcModT m ()
- unloadMappedFile :: IOish m => FilePath -> GhcModT m ()
Cradle
The environment where this library is used.
Cradle | |
|
findCradle :: (IOish m, GmOut m) => m Cradle Source
Finding Cradle
.
Find a cabal file by tracing ancestor directories.
Find a sandbox according to a cabal sandbox config
in a cabal directory.
Options
Options | |
|
newtype LineSeparator Source
The type for line separator. Historically, a Null string is used.
defaultOptions :: Options Source
A default Options
.
Logging
data GmLogLevel Source
gmSetLogLevel :: GmLog m => GmLogLevel -> m () Source
gmLog :: (MonadIO m, GmLog m, GmOut m) => GmLogLevel -> String -> Doc -> m () Source
>>>
Just GmDebug <= Nothing
False>>>
Just GmException <= Just GmDebug
True>>>
Just GmDebug <= Just GmException
False
Types
data ModuleString Source
Module name.
newtype Expression Source
Haskell expression.
GHC package database flags.
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 |
Monad Types
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.
Monad utilities
runGhcModT :: (IOish m, GmOut m) => Options -> GhcModT m a -> m (Either GhcModError a, GhcModLog) Source
Run a GhcModT m
computation.
withOptions :: GmEnv m => (Options -> Options) -> m a -> m a Source
dropSession :: IOish m => GhcModT m () Source
Drop the currently active GHC session, the next that requires a GHC session will initialize a new one.
GhcMod
utilities
Checking syntax of a target file using GHC. Warnings and errors are returned.
Checking syntax of a target file using GHC. Warnings and errors are returned.
Expanding Haskell Template.
:: IOish m | |
=> FilePath | A target file. |
-> Expression | A Haskell expression. |
-> GhcModT m String |
Obtaining information of a target expression. (GHCi's info:)
Checking syntax of a target file using hlint. Warnings and errors are returned.
pkgDoc :: IOish m => String -> GhcModT m String Source
Obtaining the package name and the doc path of a module.
Obtaining type of a target expression. (GHCi's type:)
Splitting a variable in a equation.
Create a initial body from a signature.
findSymbol :: IOish m => Symbol -> GhcModT m String Source
Looking up SymbolDb
with Symbol
to [ModuleString
]
which will be concatenated. loadSymbolDb
is called internally.
lookupSymbol :: IOish m => Symbol -> SymbolDb -> GhcModT m String Source
Looking up SymbolDb
with Symbol
to [ModuleString
]
which will be concatenated.
dumpSymbol :: IOish m => FilePath -> GhcModT m String Source
Dumping a set of (Symbol
,[ModuleString
]) to a file
if the file does not exist or is invalid.
The file name is printed.
SymbolDb
loadSymbolDb :: IOish m => FilePath -> GhcModT m SymbolDb Source
Loading a file and creates SymbolDb
.
Output
gmPutStrLn :: (MonadIO m, GmOut m) => String -> m () Source
gmErrStrLn :: (MonadIO m, GmOut m) => String -> m () Source
FileMapping
unloadMappedFile :: IOish m => FilePath -> GhcModT m () Source