| Safe Haskell | None |
|---|
Language.Haskell.GhcMod
Contents
Description
The ghc-mod library.
- data Cradle = Cradle {
- cradleCurrentDir :: FilePath
- cradleRootDir :: FilePath
- cradleCabalFile :: Maybe FilePath
- cradlePkgDbStack :: [GhcPkgDb]
- findCradle :: IO Cradle
- data Options = Options {
- outputStyle :: OutputStyle
- hlintOpts :: [String]
- ghcOpts :: [GHCOption]
- operators :: Bool
- detailed :: Bool
- qualified :: Bool
- lineSeparator :: LineSeparator
- newtype LineSeparator = LineSeparator String
- data OutputStyle
- = LispStyle
- | PlainStyle
- defaultOptions :: Options
- type ModuleString = String
- type Expression = String
- bootInfo :: Options -> Cradle -> IO String
- browseModule :: Options -> Cradle -> ModuleString -> IO String
- checkSyntax :: Options -> Cradle -> [FilePath] -> IO String
- lintSyntax :: Options -> FilePath -> IO String
- expandTemplate :: Options -> Cradle -> [FilePath] -> IO String
- infoExpr :: Options -> Cradle -> FilePath -> Expression -> IO String
- typeExpr :: Options -> Cradle -> FilePath -> Int -> Int -> IO String
- listModules :: Options -> Cradle -> IO String
- listLanguages :: Options -> IO String
- listFlags :: Options -> IO String
- debugInfo :: Options -> Cradle -> IO String
- rootInfo :: Options -> Cradle -> IO String
- packageDoc :: Options -> Cradle -> ModuleString -> IO String
- findSymbol :: Options -> Cradle -> Symbol -> IO String
Cradle
The environment where this library is used.
Constructors
| Cradle | |
Fields
| |
Finding Cradle.
Find a cabal file by tracing ancestor directories.
Find a sandbox according to a cabal sandbox config
in a cabal directory.
Options
Constructors
| Options | |
Fields
| |
newtype LineSeparator Source
The type for line separator. Historically, a Null string is used.
Constructors
| LineSeparator String |
data OutputStyle Source
Output style.
Constructors
| LispStyle | S expression style. |
| PlainStyle | Plain textstyle. |
defaultOptions :: OptionsSource
A default Options.
Types
type ModuleString = StringSource
Module name.
type Expression = StringSource
Haskell expression.
IO utilities
bootInfo :: Options -> Cradle -> IO StringSource
Printing necessary information for front-end booting.
Arguments
| :: Options | |
| -> Cradle | |
| -> ModuleString | A module name. (e.g. "Data.List") |
| -> IO String |
Checking syntax of a target file using GHC. Warnings and errors are returned.
Checking syntax of a target file using hlint. Warnings and errors are returned.
Expanding Haskell Template.
Arguments
| :: Options | |
| -> Cradle | |
| -> FilePath | A target file. |
| -> Expression | A Haskell expression. |
| -> IO String |
Obtaining information of a target expression. (GHCi's info:)
Arguments
| :: Options | |
| -> Cradle | |
| -> FilePath | A target file. |
| -> Int | Line number. |
| -> Int | Column number. |
| -> IO String |
Obtaining type of a target expression. (GHCi's type:)
listLanguages :: Options -> IO StringSource
Listing language extensions.
packageDoc :: Options -> Cradle -> ModuleString -> IO StringSource
Obtaining the package name and the doc path of a module.