Cabal-2.0.0.2: A framework for packaging Haskell software

CopyrightIsaac Jones 2003-2005
LicenseBSD3
Maintainercabal-devel@haskell.org
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Distribution.PackageDescription

Contents

Description

Backwards compatibility reexport of everything you need to know about .cabal files.

Synopsis

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
Eq PackageDescription Source # 
Instance details
Data PackageDescription Source # 
Instance details

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PackageDescription -> c PackageDescription #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PackageDescription #

toConstr :: PackageDescription -> Constr #

dataTypeOf :: PackageDescription -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c PackageDescription) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PackageDescription) #

gmapT :: (forall b. Data b => b -> b) -> PackageDescription -> PackageDescription #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PackageDescription -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PackageDescription -> r #

gmapQ :: (forall d. Data d => d -> u) -> PackageDescription -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PackageDescription -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PackageDescription -> m PackageDescription #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PackageDescription -> m PackageDescription #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PackageDescription -> m PackageDescription #

Read PackageDescription Source # 
Instance details
Show PackageDescription Source # 
Instance details
Generic PackageDescription Source # 
Instance details

Associated Types

type Rep PackageDescription :: * -> * #

Binary PackageDescription Source # 
Instance details
Package PackageDescription Source # 
Instance details
type Rep PackageDescription Source # 
Instance details
type Rep PackageDescription = D1 * (MetaData "PackageDescription" "Distribution.Types.PackageDescription" "Cabal-2.0.0.2-ArD10404PgFe4UBxSAxnL" False) (C1 * (MetaCons "PackageDescription" PrefixI True) ((:*:) * ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "package") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * PackageIdentifier)) ((:*:) * (S1 * (MetaSel (Just Symbol "license") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * License)) (S1 * (MetaSel (Just Symbol "licenseFiles") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [FilePath])))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "copyright") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String)) (S1 * (MetaSel (Just Symbol "maintainer") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String))) ((:*:) * (S1 * (MetaSel (Just Symbol "author") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String)) (S1 * (MetaSel (Just Symbol "stability") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String))))) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "testedWith") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [(CompilerFlavor, VersionRange)])) (S1 * (MetaSel (Just Symbol "homepage") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String))) ((:*:) * (S1 * (MetaSel (Just Symbol "pkgUrl") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String)) (S1 * (MetaSel (Just Symbol "bugReports") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String)))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "sourceRepos") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [SourceRepo])) (S1 * (MetaSel (Just Symbol "synopsis") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String))) ((:*:) * (S1 * (MetaSel (Just Symbol "description") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String)) (S1 * (MetaSel (Just Symbol "category") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String)))))) ((:*:) * ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "customFieldsPD") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [(String, String)])) (S1 * (MetaSel (Just Symbol "buildDepends") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Dependency]))) ((:*:) * (S1 * (MetaSel (Just Symbol "specVersionRaw") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Either Version VersionRange))) (S1 * (MetaSel (Just Symbol "buildType") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe BuildType))))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "setupBuildInfo") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe SetupBuildInfo))) (S1 * (MetaSel (Just Symbol "library") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Library)))) ((:*:) * (S1 * (MetaSel (Just Symbol "subLibraries") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Library])) (S1 * (MetaSel (Just Symbol "executables") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Executable]))))) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "foreignLibs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [ForeignLib])) (S1 * (MetaSel (Just Symbol "testSuites") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [TestSuite]))) ((:*:) * (S1 * (MetaSel (Just Symbol "benchmarks") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Benchmark])) (S1 * (MetaSel (Just Symbol "dataFiles") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [FilePath])))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "dataDir") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * FilePath)) (S1 * (MetaSel (Just Symbol "extraSrcFiles") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [FilePath]))) ((:*:) * (S1 * (MetaSel (Just Symbol "extraTmpFiles") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [FilePath])) (S1 * (MetaSel (Just Symbol "extraDocFiles") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [FilePath]))))))))

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.

data BuildType Source #

The type of build system used by this package.

Constructors

Simple

calls Distribution.Simple.defaultMain

Configure

calls Distribution.Simple.defaultMainWithHooks defaultUserHooks, which invokes configure to generate additional build information used by later phases.

Make

calls Distribution.Make.defaultMain

Custom

uses user-supplied Setup.hs or Setup.lhs (default)

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.

Instances
Eq BuildType Source # 
Instance details
Data BuildType Source # 
Instance details

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 # 
Instance details
Show BuildType Source # 
Instance details
Generic BuildType Source # 
Instance details

Associated Types

type Rep BuildType :: * -> * #

Binary BuildType Source # 
Instance details
Text BuildType Source # 
Instance details
type Rep BuildType Source # 
Instance details
type Rep BuildType = D1 * (MetaData "BuildType" "Distribution.Types.BuildType" "Cabal-2.0.0.2-ArD10404PgFe4UBxSAxnL" 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 (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., (A as B, C as C) brings B and C into scope.

DefaultRenaming

The default renaming, bringing all exported modules into scope.

HidingRenaming [ModuleName]

Hiding renaming, e.g., hiding (A, B), bringing all exported modules into scope except the hidden ones.

Instances
Eq ModuleRenaming Source # 
Instance details
Data ModuleRenaming Source # 
Instance details

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ModuleRenaming -> c ModuleRenaming #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ModuleRenaming #

toConstr :: ModuleRenaming -> Constr #

dataTypeOf :: ModuleRenaming -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ModuleRenaming) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ModuleRenaming) #

