buildwrapper-0.9.0: 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.Base

Description

Data types, State Monad, utility functions

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

logCabalArgs :: Bool

log call to cabal

data BWNoteStatus Source

status of notes: error or warning

Constructors

BWError 
BWWarning 

readObj :: Read a => String -> String -> a Source

read an object from a String, with a given error message if it fails

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

mkEmptySpan :: FilePath -> Int -> Int -> BWLocation Source

build an empty span in a given file at a given location

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

isBWNoteError :: BWNote -> Bool Source

is a note an error?

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

ifsOverlap :: InFileSpan -> InFileSpan -> Bool Source

do spans overlap?

iflOverlap :: InFileSpan -> InFileLoc -> Bool Source

does span overlap location?

mkFileSpan Source

Arguments

:: Int

start line

-> Int

start column

-> Int

end line

-> Int

end column

-> InFileSpan 

construct a file span

data NameDef Source

definition of a name

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,

odStartLineComment :: Maybe Int

comment start line if any,

mkOutlineDef Source

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

mkOutlineDefWithChildren Source

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

get the full path for the temporary directory

getDistDir :: BuildWrapper FilePath Source

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

getTargetPath Source

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)

getTargetPath' Source

Arguments

:: FilePath

relative path of source file

-> FilePath 
-> IO 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)

canonicalizeFullPath Source

Arguments

:: FilePath

relative path of source file

-> BuildWrapper FilePath 

get the full, canonicalized path of a source

getFullSrc Source

Arguments

:: FilePath

relative path of source file

-> BuildWrapper FilePath 

get the full path of a source

copyFromMain Source

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

isSourceMoreRecent :: FilePath -> FilePath -> IO Bool Source

is the source file more recent than the target file?

fileToModule :: FilePath -> String Source

replace relative file path by module name

data CabalComponent Source

component in cabal file

Constructors

CCLibrary

library

Fields

ccBuildable :: Bool

is the library buildable

CCExecutable

executable

Fields

ccExeName :: String

executable name

ccBuildable :: Bool

is the library buildable

CCTestSuite

test suite

Fields

ccTestName :: String

test suite name

ccBuildable :: Bool

is the library buildable

CCBenchmark

test suite

Fields

ccBenchName :: String

benchmark name

ccBuildable :: Bool

is the library buildable

cabalComponentName :: CabalComponent -> String Source

get the cabal component name

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

data ImportClean Source

import clean operation: the span of text to change, the new text

Constructors

ImportClean 

Fields

icSpan :: InFileSpan
 
icText :: Text
 

data LoadContents Source

information about files to load (single file or multiple files)

Constructors

SingleFile 
MultipleFile 

Fields

lmFiles :: [(FilePath, String)]
 

getLoadFiles :: LoadContents -> [(FilePath, String)] Source

get files to load

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

delete files in temp folder but not in real folder anymore

deleteTemp :: BuildWrapper () Source

delete all temporary files

deleteGenerated :: BuildWrapper () Source

delete generated files

fromJustDebug :: String -> Maybe a -> a Source

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

removeBaseDir :: FilePath -> String -> String Source

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

debug method to vaguely format JSON result to dump them

data Usage Source

Usage structure

Constructors

Usage 

Instances

readFile :: FilePath -> IO String Source

read a string from a file, forcing the read and closing the handle

writeFile :: FilePath -> String -> IO () Source

write string to file

withBinaryFile :: FilePath -> IOMode -> (Handle -> IO a) -> IO a Source

perform operation on a binary opened file

data EvalResult Source

Evaluation of result using String since we get them from GHC API this can be fully evaluated via deepseq to make sure any side effect are evaluated

splitString :: Eq a => [a] -> [a] -> ([a], [a]) Source

splits a string at the first occurence of prefix

runAndPrint :: FilePath -> [String] -> IO (ExitCode, String, String) Source

run a program, writing the output/error to standard output as we go