ghc-mod-5.7.0.0: 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

findCradle :: (GmLog m, IOish m, GmOut m) => Programs -> m 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

Instances

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.

Logging

gmLog :: (MonadIO m, GmLog m, GmOut m) => GmLogLevel -> String -> Doc -> m () Source #

>>> Just GmDebug <= Nothing
False
>>> Just GmException <= Just GmDebug
True
>>> Just GmDebug <= Just GmException
False

Types

data GhcPkgDb Source #

GHC package database flags.

Instances

Eq GhcPkgDb Source # 
Show GhcPkgDb Source # 
Generic GhcPkgDb Source # 

Associated Types

type Rep GhcPkgDb :: * -> * #

Methods

from :: GhcPkgDb -> Rep GhcPkgDb x #

to :: Rep GhcPkgDb x -> GhcPkgDb #

Binary GhcPkgDb Source # 

Methods

put :: GhcPkgDb -> Put #

get :: Get GhcPkgDb #

putList :: [GhcPkgDb] -> Put #

type Rep GhcPkgDb Source # 
type Rep GhcPkgDb = D1 (MetaData "GhcPkgDb" "Language.Haskell.GhcMod.Types" "ghc-mod-5.7.0.0-GXpIIXdKa11DltfB1EEyvg" False) ((:+:) (C1 (MetaCons "GlobalDb" PrefixI False) U1) ((:+:) (C1 (MetaCons "UserDb" PrefixI False) U1) (C1 (MetaCons "PackageDb" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)))))

type Symbol = ByteString Source #

Type of function and operation names.

data SymbolDb Source #

Database from Symbol to \['ModuleString'\].

Instances

Generic SymbolDb Source # 

Associated Types

type Rep SymbolDb :: * -> * #

Methods

from :: SymbolDb -> Rep SymbolDb x #

to :: Rep SymbolDb x -> SymbolDb #

Binary SymbolDb Source # 

Methods

put :: SymbolDb -> Put #

get :: Get SymbolDb #

putList :: [SymbolDb] -> Put #

NFData SymbolDb Source # 

Methods

rnf :: SymbolDb -> () #

type Rep SymbolDb Source # 

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.

Monad Types

type GhcModT m = GmT (GmOutT m) Source #

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.

withOptions :: GmEnv m => (Options -> Options) -> m a -> m a Source #

dropSession :: IOish m => GhcModT m () Source #

Drop the currently active GHC session, the next that requires a GHC session will initialize a new one.

GhcMod utilities

boot :: IOish m => GhcModT m String Source #

Printing necessary information for front-end booting.

browse Source #

Arguments

:: IOish m 
=> BrowseOpts

Configuration parameters

-> String

A module name. (e.g. "Data.List", "base:Prelude")

-> GhcModT m String 

Getting functions, classes, etc from a module.

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 
=> LintOpts

Configuration parameters

-> 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 :: forall m. (IOish m, GmOut m, GmEnv m) => m String Source #

Obtaining root information.

types Source #

Arguments

:: IOish m 
=> Bool

Include constraints into type signature

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

Arguments

:: (IOish m, Gm m) 
=> Bool

detailed, if True, also prints packages that modules belong to.

-> m String 

Listing installed modules.

languages :: IOish m => GhcModT m String Source #

Listing language extensions.

flags :: IOish m => GhcModT m String Source #

Listing of GHC flags, same as ghc's --show-options with ghc >= 7.10.

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

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

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

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

dumpSymbol :: IOish m => GhcModT m () Source #

Dumps a Binary representation of SymbolDb to stdout

SymbolDb

loadSymbolDb :: IOish m => GhcModT m SymbolDb Source #

Loading a file and creates SymbolDb.

Output

gmPutStr :: (MonadIO m, GmOut m) => String -> m () Source #

gmErrStr :: (MonadIO m, GmOut m) => String -> m () Source #

gmPutStrLn :: (MonadIO m, GmOut m) => String -> m () Source #

gmErrStrLn :: (MonadIO m, GmOut m) => String -> m () Source #

FileMapping

loadMappedFile Source #

Arguments

:: IOish m 
=> FilePath

'from', file that will be mapped

-> FilePath

'to', file to take source from

-> GhcModT m () 

maps FilePath, given as first argument to take source from FilePath given as second argument. Works exactly the same as first form of `--map-file` CLI option.

'from' can be either full path, or path relative to project root. 'to' has to be either relative to project root, or full path (preferred)

loadMappedFileSource Source #

Arguments

:: IOish m 
=> FilePath

'from', file that will be mapped

-> String

'src', source

-> GhcModT m () 

maps FilePath, given as first argument to have source as given by second argument.

'from' may or may not exist, and should be either full path, or relative to project root.

unloadMappedFile Source #

Arguments

:: IOish m 
=> FilePath

'file', file to unmap

-> GhcModT m () 

unloads previously mapped file 'file', so that it's no longer mapped, and removes any temporary files created when file was mapped.

'file' should be either full path, or relative to project root.