gmapT :: (forall b. Data b => b -> b) -> ModuleRenaming -> ModuleRenaming #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ModuleRenaming -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ModuleRenaming -> r #

gmapQ :: (forall d. Data d => d -> u) -> ModuleRenaming -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ModuleRenaming -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ModuleRenaming -> m ModuleRenaming #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ModuleRenaming -> m ModuleRenaming #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ModuleRenaming -> m ModuleRenaming #

Ord ModuleRenaming Source # 
Instance details
Read ModuleRenaming Source # 
Instance details
Show ModuleRenaming Source # 
Instance details
Generic ModuleRenaming Source # 
Instance details

Associated Types

type Rep ModuleRenaming :: * -> * #

Binary ModuleRenaming Source # 
Instance details
Text ModuleRenaming Source # 
Instance details
type Rep ModuleRenaming Source # 
Instance details
type Rep ModuleRenaming = D1 * (MetaData "ModuleRenaming" "Distribution.Types.ModuleRenaming" "Cabal-2.0.0.2-ArD10404PgFe4UBxSAxnL" False) ((:+:) * (C1 * (MetaCons "ModuleRenaming" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [(ModuleName, ModuleName)]))) ((:+:) * (C1 * (MetaCons "DefaultRenaming" PrefixI False) (U1 *)) (C1 * (MetaCons "HidingRenaming" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [ModuleName])))))

defaultRenaming :: ModuleRenaming Source #

The default renaming, if something is specified in build-depends only.

Libraries

data Library Source #

Constructors

Library 

Fields

Instances
Eq Library Source # 
Instance details

Methods

(==) :: Library -> Library -> Bool #

(/=) :: Library -> Library -> Bool #

Data Library Source # 
Instance details

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Library -> c Library #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Library #

toConstr :: Library -> Constr #

dataTypeOf :: Library -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Library) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Library) #

gmapT :: (forall b. Data b => b -> b) -> Library -> Library #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Library -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Library -> r #

gmapQ :: (forall d. Data d => d -> u) -> Library -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Library -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Library -> m Library #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Library -> m Library #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Library -> m Library #

Read Library Source # 
Instance details
Show Library Source # 
Instance details
Generic Library Source # 
Instance details

Associated Types

type Rep Library :: * -> * #

Methods

from :: Library -> Rep Library x #

to :: Rep Library x -> Library #

Semigroup Library Source # 
Instance details
Monoid Library Source # 
Instance details
Binary Library Source # 
Instance details

Methods

put :: Library -> Put #

get :: Get Library #

putList :: [Library] -> Put #

type Rep Library Source # 
Instance details

data ModuleReexport Source #

Instances
Eq ModuleReexport Source # 
Instance details
Data ModuleReexport Source # 
Instance details

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ModuleReexport -> c ModuleReexport #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ModuleReexport #

toConstr :: ModuleReexport -> Constr #

dataTypeOf :: ModuleReexport -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ModuleReexport) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ModuleReexport) #

gmapT :: (forall b. Data b => b -> b) -> ModuleReexport -> ModuleReexport #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ModuleReexport -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ModuleReexport -> r #

gmapQ :: (forall d. Data d => d -> u) -> ModuleReexport -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ModuleReexport -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ModuleReexport -> m ModuleReexport #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ModuleReexport -> m ModuleReexport #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ModuleReexport -> m ModuleReexport #

Read ModuleReexport Source # 
Instance details
Show ModuleReexport Source # 
Instance details
Generic ModuleReexport Source # 
Instance details

Associated Types

type Rep ModuleReexport :: * -> * #

Binary ModuleReexport Source # 
Instance details
Text ModuleReexport Source # 
Instance details
type Rep ModuleReexport Source # 
Instance details
type Rep ModuleReexport = D1 * (MetaData "ModuleReexport" "Distribution.Types.ModuleReexport" "Cabal-2.0.0.2-ArD10404PgFe4UBxSAxnL" 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 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.

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 #

Instances
Eq Executable Source # 
Instance details
Data Executable Source # 
Instance details

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Executable -> c Executable #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Executable #

toConstr :: Executable -> Constr #

dataTypeOf :: Executable -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Executable) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Executable) #

gmapT :: (forall b. Data b => b -> b) -> Executable -> Executable #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Executable -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Executable -> r #

gmapQ :: (forall d. Data d => d -> u) -> Executable -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Executable -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Executable -> m Executable #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Executable -> m Executable #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Executable -> m Executable #

Read Executable Source # 
Instance details
Show Executable Source # 
Instance details
Generic Executable Source # 
Instance details

Associated Types

type Rep Executable :: * -> * #

Semigroup Executable Source # 
Instance details
Monoid Executable Source # 
Instance details
Binary Executable Source # 
Instance details
type Rep Executable Source # 
Instance details

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

data TestSuite Source #

A "test-suite" stanza in a cabal file.

Instances
Eq TestSuite Source # 
Instance details
Data TestSuite Source # 
Instance details

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TestSuite -> c TestSuite #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TestSuite #

toConstr :: TestSuite -> Constr #

dataTypeOf :: TestSuite -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c TestSuite) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TestSuite) #

gmapT :: (forall b. Data b => b -> b) -> TestSuite -> TestSuite #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TestSuite -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TestSuite -> r #

