| Copyright | Isaac Jones 2003-2005 | 
|---|---|
| License | BSD3 | 
| Maintainer | cabal-devel@haskell.org | 
| Portability | portable | 
| Safe Haskell | None | 
| Language | Haskell2010 | 
Distribution.PackageDescription
Contents
Description
Backwards compatibility reexport of everything you need to know
 about .cabal files.
Synopsis
- data PackageDescription = PackageDescription {- specVersionRaw :: Either Version VersionRange
- package :: PackageIdentifier
- licenseRaw :: Either 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)]
- buildTypeRaw :: Maybe BuildType
- setupBuildInfo :: Maybe SetupBuildInfo
- library :: Maybe Library
- subLibraries :: [Library]
- executables :: [Executable]
- foreignLibs :: [ForeignLib]
- testSuites :: [TestSuite]
- benchmarks :: [Benchmark]
- dataFiles :: [FilePath]
- dataDir :: FilePath
- extraSrcFiles :: [FilePath]
- extraTmpFiles :: [FilePath]
- extraDocFiles :: [FilePath]
 
- emptyPackageDescription :: PackageDescription
- specVersion :: PackageDescription -> Version
- buildType :: PackageDescription -> BuildType
- license :: PackageDescription -> License
- descCabalVersion :: PackageDescription -> VersionRange
- data BuildType
- knownBuildTypes :: [BuildType]
- allLibraries :: PackageDescription -> [Library]
- data ModuleRenaming
- defaultRenaming :: ModuleRenaming
- data Library = Library {}
- data ModuleReexport = ModuleReexport {}
- emptyLibrary :: Library
- withLib :: PackageDescription -> (Library -> IO ()) -> IO ()
- hasPublicLib :: PackageDescription -> Bool
- hasLibs :: PackageDescription -> Bool
- explicitLibModules :: Library -> [ModuleName]
- libModulesAutogen :: Library -> [ModuleName]
- libModules :: Library -> [ModuleName]
- data Executable = Executable {}
- emptyExecutable :: Executable
- withExe :: PackageDescription -> (Executable -> IO ()) -> IO ()
- hasExes :: PackageDescription -> Bool
- exeModules :: Executable -> [ModuleName]
- exeModulesAutogen :: 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]
- testModulesAutogen :: TestSuite -> [ModuleName]
- 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]
- benchmarkModulesAutogen :: Benchmark -> [ModuleName]
- data BuildInfo = BuildInfo {- buildable :: Bool
- buildTools :: [LegacyExeDependency]
- buildToolDepends :: [ExeDependency]
- cppOptions :: [String]
- asmOptions :: [String]
- cmmOptions :: [String]
- ccOptions :: [String]
- cxxOptions :: [String]
- ldOptions :: [String]
- pkgconfigDepends :: [PkgconfigDependency]
- frameworks :: [String]
- extraFrameworkDirs :: [String]
- asmSources :: [FilePath]
- cmmSources :: [FilePath]
- cSources :: [FilePath]
- cxxSources :: [FilePath]
- jsSources :: [FilePath]
- hsSourceDirs :: [FilePath]
- otherModules :: [ModuleName]
- virtualModules :: [ModuleName]
- autogenModules :: [ModuleName]
- defaultLanguage :: Maybe Language
- otherLanguages :: [Language]
- defaultExtensions :: [Extension]
- otherExtensions :: [Extension]
- oldExtensions :: [Extension]
- extraLibs :: [String]
- extraGHCiLibs :: [String]
- extraBundledLibs :: [String]
- extraLibFlavours :: [String]
- extraLibDirs :: [String]
- includeDirs :: [FilePath]
- includes :: [FilePath]
- installIncludes :: [FilePath]
- options :: [(CompilerFlavor, [String])]
- profOptions :: [(CompilerFlavor, [String])]
- sharedOptions :: [(CompilerFlavor, [String])]
- staticOptions :: [(CompilerFlavor, [String])]
- customFieldsBI :: [(String, String)]
- targetBuildDepends :: [Dependency]
- mixins :: [Mixin]
 
- emptyBuildInfo :: BuildInfo
- allBuildInfo :: PackageDescription -> [BuildInfo]
- allLanguages :: BuildInfo -> [Language]
- allExtensions :: BuildInfo -> [Extension]
- usedExtensions :: BuildInfo -> [Extension]
- usesTemplateHaskellOrQQ :: BuildInfo -> Bool
- hcOptions :: CompilerFlavor -> BuildInfo -> [String]
- hcProfOptions :: CompilerFlavor -> BuildInfo -> [String]
- hcSharedOptions :: CompilerFlavor -> BuildInfo -> [String]
- hcStaticOptions :: CompilerFlavor -> BuildInfo -> [String]
- allBuildDepends :: PackageDescription -> [Dependency]
- enabledBuildDepends :: PackageDescription -> ComponentRequestedSpec -> [Dependency]
- data ComponentName
- defaultLibName :: ComponentName
- type HookedBuildInfo = (Maybe BuildInfo, [(UnqualComponentName, BuildInfo)])
- emptyHookedBuildInfo :: HookedBuildInfo
- updatePackageDescription :: HookedBuildInfo -> PackageDescription -> PackageDescription
- data GenericPackageDescription = GenericPackageDescription {- packageDescription :: PackageDescription
- genPackageFlags :: [Flag]
- condLibrary :: Maybe (CondTree ConfVar [Dependency] Library)
- condSubLibraries :: [(UnqualComponentName, CondTree ConfVar [Dependency] Library)]
- condForeignLibs :: [(UnqualComponentName, CondTree ConfVar [Dependency] ForeignLib)]
- condExecutables :: [(UnqualComponentName, CondTree ConfVar [Dependency] Executable)]
- condTestSuites :: [(UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)]
- condBenchmarks :: [(UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)]
 
- data Flag = MkFlag {}
- emptyFlag :: FlagName -> Flag
- data FlagName
- mkFlagName :: String -> FlagName
- unFlagName :: FlagName -> String
- data FlagAssignment
- mkFlagAssignment :: [(FlagName, Bool)] -> FlagAssignment
- unFlagAssignment :: FlagAssignment -> [(FlagName, Bool)]
- nullFlagAssignment :: FlagAssignment -> Bool
- showFlagValue :: (FlagName, Bool) -> String
- diffFlagAssignment :: FlagAssignment -> FlagAssignment -> FlagAssignment
- lookupFlagAssignment :: FlagName -> FlagAssignment -> Maybe Bool
- insertFlagAssignment :: FlagName -> Bool -> FlagAssignment -> FlagAssignment
- dispFlagAssignment :: FlagAssignment -> Doc
- parseFlagAssignment :: ReadP r FlagAssignment
- parsecFlagAssignment :: ParsecParser FlagAssignment
- findDuplicateFlagAssignments :: FlagAssignment -> [FlagName]
- data CondTree v c a = CondNode {- condTreeData :: a
- condTreeConstraints :: c
- condTreeComponents :: [CondBranch v c a]
 
- data ConfVar
- data Condition c
- cNot :: Condition a -> Condition a
- cAnd :: Condition a -> Condition a -> Condition a
- cOr :: Eq v => Condition v -> Condition v -> Condition v
- data SourceRepo = SourceRepo {}
- data RepoKind
- data RepoType
- knownRepoTypes :: [RepoType]
- emptySourceRepo :: RepoKind -> SourceRepo
- data SetupBuildInfo = SetupBuildInfo {}
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 | |
| Fields 
 | |
Instances
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.
buildType :: PackageDescription -> BuildType Source #
The effective build-type after applying defaulting rules.
The original build-type value parsed is stored in the
 buildTypeRaw field.  However, the build-type field is optional
 and can therefore be empty in which case we need to compute the
 effective build-type. This function implements the following
 defaulting rules:
- For cabal-version:2.0and below, default to theCustombuild-type unconditionally.
- Otherwise, if a custom-setupstanza is defined, default to theCustombuild-type; else default toSimplebuild-type.
Since: 2.2
license :: PackageDescription -> License Source #
The SPDX LicenseExpression of the package.
Since: 2.2.0.0
descCabalVersion :: PackageDescription -> VersionRange Source #
Deprecated: Use specVersion instead. This symbol will be removed in Cabal-3.0 (est. Mar 2019).
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.
Constructors
| Simple | calls  | 
| Configure | calls  | 
| Make | calls  | 
| Custom | uses user-supplied  | 
Instances
| Eq BuildType Source # | |
| Data BuildType Source # | |
| Defined in Distribution.Types.BuildType Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BuildType -> c BuildType # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c BuildType # toConstr :: BuildType -> Constr # dataTypeOf :: BuildType -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c BuildType) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BuildType) # gmapT :: (forall b. Data b => b -> b) -> BuildType -> BuildType # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BuildType -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BuildType -> r # gmapQ :: (forall d. Data d => d -> u) -> BuildType -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> BuildType -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> BuildType -> m BuildType # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BuildType -> m BuildType # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BuildType -> m BuildType # | |
| Read BuildType Source # | |
| Show BuildType Source # | |
| Generic BuildType Source # | |
| Binary BuildType Source # | |
| NFData BuildType Source # | |
| Defined in Distribution.Types.BuildType | |
| Pretty BuildType Source # | |
| Parsec BuildType Source # | |
| Defined in Distribution.Types.BuildType Methods parsec :: CabalParsing m => m BuildType Source # | |
| Text BuildType Source # | |
| type Rep BuildType Source # | |
| Defined in Distribution.Types.BuildType type Rep BuildType = D1 (MetaData "BuildType" "Distribution.Types.BuildType" "Cabal-2.4.1.0-B0ZPupqxKZe72LoceK3cGA" False) ((C1 (MetaCons "Simple" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Configure" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "Make" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Custom" PrefixI False) (U1 :: Type -> Type))) | |
knownBuildTypes :: [BuildType] Source #
allLibraries :: PackageDescription -> [Library] Source #
Renaming (syntactic)
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".
 If a renaming is omitted you get the DefaultRenaming.
(NB: This is a list not a map so that we can preserve order.)
Constructors
| ModuleRenaming [(ModuleName, ModuleName)] | A module renaming/thinning; e.g.,  | 
| DefaultRenaming | The default renaming, bringing all exported modules into scope. | 
| HidingRenaming [ModuleName] | Hiding renaming, e.g.,  | 
Instances
defaultRenaming :: ModuleRenaming Source #
The default renaming, if something is specified in build-depends
 only.
Libraries
Constructors
| Library | |
| Fields 
 | |
Instances
data ModuleReexport Source #
Constructors
| ModuleReexport | |
Instances
withLib :: PackageDescription -> (Library -> IO ()) -> IO () Source #
If the package description has a buildable library section,
 call the given function with the library build info as argument.
 You probably want withLibLBI if you have a LocalBuildInfo,
 see the note in
 Distribution.Types.ComponentRequestedSpec
 for more information.
hasPublicLib :: PackageDescription -> Bool Source #
Does this package have a buildable PUBLIC library?
hasLibs :: PackageDescription -> Bool Source #
Does this package have any libraries?
explicitLibModules :: Library -> [ModuleName] Source #
Get all the module names from the library (exposed and internal modules) which are explicitly listed in the package description which would need to be compiled. (This does not include reexports, which do not need to be compiled.) This may not include all modules for which GHC generated interface files (i.e., implicit modules.)
libModulesAutogen :: Library -> [ModuleName] Source #
Get all the auto generated module names from the library, exposed or not.
 This are a subset of libModules.
libModules :: Library -> [ModuleName] Source #
Deprecated: If you want all modules that are built with a library, use allLibModules.  Otherwise, use explicitLibModules for ONLY the modules explicitly mentioned in the package description. This symbol will be removed in Cabal-3.0 (est. Mar 2019).
Backwards-compatibility shim for explicitLibModules.  In most cases,
 you actually want allLibModules, which returns all modules that will
 actually be compiled, as opposed to those which are explicitly listed
 in the package description (explicitLibModules); unfortunately, the
 type signature for allLibModules is incompatible since we need a
 ComponentLocalBuildInfo.
Executables
data Executable Source #
Constructors
| Executable | |
| Fields | |
Instances
withExe :: PackageDescription -> (Executable -> IO ()) -> IO () Source #
Perform the action on each buildable Executable in the package
 description.  You probably want withExeLBI if you have a
 LocalBuildInfo, see the note in
 Distribution.Types.ComponentRequestedSpec
 for more information.
hasExes :: PackageDescription -> Bool Source #
does this package have any executables?
exeModules :: Executable -> [ModuleName] Source #
Get all the module names from an exe
exeModulesAutogen :: Executable -> [ModuleName] Source #
Get all the auto generated module names from an exe
 This are a subset of exeModules.
Tests
A "test-suite" stanza in a cabal file.
Constructors
| TestSuite | |
| Fields | |
Instances
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.
Constructors
| 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). | 
Instances
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 Version | Some unknown test type e.g. "type: foo" | 
Instances
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.
 You probably want withTestLBI if you have a LocalBuildInfo, see the note in
 Distribution.Types.ComponentRequestedSpec
 for more information.
testModules :: TestSuite -> [ModuleName] Source #
Get all the module names from a test suite.
testModulesAutogen :: TestSuite -> [ModuleName] Source #
Get all the auto generated module names from a test suite.
 This are a subset of testModules.
Benchmarks
A "benchmark" stanza in a cabal file.
Constructors
| Benchmark | |
Instances
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.
Constructors
| 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). | 
Instances
data BenchmarkType Source #
The "benchmark-type" field in the benchmark stanza.
Constructors
| BenchmarkTypeExe Version | "type: exitcode-stdio-x.y" | 
| BenchmarkTypeUnknown String Version | Some unknown benchmark type e.g. "type: foo" | 
Instances
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.
 You probably want withBenchLBI if you have a LocalBuildInfo, see the note in
 Distribution.Types.ComponentRequestedSpec
 for more information.
benchmarkModules :: Benchmark -> [ModuleName] Source #
Get all the module names from a benchmark.
benchmarkModulesAutogen :: Benchmark -> [ModuleName] Source #
Get all the auto generated module names from a benchmark.
 This are a subset of benchmarkModules.
Build information
Constructors
| BuildInfo | |
| Fields 
 | |
Instances
allBuildInfo :: PackageDescription -> [BuildInfo] Source #
All BuildInfo in the PackageDescription:
 libraries, executables, test-suites and benchmarks.
Useful for implementing package checks.
allExtensions :: BuildInfo -> [Extension] Source #
The Extensions that are used somewhere by this component
usedExtensions :: BuildInfo -> [Extension] Source #
The Extensions that are used by all modules in this component
usesTemplateHaskellOrQQ :: BuildInfo -> Bool Source #
Whether any modules in this component use Template Haskell or Quasi Quotes
hcOptions :: CompilerFlavor -> BuildInfo -> [String] Source #
Select options for a particular Haskell compiler.
hcProfOptions :: CompilerFlavor -> BuildInfo -> [String] Source #
hcSharedOptions :: CompilerFlavor -> BuildInfo -> [String] Source #
hcStaticOptions :: CompilerFlavor -> BuildInfo -> [String] Source #
Supplementary build information
allBuildDepends :: PackageDescription -> [Dependency] Source #
Get the combined build-depends entries of all components.
enabledBuildDepends :: PackageDescription -> ComponentRequestedSpec -> [Dependency] Source #
Get the combined build-depends entries of all enabled components, per the given request spec.
data ComponentName Source #
Constructors
| CLibName | |
| CSubLibName UnqualComponentName | |
| CFLibName UnqualComponentName | |
| CExeName UnqualComponentName | |
| CTestName UnqualComponentName | |
| CBenchName UnqualComponentName | 
Instances
type HookedBuildInfo = (Maybe BuildInfo, [(UnqualComponentName, BuildInfo)]) Source #
HookedBuildInfo is mechanism that hooks can use to
 override the BuildInfos inside packages.  One example
 use-case (which is used in core libraries today) is as
 a way of passing flags which are computed by a configure
 script into Cabal.  In this case, the autoconf build type adds
 hooks to read in a textual HookedBuildInfo format prior
 to doing any operations.
Quite honestly, this mechanism is a massive hack since we shouldn't
 be editing the PackageDescription data structure (it's easy
 to assume that this data structure shouldn't change and
 run into bugs, see for example 1c20a6328579af9e37677d507e2e9836ef70ab9d).
 But it's a bit convenient, because there isn't another data
 structure that allows adding extra BuildInfo style things.
In any case, a lot of care has to be taken to make sure the
 HookedBuildInfo is applied to the PackageDescription.  In
 general this process occurs in Distribution.Simple, which is
 responsible for orchestrating the hooks mechanism.  The
 general strategy:
- We run the pre-hook, which produces a HookedBuildInfo(e.g., in the Autoconf case, it reads it out from a file).
- We sanity-check the hooked build info with
         sanityCheckHookedBuildInfo.
- We update our PackageDescription(either freshly read or cached fromLocalBuildInfo) withupdatePackageDescription.
In principle, we are also supposed to update the copy of
         the PackageDescription stored in LocalBuildInfo
         at localPkgDescr.  Unfortunately, in practice, there
         are lots of Custom setup scripts which fail to update
         localPkgDescr so you really shouldn't rely on it.
         It's not DEPRECATED because there are legitimate uses
         for it, but... yeah.  Sharp knife.  See
         https://github.com/haskell/cabal/issues/3606
         for more information on the issue.
It is not well-specified whether or not a HookedBuildInfo applied
 at configure time is persistent to the LocalBuildInfo.  The
 fact that HookedBuildInfo is passed to confHook MIGHT SUGGEST
 that the HookedBuildInfo is applied at this time, but actually
 since 9317b67e6122ab14e53f81b573bd0ecb388eca5a it has been ONLY used
 to create a modified package description that we check for problems:
 it is never actually saved to the LBI.  Since HookedBuildInfo is
 applied monoidally to the existing build infos (and it is not an
 idempotent monoid), it could break things to save it, since we
 are obligated to apply any new HookedBuildInfo and then we'd
 get the effect twice.  But this does mean we have to re-apply
 it every time. Hey, it's more flexibility.
package configuration
data GenericPackageDescription Source #
Constructors
Instances
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 | |
| Fields 
 | |
Instances
| Eq Flag Source # | |
| Data Flag Source # | |
| Defined in Distribution.Types.GenericPackageDescription Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Flag -> c Flag # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Flag # dataTypeOf :: Flag -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Flag) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Flag) # gmapT :: (forall b. Data b => b -> b) -> Flag -> Flag # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Flag -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Flag -> r # gmapQ :: (forall d. Data d => d -> u) -> Flag -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Flag -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Flag -> m Flag # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Flag -> m Flag # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Flag -> m Flag # | |
| Show Flag Source # | |
| Generic Flag Source # | |
| Binary Flag Source # | |
| NFData Flag Source # | |
| Defined in Distribution.Types.GenericPackageDescription | |
| type Rep Flag Source # | |
| Defined in Distribution.Types.GenericPackageDescription type Rep Flag = D1 (MetaData "Flag" "Distribution.Types.GenericPackageDescription" "Cabal-2.4.1.0-B0ZPupqxKZe72LoceK3cGA" False) (C1 (MetaCons "MkFlag" PrefixI True) ((S1 (MetaSel (Just "flagName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 FlagName) :*: S1 (MetaSel (Just "flagDescription") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)) :*: (S1 (MetaSel (Just "flagDefault") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool) :*: S1 (MetaSel (Just "flagManual") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)))) | |
A FlagName is the name of a user-defined configuration flag
Use mkFlagName and unFlagName to convert from/to a String.
This type is opaque since Cabal-2.0
Since: 2.0.0.2
Instances
mkFlagName :: String -> FlagName Source #
Construct a FlagName from a String
mkFlagName is the inverse to unFlagName
Note: No validations are performed to ensure that the resulting
 FlagName is valid
Since: 2.0.0.2
data FlagAssignment 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)]
Instances
mkFlagAssignment :: [(FlagName, Bool)] -> FlagAssignment Source #
Construct a FlagAssignment from a list of flag/value pairs.
If duplicate flags occur in the input list, the later entries in the list will take precedence.
Since: 2.2.0
unFlagAssignment :: FlagAssignment -> [(FlagName, Bool)] Source #
Deconstruct a FlagAssignment into a list of flag/value pairs.
null(findDuplicateFlagAssignmentsfa) ==> (mkFlagAssignment.unFlagAssignment) fa == fa
Since: 2.2.0
nullFlagAssignment :: FlagAssignment -> Bool Source #
Test whether FlagAssignment is empty.
Since: 2.2.0
diffFlagAssignment :: FlagAssignment -> FlagAssignment -> FlagAssignment Source #
Remove all flag-assignments from the first FlagAssignment that
 are contained in the second FlagAssignment
NB/TODO: This currently only removes flag assignments which also match the value assignment! We should review the code which uses this operation to figure out if this it's not enough to only compare the flagnames without the values.
Since: 2.2.0
lookupFlagAssignment :: FlagName -> FlagAssignment -> Maybe Bool Source #
Lookup the value for a flag
Returns Nothing if the flag isn't contained in the FlagAssignment.
Since: 2.2.0
insertFlagAssignment :: FlagName -> Bool -> FlagAssignment -> FlagAssignment Source #
Insert or update the boolean value of a flag.
If the flag is already present in the FlagAssigment, the
 value will be updated and the fact that multiple values have
 been provided for that flag will be recorded so that a
 warning can be generated later on.
Since: 2.2.0
dispFlagAssignment :: FlagAssignment -> Doc Source #
Pretty-prints a flag assignment.
parseFlagAssignment :: ReadP r FlagAssignment Source #
Parses a flag assignment.
parsecFlagAssignment :: ParsecParser FlagAssignment Source #
Parses a flag assignment.
findDuplicateFlagAssignments :: FlagAssignment -> [FlagName] Source #
Find the FlagNames that have been listed more than once.
Since: 2.2.0
A CondTree is used to represent the conditional structure of
 a Cabal file, reflecting a syntax element subject to constraints,
 and then any number of sub-elements which may be enabled subject
 to some condition.  Both a and c are usually Monoids.
To be more concrete, consider the following fragment of a Cabal
 file:
build-depends: base >= 4.0
if flag(extra)
    build-depends: base >= 4.2
One way to represent this is to have CondTree ConfVar
 [Dependency] BuildInfocondTreeData represents
 the actual fields which are not behind any conditional, while
 condTreeComponents recursively records any further fields
 which are behind a conditional.  condTreeConstraints records
 the constraints (in this case, base >= 4.0) which would
 be applied if you use this syntax; in general, this is
 derived off of targetBuildInfo (perhaps a good refactoring
 would be to convert this into an opaque type, with a smart
 constructor that pre-computes the dependencies.)
Constructors
| CondNode | |
| Fields 
 | |
Instances
| Functor (CondTree v c) Source # | |
| Foldable (CondTree v c) Source # | |
| Defined in Distribution.Types.CondTree Methods fold :: Monoid m => CondTree v c m -> m # foldMap :: Monoid m => (a -> m) -> CondTree v c a -> m # foldr :: (a -> b -> b) -> b -> CondTree v c a -> b # foldr' :: (a -> b -> b) -> b -> CondTree v c a -> b # foldl :: (b -> a -> b) -> b -> CondTree v c a -> b # foldl' :: (b -> a -> b) -> b -> CondTree v c a -> b # foldr1 :: (a -> a -> a) -> CondTree v c a -> a # foldl1 :: (a -> a -> a) -> CondTree v c a -> a # toList :: CondTree v c a -> [a] # null :: CondTree v c a -> Bool # length :: CondTree v c a -> Int # elem :: Eq a => a -> CondTree v c a -> Bool # maximum :: Ord a => CondTree v c a -> a # minimum :: Ord a => CondTree v c a -> a # | |
| Traversable (CondTree v c) Source # | |
| Defined in Distribution.Types.CondTree | |
| (Eq a, Eq c, Eq v) => Eq (CondTree v c a) Source # | |
| (Data v, Data c, Data a) => Data (CondTree v c a) Source # | |
| Defined in Distribution.Types.CondTree Methods gfoldl :: (forall d b. Data d => c0 (d -> b) -> d -> c0 b) -> (forall g. g -> c0 g) -> CondTree v c a -> c0 (CondTree v c a) # gunfold :: (forall b r. Data b => c0 (b -> r) -> c0 r) -> (forall r. r -> c0 r) -> Constr -> c0 (CondTree v c a) # toConstr :: CondTree v c a -> Constr # dataTypeOf :: CondTree v c a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c0 (t d)) -> Maybe (c0 (CondTree v c a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c0 (t d e)) -> Maybe (c0 (CondTree v c a)) # gmapT :: (forall b. Data b => b -> b) -> CondTree v c a -> CondTree v c a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CondTree v c a -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CondTree v c a -> r # gmapQ :: (forall d. Data d => d -> u) -> CondTree v c a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> CondTree v c a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> CondTree v c a -> m (CondTree v c a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CondTree v c a -> m (CondTree v c a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CondTree v c a -> m (CondTree v c a) # | |
| (Show a, Show c, Show v) => Show (CondTree v c a) Source # | |
| Generic (CondTree v c a) Source # | |
| (Binary v, Binary c, Binary a) => Binary (CondTree v c a) Source # | |
| (NFData v, NFData c, NFData a) => NFData (CondTree v c a) Source # | |
| Defined in Distribution.Types.CondTree | |
| type Rep (CondTree v c a) Source # | |
| Defined in Distribution.Types.CondTree type Rep (CondTree v c a) = D1 (MetaData "CondTree" "Distribution.Types.CondTree" "Cabal-2.4.1.0-B0ZPupqxKZe72LoceK3cGA" False) (C1 (MetaCons "CondNode" PrefixI True) (S1 (MetaSel (Just "condTreeData") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: (S1 (MetaSel (Just "condTreeConstraints") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 c) :*: S1 (MetaSel (Just "condTreeComponents") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [CondBranch v c a])))) | |
A ConfVar represents the variable type used.
Constructors
| OS OS | |
| Arch Arch | |
| Flag FlagName | |
| Impl CompilerFlavor VersionRange | 
Instances
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) | 
Instances
cOr :: Eq v => Condition v -> Condition v -> Condition v Source #
Boolean OR of two Condition values.
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.
Constructors
| SourceRepo | |
| Fields 
 | |
Instances
What this repo info is for, what it represents.
Constructors
| 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 | 
Instances
| Eq RepoKind Source # | |
| Data RepoKind Source # | |
| Defined in Distribution.Types.SourceRepo Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RepoKind -> c RepoKind # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RepoKind # toConstr :: RepoKind -> Constr # dataTypeOf :: RepoKind -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c RepoKind) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RepoKind) # gmapT :: (forall b. Data b => b -> b) -> RepoKind -> RepoKind # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RepoKind -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RepoKind -> r # gmapQ :: (forall d. Data d => d -> u) -> RepoKind -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> RepoKind -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> RepoKind -> m RepoKind # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RepoKind -> m RepoKind # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RepoKind -> m RepoKind # | |
| Ord RepoKind Source # | |
| Defined in Distribution.Types.SourceRepo | |
| Read RepoKind Source # | |
| Show RepoKind Source # | |
| Generic RepoKind Source # | |
| Binary RepoKind Source # | |
| NFData RepoKind Source # | |
| Defined in Distribution.Types.SourceRepo | |
| Pretty RepoKind Source # | |
| Parsec RepoKind Source # | |
| Defined in Distribution.Types.SourceRepo Methods parsec :: CabalParsing m => m RepoKind Source # | |
| Text RepoKind Source # | |
| type Rep RepoKind Source # | |
| Defined in Distribution.Types.SourceRepo type Rep RepoKind = D1 (MetaData "RepoKind" "Distribution.Types.SourceRepo" "Cabal-2.4.1.0-B0ZPupqxKZe72LoceK3cGA" False) (C1 (MetaCons "RepoHead" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "RepoThis" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "RepoKindUnknown" PrefixI False) (S1 (MetaSel (Nothing :: Maybe 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.
Instances
knownRepoTypes :: [RepoType] Source #
emptySourceRepo :: RepoKind -> SourceRepo Source #
Custom setup build information
data SetupBuildInfo Source #
Constructors
| SetupBuildInfo | |
| Fields 
 | |