Safe Haskell | None |
---|
Low level access to the ghc-mod library.
- type LogReader = IO [String]
- type GHCOption = String
- type Package = String
- type IncludeDir = FilePath
- data CompilerOptions = CompilerOptions {
- ghcOptions :: [GHCOption]
- includeDirs :: [IncludeDir]
- depPackages :: [Package]
- parseCabalFile :: FilePath -> IO PackageDescription
- getCompilerOptions :: [GHCOption] -> Cradle -> PackageDescription -> IO CompilerOptions
- cabalAllBuildInfo :: PackageDescription -> [BuildInfo]
- cabalDependPackages :: [BuildInfo] -> [Package]
- cabalSourceDirs :: [BuildInfo] -> [IncludeDir]
- cabalAllTargets :: PackageDescription -> IO ([String], [String], [String], [String])
- canCheckFast :: ModuleGraph -> Bool
- getDynamicFlags :: IO DynFlags
- initializeFlags :: GhcMonad m => Options -> m ()
- initializeFlagsWithCradle :: GhcMonad m => Options -> Cradle -> [GHCOption] -> Bool -> m (LogReader, Maybe PackageDescription)
- setTargetFiles :: GhcMonad m => [FilePath] -> m ()
- checkSlowAndSet :: GhcMonad m => m ()
- (||>) :: Ghc a -> Ghc a -> Ghc a
- goNext :: Ghc a
- runAnyOne :: [Ghc a] -> Ghc a
- (|||>) :: GhcMonad m => m a -> m a -> m a
Types
type IncludeDir = FilePathSource
An include directory for modules.
data CompilerOptions Source
Option information for GHC
CompilerOptions | |
|
Cabal API
parseCabalFile :: FilePath -> IO PackageDescriptionSource
Parsing a cabal file and returns PackageDescription
.
IOException
is thrown if parsing fails.
getCompilerOptions :: [GHCOption] -> Cradle -> PackageDescription -> IO CompilerOptionsSource
Getting necessary CompilerOptions
from three information sources.
cabalAllBuildInfo :: PackageDescription -> [BuildInfo]Source
Extracting all BuildInfo
for libraries, executables, tests and benchmarks.
cabalDependPackages :: [BuildInfo] -> [Package]Source
Extracting package names of dependency.
cabalSourceDirs :: [BuildInfo] -> [IncludeDir]Source
Extracting include directories for modules.
cabalAllTargets :: PackageDescription -> IO ([String], [String], [String], [String])Source
Extracting all Module
FilePath
s for libraries, executables,
tests and benchmarks.
GHC API
canCheckFast :: ModuleGraph -> BoolSource
Checking if Template Haskell or quasi quotes are used. If not, the process can be faster.
Getting DynFlags
getDynamicFlags :: IO DynFlagsSource
Return the DynFlags
currently in use in the GHC session.
Initializing DynFlags
initializeFlags :: GhcMonad m => Options -> m ()Source
Initialize the DynFlags
relating to the compilation of a single
file or GHC session.
initializeFlagsWithCradle :: GhcMonad m => Options -> Cradle -> [GHCOption] -> Bool -> m (LogReader, Maybe PackageDescription)Source
GhcMonad
setTargetFiles :: GhcMonad m => [FilePath] -> m ()Source
Set the files that GHC will load / compile.
checkSlowAndSet :: GhcMonad m => m ()Source
Ghc
Choice
(||>) :: Ghc a -> Ghc a -> Ghc aSource
Try the left Ghc
action. If IOException
occurs, try
the right Ghc
action.