Cabal-2.2.0.1: A framework for packaging Haskell software

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

Distribution.Types.PackageDescription

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

Documentation

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

Defined in Distribution.Types.PackageDescription

Data PackageDescription Source # 
Instance details

Defined in Distribution.Types.PackageDescription

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

Defined in Distribution.Types.PackageDescription

Show PackageDescription Source # 
Instance details

Defined in Distribution.Types.PackageDescription

Generic PackageDescription Source # 
Instance details

Defined in Distribution.Types.PackageDescription

Associated Types

type Rep PackageDescription :: * -> * #

Binary PackageDescription Source # 
Instance details

Defined in Distribution.Types.PackageDescription

NFData PackageDescription Source # 
Instance details

Defined in Distribution.Types.PackageDescription

Methods

rnf :: PackageDescription -> () #

Package PackageDescription Source # 
Instance details

Defined in Distribution.Types.PackageDescription

type Rep PackageDescription Source # 
Instance details

Defined in Distribution.Types.PackageDescription

type Rep PackageDescription = D1 (MetaData "PackageDescription" "Distribution.Types.PackageDescription" "Cabal-2.2.0.1-inplace" False) (C1 (MetaCons "PackageDescription" PrefixI True) ((((S1 (MetaSel (Just "specVersionRaw") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Either Version VersionRange)) :*: (S1 (MetaSel (Just "package") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PackageIdentifier) :*: S1 (MetaSel (Just "licenseRaw") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Either License License)))) :*: ((S1 (MetaSel (Just "licenseFiles") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [FilePath]) :*: S1 (MetaSel (Just "copyright") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)) :*: (S1 (MetaSel (Just "maintainer") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String) :*: S1 (MetaSel (Just "author") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)))) :*: (((S1 (MetaSel (Just "stability") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String) :*: S1 (MetaSel (Just "testedWith") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [(CompilerFlavor, VersionRange)])) :*: (S1 (MetaSel (Just "homepage") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String) :*: S1 (MetaSel (Just "pkgUrl") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String))) :*: ((S1 (MetaSel (Just "bugReports") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String) :*: S1 (MetaSel (Just "sourceRepos") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [SourceRepo])) :*: (S1 (MetaSel (Just "synopsis") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String) :*: S1 (MetaSel (Just "description") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String))))) :*: ((((S1 (MetaSel (Just "category") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String) :*: S1 (MetaSel (Just "customFieldsPD") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [(String, String)])) :*: (S1 (MetaSel (Just "buildDepends") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Dependency]) :*: S1 (MetaSel (Just "buildTypeRaw") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe BuildType)))) :*: ((S1 (MetaSel (Just "setupBuildInfo") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe SetupBuildInfo)) :*: S1 (MetaSel (Just "library") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Library))) :*: (S1 (MetaSel (Just "subLibraries") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Library]) :*: S1 (MetaSel (Just "executables") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Executable])))) :*: (((S1 (MetaSel (Just "foreignLibs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [ForeignLib]) :*: S1 (MetaSel (Just "testSuites") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [TestSuite])) :*: (S1 (MetaSel (Just "benchmarks") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Benchmark]) :*: S1 (MetaSel (Just "dataFiles") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [FilePath]))) :*: ((S1 (MetaSel (Just "dataDir") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 FilePath) :*: S1 (MetaSel (Just "extraSrcFiles") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [FilePath])) :*: (S1 (MetaSel (Just "extraTmpFiles") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [FilePath]) :*: S1 (MetaSel (Just "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.

license :: PackageDescription -> License Source #

The SPDX LicenseExpression of the package.

Since: 2.2.0.0

descCabalVersion :: PackageDescription -> VersionRange Source #

Deprecated: Use specVersion instead. This symbol will be removed in Cabal-3.0 (est. Oct 2018).

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.

buildType :: PackageDescription -> BuildType Source #

The effective build-type after applying defaulting rules.

The original build-type value parsed is stored in the buildTypeRaw field. However, the build-type field is optional and can therefore be empty in which case we need to compute the effective build-type. This function implements the following defaulting rules:

  • For cabal-version:2.0 and below, default to the Custom build-type unconditionally.
  • Otherwise, if a custom-setup stanza is defined, default to the Custom build-type; else default to Simple build-type.

Since: 2.2

hasPublicLib :: PackageDescription -> Bool Source #

Does this package have a buildable PUBLIC library?

hasLibs :: PackageDescription -> Bool Source #

Does this package have any libraries?

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.

hasExes :: PackageDescription -> Bool Source #

does this package have any executables?

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.

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.

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.

hasForeignLibs :: PackageDescription -> Bool Source #

Does this package have any foreign libraries?

withForeignLib :: PackageDescription -> (ForeignLib -> IO ()) -> IO () Source #

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

allBuildInfo :: PackageDescription -> [BuildInfo] Source #

All BuildInfo in the PackageDescription: libraries, executables, test-suites and benchmarks.

Useful for implementing package checks.

enabledBuildInfos :: PackageDescription -> ComponentRequestedSpec -> [BuildInfo] Source #

Return all of the BuildInfos of enabled components, i.e., all of the ones that would be built if you run ./Setup build.

pkgComponents :: PackageDescription -> [Component] Source #

All the components in the package.

pkgBuildableComponents :: PackageDescription -> [Component] Source #

A list of all components in the package that are buildable, i.e., were not marked with buildable: False. This does NOT indicate if we are actually going to build the component, see enabledComponents instead.

Since: 2.0.0.2

enabledComponents :: PackageDescription -> ComponentRequestedSpec -> [Component] Source #

A list of all components in the package that are enabled.

Since: 2.0.0.2