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

Safe HaskellNone

Language.Haskell.BuildWrapper.Base

Synopsis

Documentation

data BuildWrapperState Source

the state we keep

Constructors

BuildWrapperState 

Fields

tempFolder :: String

name of temporary folder

cabalPath :: FilePath

path to the cabal executable

cabalFile :: FilePath

path of the project cabal file

verbosity :: Verbosity

verbosity of logging

cabalFlags :: String

flags to pass cabal

cabalOpts :: [String]

extra arguments to cabal configure

data BWNoteStatus Source

status of notes: error or warning

Constructors

BWError 
BWWarning 

data BWLocation Source

location of a note/error (lines and columns start at 1)

Constructors

BWLocation 

Fields

bwlSrc :: FilePath

source file

bwlLine :: Int

line

bwlCol :: Int

column

bwlEndLine :: Int

end line

bwlEndCol :: Int

end line

data BWNote Source

a note on a source file

Constructors

BWNote 

Fields

bwnStatus :: BWNoteStatus

status of the note

bwnTitle :: String

message

bwnLocation :: BWLocation

where the note is

type OpResult a = (a, [BWNote])Source

simple type encapsulating the fact the operations return along with notes generated on files

data BuildResult Source

result: success + files impacted

Constructors

BuildResult Bool [FilePath] 

data WhichCabal Source

result for building one file: success + names data Build1Result=Build1Result Bool [NameDef] deriving (Show,Read,Eq)

instance ToJSON Build1Result where toJSON (Build1Result b ns)= object [r .= b, ns .= map toJSON ns]

instance FromJSON Build1Result where parseJSON (Object v) =Build1Result $ v .: r * v .: ns parseJSON _= mzero

which cabal file to use operations

Constructors

Source

use proper file

Target

use temporary file that was saved in temp folder

data InFileLoc Source

Location inside a file, the file is known and doesn't need to be repeated

Constructors

InFileLoc 

Fields

iflLine :: Int

line

iflColumn :: Int

column

data InFileSpan Source

Span inside a file, the file is known and doesn't need to be repeated

Constructors

InFileSpan 

Fields

ifsStart :: InFileLoc

start location

ifsEnd :: InFileLoc

end location

mkFileSpanSource

Arguments

:: Int

start line

-> Int

start column

-> Int

end line

-> Int

end column

-> InFileSpan 

construct a file span

data NameDef Source

Constructors

NameDef 

Fields

ndName :: Text

name

ndType :: [OutlineDefType]

types: can have several to combine

ndSignature :: Maybe Text

type signature if any

data OutlineDef Source

element of the outline result

Constructors

OutlineDef 

Fields

odName :: Text

name

odType :: [OutlineDefType]

types: can have several to combine

odLoc :: InFileSpan

span in source

odChildren :: [OutlineDef]

children (constructors...)

odSignature :: Maybe Text

type signature if any

odComment :: Maybe Text

comment if any

mkOutlineDefSource

Arguments

:: Text

name

-> [OutlineDefType]

types: can have several to combine

-> InFileSpan

span in source

-> OutlineDef 

constructs an OutlineDef with no children and no type signature

mkOutlineDefWithChildrenSource

Arguments

:: Text

name

-> [OutlineDefType]

types: can have several to combine

-> InFileSpan

span in source

-> [OutlineDef]

children (constructors...)

-> OutlineDef 

constructs an OutlineDef with children and no type signature

data TokenDef Source

Lexer token

Constructors

TokenDef 

Fields

tdName :: Text

type of token

tdLoc :: InFileSpan

location

data ImportExportType Source

Type of import/export directive

Constructors

IEVar

Var

IEAbs

Abs

IEThingAll

import/export everything

IEThingWith

specific import/export list

IEModule

reexport module

data ExportDef Source

definition of export

Constructors

ExportDef 

Fields

eName :: Text

name

eType :: ImportExportType

type

