Safe Haskell | None |
---|---|
Language | Haskell2010 |
The ghc-mod library.
- data Cradle = Cradle {}
- data Project
- findCradle :: (GmLog m, IOish m, GmOut m) => Programs -> m Cradle
- data Options = Options {}
- 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 = ByteString
- 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]
- type GhcModT m = GmT (GmOutT m)
- type IOish m = (Functor m, MonadIO m, MonadBaseControl IO m, ExceptionMonad m)
- runGhcModT :: IOish 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 => BrowseOpts -> 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 => LintOpts -> FilePath -> GhcModT m String
- pkgDoc :: IOish m => String -> GhcModT m String
- rootInfo :: forall m. (IOish m, GmOut m, GmEnv m) => m String
- types :: IOish m => Bool -> FilePath -> Int -> Int -> GhcModT m String
- test :: IOish m => FilePath -> 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) => Bool -> m String
- languages :: IOish m => GhcModT m String
- flags :: IOish m => GhcModT m String
- findSymbol :: IOish m => String -> GhcModT m String
- lookupSymbol :: IOish m => String -> SymbolDb -> GhcModT m String
- dumpSymbol :: IOish m => GhcModT m ()
- loadSymbolDb :: IOish m => 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 :: (GmLog m, IOish m, GmOut m) => Programs -> 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.
type Symbol = ByteString Source #
Type of function and operation names.
Database from Symbol
to \['ModuleString'\].
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. |
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 => Options -> GhcModT m a -> m (Either GhcModError a, GhcModLog) Source #
Run a GhcModT m
computation.
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
:: IOish m | |
=> BrowseOpts | Configuration parameters |
-> String | A module name. (e.g. "Data.List", "base:Prelude") |
-> GhcModT m String |
Getting functions, classes, etc from a module.
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.
:: IOish m | |
=> Bool | Include constraints into type signature |
-> FilePath | A target file. |
-> Int | Line number. |
-> Int | Column number. |
-> GhcModT m String |
Obtaining type of a target expression. (GHCi's type:)
Splitting a variable in a equation.
Create a initial body from a signature.
:: (IOish m, Gm m) | |
=> Bool |
|
-> m String |
Listing installed modules.
flags :: IOish m => GhcModT m String Source #
Listing of GHC flags, same as ghc
's --show-options
with ghc >= 7.10
.
findSymbol :: IOish m => String -> GhcModT m String Source #
Looking up SymbolDb
with Symbol
to \['ModuleString'\]
which will be concatenated. loadSymbolDb
is called internally.
SymbolDb
Output
FileMapping
maps FilePath
, given as first argument to have source as given
by second argument.
'from' may or may not exist, and should be either full path, or relative to project root.