Cabal-1.24.2.0: A framework for packaging Haskell software

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

Distribution.PackageDescription

Contents

Description

This defines the data structure for the .cabal file format. There are several parts to this structure. It has top level info and then Library, Executable, TestSuite, and Benchmark sections each of which have associated BuildInfo data that's used to build the library, exe, test, or benchmark. To further complicate things there is both a PackageDescription and a GenericPackageDescription. This distinction relates to cabal configurations. When we initially read a .cabal file we get a GenericPackageDescription which has all the conditional sections. Before actually building a package we have to decide on each conditional. Once we've done that we get a PackageDescription. It was done this way initially to avoid breaking too much stuff when the feature was introduced. It could probably do with being rationalised at some point to make it simpler.

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

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 # 
Show PackageDescription Source # 
Generic PackageDescription Source # 
Binary PackageDescription Source # 
Package PackageDescription Source # 
type Rep PackageDescription Source # 
type Rep PackageDescription = D1 (MetaData "PackageDescription" "Distribution.PackageDescription" "Cabal-1.24.2.0-DZNolZ9MBQLKV7GSAwAGX6" 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 "executables") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Executable])) (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 # 
Data BuildType Source # 

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 # 

Associated Types

type Rep BuildType :: * -> * #

Binary BuildType Source # 
Text BuildType Source # 
type Rep BuildType Source # 
type Rep BuildType = D1 (MetaData "BuildType" "Distribution.PackageDescription" "Cabal-1.24.2.0-DZNolZ9MBQLKV7GSAwAGX6" False) ((:+:) ((:+:) (C1 (MetaCons "Simple" PrefixI False) U1) (C1 (MetaCons "Configure" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Make" PrefixI False) U1) ((:+:) (C1 (MetaCons "Custom" PrefixI False) U1) (C1 (MetaCons "UnknownBuildType" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String))))))

Renaming

data ModuleRenaming Source #

Renaming applied to the modules provided by a package. The boolean indicates whether or not to also include all of the original names of modules. Thus, ModuleRenaming False [] is "don't expose any modules, and ModuleRenaming True [(Data.Bool, Bool)] is, "expose all modules, but also expose Data.Bool as Bool".

Instances

Eq ModuleRenaming Source # 
Data ModuleRenaming Source # 

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 # 
Read ModuleRenaming Source # 
Show ModuleRenaming Source # 
Generic ModuleRenaming Source # 

Associated Types

type Rep ModuleRenaming :: * -> * #

Semigroup ModuleRenaming Source # 
Monoid ModuleRenaming Source # 
Binary ModuleRenaming Source # 
Text ModuleRenaming Source # 
type Rep ModuleRenaming Source # 
type Rep ModuleRenaming = D1 (MetaData "ModuleRenaming" "Distribution.PackageDescription" "Cabal-1.24.2.0-DZNolZ9MBQLKV7GSAwAGX6" False) (C1 (MetaCons "ModuleRenaming" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [(ModuleName, ModuleName)]))))

Libraries

data Library Source #

Constructors

Library 

Fields

Instances

Eq Library Source # 

Methods

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

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

Data Library Source # 

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 # 
Show Library Source # 
Generic Library Source # 

Associated Types

type Rep Library :: * -> * #

Methods

from :: Library -> Rep Library x #

to :: Rep Library x -> Library #

Semigroup Library Source # 
Monoid Library Source # 
Binary Library Source # 

Methods

put :: Library -> Put #

get :: Get Library #

putList :: [Library] -> Put #

type Rep Library Source # 

data ModuleReexport Source #

Instances

Eq ModuleReexport Source # 
Data ModuleReexport Source # 

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 # 
Show ModuleReexport Source # 
Generic ModuleReexport Source # 

Associated Types

type Rep ModuleReexport :: * -> * #

Binary ModuleReexport Source # 
Text ModuleReexport Source # 
type Rep ModuleReexport Source # 
type Rep ModuleReexport = D1 (MetaData "ModuleReexport" "Distribution.PackageDescription" "Cabal-1.24.2.0-DZNolZ9MBQLKV7GSAwAGX6" False) (C1 (MetaCons "ModuleReexport" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "moduleReexportOriginalPackage") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe PackageName))) ((:*:) (S1 (MetaSel (Just Symbol "moduleReexportOriginalName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ModuleName)) (S1 (MetaSel (Just Symbol "moduleReexportName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ModuleName)))))

