Cabal-1.10.1.0: A framework for packaging Haskell softwareContentsIndex
Distribution.PackageDescription
Portabilityportable
Maintainercabal-devel@haskell.org
Contents
Package descriptions
Libraries
Executables
Tests
Build information
Supplementary build information
package configuration
Source repositories
Description
This defines the data structure for the .cabal file format. There are several parts to this structure. It has top level info and then Library, Executable, and TestSuite sections each of which have associated BuildInfo data that's used to build the library, exe, or test. To further complicate things there is both a PackageDescription and a GenericPackageDescription. This distinction relates to cabal configurations. When we initially read a .cabal file we get a GenericPackageDescription which has all the conditional sections. Before actually building a package we have to decide on each conditional. Once we've done that we get a PackageDescription. It was done this way initially to avoid breaking too much stuff when the feature was introduced. It could probably do with being rationalised at some point to make it simpler.
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
bugReports :: String
sourceRepos :: [SourceRepo]
synopsis :: String
description :: String
category :: String
customFieldsPD :: [(String, String)]
buildDepends :: [Dependency]
specVersionRaw :: Either Version VersionRange
buildType :: Maybe BuildType
library :: Maybe Library
executables :: [Executable]
testSuites :: [TestSuite]
dataFiles :: [FilePath]
dataDir :: FilePath
extraSrcFiles :: [FilePath]
extraTmpFiles :: [FilePath]
}
emptyPackageDescription :: PackageDescription
specVersion :: PackageDescription -> Version
descCabalVersion :: PackageDescription -> VersionRange
data BuildType
= Simple
| Configure
| Make
| Custom
| UnknownBuildType String
knownBuildTypes :: [BuildType]
data Library = Library {
exposedModules :: [ModuleName]
libExposed :: Bool
libBuildInfo :: BuildInfo
}
emptyLibrary :: Library
withLib :: PackageDescription -> (Library -> IO ()) -> IO ()
hasLibs :: PackageDescription -> Bool
libModules :: Library -> [ModuleName]
data Executable = Executable {
exeName :: String
modulePath :: FilePath
buildInfo :: BuildInfo
}
emptyExecutable :: Executable
withExe :: PackageDescription -> (Executable -> IO ()) -> IO ()
hasExes :: PackageDescription -> Bool
exeModules :: Executable -> [ModuleName]
data TestSuite = TestSuite {
testName :: String
testInterface :: TestSuiteInterface
testBuildInfo :: BuildInfo
testEnabled :: Bool
}
data TestSuiteInterface
= TestSuiteExeV10 Version FilePath
| TestSuiteLibV09 Version ModuleName
| TestSuiteUnsupported TestType
data TestType
= TestTypeExe Version
| TestTypeLib Version
| TestTypeUnknown String Version
testType :: TestSuite -> TestType
knownTestTypes :: [TestType]
emptyTestSuite :: TestSuite
hasTests :: PackageDescription -> Bool
withTest :: PackageDescription -> (TestSuite -> IO ()) -> IO ()
testModules :: TestSuite -> [ModuleName]
enabledTests :: PackageDescription -> [TestSuite]
data BuildInfo = BuildInfo {
buildable :: Bool
buildTools :: [Dependency]
cppOptions :: [String]
ccOptions :: [String]
ldOptions :: [String]
pkgconfigDepends :: [Dependency]
frameworks :: [String]
cSources :: [FilePath]
hsSourceDirs :: [FilePath]
otherModules :: [ModuleName]
defaultLanguage :: Maybe Language
otherLanguages :: [Language]
defaultExtensions :: [Extension]
otherExtensions :: [Extension]
oldExtensions :: [Extension]
extraLibs :: [String]
extraLibDirs :: [String]
includeDirs :: [FilePath]
includes :: [FilePath]
installIncludes :: [FilePath]
options :: [(CompilerFlavor, [String])]
ghcProfOptions :: [String]
ghcSharedOptions :: [String]
customFieldsBI :: [(String, String)]
targetBuildDepends :: [Dependency]
}
emptyBuildInfo :: BuildInfo
allBuildInfo :: PackageDescription -> [BuildInfo]
allLanguages :: BuildInfo -> [Language]
allExtensions :: BuildInfo -> [Extension]
usedExtensions :: BuildInfo -> [Extension]
hcOptions :: CompilerFlavor -> BuildInfo -> [String]
type HookedBuildInfo = (Maybe BuildInfo, [(String, BuildInfo)])
emptyHookedBuildInfo :: HookedBuildInfo
updatePackageDescription :: HookedBuildInfo -> PackageDescription -> PackageDescription
data GenericPackageDescription = GenericPackageDescription {
packageDescription :: PackageDescription
genPackageFlags :: [Flag]
condLibrary :: Maybe (CondTree ConfVar [Dependency] Library)
condExecutables :: [(String, CondTree ConfVar [Dependency] Executable)]
condTestSuites :: [(String, CondTree ConfVar [Dependency] TestSuite)]
}
data Flag = MkFlag {
flagName :: FlagName
flagDescription :: String
flagDefault :: Bool
flagManual :: 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)
data SourceRepo = SourceRepo {
repoKind :: RepoKind
repoType :: Maybe RepoType
repoLocation :: Maybe String
repoModule :: Maybe String
repoBranch :: Maybe String
repoTag :: Maybe String
repoSubdir :: Maybe FilePath
}
data RepoKind
= RepoHead
| RepoThis
| RepoKindUnknown String
data RepoType
= Darcs
| Git
| SVN
| CVS
| Mercurial
| GnuArch
| Bazaar
| Monotone
| OtherRepoType String
knownRepoTypes :: [RepoType]
Package descriptions
data PackageDescription
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
bugReports :: String
sourceRepos :: [SourceRepo]
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]
specVersionRaw :: Either Version VersionRangeThe version of the Cabal spec that this package description uses. For historical reasons this is specified with a version range but only ranges of the form >= v make sense. We are in the process of transitioning to specifying just a single version, not a range.
buildType :: Maybe BuildType
library :: Maybe Library
executables :: [Executable]
testSuites :: [TestSuite]
dataFiles :: [FilePath]
dataDir :: FilePath
extraSrcFiles :: [FilePath]
extraTmpFiles :: [FilePath]
show/hide Instances
emptyPackageDescription :: PackageDescription
specVersion :: PackageDescription -> Version

