ghc-mod-5.4.0.0: Happy Haskell Programming

Safe HaskellNone
LanguageHaskell2010

Language.Haskell.GhcMod.Types

Synopsis

Documentation

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.

class MonadIOC m => MonadIO m where Source

Methods

liftIO :: IO a -> m a Source

data OutputStyle Source

Output style.

Constructors

LispStyle

S expression style.

PlainStyle

Plain textstyle.

newtype LineSeparator Source

The type for line separator. Historically, a Null string is used.

Constructors

LineSeparator String 

data FileMapping Source

Constructors

FileMapping 

Fields

fmPath :: FilePath
 
fmTemp :: Bool
 

data Programs Source

Constructors

Programs 

Fields

ghcProgram :: FilePath

ghc program name.

ghcPkgProgram :: FilePath

ghc-pkg program name.

cabalProgram :: FilePath

cabal program name.

stackProgram :: FilePath

stack program name.

Instances

data OutputOpts Source

Constructors

OutputOpts 

Fields

ooptLogLevel :: GmLogLevel

Verbosity

ooptStyle :: OutputStyle
 
ooptLineSeparator :: LineSeparator

Line separator string.

ooptLinePrefix :: Maybe (String, String)

Stdout/err line multiplexing using prefix encoding. fst is stdout, snd is stderr prefix.

data Options Source

Constructors

Options 

Fields

optOutput :: OutputOpts
 
optPrograms :: Programs
 
optGhcUserOptions :: [GHCOption]

GHC command line options set on the ghc-mod command line

optOperators :: Bool

If True, browse also returns operators.

optDetailed :: Bool

If True, browse also returns types.

optQualified :: Bool

If True, browse will return fully qualified name

optHlintOpts :: [String]
 
optFileMappings :: [(FilePath, Maybe FilePath)]
 

Instances

data Cradle Source

The environment where this library is used.

Constructors

Cradle 

Fields

cradleProject :: Project
 
cradleCurrentDir :: FilePath

The directory where this library is executed.

cradleRootDir :: FilePath

The project root directory.

cradleTempDir :: FilePath

Per-Project temporary directory

cradleCabalFile :: Maybe FilePath

The file name of the found cabal file.

cradleDistDir :: FilePath

The build info directory.

data GhcModEnv Source

Constructors

GhcModEnv 

type GHCOption = String Source

A single GHC command line option.

type IncludeDir = FilePath Source

An include directory for modules.

type PackageBaseName = String Source

A package name.

type PackageVersion = String Source

A package version.

type PackageId = String Source

A package id.

type Package = (PackageBaseName, PackageVersion, PackageId) Source

A package's name, verson and id.

newtype Expression Source

Haskell expression.

Constructors

Expression 

type PkgDb = Map Package PackageConfig Source

Collection of packages

data GhcModError Source

Constructors

GMENoMsg

Unknown error

GMEString String

Some Error with a message. These are produced mostly by fail calls on GhcModT.

GMECabalConfigure GhcModError

Configuring a cabal project failed.

GMEStackConfigure GhcModError

Configuring a stack project failed.

GMEStackBootstrap GhcModError

Bootstrapping stack environment failed (process exited with failure)

GMECabalCompAssignment [(Either FilePath ModuleName, Set ChComponentName)]

Could not find a consistent component assignment for modules

GMEProcess String String [String] (Either Int GhcModError)

Launching an operating system process failed. Fields in order: function, command, arguments, (stdout, stderr, exitcode)

GMENoCabalFile

No cabal file found.

GMETooManyCabalFiles [FilePath]

Too many cabal files found.

GMEWrongWorkingDirectory FilePath FilePath 

lOptQualified :: forall cat. ArrowApply cat => Lens cat Options Bool Source

lOptOperators :: forall cat. ArrowApply cat => Lens cat Options Bool Source

lOptHlintOpts :: forall cat. ArrowApply cat => Lens cat Options [String] Source

lOptDetailed :: forall cat. ArrowApply cat => Lens cat Options Bool Source

data ModuleName :: *

A ModuleName is essentially a simple string, e.g. Data.List.