Safe Haskell | None |
---|
The ghc-mod library.
- data Cradle = Cradle {
- cradleCurrentDir :: FilePath
- cradleRootDir :: FilePath
- cradleTempDir :: FilePath
- cradleCabalFile :: Maybe FilePath
- cradlePkgDbStack :: [GhcPkgDb]
- findCradle :: IO Cradle
- data Options = Options {
- outputStyle :: OutputStyle
- lineSeparator :: LineSeparator
- ghcProgram :: FilePath
- cabalProgram :: FilePath
- ghcUserOptions :: [GHCOption]
- operators :: Bool
- detailed :: Bool
- qualified :: Bool
- hlintOpts :: [String]
- newtype LineSeparator = LineSeparator String
- data OutputStyle
- = LispStyle
- | PlainStyle
- defaultOptions :: Options
- type ModuleString = String
- type Expression = String
- data GhcPkgDb
- type Symbol = String
- data SymbolDb
- data GhcModError
- = GMENoMsg
- | GMEString String
- | GMECabalConfigure GhcModError
- | GMECabalFlags GhcModError
- | GMEProcess [String] GhcModError
- data GhcModT m a
- 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 :: IOish m => (Options -> Options) -> GhcModT m a -> GhcModT m a
- boot :: IOish m => GhcModT m String
- browse :: IOish m => ModuleString -> 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
- 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 => GhcModT 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 => GhcModT 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 => GhcModT m SymbolDb
- isOutdated :: SymbolDb -> IO Bool
Cradle
The environment where this library is used.
Cradle | |
|
findCradle :: IO CradleSource
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 | |
|
Show Options |
newtype LineSeparator Source
The type for line separator. Historically, a Null string is used.
LineSeparator String |
Show LineSeparator |
data OutputStyle Source
Output style.
LispStyle | S expression style. |
PlainStyle | Plain textstyle. |
Show OutputStyle |
defaultOptions :: OptionsSource
A default Options
.
Types
type ModuleString = StringSource
Module name.
type Expression = StringSource
Haskell expression.
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. |
GMECabalFlags GhcModError | Retrieval of the cabal configuration flags failed. |
GMEProcess [String] GhcModError | Launching an operating system process failed. The first field is the command. |
Eq GhcModError | |
Show GhcModError | |
Error GhcModError | |
Monad m => MonadError GhcModError (GhcModT m) |
Monad Types
This is basically a newtype wrapper around StateT
, ErrorT
, JournalT
and ReaderT
with custom instances for GhcMonad
and it's constraints that
means you can run (almost) all functions from the GHC API on top of GhcModT
transparently.
The inner monad m
should have instances for MonadIO
and
MonadBaseControl
IO
, in the common case this is simply IO
. Most mtl
monads already have MonadBaseControl
IO
instances, see the
monad-control
package.
MonadTrans GhcModT | |
MonadBaseControl IO m => MonadBase IO (GhcModT m) | |
MonadBaseControl IO m => MonadBaseControl IO (GhcModT m) | |
Monad m => MonadError GhcModError (GhcModT m) | |
Monad m => MonadReader GhcModEnv (GhcModT m) | |
MonadState s m => MonadState s (GhcModT m) | |
MonadWriter w m => MonadWriter w (GhcModT m) | |
Monad m => Monad (GhcModT m) | |
Functor m => Functor (GhcModT m) | |
Monad m => MonadPlus (GhcModT m) | |
(Monad m, Functor m) => Applicative (GhcModT m) | |
(Monad m, Functor m) => Alternative (GhcModT m) | |
MonadIO m => MonadIO (GhcModT m) | |
MonadIO m => MonadIO (GhcModT m) | |
(Functor m, MonadIO m, MonadBaseControl IO m) => HasDynFlags (GhcModT m) | |
(MonadIO m, MonadBaseControl IO m) => ExceptionMonad (GhcModT m) | |
(Functor m, MonadIO m, MonadBaseControl IO m) => GhcMonad (GhcModT m) |
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.
GhcMod
utilities
:: IOish m | |
=> ModuleString | A module name. (e.g. "Data.List") |
-> GhcModT m String |
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 StringSource
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.
:: IOish m | |
=> FilePath | A target file. |
-> Int | Line number. |
-> Int | Column number. |
-> Expression | A Haskell expression. |
-> GhcModT m String |
findSymbol :: IOish m => Symbol -> GhcModT m StringSource
Looking up SymbolDb
with Symbol
to [ModuleString
]
which will be concatenated. loadSymbolDb
is called internally.
lookupSymbol :: IOish m => Symbol -> SymbolDb -> GhcModT m StringSource
Looking up SymbolDb
with Symbol
to [ModuleString
]
which will be concatenated.
dumpSymbol :: IOish m => FilePath -> GhcModT m StringSource
Dumping a set of (Symbol
,[ModuleString
]) to a file
if the file does not exist or is invalid.
The file name is printed.
SymbolDb
isOutdated :: SymbolDb -> IO BoolSource