gmapQ :: (forall d. Data d => d -> u) -> TestSuite -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TestSuite -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TestSuite -> m TestSuite #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TestSuite -> m TestSuite #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TestSuite -> m TestSuite #

Read TestSuite Source # 
Instance details
Show TestSuite Source # 
Instance details
Generic TestSuite Source # 
Instance details

Associated Types

type Rep TestSuite :: * -> * #

Semigroup TestSuite Source # 
Instance details
Monoid TestSuite Source # 
Instance details
Binary TestSuite Source # 
Instance details
type Rep TestSuite Source # 
Instance details
type Rep TestSuite = D1 * (MetaData "TestSuite" "Distribution.Types.TestSuite" "Cabal-2.0.0.2-ArD10404PgFe4UBxSAxnL" False) (C1 * (MetaCons "TestSuite" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "testName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * UnqualComponentName)) ((:*:) * (S1 * (MetaSel (Just Symbol "testInterface") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * TestSuiteInterface)) (S1 * (MetaSel (Just Symbol "testBuildInfo") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * BuildInfo)))))

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
Eq TestSuiteInterface Source # 
Instance details
Data TestSuiteInterface Source # 
Instance details

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TestSuiteInterface -> c TestSuiteInterface #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TestSuiteInterface #

toConstr :: TestSuiteInterface -> Constr #

dataTypeOf :: TestSuiteInterface -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c TestSuiteInterface) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TestSuiteInterface) #

gmapT :: (forall b. Data b => b -> b) -> TestSuiteInterface -> TestSuiteInterface #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TestSuiteInterface -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TestSuiteInterface -> r #

gmapQ :: (forall d. Data d => d -> u) -> TestSuiteInterface -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TestSuiteInterface -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TestSuiteInterface -> m TestSuiteInterface #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TestSuiteInterface -> m TestSuiteInterface #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TestSuiteInterface -> m TestSuiteInterface #

Read TestSuiteInterface Source # 
Instance details
Show TestSuiteInterface Source # 
Instance details
Generic TestSuiteInterface Source # 
Instance details

Associated Types

type Rep TestSuiteInterface :: * -> * #

Semigroup TestSuiteInterface Source # 
Instance details
Monoid TestSuiteInterface Source # 
Instance details
Binary TestSuiteInterface Source # 
Instance details
type Rep TestSuiteInterface Source # 
Instance details

data TestType Source #

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
Eq TestType Source # 
Instance details
Data TestType Source # 
Instance details

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TestType -> c TestType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TestType #

toConstr :: TestType -> Constr #

dataTypeOf :: TestType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c TestType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TestType) #

gmapT :: (forall b. Data b => b -> b) -> TestType -> TestType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TestType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TestType -> r #

gmapQ :: (forall d. Data d => d -> u) -> TestType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TestType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TestType -> m TestType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TestType -> m TestType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TestType -> m TestType #

Read TestType Source # 
Instance details
Show TestType Source # 
Instance details
Generic TestType Source # 
Instance details

Associated Types

type Rep TestType :: * -> * #

Methods

from :: TestType -> Rep TestType x #

to :: Rep TestType x -> TestType #

Binary TestType Source # 
Instance details

Methods

put :: TestType -> Put #

get :: Get TestType #

putList :: [TestType] -> Put #

Text TestType Source # 
Instance details
type Rep TestType Source # 
Instance details

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

data Benchmark Source #

A "benchmark" stanza in a cabal file.

Instances
Eq Benchmark Source # 
Instance details
Data Benchmark Source # 
Instance details

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Benchmark -> c Benchmark #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Benchmark #

toConstr :: Benchmark -> Constr #

dataTypeOf :: Benchmark -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Benchmark) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Benchmark) #

gmapT :: (forall b. Data b => b -> b) -> Benchmark -> Benchmark #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Benchmark -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Benchmark -> r #

gmapQ :: (forall d. Data d => d -> u) -> Benchmark -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Benchmark -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Benchmark -> m Benchmark #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Benchmark -> m Benchmark #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Benchmark -> m Benchmark #

Read Benchmark Source # 
Instance details
Show Benchmark Source # 
Instance details
Generic Benchmark Source # 
Instance details

Associated Types

type Rep Benchmark :: * -> * #

Semigroup Benchmark Source # 
Instance details
Monoid Benchmark Source # 
Instance details
Binary Benchmark Source # 
Instance details
type Rep Benchmark Source # 
Instance details
type Rep Benchmark = D1 * (MetaData "Benchmark" "Distribution.Types.Benchmark" "Cabal-2.0.0.2-ArD10404PgFe4UBxSAxnL" False) (C1 * (MetaCons "Benchmark" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "benchmarkName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * UnqualComponentName)) ((:*:) * (S1 * (MetaSel (Just Symbol "benchmarkInterface") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * BenchmarkInterface)) (S1 * (MetaSel (Just Symbol "benchmarkBuildInfo") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * BuildInfo)))))

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
Eq BenchmarkInterface Source # 
Instance details
Data BenchmarkInterface Source # 
Instance details

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BenchmarkInterface -> c BenchmarkInterface #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c BenchmarkInterface #

toConstr :: BenchmarkInterface -> Constr #

dataTypeOf :: BenchmarkInterface -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c BenchmarkInterface) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BenchmarkInterface) #

gmapT :: (forall b. Data b => b -> b) -> BenchmarkInterface -> BenchmarkInterface #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BenchmarkInterface -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BenchmarkInterface -> r #