withLib :: PackageDescription -> (Library -> IO ()) -> IO () Source #

If the package description has a library section, call the given function with the library build info as argument.

hasLibs :: PackageDescription -> Bool Source #

does this package have any libraries?

libModules :: Library -> [ModuleName] Source #

Get all the module names from the library (exposed and internal modules) which need to be compiled. (This does not include reexports, which do not need to be compiled.)

Executables

data Executable Source #

Instances

Eq Executable Source # 
Data Executable Source # 

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 # 
Show Executable Source # 
Generic Executable Source # 

Associated Types

type Rep Executable :: * -> * #

Semigroup Executable Source # 
Monoid Executable Source # 
Binary Executable Source # 
type Rep Executable Source # 
type Rep Executable = D1 (MetaData "Executable" "Distribution.PackageDescription" "Cabal-1.24.2.0-DZNolZ9MBQLKV7GSAwAGX6" False) (C1 (MetaCons "Executable" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "exeName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)) ((:*:) (S1 (MetaSel (Just Symbol "modulePath") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 FilePath)) (S1 (MetaSel (Just Symbol "buildInfo") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 BuildInfo)))))

withExe :: PackageDescription -> (Executable -> IO ()) -> IO () Source #

Perform the action on each buildable Executable in the package description.

hasExes :: PackageDescription -> Bool Source #

does this package have any executables?

exeModules :: Executable -> [ModuleName] Source #

Get all the module names from an exe

Tests

data TestSuite Source #

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

Instances

Eq TestSuite Source # 
Data TestSuite Source # 

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 # 
Show TestSuite Source # 
Generic TestSuite Source # 

Associated Types

type Rep TestSuite :: * -> * #

Semigroup TestSuite Source # 
Monoid TestSuite Source # 
Binary TestSuite Source # 
type Rep TestSuite Source # 

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

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 # 
Show TestSuiteInterface Source # 
Generic TestSuiteInterface Source # 
Semigroup TestSuiteInterface Source # 
Monoid TestSuiteInterface Source # 
Binary TestSuiteInterface Source # 
type Rep TestSuiteInterface Source # 

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

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 # 
Show TestType Source # 
Generic TestType Source # 

Associated Types

type Rep TestType :: * -> * #

Methods

from :: TestType -> Rep TestType x #

to :: Rep TestType x -> TestType #

Binary TestType Source # 

Methods

put :: TestType -> Put #

get :: Get TestType #

putList :: [TestType] -> Put #

Text TestType Source # 
type Rep TestType Source # 

hasTests :: PackageDescription -> Bool Source #

Does this package have any test suites?

withTest :: PackageDescription -> (TestSuite -> IO ()) -> IO () Source #

Perform an action on each buildable TestSuite in a package.

testModules :: TestSuite -> [ModuleName] Source #

Get all the module names from a test suite.

enabledTests :: PackageDescription -> [TestSuite] Source #

Get all the enabled test suites from a package.

Benchmarks

data Benchmark Source #

A "benchmark" stanza in a cabal file.

Instances

Eq Benchmark Source # 
Data Benchmark Source # 

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 # 
Show Benchmark Source # 
Generic Benchmark Source # 

Associated Types

type Rep Benchmark :: * -> * #

Semigroup Benchmark Source # 
Monoid Benchmark Source # 
Binary Benchmark Source # 
type Rep Benchmark Source # 
type Rep Benchmark = D1 (MetaData "Benchmark" "Distribution.PackageDescription" "Cabal-1.24.2.0-DZNolZ9MBQLKV7GSAwAGX6" False) (C1 (MetaCons "Benchmark" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "benchmarkName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)) (S1 (MetaSel (Just Symbol "benchmarkInterface") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 BenchmarkInterface))) ((:*:) (S1 (MetaSel (Just Symbol "benchmarkBuildInfo") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 BuildInfo)) (S1 (MetaSel (Just Symbol "benchmarkEnabled") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)))))

data BenchmarkInterface Source #

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

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

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

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 # 
Show BenchmarkInterface Source # 
Generic BenchmarkInterface Source # 
Semigroup BenchmarkInterface Source # 
Monoid BenchmarkInterface Source # 
Binary BenchmarkInterface Source # 
type Rep BenchmarkInterface Source # 

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 # 
Data BenchmarkType Source # 

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 # 
Show BenchmarkType Source # 
Generic BenchmarkType Source # 

Associated Types

type Rep BenchmarkType :: * -> * #

Binary BenchmarkType Source # 
Text BenchmarkType Source # 
type Rep BenchmarkType Source # 

hasBenchmarks :: PackageDescription -> Bool Source #

Does this package have any benchmarks?

withBenchmark :: PackageDescription -> (Benchmark -> IO ()) -> IO () Source #

Perform an action on each buildable Benchmark in a package.

benchmarkModules :: Benchmark -> [ModuleName] Source #

Get all the module names from a benchmark.

enabledBenchmarks :: PackageDescription -> [Benchmark] Source #

Get all the enabled benchmarks from a package.

Build information

data BuildInfo Source #

Constructors

BuildInfo 

Fields

Instances

Eq BuildInfo Source # 
Data BuildInfo Source # 

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 # 
Show BuildInfo Source # 
Generic BuildInfo Source # 

Associated Types

type Rep BuildInfo :: * -> * #

Semigroup BuildInfo Source # 
Monoid BuildInfo Source # 
Binary BuildInfo Source # 
type Rep BuildInfo Source # 
type Rep BuildInfo = D1 (MetaData "BuildInfo" "Distribution.PackageDescription" "Cabal-1.24.2.0-DZNolZ9MBQLKV7GSAwAGX6" 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 [Dependency])) (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 [Dependency])) (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 "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 "targetBuildRenaming") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Map PackageName ModuleRenaming)))))))))

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

package configuration

data GenericPackageDescription Source #

Instances

Eq GenericPackageDescription Source # 
Data GenericPackageDescription Source # 

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 # 
Generic GenericPackageDescription Source # 
Binary GenericPackageDescription Source # 
Package GenericPackageDescription Source # 
type Rep GenericPackageDescription Source # 

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 # 

Methods

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

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

Data Flag Source # 

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 # 

Methods

showsPrec :: Int -> Flag -> ShowS #

show :: Flag -> String #

showList :: [Flag] -> ShowS #

Generic Flag Source # 

Associated Types

type Rep Flag :: * -> * #

Methods

from :: Flag -> Rep Flag x #

to :: Rep Flag x -> Flag #

Binary Flag Source # 

Methods

put :: Flag -> Put #

get :: Get Flag #

putList :: [Flag] -> Put #

type Rep Flag Source # 

newtype FlagName Source #

A FlagName is the name of a user-defined configuration flag

Constructors

FlagName String 

Instances

Eq FlagName Source # 
Data FlagName Source # 

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 # 
Read FlagName Source # 
Show FlagName Source # 
Generic FlagName Source # 

Associated Types

type Rep FlagName :: * -> * #

Methods

from :: FlagName -> Rep FlagName x #

to :: Rep FlagName x -> FlagName #

Binary FlagName Source # 

Methods

put :: FlagName -> Put #

get :: Get FlagName #

putList :: [FlagName] -> Put #

type Rep FlagName Source # 
type Rep FlagName = D1 (MetaData "FlagName" "Distribution.PackageDescription" "Cabal-1.24.2.0-DZNolZ9MBQLKV7GSAwAGX6" True) (C1 (MetaCons "FlagName" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)))

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

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

data CondTree v c a Source #

Constructors

CondNode 

Instances

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

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 # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CondTree v c a -> c (CondTree v c a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (CondTree v c a) #

toConstr :: CondTree v c a -> Constr #

dataTypeOf :: CondTree v c a -> DataType #

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

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (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 # 

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 # 

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 # 

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 # 
type Rep (CondTree v c a) = D1 (MetaData "CondTree" "Distribution.PackageDescription" "Cabal-1.24.2.0-DZNolZ9MBQLKV7GSAwAGX6" False) (C1 (MetaCons "CondNode" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "condTreeData") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)) ((:*:) (S1 (MetaSel (Just Symbol "condTreeConstraints") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 c)) (S1 (MetaSel (Just Symbol "condTreeComponents") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [(Condition v, CondTree v c a, Maybe (CondTree v c a))])))))

