buildwrapper-0.8.11: A library and an executable that provide an easy API for a Haskell IDE

Copyright(c) JP Moresmau 2011
LicenseBSD3
Maintainerjpmoresmau@gmail.com
Stabilitybeta
Portabilityportable
Safe HaskellNone
LanguageHaskell98

Language.Haskell.BuildWrapper.GHC

Description

Load relevant module in the GHC AST and get GHC messages and thing at point info. Also use the GHC lexer for syntax highlighting.

Synopsis

Documentation

type GHCApplyFunction a = FilePath -> TypecheckedModule -> Ghc a Source

a function taking the file name and typechecked module as parameters

getAST Source

Arguments

:: FilePath

the source file

-> FilePath

the base directory

-> String

the module name

-> [String]

the GHC options

-> IO (OpResult (Maybe TypecheckedSource)) 

get the GHC typechecked AST

withAST Source

Arguments

:: (TypecheckedModule -> Ghc a)

the action

-> FilePath

the source file

-> FilePath

the base directory

-> String

the module name

-> [String]

the GHC options

-> IO (Maybe a) 

perform an action on the GHC Typechecked module

withJSONAST Source

Arguments

:: (Value -> IO a)

the action

-> FilePath

the source file

-> FilePath

the base directory

-> String

the module name

-> [String]

the GHC options

-> IO (Maybe a) 

perform an action on the GHC JSON AST

withASTNotes Source

Arguments

:: GHCApplyFunction a

the final action to perform on the result

-> (FilePath -> FilePath)

transform given file path to find bwinfo path

-> FilePath

the base directory

-> LoadContents

what to load

-> [String]

the GHC options

-> IO (OpResult [a]) 

the main method loading the source contents into GHC

initGHC Source

Arguments

:: Ghc a 
-> [String]

the GHC options

-> IO a 

init GHC session

ghcWithASTNotes Source

Arguments

:: GHCApplyFunction a

the final action to perform on the result

-> (FilePath -> FilePath)

transform given file path to find bwinfo path

-> FilePath

the base directory

-> LoadContents

what to load

-> Bool

add the target?

-> Ghc (OpResult [a]) 

run a GHC action and get results with notes

isWarnIsError :: DynFlags -> Bool Source

do we have -Werror

ghcMessagesToNotes Source

Arguments

:: DynFlags 
-> FilePath

base directory

-> Messages

GHC messages

-> [BWNote] 

Convert Messages to '[BWNote]'.

This will mix warnings and errors, but you can split them back up by filtering the '[BWNote]' based on the bw_status.

getGhcNamesInScope Source

Arguments

:: FilePath

source path

-> FilePath

base directory

-> String

module name

-> [String]

build options

-> IO [String] 

get all names in scope

getGhcNameDefsInScope Source

Arguments

:: FilePath

source path

-> FilePath

base directory

-> String

module name

-> [String]

build options

-> IO (OpResult (Maybe [NameDef])) 

get all names in scope, packaged in NameDefs

getGhcNameDefsInScopeLongRunning Source

Arguments

:: FilePath

source path

-> FilePath

base directory

-> String

module name

-> [String]

build options

-> IO () 

get all names in scope, packaged in NameDefs, and keep running a loop listening to commands

getEvalResults :: forall m. GhcMonad m => String -> m [EvalResult] Source

evaluate expression in the GHC monad

name2nd :: GhcMonad m => DynFlags -> Name -> m NameDef Source

convert a Name int a NameDef

getThingAtPointJSON Source

Arguments

:: Int

line

-> Int

column -> Bool ^ do we want the result qualified by the module -> Bool ^ do we want the full type or just the haddock type

-> FilePath

source file path

-> FilePath

base directory

-> String

module name

-> [String]

build flags

-> IO (Maybe ThingAtPoint) 

get the "thing" at a particular point (line/column) in the source this is using the saved JSON info if available

getLocalsJSON Source

Arguments

:: Int

start line

-> Int

start column

-> Int

end line

-> Int

end column

-> FilePath

source file path

-> FilePath

base directory

-> String

module name

-> [String]

build flags

-> IO [ThingAtPoint] 

get the "thing" at a particular point (line/column) in the source this is using the saved JSON info if available

eval Source

Arguments

:: String

the expression

-> FilePath

source file path

-> FilePath

base directory

-> String

module name

-> [String]

build flags

-> IO [EvalResult] 

evaluate an expression

ghcSpanToLocation :: SrcSpan -> InFileSpan Source

convert a GHC SrcSpan to a Span, ignoring the actual file info

ghcSpanToBWLocation Source

Arguments

:: FilePath

Base directory

-> SrcSpan 
-> BWLocation 

convert a GHC SrcSpan to a BWLocation

ghcColToScionCol :: Int -> Int Source

convert a column info from GHC to our system (1 based)

scionColToGhcCol :: Int -> Int Source

convert a column info from our system (1 based) to GHC

ghctokensArbitrary Source

Arguments

:: FilePath

The file path to the document

-> String

The document's contents

-> [String]

The options

-> IO (Either BWNote [Located Token]) 

Get a stream of tokens generated by the GHC lexer from the current document

ghctokensArbitrary' Source

Arguments

:: FilePath

The file path to the document

-> String

The document's contents

-> Ghc (Either BWNote [Located Token]) 

Get a stream of tokens generated by the GHC lexer from the current document