gmapQ :: (forall d. Data d => d -> u) -> BenchmarkInterface -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> BenchmarkInterface -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> BenchmarkInterface -> m BenchmarkInterface #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BenchmarkInterface -> m BenchmarkInterface #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BenchmarkInterface -> m BenchmarkInterface #

Read BenchmarkInterface Source # 
Instance details
Show BenchmarkInterface Source # 
Instance details
Generic BenchmarkInterface Source # 
Instance details

Associated Types

type Rep BenchmarkInterface :: * -> * #

Semigroup BenchmarkInterface Source # 
Instance details
Monoid BenchmarkInterface Source # 
Instance details
Binary BenchmarkInterface Source # 
Instance details
type Rep BenchmarkInterface Source # 
Instance details
type Rep BenchmarkInterface = D1 * (MetaData "BenchmarkInterface" "Distribution.Types.BenchmarkInterface" "Cabal-2.0.0.2-ArD10404PgFe4UBxSAxnL" 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.

Constructors

BenchmarkTypeExe Version

"type: exitcode-stdio-x.y"

BenchmarkTypeUnknown String Version

Some unknown benchmark type e.g. "type: foo"

Instances
Eq BenchmarkType Source # 
Instance details
Data BenchmarkType Source # 
Instance details

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BenchmarkType -> c BenchmarkType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c BenchmarkType #

toConstr :: BenchmarkType -> Constr #

dataTypeOf :: BenchmarkType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c BenchmarkType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BenchmarkType) #

gmapT :: (forall b. Data b => b -> b) -> BenchmarkType -> BenchmarkType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BenchmarkType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BenchmarkType -> r #

gmapQ :: (forall d. Data d => d -> u) -> BenchmarkType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> BenchmarkType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> BenchmarkType -> m BenchmarkType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BenchmarkType -> m BenchmarkType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BenchmarkType -> m BenchmarkType #

Read BenchmarkType Source # 
Instance details
Show BenchmarkType Source # 
Instance details
Generic BenchmarkType Source # 
Instance details

Associated Types

type Rep BenchmarkType :: * -> * #

Binary BenchmarkType Source # 
Instance details
Text BenchmarkType Source # 
Instance details
type Rep BenchmarkType Source # 
Instance details
type Rep BenchmarkType = D1 * (MetaData "BenchmarkType" "Distribution.Types.BenchmarkType" "Cabal-2.0.0.2-ArD10404PgFe4UBxSAxnL" 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. 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

data BuildInfo Source #

Constructors

BuildInfo 

Fields

Instances
Eq BuildInfo Source # 
Instance details
Data BuildInfo Source # 
Instance details

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BuildInfo -> c BuildInfo #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c BuildInfo #

toConstr :: BuildInfo -> Constr #

dataTypeOf :: BuildInfo -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c BuildInfo) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BuildInfo) #

gmapT :: (forall b. Data b => b -> b) -> BuildInfo -> BuildInfo #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BuildInfo -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BuildInfo -> r #

gmapQ :: (forall d. Data d => d -> u) -> BuildInfo -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> BuildInfo -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> BuildInfo -> m BuildInfo #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BuildInfo -> m BuildInfo #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BuildInfo -> m BuildInfo #

Read BuildInfo Source # 
Instance details
Show BuildInfo Source # 
Instance details
Generic BuildInfo Source # 
Instance details

Associated Types

type Rep BuildInfo :: * -> * #

Semigroup BuildInfo Source # 
Instance details
Monoid BuildInfo Source # 
Instance details
Binary BuildInfo Source # 
Instance details
type Rep BuildInfo Source # 
Instance details
type Rep BuildInfo = D1 * (MetaData "BuildInfo" "Distribution.Types.BuildInfo" "Cabal-2.0.0.2-ArD10404PgFe4UBxSAxnL" False) (C1 * (MetaCons "BuildInfo" PrefixI True) ((:*:) * ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "buildable") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool)) ((:*:) * (S1 * (MetaSel (Just Symbol "buildTools") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [LegacyExeDependency])) (S1 * (MetaSel (Just Symbol "buildToolDepends") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [ExeDependency])))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "cppOptions") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [String])) (S1 * (MetaSel (Just Symbol "ccOptions") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [String]))) ((:*:) * (S1 * (MetaSel (Just Symbol "ldOptions") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [String])) (S1 * (MetaSel (Just Symbol "pkgconfigDepends") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [PkgconfigDependency]))))) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "frameworks") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [String])) (S1 * (MetaSel (Just Symbol "extraFrameworkDirs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [String]))) ((:*:) * (S1 * (MetaSel (Just Symbol "cSources") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [FilePath])) (S1 * (MetaSel (Just Symbol "jsSources") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [FilePath])))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "hsSourceDirs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [FilePath])) (S1 * (MetaSel (Just Symbol "otherModules") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [ModuleName]))) ((:*:) * (S1 * (MetaSel (Just Symbol "autogenModules") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [ModuleName])) (S1 * (MetaSel (Just Symbol "defaultLanguage") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe Language))))))) ((:*:) * ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "otherLanguages") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Language])) (S1 * (MetaSel (Just Symbol "defaultExtensions") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Extension]))) ((:*:) * (S1 * (MetaSel (Just Symbol "otherExtensions") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Extension])) (S1 * (MetaSel (Just Symbol "oldExtensions") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Extension])))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "extraLibs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [String])) (S1 * (MetaSel (Just Symbol "extraGHCiLibs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [String]))) ((:*:) * (S1 * (MetaSel (Just Symbol "extraLibDirs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [String])) (S1 * (MetaSel (Just Symbol "includeDirs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [FilePath]))))) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "includes") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [FilePath])) (S1 * (MetaSel (Just Symbol "installIncludes") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [FilePath]))) ((:*:) * (S1 * (MetaSel (Just Symbol "options") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [(CompilerFlavor, [String])])) (S1 * (MetaSel (Just Symbol "profOptions") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [(CompilerFlavor, [String])])))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "sharedOptions") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [(CompilerFlavor, [String])])) (S1 * (MetaSel (Just Symbol "customFieldsBI") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [(String, String)]))) ((:*:) * (S1 * (MetaSel (Just Symbol "targetBuildDepends") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Dependency])) (S1 * (MetaSel (Just Symbol "mixins") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Mixin]))))))))

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 Languages used by this component

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