data ConfVar Source #

A ConfVar represents the variable type used.

Instances

Eq ConfVar Source # 

Methods

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

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

Data ConfVar Source # 

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 # 
Generic ConfVar Source # 

Associated Types

type Rep ConfVar :: * -> * #

Methods

from :: ConfVar -> Rep ConfVar x #

to :: Rep ConfVar x -> ConfVar #

Binary ConfVar Source # 

Methods

put :: ConfVar -> Put #

get :: Get ConfVar #

putList :: [ConfVar] -> Put #

type Rep ConfVar Source # 

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 # 

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 # 

Methods

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

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

Applicative Condition Source # 

Methods

pure :: a -> Condition a #

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

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

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

Foldable Condition Source # 

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 # 

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 # 

Methods

empty :: Condition a #

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

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

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

MonadPlus Condition Source # 

Methods

mzero :: Condition a #

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

Eq c => Eq (Condition c) Source # 

Methods

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

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

Data c => Data (Condition c) Source # 

Methods

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

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

toConstr :: Condition c -> Constr #

dataTypeOf :: Condition c -> DataType #

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

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (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 # 
Generic (Condition c) Source # 

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 # 

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 # 
Binary c => Binary (Condition c) Source # 

Methods

put :: Condition c -> Put #

get :: Get (Condition c) #

putList :: [Condition c] -> Put #

type Rep (Condition c) Source # 

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 # 
Data SourceRepo Source # 

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 # 
Show SourceRepo Source # 
Generic SourceRepo Source # 

Associated Types

type Rep SourceRepo :: * -> * #

Binary SourceRepo Source # 
type Rep SourceRepo Source # 

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

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

Associated Types

type Rep RepoKind :: * -> * #

Methods

from :: RepoKind -> Rep RepoKind x #

to :: Rep RepoKind x -> RepoKind #

Binary RepoKind Source # 

Methods

put :: RepoKind -> Put #

get :: Get RepoKind #

putList :: [RepoKind] -> Put #

Text RepoKind Source # 
type Rep RepoKind Source # 
type Rep RepoKind = D1 (MetaData "RepoKind" "Distribution.PackageDescription" "Cabal-1.24.2.0-DZNolZ9MBQLKV7GSAwAGX6" 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 # 
Data RepoType Source # 

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 # 
Read RepoType Source # 
Show RepoType Source # 
Generic RepoType Source # 

Associated Types

type Rep RepoType :: * -> * #

Methods

from :: RepoType -> Rep RepoType x #

to :: Rep RepoType x -> RepoType #

Binary RepoType Source # 

Methods

put :: RepoType -> Put #

get :: Get RepoType #

putList :: [RepoType] -> Put #

Text RepoType Source # 
type Rep RepoType Source # 
type Rep RepoType = D1 (MetaData "RepoType" "Distribution.PackageDescription" "Cabal-1.24.2.0-DZNolZ9MBQLKV7GSAwAGX6" 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 # 
Data SetupBuildInfo Source # 

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 # 
Show SetupBuildInfo Source # 
Generic SetupBuildInfo Source # 

Associated Types

type Rep SetupBuildInfo :: * -> * #

Semigroup SetupBuildInfo Source # 
Monoid SetupBuildInfo Source # 
Binary SetupBuildInfo Source # 
type Rep SetupBuildInfo Source # 
type Rep SetupBuildInfo = D1 (MetaData "SetupBuildInfo" "Distribution.PackageDescription" "Cabal-1.24.2.0-DZNolZ9MBQLKV7GSAwAGX6" 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))))