ghc-mod-5.2.0.0: Happy Haskell Programming

Safe HaskellNone

Language.Haskell.GhcMod

Contents

Description

The ghc-mod library.

Synopsis

Cradle

data Cradle Source

The environment where this library is used.

Constructors

Cradle 

Fields

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.

cradlePkgDbStack :: [GhcPkgDb]

Package database stack

Instances

Eq Cradle 
Show Cradle 

findCradle :: IO CradleSource

Finding Cradle. Find a cabal file by tracing ancestor directories. Find a sandbox according to a cabal sandbox config in a cabal directory.

Options

data Options Source

Constructors

Options 

Fields

outputStyle :: OutputStyle
 
lineSeparator :: LineSeparator

Line separator string.

ghcProgram :: FilePath

ghc program name.

cabalProgram :: FilePath

cabal program name.

ghcUserOptions :: [GHCOption]

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

operators :: Bool

If True, browse also returns operators.

detailed :: Bool

If True, browse also returns types.

qualified :: Bool

If True, browse will return fully qualified name

hlintOpts :: [String]
 

Instances

Show Options 

newtype LineSeparator Source

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

Constructors

LineSeparator String 

Instances

data OutputStyle Source

Output style.

Constructors

LispStyle

S expression style.

PlainStyle

Plain textstyle.

Instances

Types

type ModuleString = StringSource

Module name.

type Expression = StringSource

Haskell expression.

data GhcPkgDb Source

GHC package database flags.

Instances

Eq GhcPkgDb 
Show GhcPkgDb 

type Symbol = StringSource

Type of function and operation names.

data SymbolDb Source

Database from Symbol to [ModuleString].

Instances

Show SymbolDb 

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.

GMECabalFlags GhcModError

Retrieval of the cabal configuration flags failed.

GMEProcess [String] GhcModError

Launching an operating system process failed. The first field is the command.

Monad Types

data GhcModT m a Source

This is basically a newtype wrapper around StateT, ErrorT, JournalT and ReaderT with custom instances for GhcMonad and it's constraints that means you can run (almost) all functions from the GHC API on top of GhcModT transparently.

The inner monad m should have instances for MonadIO and MonadBaseControl IO, in the common case this is simply IO. Most mtl monads already have MonadBaseControl IO instances, see the monad-control package.

Instances

MonadTrans GhcModT 
MonadBaseControl IO m => MonadBase IO (GhcModT m) 
MonadBaseControl IO m => MonadBaseControl IO (GhcModT m) 
Monad m => MonadError GhcModError (GhcModT m) 
Monad m => MonadReader GhcModEnv (GhcModT m) 
MonadState s m => MonadState s (GhcModT m) 
MonadWriter w m => MonadWriter w (GhcModT m) 
Monad m => Monad (GhcModT m) 
Functor m => Functor (GhcModT m) 
Monad m => MonadPlus (GhcModT m) 
(Monad m, Functor m) => Applicative (GhcModT m) 
(Monad m, Functor m) => Alternative (GhcModT m) 
MonadIO m => MonadIO (GhcModT m) 
MonadIO m => MonadIO (GhcModT m) 
(Functor m, MonadIO m, MonadBaseControl IO m) => HasDynFlags (GhcModT m) 
(MonadIO m, MonadBaseControl IO m) => ExceptionMonad (GhcModT m) 
(Functor m, MonadIO m, MonadBaseControl IO m) => GhcMonad (GhcModT m) 

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.

Monad utilities

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

Run a GhcModT m computation.

GhcMod utilities

boot :: IOish m => GhcModT m StringSource

Printing necessary information for front-end booting.

browseSource

Arguments

:: IOish m 
=> ModuleString

A module name. (e.g. "Data.List")

-> GhcModT m String 

Getting functions, classes, etc from a module. If detailed is True, their types are also obtained. If operators is True, operators are also returned.

checkSource

Arguments

:: IOish m 
=> [FilePath]

The target files.

-> GhcModT m (Either String String) 

Checking syntax of a target file using GHC. Warnings and errors are returned.

checkSyntaxSource

Arguments

:: IOish m 
=> [FilePath]

The target files.

-> GhcModT m String 

Checking syntax of a target file using GHC. Warnings and errors are returned.

debugInfo :: IOish m => GhcModT m StringSource

Obtaining debug information.

expandTemplateSource

Arguments

:: IOish m 
=> [FilePath]

The target files.

-> GhcModT m String 

Expanding Haskell Template.

infoSource

Arguments

:: IOish m 
=> FilePath

A target file.

-> Expression

A Haskell expression.

-> GhcModT m String 

Obtaining information of a target expression. (GHCi's info:)

lintSource

Arguments

:: IOish m 
=> FilePath

A target file.

-> GhcModT m String 

Checking syntax of a target file using hlint. Warnings and errors are returned.

pkgDoc :: IOish m => String -> GhcModT m StringSource

Obtaining the package name and the doc path of a module.

rootInfo :: IOish m => GhcModT m StringSource

Obtaining root information.

typesSource

Arguments

:: IOish m 
=> FilePath

A target file.

-> Int

Line number.

-> Int

Column number.

-> GhcModT m String 

Obtaining type of a target expression. (GHCi's type:)

splitsSource

Arguments

:: IOish m 
=> FilePath

A target file.

-> Int

Line number.

-> Int

Column number.

-> GhcModT m String 

Splitting a variable in a equation.

sigSource

Arguments

:: IOish m 
=> FilePath

A target file.

-> Int

Line number.

-> Int

Column number.

-> GhcModT m String 

Create a initial body from a signature.

refineSource

Arguments

:: IOish m 
=> FilePath

A target file.

-> Int

Line number.

-> Int

Column number.

-> Expression

A Haskell expression.

-> GhcModT m String 

autoSource

Arguments

:: IOish m 
=> FilePath

A target file.

-> Int

Line number.

-> Int

Column number.

-> GhcModT m String 

modules :: IOish m => GhcModT m StringSource

Listing installed modules.

languages :: IOish m => GhcModT m StringSource

Listing language extensions.

flags :: IOish m => GhcModT m StringSource

Listing GHC flags. (e.g -fno-warn-orphans)

findSymbol :: IOish m => Symbol -> GhcModT m StringSource

Looking up SymbolDb with Symbol to [ModuleString] which will be concatenated. loadSymbolDb is called internally.

lookupSymbol :: IOish m => Symbol -> SymbolDb -> GhcModT m StringSource

Looking up SymbolDb with Symbol to [ModuleString] which will be concatenated.

dumpSymbol :: IOish m => FilePath -> GhcModT m StringSource

Dumping a set of (Symbol,[ModuleString]) to a file if the file does not exist or is invalid. The file name is printed.

SymbolDb

loadSymbolDb :: IOish m => GhcModT m SymbolDbSource

Loading a file and creates SymbolDb.