Portability | portable |
---|---|
Maintainer | cabal-devel@haskell.org |
Safe Haskell | Safe-Inferred |
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
, TestSuite
, and Benchmark
sections each of which have
associated BuildInfo
data that's used to build the library, exe, test, or
benchmark. 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.
- data PackageDescription = PackageDescription {
- package :: PackageIdentifier
- license :: License
- licenseFiles :: [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]
- benchmarks :: [Benchmark]
- dataFiles :: [FilePath]
- dataDir :: FilePath
- extraSrcFiles :: [FilePath]
- extraTmpFiles :: [FilePath]
- extraDocFiles :: [FilePath]
- emptyPackageDescription :: PackageDescription
- specVersion :: PackageDescription -> Version
- descCabalVersion :: PackageDescription -> VersionRange
- data BuildType
- = Simple
- | Configure
- | Make
- | Custom
- | UnknownBuildType String
- knownBuildTypes :: [BuildType]
- data ModuleRenaming = ModuleRenaming Bool [(ModuleName, ModuleName)]
- defaultRenaming :: ModuleRenaming
- lookupRenaming :: Package pkg => pkg -> Map PackageName ModuleRenaming -> ModuleRenaming
- data Library = Library {
- exposedModules :: [ModuleName]
- reexportedModules :: [ModuleReexport]
- requiredSignatures :: [ModuleName]
- exposedSignatures :: [ModuleName]
- libExposed :: Bool
- libBuildInfo :: BuildInfo
- data ModuleReexport = ModuleReexport {}
- 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 Benchmark = Benchmark {
- benchmarkName :: String
- benchmarkInterface :: BenchmarkInterface
- benchmarkBuildInfo :: BuildInfo
- benchmarkEnabled :: Bool
- data BenchmarkInterface
- = BenchmarkExeV10 Version FilePath
- | BenchmarkUnsupported BenchmarkType
- data BenchmarkType
- = BenchmarkTypeExe Version
- | BenchmarkTypeUnknown String Version
- benchmarkType :: Benchmark -> BenchmarkType
- knownBenchmarkTypes :: [BenchmarkType]
- emptyBenchmark :: Benchmark
- hasBenchmarks :: PackageDescription -> Bool
- withBenchmark :: PackageDescription -> (Benchmark -> IO ()) -> IO ()
- benchmarkModules :: Benchmark -> [ModuleName]
- enabledBenchmarks :: PackageDescription -> [Benchmark]
- data BuildInfo = BuildInfo {
- buildable :: Bool
- buildTools :: [Dependency]
- cppOptions :: [String]
- ccOptions :: [String]
- ldOptions :: [String]
- pkgconfigDepends :: [Dependency]
- frameworks :: [String]
- cSources :: [FilePath]
- jsSources :: [FilePath]
- hsSourceDirs :: [FilePath]
- otherModules :: [ModuleName]
- defaultLanguage :: Maybe Language
- otherLanguages :: [Language]
- defaultExtensions :: [Extension]
- otherExtensions :: [Extension]
- oldExtensions :: [Extension]
- extraLibs :: [String]
- extraGHCiLibs :: [String]
- extraLibDirs :: [String]
- includeDirs :: [FilePath]
- includes :: [FilePath]
- installIncludes :: [FilePath]
- options :: [(CompilerFlavor, [String])]
- profOptions :: [(CompilerFlavor, [String])]
- sharedOptions :: [(CompilerFlavor, [String])]
- customFieldsBI :: [(String, String)]
- targetBuildDepends :: [Dependency]
- targetBuildRenaming :: Map PackageName ModuleRenaming
- emptyBuildInfo :: BuildInfo
- allBuildInfo :: PackageDescription -> [BuildInfo]
- allLanguages :: BuildInfo -> [Language]
- allExtensions :: BuildInfo -> [Extension]
- usedExtensions :: BuildInfo -> [Extension]
- hcOptions :: CompilerFlavor -> BuildInfo -> [String]
- hcProfOptions :: CompilerFlavor -> BuildInfo -> [String]
- hcSharedOptions :: 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)]
- condBenchmarks :: [(String, CondTree ConfVar [Dependency] Benchmark)]
- 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
- 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
- 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.
PackageDescription | |
|
Eq PackageDescription | |
Data PackageDescription | |
Read PackageDescription | |
Show PackageDescription | |
Typeable PackageDescription | |
Generic PackageDescription | |
Package 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
Deprecated: Use specVersion instead
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.
Simple | calls |
Configure | calls |
Make | calls |
Custom | uses user-supplied |
UnknownBuildType String | a 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. |
knownBuildTypes :: [BuildType]
Renaming
data ModuleRenaming
ModuleRenaming Bool [(ModuleName, ModuleName)] |
Eq ModuleRenaming | |
Data ModuleRenaming | |
Ord ModuleRenaming | |
Read ModuleRenaming | |
Show ModuleRenaming | |
Typeable ModuleRenaming | |
Generic ModuleRenaming | |
Monoid ModuleRenaming | |
Text ModuleRenaming |
lookupRenaming :: Package pkg => pkg -> Map PackageName ModuleRenaming -> ModuleRenaming
Libraries
data Library
Library | |
|
data ModuleReexport
Eq ModuleReexport | |
Data ModuleReexport | |
Read ModuleReexport | |
Show ModuleReexport | |
Typeable ModuleReexport | |
Generic ModuleReexport | |
Text ModuleReexport |
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) which need to be compiled. (This does not include reexports, which do not need to be compiled.)
Executables
data Executable
Executable | |
|
Eq Executable | |
Data Executable | |
Read Executable | |
Show Executable | |
Typeable Executable | |
Generic Executable | |
Monoid 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.
TestSuite | |
|
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.
TestSuiteExeV10 Version FilePath | Test 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 ModuleName | Test interface "detailed-0.9". The test-suite takes the form of a library containing a designated module that exports "tests :: [Test]". |
TestSuiteUnsupported TestType | A test suite that does not conform to one of the above interfaces for the given reason (e.g. unknown test type). |
Eq TestSuiteInterface | |
Data TestSuiteInterface | |
Read TestSuiteInterface | |
Show TestSuiteInterface | |
Typeable TestSuiteInterface | |
Generic TestSuiteInterface | |
Monoid TestSuiteInterface |
data TestType
The "test-type" field in the test suite stanza.
TestTypeExe Version | "type: exitcode-stdio-x.y" |
TestTypeLib Version | "type: detailed-x.y" |
TestTypeUnknown String Version | Some unknown test type e.g. "type: foo" |
knownTestTypes :: [TestType]
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.
Benchmarks
data Benchmark
A "benchmark" stanza in a cabal file.
Benchmark | |
|
data BenchmarkInterface
The benchmark interfaces that are currently defined. Each benchmark must specify which interface it supports.
More interfaces may be defined in future, either new revisions or totally new interfaces.
BenchmarkExeV10 Version FilePath | Benchmark interface "exitcode-stdio-1.0". The benchmark 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. |
BenchmarkUnsupported BenchmarkType | A benchmark that does not conform to one of the above interfaces for the given reason (e.g. unknown benchmark type). |
Eq BenchmarkInterface | |
Data BenchmarkInterface | |
Read BenchmarkInterface | |
Show BenchmarkInterface | |
Typeable BenchmarkInterface | |
Generic BenchmarkInterface | |
Monoid BenchmarkInterface |
data BenchmarkType
The "benchmark-type" field in the benchmark stanza.
BenchmarkTypeExe Version | "type: exitcode-stdio-x.y" |
BenchmarkTypeUnknown String Version | Some unknown benchmark type e.g. "type: foo" |
Eq BenchmarkType | |
Data BenchmarkType | |
Read BenchmarkType | |
Show BenchmarkType | |
Typeable BenchmarkType | |
Generic BenchmarkType | |
Text BenchmarkType |
hasBenchmarks :: PackageDescription -> Bool
Does this package have any benchmarks?
withBenchmark :: PackageDescription -> (Benchmark -> IO ()) -> IO ()
Perform an action on each buildable Benchmark
in a package.
benchmarkModules :: Benchmark -> [ModuleName]
Get all the module names from a benchmark.
enabledBenchmarks :: PackageDescription -> [Benchmark]
Get all the enabled benchmarks from a package.
Build information
data BuildInfo
BuildInfo | |
|
allBuildInfo :: PackageDescription -> [BuildInfo]
The BuildInfo
for the library (if there is one and it's buildable), and
all buildable executables, test suites and benchmarks. Useful for gathering
dependencies.
allLanguages :: BuildInfo -> [Language]
The Language
s used by this component
allExtensions :: BuildInfo -> [Extension]
The Extension
s 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.
hcProfOptions :: CompilerFlavor -> BuildInfo -> [String]
hcSharedOptions :: CompilerFlavor -> BuildInfo -> [String]
Supplementary build information
type HookedBuildInfo = (Maybe BuildInfo, [(String, BuildInfo)])
package configuration
data GenericPackageDescription
GenericPackageDescription | |
|
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.
MkFlag | |
|
type FlagAssignment = [(FlagName, Bool)]
A FlagAssignment
is a total or partial mapping of FlagName
s 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
CondNode | |
|
data ConfVar
A ConfVar
represents the variable type used.
data Condition c
A boolean expression parameterized over the variable type used.
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.
SourceRepo | |
|
Eq SourceRepo | |
Data SourceRepo | |
Read SourceRepo | |
Show SourceRepo | |
Typeable SourceRepo | |
Generic SourceRepo |
data RepoKind
What this repo info is for, what it represents.
RepoHead | The 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. |
RepoThis | The 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 |
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.
knownRepoTypes :: [RepoType]