The version of the Cabal spec that this package should be interpreted against.

Historically we used a version range but we are switching to using a single version. Currently we accept either. This function converts into a single version by ignoring upper bounds in the version range.

descCabalVersion :: PackageDescription -> VersionRange

The range of versions of the Cabal tools that this package is intended to work with.

This function is deprecated and should not be used for new purposes, only to support old packages that rely on the old interpretation.

data BuildType
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]
Libraries
data Library
Constructors
Library
exposedModules :: [ModuleName]
libExposed :: BoolIs the lib to be exposed by default?
libBuildInfo :: BuildInfo
show/hide Instances
Eq Library
Read Library
Show Library
Monoid Library
emptyLibrary :: Library
withLib :: PackageDescription -> (Library -> IO ()) -> IO ()
If the package description has a library section, call the given function with the library build info as argument.
hasLibs :: PackageDescription -> Bool
does this package have any libraries?
libModules :: Library -> [ModuleName]
Get all the module names from the library (exposed and internal modules)
Executables
data Executable
Constructors
Executable
exeName :: String
modulePath :: FilePath
buildInfo :: BuildInfo
show/hide Instances
emptyExecutable :: Executable
withExe :: PackageDescription -> (Executable -> IO ()) -> IO ()
Perform the action on each buildable Executable in the package description.
hasExes :: PackageDescription -> Bool
does this package have any executables?
exeModules :: Executable -> [ModuleName]
Get all the module names from an exe
Tests
data TestSuite
A "test-suite" stanza in a cabal file.
Constructors
TestSuite
testName :: String
testInterface :: TestSuiteInterface
testBuildInfo :: BuildInfo
testEnabled :: Bool
show/hide Instances
data TestSuiteInterface

The test suite interfaces that are currently defined. Each test suite must specify which interface it supports.

More interfaces may be defined in future, either new revisions or totally new interfaces.