eLoc :: InFileSpan

location in source file

eChildren :: [Text]

children (constructor names, etc.)

data ImportSpecDef Source

definition of an import element

Constructors

ImportSpecDef 

Fields

isName :: Text

name

isType :: ImportExportType

type

isLoc :: InFileSpan

location in source file

isChildren :: [Text]

children (constructor names, etc.)

data ImportDef Source

definition of an import statement

Constructors

ImportDef 

Fields

iModule :: Text

module name

iPackage :: Maybe Text

package name

iLoc :: InFileSpan

location in source file

iQualified :: Bool

is the import qualified

iHiding :: Bool

is the import element list for hiding or exposing

iAlias :: Text

alias name

iChildren :: Maybe [ImportSpecDef]

specific import elements

data OutlineResult Source

complete result for outline

Constructors

OutlineResult 

Fields

orOutline :: [OutlineDef]

outline contents

orExports :: [ExportDef]

exports

orImports :: [ImportDef]

imports

data BuildFlags Source

build flags for a specific file

Constructors

BuildFlags 

Fields

bfAst :: [String]

flags for GHC

bfPreproc :: [String]

flags for preprocessor

bfModName :: Maybe String

module name if known

bfComponent :: Maybe String

component used to get flags, if known

getFullTempDir :: BuildWrapper FilePathSource

get the full path for the temporary directory

getDistDir :: BuildWrapper FilePathSource

get the full path for the temporary dist directory (where cabal will write its output)

getTargetPathSource

Arguments

:: FilePath

relative path of source file

-> BuildWrapper FilePath 

get full path in temporary folder for source file (i.e. where we're going to write the temporary contents of an edited file)

canonicalizeFullPathSource

Arguments

:: FilePath

relative path of source file

-> BuildWrapper FilePath 

get the full, canonicalized path of a source

getFullSrcSource

Arguments

:: FilePath

relative path of source file

-> BuildWrapper FilePath 

get the full path of a source

copyFromMainSource

Arguments

:: Bool

copy even if temp file is newer

-> FilePath

relative path of source file

-> BuildWrapper (Maybe FilePath)

return Just the file if copied, Nothing if no copy was done

copy a file from the normal folders to the temp folder

fileToModule :: FilePath -> StringSource

replace relative file path by module name

data CabalComponent Source

component in cabal file

Constructors

CCLibrary

library

Fields

ccBuildable :: Bool

is the test suite buildable

is the executable buildable

is the library buildable

CCExecutable

executable

Fields

ccExeName :: String

executable name

ccBuildable :: Bool

is the test suite buildable

is the executable buildable

is the library buildable

CCTestSuite

test suite

Fields

ccTestName :: String

test suite name

ccBuildable :: Bool

is the test suite buildable

is the executable buildable

is the library buildable

data CabalPackage Source

a cabal package

Constructors

CabalPackage 

Fields

cpName :: String

name of package

cpVersion :: String

version

cpExposed :: Bool

is the package exposed or hidden

cpDependent :: [CabalComponent]

components in the cabal file that use this package

cpModules :: [String]

all modules. We keep all modules so that we can try to open non exposed but imported modules directly

getRecursiveContents :: FilePath -> IO [FilePath]Source

http:book.realworldhaskell.orgreadio-case-study-a-library-for-searching-the-filesystem.html

deleteGhosts :: [FilePath] -> BuildWrapper [FilePath]Source

delete files in temp folder but not in real folder anymore

fromJustDebug :: String -> Maybe a -> aSource

debug method: fromJust with a message to display when we get Nothing

removeBaseDir :: FilePath -> String -> StringSource

remove a base directory from a string representing a full path

nubOrd :: Ord a => [a] -> [a]Source

nub for Ord objects: use a set

formatJSON :: String -> StringSource

debug method to vaguely format JSON result to dump them

data Usage Source

Usage structure

Constructors

Usage 

Instances