Copyright | Isaac Jones 2003-2005 |
---|---|
License | BSD3 |
Maintainer | cabal-devel@haskell.org |
Portability | portable |
Safe Haskell | None |
Language | Haskell98 |
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
- setupBuildInfo :: Maybe SetupBuildInfo
- 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
- knownBuildTypes :: [BuildType]
- data ModuleRenaming = ModuleRenaming Bool [(ModuleName, ModuleName)]
- defaultRenaming :: ModuleRenaming
- lookupRenaming :: Package pkg => pkg -> Map PackageName ModuleRenaming -> ModuleRenaming
- data Library = Library {}
- data ModuleReexport = ModuleReexport {}
- emptyLibrary :: Library
- withLib :: PackageDescription -> (Library -> IO ()) -> IO ()
- hasLibs :: PackageDescription -> Bool
- libModules :: Library -> [ModuleName]
- data Executable = Executable {}
- emptyExecutable :: Executable
- withExe :: PackageDescription -> (Executable -> IO ()) -> IO ()
- hasExes :: PackageDescription -> Bool
- exeModules :: Executable -> [ModuleName]
- data TestSuite = TestSuite {}
- data TestSuiteInterface
- data TestType
- testType :: TestSuite -> TestType
- knownTestTypes :: [TestType]
- emptyTestSuite :: TestSuite
- hasTests :: PackageDescription -> Bool
- withTest :: PackageDescription -> (TestSuite -> IO ()) -> IO ()
- testModules :: TestSuite -> [ModuleName]
- enabledTests :: PackageDescription -> [TestSuite]
- data Benchmark = Benchmark {}
- data BenchmarkInterface
- data BenchmarkType
- 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 {}
- 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
- data Condition c
- cNot :: Condition a -> Condition a
- data SourceRepo = SourceRepo {}
- data RepoKind
- data RepoType
- knownRepoTypes :: [RepoType]
- data SetupBuildInfo = SetupBuildInfo {
- setupDepends :: [Dependency]
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.
PackageDescription | |
|
specVersion :: PackageDescription -> Version Source
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 Source
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.
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. |
Eq BuildType | |
Data BuildType | |
Read BuildType | |
Show BuildType | |
Generic BuildType | |
Binary BuildType | |
Text BuildType | |
type Rep BuildType = D1 (MetaData "BuildType" "Distribution.PackageDescription" "Cabal-1.23.1.0" False) ((:+:) ((:+:) (C1 (MetaCons "Simple" PrefixI False) U1) (C1 (MetaCons "Configure" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Make" PrefixI False) U1) ((:+:) (C1 (MetaCons "Custom" PrefixI False) U1) (C1 (MetaCons "UnknownBuildType" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)))))) |
Renaming
data ModuleRenaming Source
Renaming applied to the modules provided by a package.
The boolean indicates whether or not to also include all of the
original names of modules. Thus, ModuleRenaming False []
is
"don't expose any modules, and ModuleRenaming True [(Data.Bool, Bool)]
is, "expose all modules, but also expose Data.Bool
as Bool
".
Eq ModuleRenaming | |
Data ModuleRenaming | |
Ord ModuleRenaming | |
Read ModuleRenaming | |
Show ModuleRenaming | |
Generic ModuleRenaming | |
Semigroup ModuleRenaming | |
Monoid ModuleRenaming | |
Binary ModuleRenaming | |
Text ModuleRenaming | |
type Rep ModuleRenaming = D1 (MetaData "ModuleRenaming" "Distribution.PackageDescription" "Cabal-1.23.1.0" False) (C1 (MetaCons "ModuleRenaming" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [(ModuleName, ModuleName)])))) |
lookupRenaming :: Package pkg => pkg -> Map PackageName ModuleRenaming -> ModuleRenaming Source
Libraries
Library | |
|
Eq Library | |
Data Library | |
Read Library | |
Show Library | |
Generic Library | |
Semigroup Library | |
Monoid Library | |
Binary Library | |
type Rep Library = D1 (MetaData "Library" "Distribution.PackageDescription" "Cabal-1.23.1.0" False) (C1 (MetaCons "Library" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "exposedModules") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [ModuleName])) ((:*:) (S1 (MetaSel (Just Symbol "reexportedModules") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [ModuleReexport])) (S1 (MetaSel (Just Symbol "requiredSignatures") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [ModuleName])))) ((:*:) (S1 (MetaSel (Just Symbol "exposedSignatures") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [ModuleName])) ((:*:) (S1 (MetaSel (Just Symbol "libExposed") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)) (S1 (MetaSel (Just Symbol "libBuildInfo") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 BuildInfo)))))) |
data ModuleReexport Source
Eq ModuleReexport | |
Data ModuleReexport | |
Read ModuleReexport | |
Show ModuleReexport | |
Generic ModuleReexport | |
Binary ModuleReexport | |
Text ModuleReexport | |
type Rep ModuleReexport = D1 (MetaData "ModuleReexport" "Distribution.PackageDescription" "Cabal-1.23.1.0" False) (C1 (MetaCons "ModuleReexport" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "moduleReexportOriginalPackage") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe PackageName))) ((:*:) (S1 (MetaSel (Just Symbol "moduleReexportOriginalName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ModuleName)) (S1 (MetaSel (Just Symbol "moduleReexportName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ModuleName))))) |
withLib :: PackageDescription -> (Library -> IO ()) -> IO () Source
If the package description has a library section, call the given function with the library build info as argument.
hasLibs :: PackageDescription -> Bool Source
does this package have any libraries?
libModules :: Library -> [ModuleName] Source
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 Source
Eq Executable | |
Data Executable | |
Read Executable | |
Show Executable | |
Generic Executable | |
Semigroup Executable | |
Monoid Executable | |
Binary Executable | |
type Rep Executable = D1 (MetaData "Executable" "Distribution.PackageDescription" "Cabal-1.23.1.0" False) (C1 (MetaCons "Executable" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "exeName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)) ((:*:) (S1 (MetaSel (Just Symbol "modulePath") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 FilePath)) (S1 (MetaSel (Just Symbol "buildInfo") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 BuildInfo))))) |
withExe :: PackageDescription -> (Executable -> IO ()) -> IO () Source
Perform the action on each buildable Executable
in the package
description.
hasExes :: PackageDescription -> Bool Source
does this package have any executables?
exeModules :: Executable -> [ModuleName] Source
Get all the module names from an exe
Tests
A "test-suite" stanza in a cabal file.
Eq TestSuite | |
Data TestSuite | |
Read TestSuite | |
Show TestSuite | |
Generic TestSuite | |
Semigroup TestSuite | |
Monoid TestSuite | |
Binary TestSuite | |
type Rep TestSuite = D1 (MetaData "TestSuite" "Distribution.PackageDescription" "Cabal-1.23.1.0" False) (C1 (MetaCons "TestSuite" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "testName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)) (S1 (MetaSel (Just Symbol "testInterface") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 TestSuiteInterface))) ((:*:) (S1 (MetaSel (Just Symbol "testBuildInfo") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 BuildInfo)) (S1 (MetaSel (Just Symbol "testEnabled") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool))))) |
data TestSuiteInterface Source
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). |
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" |
Eq TestType | |
Data TestType | |
Read TestType | |
Show TestType | |
Generic TestType | |
Binary TestType | |
Text TestType | |
type Rep TestType = D1 (MetaData "TestType" "Distribution.PackageDescription" "Cabal-1.23.1.0" False) ((:+:) (C1 (MetaCons "TestTypeExe" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Version))) ((:+:) (C1 (MetaCons "TestTypeLib" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Version))) (C1 (MetaCons "TestTypeUnknown" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Version)))))) |
knownTestTypes :: [TestType] Source
hasTests :: PackageDescription -> Bool Source
Does this package have any test suites?
withTest :: PackageDescription -> (TestSuite -> IO ()) -> IO () Source
Perform an action on each buildable TestSuite
in a package.
testModules :: TestSuite -> [ModuleName] Source
Get all the module names from a test suite.
enabledTests :: PackageDescription -> [TestSuite] Source
Get all the enabled test suites from a package.
Benchmarks
A "benchmark" stanza in a cabal file.
Eq Benchmark | |
Data Benchmark | |
Read Benchmark | |
Show Benchmark | |
Generic Benchmark | |
Semigroup Benchmark | |
Monoid Benchmark | |
Binary Benchmark | |
type Rep Benchmark = D1 (MetaData "Benchmark" "Distribution.PackageDescription" "Cabal-1.23.1.0" False) (C1 (MetaCons "Benchmark" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "benchmarkName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)) (S1 (MetaSel (Just Symbol "benchmarkInterface") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 BenchmarkInterface))) ((:*:) (S1 (MetaSel (Just Symbol "benchmarkBuildInfo") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 BuildInfo)) (S1 (MetaSel (Just Symbol "benchmarkEnabled") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool))))) |
data BenchmarkInterface Source
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 | |
Generic BenchmarkInterface | |
Semigroup BenchmarkInterface | |
Monoid BenchmarkInterface | |
Binary BenchmarkInterface | |
type Rep BenchmarkInterface = D1 (MetaData "BenchmarkInterface" "Distribution.PackageDescription" "Cabal-1.23.1.0" False) ((:+:) (C1 (MetaCons "BenchmarkExeV10" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Version)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 FilePath)))) (C1 (MetaCons "BenchmarkUnsupported" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 BenchmarkType)))) |
data BenchmarkType Source
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 | |
Generic BenchmarkType | |
Binary BenchmarkType | |
Text BenchmarkType | |
type Rep BenchmarkType = D1 (MetaData "BenchmarkType" "Distribution.PackageDescription" "Cabal-1.23.1.0" False) ((:+:) (C1 (MetaCons "BenchmarkTypeExe" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Version))) (C1 (MetaCons "BenchmarkTypeUnknown" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Version))))) |
hasBenchmarks :: PackageDescription -> Bool Source
Does this package have any benchmarks?
withBenchmark :: PackageDescription -> (Benchmark -> IO ()) -> IO () Source
Perform an action on each buildable Benchmark
in a package.
benchmarkModules :: Benchmark -> [ModuleName] Source
Get all the module names from a benchmark.
enabledBenchmarks :: PackageDescription -> [Benchmark] Source
Get all the enabled benchmarks from a package.
Build information
BuildInfo | |
|
allBuildInfo :: PackageDescription -> [BuildInfo] Source
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] Source
The Language
s used by this component
allExtensions :: BuildInfo -> [Extension] Source
The Extension
s that are used somewhere by this component
usedExtensions :: BuildInfo -> [Extension] Source
The Extensions
that are used by all modules in this component
hcOptions :: CompilerFlavor -> BuildInfo -> [String] Source
Select options for a particular Haskell compiler.
hcProfOptions :: CompilerFlavor -> BuildInfo -> [String] Source
hcSharedOptions :: CompilerFlavor -> BuildInfo -> [String] Source
Supplementary build information
package configuration
data GenericPackageDescription Source
GenericPackageDescription | |
|
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 | |
|
Eq Flag | |
Data Flag | |
Show Flag | |
Generic Flag | |
Binary Flag | |
type Rep Flag = D1 (MetaData "Flag" "Distribution.PackageDescription" "Cabal-1.23.1.0" False) (C1 (MetaCons "MkFlag" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "flagName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 FlagName)) (S1 (MetaSel (Just Symbol "flagDescription") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String))) ((:*:) (S1 (MetaSel (Just Symbol "flagDefault") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)) (S1 (MetaSel (Just Symbol "flagManual") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool))))) |
A FlagName
is the name of a user-defined configuration flag
Eq FlagName | |
Data FlagName | |
Ord FlagName | |
Read FlagName | |
Show FlagName | |
Generic FlagName | |
Binary FlagName | |
type Rep FlagName = D1 (MetaData "FlagName" "Distribution.PackageDescription" "Cabal-1.23.1.0" True) (C1 (MetaCons "FlagName" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String))) |
type FlagAssignment = [(FlagName, Bool)] Source
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)]
CondNode | |
|
(Eq v, Eq c, Eq a) => Eq (CondTree v c a) | |
(Data v, Data c, Data a) => Data (CondTree v c a) | |
(Show v, Show c, Show a) => Show (CondTree v c a) | |
Generic (CondTree v c a) | |
(Binary v, Binary c, Binary a) => Binary (CondTree v c a) | |
type Rep (CondTree v c a) = D1 (MetaData "CondTree" "Distribution.PackageDescription" "Cabal-1.23.1.0" False) (C1 (MetaCons "CondNode" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "condTreeData") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)) ((:*:) (S1 (MetaSel (Just Symbol "condTreeConstraints") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 c)) (S1 (MetaSel (Just Symbol "condTreeComponents") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [(Condition v, CondTree v c a, Maybe (CondTree v c a))]))))) |
A ConfVar
represents the variable type used.
Eq ConfVar | |
Data ConfVar | |
Show ConfVar | |
Generic ConfVar | |
Binary ConfVar | |
type Rep ConfVar = D1 (MetaData "ConfVar" "Distribution.PackageDescription" "Cabal-1.23.1.0" False) ((:+:) ((:+:) (C1 (MetaCons "OS" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 OS))) (C1 (MetaCons "Arch" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Arch)))) ((:+:) (C1 (MetaCons "Flag" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 FlagName))) (C1 (MetaCons "Impl" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 CompilerFlavor)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 VersionRange)))))) |
A boolean expression parameterized over the variable type used.
Source repositories
data SourceRepo Source
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 | |
|
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 |
Eq RepoKind | |
Data RepoKind | |
Ord RepoKind | |
Read RepoKind | |
Show RepoKind | |
Generic RepoKind | |
Binary RepoKind | |
Text RepoKind | |
type Rep RepoKind = D1 (MetaData "RepoKind" "Distribution.PackageDescription" "Cabal-1.23.1.0" False) ((:+:) (C1 (MetaCons "RepoHead" PrefixI False) U1) ((:+:) (C1 (MetaCons "RepoThis" PrefixI False) U1) (C1 (MetaCons "RepoKindUnknown" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String))))) |
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.
Eq RepoType | |
Data RepoType | |
Ord RepoType | |
Read RepoType | |
Show RepoType | |
Generic RepoType | |
Binary RepoType | |
Text RepoType | |
type Rep RepoType = D1 (MetaData "RepoType" "Distribution.PackageDescription" "Cabal-1.23.1.0" False) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "Darcs" PrefixI False) U1) (C1 (MetaCons "Git" PrefixI False) U1)) ((:+:) (C1 (MetaCons "SVN" PrefixI False) U1) (C1 (MetaCons "CVS" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "Mercurial" PrefixI False) U1) (C1 (MetaCons "GnuArch" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Bazaar" PrefixI False) U1) ((:+:) (C1 (MetaCons "Monotone" PrefixI False) U1) (C1 (MetaCons "OtherRepoType" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String))))))) |
knownRepoTypes :: [RepoType] Source
Custom setup build information
data SetupBuildInfo Source
Eq SetupBuildInfo | |
Data SetupBuildInfo | |
Read SetupBuildInfo | |
Show SetupBuildInfo | |
Generic SetupBuildInfo | |
Semigroup SetupBuildInfo | |
Monoid SetupBuildInfo | |
Binary SetupBuildInfo | |
type Rep SetupBuildInfo = D1 (MetaData "SetupBuildInfo" "Distribution.PackageDescription" "Cabal-1.23.1.0" False) (C1 (MetaCons "SetupBuildInfo" PrefixI True) (S1 (MetaSel (Just Symbol "setupDepends") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Dependency]))) |