lexTokenStreamH :: StringBuffer -> RealSrcLoc -> DynFlags -> ParseResult [Located Token] Source

like lexTokenStream, but keep Haddock flag

lexLoc :: RealSrcLoc Source

get lexer initial location

lexerFlags :: [ExtensionFlag] Source

get lexer flags

ofInterest :: Located Token -> Bool Source

Filter tokens whose span appears legitimate (start line is less than end line, start column is less than end column.)

tokenToType :: Located Token -> TokenDef Source

Convert a GHC token to an interactive token (abbreviated token type)

tokenTypesArbitrary :: FilePath -> String -> Bool -> [String] -> IO (Either BWNote [TokenDef]) Source

Generate the interactive token list used by EclipseFP for syntax highlighting, in the IO monad

tokenTypesArbitrary' :: FilePath -> String -> Bool -> Ghc (Either BWNote [TokenDef]) Source

Generate the interactive token list used by EclipseFP for syntax highlighting, when already in a GHC session

occurrences Source

Arguments

:: FilePath

Project root or base directory for absolute path conversion

-> String

Contents to be parsed

-> Text

Token value to find

-> Bool

Literate source flag (True = literate, False = ordinary)

-> [String]

Options

-> IO (Either BWNote [TokenDef]) 

Extract occurrences based on lexing

occurrences' Source

Arguments

:: FilePath

Project root or base directory for absolute path conversion

-> String

Contents to be parsed

-> Text

Token value to find

-> Bool

Literate source flag (True = literate, False = ordinary)

-> Ghc (Either BWNote [TokenDef]) 

Extract occurrences based on lexing

generateTokens Source

Arguments

:: FilePath

The project's root directory

-> String

The current document contents, to be parsed

-> Bool

Literate Haskell flag

-> [String]

The options

-> ([Located Token] -> [TokenDef])

Transform function from GHC tokens to TokenDefs

-> ([TokenDef] -> a)

The TokenDef filter function

-> IO (Either BWNote a) 

Parse the current document, generating a TokenDef list, filtered by a function

generateTokens' Source

Arguments

:: FilePath

The project's root directory

-> String

The current document contents, to be parsed

-> Bool

Literate Haskell flag

-> ([Located Token] -> [TokenDef])

Transform function from GHC tokens to TokenDefs

-> ([TokenDef] -> a)

The TokenDef filter function

-> Ghc (Either BWNote a) 

Parse the current document, generating a TokenDef list, filtered by a function

preprocessSource Source

Arguments

:: String

the source contents

-> Bool

is the source literate Haskell

-> ([TokenDef], String)

the preprocessor tokens and the final valid Haskell source

Preprocess some source, returning the literate and Haskell source as tuple.

data PPBehavior Source

preprocessor behavior data

Instances

ghcErrMsgToNote :: DynFlags -> FilePath -> ErrMsg -> BWNote Source

convert a GHC error message to our note type

ghcWarnMsgToNote :: DynFlags -> FilePath -> WarnMsg -> BWNote Source

convert a GHC warning message to our note type

ghcMsgToNote :: DynFlags -> BWNoteStatus -> FilePath -> ErrMsg -> BWNote Source

convert a GHC message to our note type Note that we do *not* include the extra info, since that information is only useful in the case where we do not show the error location directly in the source.

removeStatus :: BWNoteStatus -> String -> String Source

remove the initial status text from a message

mkUnqualTokenValue Source

Arguments

:: FastString

the name

-> Text 

make unqualified token

mkQualifiedTokenValue Source

Arguments

:: FastString

the qualifier

-> FastString

the name

-> Text 

make qualified token: join the qualifier and the name by a dot

mkTokenName :: Token -> Text Source

make a text name from a token

tokenType :: Token -> Text Source

get token type from Token

dotFS :: FastString Source

a dot as a FastString

tokenValue :: Bool -> Token -> Text Source

generate a token value

start :: SrcSpan -> (Int, Int) Source

extract start line and column from SrcSpan

end :: SrcSpan -> (Int, Int) Source

extract end line and column from SrcSpan

type AliasMap = Map ModuleName [ModuleName] Source

map of module aliases

ghcImportToUsage :: Text -> LImportDecl Name -> ([Usage], AliasMap) -> Ghc ([Usage], AliasMap) Source

get usages from GHC imports

ghcLIEToUsage :: DynFlags -> Maybe Text -> Text -> Text -> LIE Name -> [Usage] Source

get usages from GHC IE

ghcExportToUsage :: DynFlags -> Text -> Text -> AliasMap -> LIE Name -> Ghc [Usage] Source

get usage from GHC exports

ghcNameToUsage :: DynFlags -> Maybe Text -> Text -> Text -> Name -> SrcSpan -> Bool -> Usage Source

generate a usage for a name

type ImportMap = Map Text (LImportDecl Name, [Text]) Source

map of imports

ghcImportMap :: LImportDecl Name -> Ghc ImportMap Source

build an import map from all imports

type TypeMap = Map Text (Map Text (Set Text)) Source

module, function/type, constructors

type FinalImportValue = (LImportDecl Name, Map Text (Set Text)) Source

mapping to import declaration to actually needed names

type FinalImportMap = Map Text FinalImportValue Source

map from original text to needed names

ghcCleanImports Source

Arguments

:: FilePath

source path

-> FilePath

base directory

-> String

module name

-> [String]

build options

-> Bool

format?

-> IO (OpResult [ImportClean]) 

clean imports