ghc-mod-5.1.0.2: Happy Haskell Programming

Safe HaskellNone
LanguageHaskell2010

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.

cradleCabalFile :: Maybe FilePath

The file name of the found cabal file.

cradlePkgDbStack :: [GhcPkgDb]

Package database stack

Instances

findCradle :: IO Cradle Source

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
 
hlintOpts :: [String]
 
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

lineSeparator :: LineSeparator

Line separator string.

newtype LineSeparator Source

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

Constructors

LineSeparator String 

data OutputStyle Source

Output style.

Constructors

LispStyle

S expression style.

PlainStyle

Plain textstyle.

Types

type ModuleString = String Source

Module name.

type Expression = String Source

Haskell expression.

data GhcPkgDb Source

GHC package database flags.

Instances

type Symbol = String Source

Type of function and operation names.

data SymbolDb Source

Database from Symbol to [ModuleString].

Instances

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.

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 String Source

Printing necessary information for front-end booting.

browse Source

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.

check Source

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.

checkSyntax Source

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 String Source

Obtaining debug information.

expandTemplate Source

Arguments

:: IOish m 
=> [FilePath]

The target files.

-> GhcModT m String 

Expanding Haskell Template.

info Source

Arguments

:: IOish m 
=> FilePath

A target file.

-> Expression

A Haskell expression.

-> GhcModT m String 

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

lint Source

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 String Source

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

rootInfo :: IOish m => GhcModT m String Source

Obtaining root information.

types Source

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:)

splits Source

Arguments

:: IOish m 
=> FilePath

A target file.

-> Int

Line number.

-> Int

Column number.

-> GhcModT m String 

Splitting a variable in a equation.

sig Source

Arguments

:: IOish m 
=> FilePath

A target file.

-> Int

Line number.

-> Int

Column number.

-> GhcModT m String 

Create a initial body from a signature.

refine Source

Arguments

:: IOish m 
=> FilePath

A target file.

-> Int

Line number.

-> Int

Column number.

-> Expression

A Haskell expression.

-> GhcModT m String 

auto Source

Arguments

:: IOish m 
=> FilePath

A target file.

-> Int

Line number.

-> Int

Column number.

-> GhcModT m String 

modules :: IOish m => GhcModT m String Source

Listing installed modules.

languages :: IOish m => GhcModT m String Source

Listing language extensions.

flags :: IOish m => GhcModT m String Source

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

findSymbol :: IOish m => Symbol -> GhcModT m String Source

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

lookupSymbol :: IOish m => Symbol -> SymbolDb -> GhcModT m String Source

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

dumpSymbol :: IOish m => GhcModT m String Source

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, MonadError GhcModError m) => m SymbolDb Source

Loading a file and creates SymbolDb.