Cabal-1.4.0.0: A framework for packaging Haskell softwareSource codeContentsIndex
Distribution.PackageDescription
Portabilityportable
Stabilityalpha
MaintainerIsaac Jones <ijones@syntaxpolice.org>
Contents
Package descriptions
Libraries
Executables
Parsing
Build information
Supplementary build information
package configuration
Supplementary build information
Deprecated compat stuff
Description
Package description and parsing.
Synopsis
data PackageDescription = PackageDescription {
package :: PackageIdentifier
license :: License
licenseFile :: FilePath
copyright :: String
maintainer :: String
author :: String
stability :: String
testedWith :: [(CompilerFlavor, VersionRange)]
homepage :: String
pkgUrl :: String
synopsis :: String
description :: String
category :: String
customFieldsPD :: [(String, String)]
buildDepends :: [Dependency]
descCabalVersion :: VersionRange
buildType :: Maybe BuildType
library :: Maybe Library
executables :: [Executable]
dataFiles :: [FilePath]
dataDir :: FilePath
extraSrcFiles :: [FilePath]
extraTmpFiles :: [FilePath]
}
data GenericPackageDescription = GenericPackageDescription {
packageDescription :: PackageDescription
genPackageFlags :: [Flag]
condLibrary :: Maybe (CondTree ConfVar [Dependency] Library)
condExecutables :: [(String, CondTree ConfVar [Dependency] Executable)]
}
emptyPackageDescription :: PackageDescription
readPackageDescription :: Verbosity -> FilePath -> IO GenericPackageDescription
writePackageDescription :: FilePath -> PackageDescription -> IO ()
parsePackageDescription :: String -> ParseResult GenericPackageDescription
showPackageDescription :: PackageDescription -> String
data BuildType
= Simple
| Configure
| Make
| Custom
| UnknownBuildType String
knownBuildTypes :: [BuildType]
data Library = Library {
exposedModules :: [String]
libBuildInfo :: BuildInfo
}
emptyLibrary :: Library
withLib :: PackageDescription -> a -> (Library -> IO a) -> IO a
hasLibs :: PackageDescription -> Bool
libModules :: PackageDescription -> [String]
data Executable = Executable {
exeName :: String
modulePath :: FilePath
buildInfo :: BuildInfo
}
emptyExecutable :: Executable
withExe :: PackageDescription -> (Executable -> IO a) -> IO ()
hasExes :: PackageDescription -> Bool
exeModules :: PackageDescription -> [String]
data FieldDescr a = FieldDescr {
fieldName :: String
fieldGet :: a -> Doc
fieldSet :: LineNo -> String -> a -> ParseResult a
}
type LineNo = Int
data BuildInfo = BuildInfo {
buildable :: Bool
buildTools :: [Dependency]
cppOptions :: [String]
ccOptions :: [String]
ldOptions :: [String]
pkgconfigDepends :: [Dependency]
frameworks :: [String]
cSources :: [FilePath]
hsSourceDirs :: [FilePath]
otherModules :: [String]
extensions :: [Extension]
extraLibs :: [String]
extraLibDirs :: [String]
includeDirs :: [FilePath]
includes :: [FilePath]
installIncludes :: [FilePath]
options :: [(CompilerFlavor, [String])]
ghcProfOptions :: [String]
ghcSharedOptions :: [String]
customFieldsBI :: [(String, String)]
}
emptyBuildInfo :: BuildInfo
allBuildInfo :: PackageDescription -> [BuildInfo]
hcOptions :: CompilerFlavor -> BuildInfo -> [String]
type HookedBuildInfo = (Maybe BuildInfo, [(String, BuildInfo)])
emptyHookedBuildInfo :: HookedBuildInfo
updatePackageDescription :: HookedBuildInfo -> PackageDescription -> PackageDescription
data Flag = MkFlag {
flagName :: FlagName
flagDescription :: String
flagDefault :: Bool
}
newtype FlagName = FlagName String
type FlagAssignment = [(FlagName, Bool)]
data CondTree v c a = CondNode {
condTreeData :: a
condTreeConstraints :: c
condTreeComponents :: [(Condition v, CondTree v c a, Maybe (CondTree v c a))]
}
data ConfVar
= OS OS
| Arch Arch
| Flag FlagName
| Impl CompilerFlavor VersionRange
data Condition c
= Var c
| Lit Bool
| CNot (Condition c)
| COr (Condition c) (Condition c)
| CAnd (Condition c) (Condition c)
freeVars :: CondTree ConfVar c a -> [FlagName]
readHookedBuildInfo :: Verbosity -> FilePath -> IO HookedBuildInfo
parseHookedBuildInfo :: String -> ParseResult HookedBuildInfo
writeHookedBuildInfo :: FilePath -> HookedBuildInfo -> IO ()
showHookedBuildInfo :: HookedBuildInfo -> String
data ParseResult a
= ParseFailed PError
| ParseOk [PWarning] a
setupMessage :: Verbosity -> String -> PackageDescription -> IO ()
cabalVersion :: Version
Package descriptions
data PackageDescription Source
This data type is the internal representation of the file pkg.cabal. It contains two kinds of information about the package: information which is needed for all packages, such as the package name and version, and information which is needed for the simple build system only, such as the compiler options and library name.
Constructors
PackageDescription
package :: PackageIdentifier
license :: License
licenseFile :: FilePath
copyright :: String
maintainer :: String
author :: String
stability :: String
testedWith :: [(CompilerFlavor, VersionRange)]
homepage :: String
pkgUrl :: String
synopsis :: StringA one-line summary of this package
description :: StringA more verbose description of this package
category :: String
customFieldsPD :: [(String, String)]Custom fields starting with x-, stored in a simple assoc-list.
buildDepends :: [Dependency]
descCabalVersion :: VersionRangeIf this package depends on a specific version of Cabal, give that here.
buildType :: Maybe BuildType
library :: Maybe Library
executables :: [Executable]
dataFiles :: [FilePath]
dataDir :: FilePath
extraSrcFiles :: [FilePath]
extraTmpFiles :: [FilePath]
show/hide Instances
data GenericPackageDescription Source
Constructors
GenericPackageDescription
packageDescription :: PackageDescription
genPackageFlags :: [Flag]
condLibrary :: Maybe (CondTree ConfVar [Dependency] Library)
condExecutables :: [(String, CondTree ConfVar [Dependency] Executable)]
show/hide Instances
emptyPackageDescription :: PackageDescriptionSource
readPackageDescription :: Verbosity -> FilePath -> IO GenericPackageDescriptionSource
Parse the given package file.
writePackageDescription :: FilePath -> PackageDescription -> IO ()Source
parsePackageDescription :: String -> ParseResult GenericPackageDescriptionSource