hcOptions :: CompilerFlavor -> BuildInfo -> [String] Source #

Select options for a particular Haskell compiler.

Supplementary build information

data ComponentName Source #

Instances
Eq ComponentName Source # 
Instance details
Ord ComponentName Source # 
Instance details
Read ComponentName Source # 
Instance details
Show ComponentName Source # 
Instance details
Generic ComponentName Source # 
Instance details

Associated Types

type Rep ComponentName :: * -> * #

Binary ComponentName Source # 
Instance details
Text ComponentName Source # 
Instance details
type Rep ComponentName Source # 
Instance details

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:

  1. We run the pre-hook, which produces a HookedBuildInfo (e.g., in the Autoconf case, it reads it out from a file).
  2. We sanity-check the hooked build info with sanityCheckHookedBuildInfo.
  3. We update our PackageDescription (either freshly read or cached from LocalBuildInfo) with updatePackageDescription.

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 #

Instances
Eq GenericPackageDescription Source # 
Instance details
Data GenericPackageDescription Source # 
Instance details

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GenericPackageDescription -> c GenericPackageDescription #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c GenericPackageDescription #

toConstr :: GenericPackageDescription -> Constr #

dataTypeOf :: GenericPackageDescription -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c GenericPackageDescription) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c GenericPackageDescription) #

gmapT :: (forall b. Data b => b -> b) -> GenericPackageDescription -> GenericPackageDescription #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GenericPackageDescription -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GenericPackageDescription -> r #

gmapQ :: (forall d. Data d => d -> u) -> GenericPackageDescription -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GenericPackageDescription -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GenericPackageDescription -> m GenericPackageDescription #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GenericPackageDescription -> m GenericPackageDescription #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GenericPackageDescription -> m GenericPackageDescription #

Show GenericPackageDescription Source # 
Instance details
Generic GenericPackageDescription Source # 
Instance details

Associated Types

type Rep GenericPackageDescription :: * -> * #

Binary GenericPackageDescription Source # 
Instance details
Package GenericPackageDescription Source # 
Instance details
type Rep GenericPackageDescription Source # 
Instance details
type Rep GenericPackageDescription = D1 * (MetaData "GenericPackageDescription" "Distribution.Types.GenericPackageDescription" "Cabal-2.0.0.2-ArD10404PgFe4UBxSAxnL" False) (C1 * (MetaCons "GenericPackageDescription" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "packageDescription") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * PackageDescription)) (S1 * (MetaSel (Just Symbol "genPackageFlags") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Flag]))) ((:*:) * (S1 * (MetaSel (Just Symbol "condLibrary") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe (CondTree ConfVar [Dependency] Library)))) (S1 * (MetaSel (Just Symbol "condSubLibraries") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [(UnqualComponentName, CondTree ConfVar [Dependency] Library)])))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "condForeignLibs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [(UnqualComponentName, CondTree ConfVar [Dependency] ForeignLib)])) (S1 * (MetaSel (Just Symbol "condExecutables") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [(UnqualComponentName, CondTree ConfVar [Dependency] Executable)]))) ((:*:) * (S1 * (MetaSel (Just Symbol "condTestSuites") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [(UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)])) (S1 * (MetaSel (Just Symbol "condBenchmarks") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [(UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)]))))))

data Flag Source #

A flag can represent a feature to be included, or a way of linking a target against its dependencies, or in fact whatever you can think of.

Instances
Eq Flag Source # 
Instance details

Methods

(==) :: Flag -> Flag -> Bool #

(/=) :: Flag -> Flag -> Bool #

Data Flag Source # 
Instance details

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 #

toConstr :: Flag -> Constr #

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 # 
Instance details

Methods

showsPrec :: Int -> Flag -> ShowS #

show :: Flag -> String #

showList :: [Flag] -> ShowS #

Generic Flag Source # 
Instance details

Associated Types

type Rep Flag :: * -> * #

Methods

from :: Flag -> Rep Flag x #

to :: Rep Flag x -> Flag #

Binary Flag Source # 
Instance details

Methods

put :: Flag -> Put #

get :: Get Flag #

putList :: [Flag] -> Put #

type Rep Flag Source # 
Instance details
type Rep Flag = D1 * (MetaData "Flag" "Distribution.Types.GenericPackageDescription" "Cabal-2.0.0.2-ArD10404PgFe4UBxSAxnL" 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)))))

emptyFlag :: FlagName -> Flag Source #

A Flag initialized with default parameters.

data FlagName Source #

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