Constructors
TestSuiteExeV10 Version FilePathTest interface "exitcode-stdio-1.0". The test-suite takes the form of an executable. It returns a zero exit code for success, non-zero for failure. The stdout and stderr channels may be logged. It takes no command line parameters and nothing on stdin.
TestSuiteLibV09 Version ModuleNameTest interface "detailed-0.9". The test-suite takes the form of a library containing a designated module that exports "tests :: [Test]".
TestSuiteUnsupported TestTypeA test suite that does not conform to one of the above interfaces for the given reason (e.g. unknown test type).
show/hide Instances
data TestType
The "test-type" field in the test suite stanza.
Constructors
TestTypeExe Version"type: exitcode-stdio-x.y"
TestTypeLib Version"type: detailed-x.y"
TestTypeUnknown String VersionSome unknown test type e.g. "type: foo"
show/hide Instances
testType :: TestSuite -> TestType
knownTestTypes :: [TestType]
emptyTestSuite :: TestSuite
hasTests :: PackageDescription -> Bool
Does this package have any test suites?
withTest :: PackageDescription -> (TestSuite -> IO ()) -> IO ()
Perform an action on each buildable TestSuite in a package.
testModules :: TestSuite -> [ModuleName]
Get all the module names from a test suite.
enabledTests :: PackageDescription -> [TestSuite]
Get all the enabled test suites from a package.
Build information
data BuildInfo
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 :: [ModuleName]non-exposed or non-main modules
defaultLanguage :: Maybe Languagelanguage used when not explicitly specified
otherLanguages :: [Language]other languages used within the package
defaultExtensions :: [Extension]language extensions used by all modules
otherExtensions :: [Extension]other language extensions used within the package
oldExtensions :: [Extension]the old extensions field, treated same as defaultExtensions
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.
targetBuildDepends :: [Dependency]Dependencies specific to a library or executable target
show/hide Instances
emptyBuildInfo :: BuildInfo
allBuildInfo :: PackageDescription -> [BuildInfo]
The BuildInfo for the library (if there is one and it's buildable) and all the buildable executables. Useful for gathering dependencies.
allLanguages :: BuildInfo -> [Language]
The Languages used by this component
allExtensions :: BuildInfo -> [Extension]
The Extensions that are used somewhere by this component
usedExtensions :: BuildInfo -> [Extension]
The Extensions that are used by all modules in this component
hcOptions :: CompilerFlavor -> BuildInfo -> [String]
Select options for a particular Haskell compiler.
Supplementary build information
type HookedBuildInfo = (Maybe BuildInfo, [(String, BuildInfo)])
emptyHookedBuildInfo :: HookedBuildInfo
updatePackageDescription :: HookedBuildInfo -> PackageDescription -> PackageDescription
package configuration
data GenericPackageDescription
Constructors
GenericPackageDescription
packageDescription :: PackageDescription
genPackageFlags :: [Flag]
condLibrary :: Maybe (CondTree ConfVar [Dependency] Library)
condExecutables :: [(String, CondTree ConfVar [Dependency] Executable)]
condTestSuites :: [(String, CondTree ConfVar [Dependency] TestSuite)]
show/hide Instances
data Flag
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
flagManual :: Bool
show/hide Instances
Eq Flag
Show Flag
newtype FlagName
A FlagName is the name of a user-defined configuration flag
Constructors
FlagName String
show/hide Instances
type FlagAssignment = [(FlagName, Bool)]
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
Constructors
CondNode
condTreeData :: a
condTreeConstraints :: c
condTreeComponents :: [(Condition v, CondTree v c a, Maybe (CondTree v c a))]
show/hide Instances
(Eq v, Eq c, Eq a) => Eq (CondTree v c a)
(Show v, Show c, Show a) => Show (CondTree v c a)
data ConfVar
A ConfVar represents the variable type used.
Constructors
OS OS
Arch Arch
Flag FlagName
Impl CompilerFlavor VersionRange
show/hide Instances
data Condition c
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
Eq c => Eq (Condition c)
Show c => Show (Condition c)
Source repositories
data SourceRepo

Information about the source revision control system for a package.

When specifying a repo it is useful to know the meaning or intention of the information as doing so enables automation. There are two obvious common purposes: one is to find the repo for the latest development version, the other is to find the repo for this specific release. The ReopKind specifies which one we mean (or another custom one).

A package can specify one or the other kind or both. Most will specify just a head repo but some may want to specify a repo to reconstruct the sources for this package release.

The required information is the RepoType which tells us if it's using Darcs, Git for example. The repoLocation and other details are interpreted according to the repo type.

Constructors
SourceRepo
repoKind :: RepoKindThe kind of repo. This field is required.
repoType :: Maybe RepoTypeThe type of the source repository system for this repo, eg Darcs or Git. This field is required.
repoLocation :: Maybe StringThe location of the repository. For most RepoTypes this is a URL. This field is required.
repoModule :: Maybe StringCVS can put multiple "modules" on one server and requires a module name in addition to the location to identify a particular repo. Logically this is part of the location but unfortunately has to be specified separately. This field is required for the CVS RepoType and should not be given otherwise.
repoBranch :: Maybe StringThe name or identifier of the branch, if any. Many source control systems have the notion of multiple branches in a repo that exist in the same location. For example Git and CVS use this while systems like Darcs use different locations for different branches. This field is optional but should be used if necessary to identify the sources, especially for the RepoThis repo kind.
repoTag :: Maybe StringThe tag identify a particular state of the repository. This should be given for the RepoThis repo kind and not for RepoHead kind.
repoSubdir :: Maybe FilePathSome repositories contain multiple projects in different subdirectories This field specifies the subdirectory where this packages sources can be found, eg the subdirectory containing the .cabal file. It is interpreted relative to the root of the repository. This field is optional. If not given the default is "." ie no subdirectory.
show/hide Instances
data RepoKind
What this repo info is for, what it represents.
Constructors
RepoHeadThe repository for the "head" or development version of the project. This repo is where we should track the latest development activity or the usual repo people should get to contribute patches.
RepoThisThe repository containing the sources for this exact package version or release. For this kind of repo a tag should be given to give enough information to re-create the exact sources.
RepoKindUnknown String
show/hide Instances
data RepoType
An enumeration of common source control systems. The fields used in the SourceRepo depend on the type of repo. The tools and methods used to obtain and track the repo depend on the repo type.
Constructors
Darcs
Git
SVN
CVS
Mercurial
GnuArch
Bazaar
Monotone
OtherRepoType String
show/hide Instances
knownRepoTypes :: [RepoType]
Produced by Haddock version 2.6.1