Parses the given file into a GenericPackageDescription.

In Cabal 1.2 the syntax for package descriptions was changed to a format with sections and possibly indented property descriptions.

showPackageDescription :: PackageDescription -> StringSource
data BuildType Source
The type of build system used by this package.
Constructors
Simplecalls Distribution.Simple.defaultMain
Configurecalls Distribution.Simple.defaultMainWithHooks defaultUserHooks, which invokes configure to generate additional build information used by later phases.
Makecalls Distribution.Make.defaultMain
Customuses user-supplied Setup.hs or Setup.lhs (default)
UnknownBuildType Stringa package that uses an unknown build type cannot actually be built. Doing it this way rather than just giving a parse error means we get better error messages and allows you to inspect the rest of the package description.
show/hide Instances
knownBuildTypes :: [BuildType]Source
Libraries
data Library Source
Constructors
Library
exposedModules :: [String]
libBuildInfo :: BuildInfo
show/hide Instances
emptyLibrary :: LibrarySource
withLib :: PackageDescription -> a -> (Library -> IO a) -> IO aSource
If the package description has a library section, call the given function with the library build info as argument.
hasLibs :: PackageDescription -> BoolSource
does this package have any libraries?
libModules :: PackageDescription -> [String]Source
Get all the module names from the libraries in this package
Executables
data Executable Source
Constructors
Executable
exeName :: String
modulePath :: FilePath
buildInfo :: BuildInfo
show/hide Instances
emptyExecutable :: ExecutableSource
withExe :: PackageDescription -> (Executable -> IO a) -> IO ()Source
Perform the action on each buildable Executable in the package description.
hasExes :: PackageDescription -> BoolSource
does this package have any executables?
exeModules :: PackageDescription -> [String]Source
Get all the module names from the exes in this package
Parsing
data FieldDescr a Source
Field descriptor. The parameter a parameterizes over where the field's value is stored in.
Constructors
FieldDescr
fieldName :: String
fieldGet :: a -> Doc
fieldSet :: LineNo -> String -> a -> ParseResult afieldSet n str x Parses the field value from the given input string str and stores the result in x if the parse was successful. Otherwise, reports an error on line number n.
type LineNo = IntSource
Build information
data BuildInfo Source
Constructors
BuildInfo
buildable :: Boolcomponent is buildable here
buildTools :: [Dependency]tools needed to build this bit
cppOptions :: [String]options for pre-processing Haskell code
ccOptions :: [String]options for C compiler
ldOptions :: [String]options for linker
pkgconfigDepends :: [Dependency]pkg-config packages that are used
frameworks :: [String]support frameworks for Mac OS X
cSources :: [FilePath]
hsSourceDirs :: [FilePath]where to look for the haskell module hierarchy
otherModules :: [String]non-exposed or non-main modules
extensions :: [Extension]
extraLibs :: [String]what libraries to link with when compiling a program that uses your package
extraLibDirs :: [String]
includeDirs :: [FilePath]directories to find .h files
includes :: [FilePath]The .h files to be found in includeDirs
installIncludes :: [FilePath].h files to install with the package
options :: [(CompilerFlavor, [String])]
ghcProfOptions :: [String]
ghcSharedOptions :: [String]
customFieldsBI :: [(String, String)]Custom fields starting with x-, stored in a simple assoc-list.
show/hide Instances
emptyBuildInfo :: BuildInfoSource
allBuildInfo :: PackageDescription -> [BuildInfo]Source
The BuildInfo for the library (if there is one and it's buildable) and all the buildable executables. Useful for gathering dependencies.
hcOptions :: CompilerFlavor -> BuildInfo -> [String]Source
Select options for a particular Haskell compiler.
Supplementary build information
type HookedBuildInfo = (Maybe BuildInfo, [(String, BuildInfo)])Source
emptyHookedBuildInfo :: HookedBuildInfoSource
updatePackageDescription :: HookedBuildInfo -> PackageDescription -> PackageDescriptionSource
package configuration
data Flag Source
A flag can represent a feature to be included, or a way of linking a target against its dependencies, or in fact whatever you can think of.
Constructors
MkFlag
flagName :: FlagName
flagDescription :: String
flagDefault :: Bool
show/hide Instances
newtype FlagName Source
A FlagName is the name of a user-defined configuration flag
Constructors
FlagName String
show/hide Instances
type FlagAssignment = [(FlagName, Bool)]Source
A FlagAssignment is a total or partial mapping of FlagNames to Bool flag values. It represents the flags chosen by the user or discovered during configuration. For example --flags=foo --flags=-bar becomes [(foo, True), (bar, False)]
data CondTree v c a Source
Constructors
CondNode
condTreeData :: a
condTreeConstraints :: c
condTreeComponents :: [(Condition v, CondTree v c a, Maybe (CondTree v c a))]
show/hide Instances
(Show v, Show c, Show a) => Show (CondTree v c a)
data ConfVar Source
A ConfVar represents the variable type used.
Constructors
OS OS
Arch Arch
Flag FlagName
Impl CompilerFlavor VersionRange
show/hide Instances
data Condition c Source
A boolean expression parameterized over the variable type used.
Constructors
Var c
Lit Bool
CNot (Condition c)
COr (Condition c) (Condition c)
CAnd (Condition c) (Condition c)
show/hide Instances
freeVars :: CondTree ConfVar c a -> [FlagName]Source
Supplementary build information
readHookedBuildInfo :: Verbosity -> FilePath -> IO HookedBuildInfoSource
parseHookedBuildInfo :: String -> ParseResult HookedBuildInfoSource
writeHookedBuildInfo :: FilePath -> HookedBuildInfo -> IO ()Source
showHookedBuildInfo :: HookedBuildInfo -> StringSource
Deprecated compat stuff
data ParseResult a Source
Constructors
ParseFailed PError
ParseOk [PWarning] a
show/hide Instances
setupMessage :: Verbosity -> String -> PackageDescription -> IO ()Source
cabalVersion :: VersionSource
Produced by Haddock version 2.3.0