Instances
Eq FlagName Source # 
Instance details
Data FlagName Source # 
Instance details

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FlagName -> c FlagName #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FlagName #

toConstr :: FlagName -> Constr #

dataTypeOf :: FlagName -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c FlagName) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FlagName) #

gmapT :: (forall b. Data b => b -> b) -> FlagName -> FlagName #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FlagName -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FlagName -> r #

gmapQ :: (forall d. Data d => d -> u) -> FlagName -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FlagName -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FlagName -> m FlagName #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FlagName -> m FlagName #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FlagName -> m FlagName #

Ord FlagName Source # 
Instance details
Read FlagName Source # 
Instance details
Show FlagName Source # 
Instance details
IsString FlagName Source #

mkFlagName

Since: 2.0

Instance details
Generic FlagName Source # 
Instance details

Associated Types

type Rep FlagName :: * -> * #

Methods

from :: FlagName -> Rep FlagName x #

to :: Rep FlagName x -> FlagName #

Binary FlagName Source # 
Instance details

Methods

put :: FlagName -> Put #

get :: Get FlagName #

putList :: [FlagName] -> Put #

type Rep FlagName Source # 
Instance details
type Rep FlagName = D1 * (MetaData "FlagName" "Distribution.Types.GenericPackageDescription" "Cabal-2.0.0.2-ArD10404PgFe4UBxSAxnL" True) (C1 * (MetaCons "FlagName" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * ShortText)))

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

unFlagName :: FlagName -> String Source #

Convert FlagName to String

Since: 2.0

type FlagAssignment = [(FlagName, Bool)] Source #

A FlagAssignment is a total or partial mapping of FlagNames to Bool flag values. It represents the flags chosen by the user or discovered during configuration. For example --flags=foo --flags=-bar becomes [("foo", True), ("bar", False)]

showFlagValue :: (FlagName, Bool) -> String Source #

String representation of a flag-value pair.

dispFlagAssignment :: FlagAssignment -> Doc Source #

Pretty-prints a flag assignment.

parseFlagAssignment :: ReadP r FlagAssignment Source #

Parses a flag assignment.

data CondTree v c a Source #

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] BuildInfo. Here, condTreeData 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 
Instances
Functor (CondTree v c) Source # 
Instance details

Methods

fmap :: (a -> b) -> CondTree v c a -> CondTree v c b #

(<$) :: a -> CondTree v c b -> CondTree v c a #

Foldable (CondTree v c) Source # 
Instance details

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 #

sum :: Num a => CondTree v c a -> a #

product :: Num a => CondTree v c a -> a #

Traversable (CondTree v c) Source # 
Instance details

Methods

traverse :: Applicative f => (a -> f b) -> CondTree v c a -> f (CondTree v c b) #

sequenceA :: Applicative f => CondTree v c (f a) -> f (CondTree v c a) #

mapM :: Monad m => (a -> m b) -> CondTree v c a -> m (CondTree v c b) #

sequence :: Monad m => CondTree v c (m a) -> m (CondTree v c a) #

(Eq v, Eq c, Eq a) => Eq (CondTree v c a) Source # 
Instance details

Methods

(==) :: CondTree v c a -> CondTree v c a -> Bool #

(/=) :: CondTree v c a -> CondTree v c a -> Bool #

(Data a, Data c, Data v) => Data (CondTree v c a) Source # 
Instance details

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 v, Show c, Show a) => Show (CondTree v c a) Source # 
Instance details

Methods

showsPrec :: Int -> CondTree v c a -> ShowS #

show :: CondTree v c a -> String #

showList :: [CondTree v c a] -> ShowS #

Generic (CondTree v c a) Source # 
Instance details

Associated Types

type Rep (CondTree v c a) :: * -> * #

Methods

from :: CondTree v c a -> Rep (CondTree v c a) x #

to :: Rep (CondTree v c a) x -> CondTree v c a #

(Binary v, Binary c, Binary a) => Binary (CondTree v c a) Source # 
Instance details

Methods

put :: CondTree v c a -> Put #

get :: Get (CondTree v c a) #

putList :: [CondTree v c a] -> Put #

type Rep (CondTree v c a) Source # 
Instance details
type Rep (CondTree v c a) = D1 * (MetaData "CondTree" "Distribution.Types.CondTree" "Cabal-2.0.0.2-ArD10404PgFe4UBxSAxnL" 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 * [CondBranch v c a])))))

data ConfVar Source #

A ConfVar represents the variable type used.

Instances
Eq ConfVar Source # 
Instance details

Methods

(==) :: ConfVar -> ConfVar -> Bool #

(/=) :: ConfVar -> ConfVar -> Bool #

Data ConfVar Source # 
Instance details

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ConfVar -> c ConfVar #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ConfVar #

toConstr :: ConfVar -> Constr #

dataTypeOf :: ConfVar -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ConfVar) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ConfVar) #

gmapT :: (forall b. Data b => b -> b) -> ConfVar -> ConfVar #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ConfVar -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ConfVar -> r #

gmapQ :: (forall d. Data d => d -> u) -> ConfVar -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ConfVar -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ConfVar -> m ConfVar #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ConfVar -> m ConfVar #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ConfVar -> m ConfVar #

Show ConfVar Source # 
Instance details
Generic ConfVar Source # 
Instance details

Associated Types

type Rep ConfVar :: * -> * #

Methods

from :: ConfVar -> Rep ConfVar x #

