Safe Haskell | None |
---|
The ghc-mod library.
- data Cradle = Cradle {}
- findCradle :: IO Cradle
- data Options = Options {
- outputStyle :: OutputStyle
- hlintOpts :: [String]
- ghcOpts :: [String]
- operators :: Bool
- detailed :: Bool
- qualified :: Bool
- expandSplice :: Bool
- lineSeparator :: LineSeparator
- packageId :: Maybe String
- newtype LineSeparator = LineSeparator String
- data OutputStyle
- = LispStyle
- | PlainStyle
- defaultOptions :: Options
- type ModuleString = String
- type Expression = String
- browseModule :: Options -> Cradle -> ModuleString -> IO String
- checkSyntax :: Options -> Cradle -> [FilePath] -> IO String
- lintSyntax :: Options -> FilePath -> IO String
- infoExpr :: Options -> Cradle -> FilePath -> ModuleString -> Expression -> IO String
- typeExpr :: Options -> Cradle -> FilePath -> ModuleString -> Int -> Int -> IO String
- listModules :: Options -> Cradle -> IO String
- listLanguages :: Options -> IO String
- listFlags :: Options -> IO String
- debugInfo :: Options -> Cradle -> FilePath -> IO String
- withGHC :: Alternative m => FilePath -> Ghc (m a) -> IO (m a)
- withGHCDummyFile :: Alternative m => Ghc (m a) -> IO (m a)
- browse :: Options -> Cradle -> ModuleString -> Ghc [String]
- check :: Options -> Cradle -> [FilePath] -> Ghc [String]
- info :: Options -> Cradle -> FilePath -> ModuleString -> Expression -> Ghc String
- typeOf :: Options -> Cradle -> FilePath -> ModuleString -> Int -> Int -> Ghc String
- listMods :: Options -> Cradle -> Ghc [(String, String)]
- debug :: Options -> Cradle -> FilePath -> Ghc [String]
Cradle
The environment where this library is used.
Cradle | |
|
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 :: OptionsSource
A default Options
.
Types
type ModuleString = StringSource
Module name.
type Expression = StringSource
Haskell expression.
IO
utilities
:: 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.
:: Options | |
-> Cradle | |
-> FilePath | A target file. |
-> ModuleString | A module name. |
-> Expression | A Haskell expression. |
-> IO String |
Obtaining information of a target expression. (GHCi's info:)
:: Options | |
-> Cradle | |
-> FilePath | A target file. |
-> ModuleString | A odule name. |
-> Int | Line number. |
-> Int | Column number. |
-> IO String |
Obtaining type of a target expression. (GHCi's type:)
listLanguages :: Options -> IO StringSource
Listing language extensions.
Obtaining debug information.
Converting the Ghc
monad to the IO
monad
:: Alternative m | |
=> FilePath | A target file displayed in an error message. |
-> Ghc (m a) |
|
-> IO (m a) |
:: Alternative m | |
=> Ghc (m a) |
|
-> IO (m a) |
Ghc
utilities
:: Options | |
-> Cradle | |
-> ModuleString | A module name. (e.g. "Data.List") |
-> Ghc [String] |
Checking syntax of a target file using GHC. Warnings and errors are returned.
:: Options | |
-> Cradle | |
-> FilePath | A target file. |
-> ModuleString | A module name. |
-> Expression | A Haskell expression. |
-> Ghc String |
Obtaining information of a target expression. (GHCi's info:)