ghc-mod-5.2.0.0: Happy Haskell Programming

Safe HaskellNone

Language.Haskell.GhcMod.Internal

Contents

Description

Low level access to the ghc-mod library.

Synopsis

Types

type GHCOption = StringSource

A single GHC command line option.

type Package = (PackageBaseName, PackageVersion, PackageId)Source

A package's name, verson and id.

type PackageBaseName = StringSource

A package name.

type PackageVersion = StringSource

A package version.

type PackageId = StringSource

A package id.

type IncludeDir = FilePathSource

An include directory for modules.

data CompilerOptions Source

Option information for GHC

Constructors

CompilerOptions 

Fields

ghcOptions :: [GHCOption]

Command line options

includeDirs :: [IncludeDir]

Include directories for modules

depPackages :: [Package]

Dependent package names

Instances

Cabal API

parseCabalFile :: (IOish m, MonadError GhcModError m) => Cradle -> FilePath -> m PackageDescriptionSource

Parse a cabal file and return a PackageDescription.

getCompilerOptions :: (IOish m, MonadError GhcModError m) => [GHCOption] -> Cradle -> PackageDescription -> m CompilerOptionsSource

Getting necessary CompilerOptions from three information sources.

cabalAllBuildInfo :: PackageDescription -> [BuildInfo]Source

Extracting all BuildInfo for libraries, executables, and tests.

cabalDependPackages :: [BuildInfo] -> [PackageBaseName]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 FilePaths for libraries, executables, tests and benchmarks.

Various Paths

ghcLibDir :: FilePathSource

Obtaining the directory for ghc system libraries.

ghcModExecutable :: IO FilePathSource

Returns the path to the currently running ghc-mod executable. With ghc<7.6 this is a guess but >=7.6 uses getExecutablePath.

IO

getDynamicFlags :: IO DynFlagsSource

Return the DynFlags currently in use in the GHC session.

Targets

setTargetFiles :: IOish m => [FilePath] -> GhcModT m ()Source

Set the files as targets and load them.

Logging

withLogger :: IOish m => (DynFlags -> DynFlags) -> GhcModT m () -> GhcModT m (Either String String)Source

Set the session flag (e.g. -Wall or -w:) then executes a body. Logged messages are returned as String. Right is success and Left is failure.

setNoWarningFlags :: DynFlags -> DynFlagsSource

Set DynFlags equivalent to -w:.

setAllWarningFlags :: DynFlags -> DynFlagsSource

Set DynFlags equivalent to -Wall.

Environment, state and logging

data GhcModEnv Source

Constructors

GhcModEnv 

Fields

gmGhcSession :: !(IORef HscEnv)
 
gmOptions :: Options
 
gmCradle :: Cradle
 

Instances

Monad m => MonadReader GhcModEnv (GhcModT m) 

newGhcModEnv :: Options -> FilePath -> IO GhcModEnvSource

data GhcModState Source

Instances

data CompilerMode Source

Constructors

Simple 
Intelligent 

Instances

type GhcModLog = ()Source

Monad utilities

runGhcModT' :: IOish m => GhcModEnv -> GhcModState -> GhcModT m a -> m (Either GhcModError (a, GhcModState), GhcModLog)Source

Run a computation inside GhcModT providing the RWST environment and initial state. This is a low level function, use it only if you know what to do with GhcModEnv and GhcModState.

You should probably look at runGhcModT instead.

hoistGhcModT :: IOish m => (Either GhcModError a, GhcModLog) -> GhcModT m aSource

hoistGhcModT result. Embed a GhcModT computation's result into a GhcModT computation. Note that if the computation that returned result modified the state part of GhcModT this cannot be restored.

Accessing GhcModEnv and GhcModState

GhcModError

GhcMonad Choice

(||>) :: GhcMonad m => m a -> m a -> m aSource

Try the left Ghc action. If IOException occurs, try the right Ghc action.

goNext :: GhcMonad m => m aSource

Go to the next Ghc monad by throwing AltGhcgoNext.

runAnyOne :: GhcMonad m => [m a] -> m aSource

Run any one Ghc monad.

World

data World Source

Instances

Eq World 
Show World