to :: Rep ConfVar x -> ConfVar #

Binary ConfVar Source # 
Instance details

Methods

put :: ConfVar -> Put #

get :: Get ConfVar #

putList :: [ConfVar] -> Put #

type Rep ConfVar Source # 
Instance details

data Condition c Source #

A boolean expression parameterized over the variable type used.

Constructors

Var c 
Lit Bool 
CNot (Condition c) 
COr (Condition c) (Condition c) 
CAnd (Condition c) (Condition c) 
Instances
Monad Condition Source # 
Instance details

Methods

(>>=) :: Condition a -> (a -> Condition b) -> Condition b #

(>>) :: Condition a -> Condition b -> Condition b #

return :: a -> Condition a #

fail :: String -> Condition a #

Functor Condition Source # 
Instance details

Methods

fmap :: (a -> b) -> Condition a -> Condition b #

(<$) :: a -> Condition b -> Condition a #

Applicative Condition Source # 
Instance details

Methods

pure :: a -> Condition a #

(<*>) :: Condition (a -> b) -> Condition a -> Condition b #

liftA2 :: (a -> b -> c) -> Condition a -> Condition b -> Condition c #

(*>) :: Condition a -> Condition b -> Condition b #

(<*) :: Condition a -> Condition b -> Condition a #

Foldable Condition Source # 
Instance details

Methods

fold :: Monoid m => Condition m -> m #

foldMap :: Monoid m => (a -> m) -> Condition a -> m #

foldr :: (a -> b -> b) -> b -> Condition a -> b #

foldr' :: (a -> b -> b) -> b -> Condition a -> b #

foldl :: (b -> a -> b) -> b -> Condition a -> b #

foldl' :: (b -> a -> b) -> b -> Condition a -> b #

foldr1 :: (a -> a -> a) -> Condition a -> a #

foldl1 :: (a -> a -> a) -> Condition a -> a #

toList :: Condition a -> [a] #

null :: Condition a -> Bool #

length :: Condition a -> Int #

elem :: Eq a => a -> Condition a -> Bool #

maximum :: Ord a => Condition a -> a #

minimum :: Ord a => Condition a -> a #

sum :: Num a => Condition a -> a #

product :: Num a => Condition a -> a #

Traversable Condition Source # 
Instance details

Methods

traverse :: Applicative f => (a -> f b) -> Condition a -> f (Condition b) #

sequenceA :: Applicative f => Condition (f a) -> f (Condition a) #

mapM :: Monad m => (a -> m b) -> Condition a -> m (Condition b) #

sequence :: Monad m => Condition (m a) -> m (Condition a) #

Alternative Condition Source # 
Instance details

Methods

empty :: Condition a #

(<|>) :: Condition a -> Condition a -> Condition a #

some :: Condition a -> Condition [a] #

many :: Condition a -> Condition [a] #

MonadPlus Condition Source # 
Instance details

Methods

mzero :: Condition a #

mplus :: Condition a -> Condition a -> Condition a #

Eq c => Eq (Condition c) Source # 
Instance details

Methods

(==) :: Condition c -> Condition c -> Bool #

(/=) :: Condition c -> Condition c -> Bool #

Data c => Data (Condition c) Source # 
Instance details

Methods

gfoldl :: (forall d b. Data d => c0 (d -> b) -> d -> c0 b) -> (forall g. g -> c0 g) -> Condition c -> c0 (Condition c) #

gunfold :: (forall b r. Data b => c0 (b -> r) -> c0 r) -> (forall r. r -> c0 r) -> Constr -> c0 (Condition c) #

toConstr :: Condition c -> Constr #

dataTypeOf :: Condition c -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c0 (t d)) -> Maybe (c0 (Condition c)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c0 (t d e)) -> Maybe (c0 (Condition c)) #

gmapT :: (forall b. Data b => b -> b) -> Condition c -> Condition c #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Condition c -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Condition c -> r #

gmapQ :: (forall d. Data d => d -> u) -> Condition c -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Condition c -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Condition c -> m (Condition c) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Condition c -> m (Condition c) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Condition c -> m (Condition c) #

Show c => Show (Condition c) Source # 
Instance details
Generic (Condition c) Source # 
Instance details

Associated Types

type Rep (Condition c) :: * -> * #

Methods

from :: Condition c -> Rep (Condition c) x #

to :: Rep (Condition c) x -> Condition c #

Semigroup (Condition a) Source # 
Instance details

Methods

(<>) :: Condition a -> Condition a -> Condition a #

sconcat :: NonEmpty (Condition a) -> Condition a #

stimes :: Integral b => b -> Condition a -> Condition a #

Monoid (Condition a) Source # 
Instance details
Binary c => Binary (Condition c) Source # 
Instance details

Methods

put :: Condition c -> Put #

get :: Get (Condition c) #

putList :: [Condition c] -> Put #

type Rep (Condition c) Source # 
Instance details

cNot :: Condition a -> Condition a Source #

Boolean negation of a Condition value.

cAnd :: Condition a -> Condition a -> Condition a Source #

Boolean AND of two Condtion values.

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

  • repoKind :: RepoKind

    The kind of repo. This field is required.

  • repoType :: Maybe RepoType

    The type of the source repository system for this repo, eg Darcs or Git. This field is required.

  • repoLocation :: Maybe String

    The location of the repository. For most RepoTypes this is a URL. This field is required.

  • repoModule :: Maybe String

    CVS 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 String

    The 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 String

    The tag identify a particular state of the repository. This should be given for the RepoThis repo kind and not for RepoHead kind.

  • repoSubdir :: Maybe FilePath

    Some 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.

Instances
Eq SourceRepo Source # 
Instance details
Data SourceRepo Source # 
Instance details

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SourceRepo -> c SourceRepo #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SourceRepo #

toConstr :: SourceRepo -> Constr #

dataTypeOf :: SourceRepo -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c SourceRepo) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SourceRepo) #

gmapT :: (forall b. Data b => b -> b) -> SourceRepo -> SourceRepo #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SourceRepo -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SourceRepo -> r #

gmapQ :: (forall d. Data d => d -> u) -> SourceRepo -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SourceRepo -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SourceRepo -> m SourceRepo #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SourceRepo -> m SourceRepo #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SourceRepo -> m SourceRepo #

Read SourceRepo Source # 
Instance details
Show SourceRepo Source # 
Instance details
Generic SourceRepo Source # 
Instance details

Associated Types

type Rep SourceRepo :: * -> * #

Binary SourceRepo Source # 
Instance details
type Rep SourceRepo Source # 
Instance details

data RepoKind Source #

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 # 
Instance details
Data RepoKind Source # 
Instance details

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 # 
Instance details
Read RepoKind Source # 
Instance details
Show RepoKind Source # 
Instance details
Generic RepoKind Source # 
Instance details

Associated Types

type Rep RepoKind :: * -> * #

Methods

from :: RepoKind -> Rep RepoKind x #

to :: Rep RepoKind x -> RepoKind #

Binary RepoKind Source # 
Instance details

Methods

put :: RepoKind -> Put #

get :: Get RepoKind #

putList :: [RepoKind] -> Put #

Text RepoKind Source # 
Instance details
type Rep RepoKind Source # 
Instance details
type Rep RepoKind = D1 * (MetaData "RepoKind" "Distribution.Types.SourceRepo" "Cabal-2.0.0.2-ArD10404PgFe4UBxSAxnL" 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)))))

data RepoType Source #

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
Eq RepoType Source # 
Instance details
Data RepoType Source # 
Instance details

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RepoType -> c RepoType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RepoType #

toConstr :: RepoType -> Constr #

dataTypeOf :: RepoType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c RepoType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RepoType) #

gmapT :: (forall b. Data b => b -> b) -> RepoType -> RepoType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RepoType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RepoType -> r #

gmapQ :: (forall d. Data d => d -> u) -> RepoType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RepoType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RepoType -> m RepoType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RepoType -> m RepoType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RepoType -> m RepoType #

Ord RepoType Source # 
Instance details
Read RepoType Source # 
Instance details
Show RepoType Source # 
Instance details
Generic RepoType Source # 
Instance details

Associated Types

type Rep RepoType :: * -> * #

Methods

from :: RepoType -> Rep RepoType x #

to :: Rep RepoType x -> RepoType #

Binary RepoType Source # 
Instance details

Methods

put :: RepoType -> Put #

get :: Get RepoType #

putList :: [RepoType] -> Put #

Text RepoType Source # 
Instance details
type Rep RepoType Source # 
Instance details
type Rep RepoType = D1 * (MetaData "RepoType" "Distribution.Types.SourceRepo" "Cabal-2.0.0.2-ArD10404PgFe4UBxSAxnL" 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)))))))

Custom setup build information

data SetupBuildInfo Source #

Constructors

SetupBuildInfo 

Fields

  • setupDepends :: [Dependency]
     
  • defaultSetupDepends :: Bool

    Is this a default 'custom-setup' section added by the cabal-install code (as opposed to user-provided)? This field is only used internally, and doesn't correspond to anything in the .cabal file. See #3199.

Instances
Eq SetupBuildInfo Source # 
Instance details
Data SetupBuildInfo Source # 
Instance details

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SetupBuildInfo -> c SetupBuildInfo #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SetupBuildInfo #

toConstr :: SetupBuildInfo -> Constr #

dataTypeOf :: SetupBuildInfo -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c SetupBuildInfo) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SetupBuildInfo) #

gmapT :: (forall b. Data b => b -> b) -> SetupBuildInfo -> SetupBuildInfo #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SetupBuildInfo -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SetupBuildInfo -> r #

gmapQ :: (forall d. Data d => d -> u) -> SetupBuildInfo -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SetupBuildInfo -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SetupBuildInfo -> m SetupBuildInfo #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SetupBuildInfo -> m SetupBuildInfo #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SetupBuildInfo -> m SetupBuildInfo #

Read SetupBuildInfo Source # 
Instance details
Show SetupBuildInfo Source # 
Instance details
Generic SetupBuildInfo Source # 
Instance details

Associated Types

type Rep SetupBuildInfo :: * -> * #

Semigroup SetupBuildInfo Source # 
Instance details
Monoid SetupBuildInfo Source # 
Instance details
Binary SetupBuildInfo Source # 
Instance details
type Rep SetupBuildInfo Source # 
Instance details
type Rep SetupBuildInfo = D1 * (MetaData "SetupBuildInfo" "Distribution.Types.SetupBuildInfo" "Cabal-2.0.0.2-ArD10404PgFe4UBxSAxnL" False) (C1 * (MetaCons "SetupBuildInfo" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "setupDepends") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Dependency])) (S1 * (MetaSel (Just Symbol "defaultSetupDepends") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool))))