{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE RankNTypes #-}

-----------------------------------------------------------------------------
-- |
-- Module      :  Distribution.Types.PackageDescription
-- Copyright   :  Isaac Jones 2003-2005
-- License     :  BSD3
--
-- Maintainer  :  cabal-devel@haskell.org
-- Portability :  portable
--
-- 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.

module Distribution.Types.PackageDescription (
    PackageDescription(..),
    license,
    license',
    buildType,
    emptyPackageDescription,
    hasPublicLib,
    hasLibs,
    allLibraries,
    withLib,
    hasExes,
    withExe,
    hasTests,
    withTest,
    hasBenchmarks,
    withBenchmark,
    hasForeignLibs,
    withForeignLib,
    allBuildInfo,
    enabledBuildInfos,
    allBuildDepends,
    enabledBuildDepends,
    updatePackageDescription,
    pkgComponents,
    pkgBuildableComponents,
    enabledComponents,
    lookupComponent,
    getComponent,
  ) where

import Prelude ()
import Distribution.Compat.Prelude

import Control.Monad ((<=<))

-- lens
import qualified Distribution.Types.BuildInfo.Lens  as L
import Distribution.Types.Library
import Distribution.Types.TestSuite
import Distribution.Types.Executable
import Distribution.Types.Benchmark
import Distribution.Types.ForeignLib

import Distribution.Types.Component
import Distribution.Types.ComponentRequestedSpec
import Distribution.Types.Dependency
import Distribution.Types.PackageId
import Distribution.Types.ComponentName
import Distribution.Types.PackageName
import Distribution.Types.UnqualComponentName
import Distribution.Types.SetupBuildInfo
import Distribution.Types.BuildInfo
import Distribution.Types.BuildType
import Distribution.Types.SourceRepo
import Distribution.Types.HookedBuildInfo

import Distribution.CabalSpecVersion
import Distribution.Compiler
import Distribution.License
import Distribution.Package
import Distribution.Version
import Distribution.Utils.Path
import Distribution.Utils.ShortText

import qualified Distribution.SPDX as SPDX

-- -----------------------------------------------------------------------------
-- The PackageDescription type

-- | 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.
--
data PackageDescription
    =  PackageDescription {
        -- the following are required by all packages:

        -- | The version of the Cabal spec that this package description uses.
        PackageDescription -> CabalSpecVersion
specVersion    :: CabalSpecVersion,
        PackageDescription -> PackageIdentifier
package        :: PackageIdentifier,
        PackageDescription -> Either License License
licenseRaw     :: Either SPDX.License License,
        PackageDescription -> [SymbolicPath PackageDir LicenseFile]
licenseFiles   :: [SymbolicPath PackageDir LicenseFile],
        PackageDescription -> ShortText
copyright      :: !ShortText,
        PackageDescription -> ShortText
maintainer     :: !ShortText,
        PackageDescription -> ShortText
author         :: !ShortText,
        PackageDescription -> ShortText
stability      :: !ShortText,
        PackageDescription -> [(CompilerFlavor, VersionRange)]
testedWith     :: [(CompilerFlavor,VersionRange)],
        PackageDescription -> ShortText
homepage       :: !ShortText,
        PackageDescription -> ShortText
pkgUrl         :: !ShortText,
        PackageDescription -> ShortText
bugReports     :: !ShortText,
        PackageDescription -> [SourceRepo]
sourceRepos    :: [SourceRepo],
        PackageDescription -> ShortText
synopsis       :: !ShortText, -- ^A one-line summary of this package
        PackageDescription -> ShortText
description    :: !ShortText, -- ^A more verbose description of this package
        PackageDescription -> ShortText
category       :: !ShortText,
        PackageDescription -> [(String, String)]
customFieldsPD :: [(String,String)], -- ^Custom fields starting
                                             -- with x-, stored in a
                                             -- simple assoc-list.

        -- | The original @build-type@ value as parsed from the
        -- @.cabal@ file without defaulting. See also 'buildType'.
        --
        -- @since 2.2
        PackageDescription -> Maybe BuildType
buildTypeRaw   :: Maybe BuildType,
        PackageDescription -> Maybe SetupBuildInfo
setupBuildInfo :: Maybe SetupBuildInfo,
        -- components
        PackageDescription -> Maybe Library
library        :: Maybe Library,
        PackageDescription -> [Library]
subLibraries   :: [Library],
        PackageDescription -> [Executable]
executables    :: [Executable],
        PackageDescription -> [ForeignLib]
foreignLibs    :: [ForeignLib],
        PackageDescription -> [TestSuite]
testSuites     :: [TestSuite],
        PackageDescription -> [Benchmark]
benchmarks     :: [Benchmark],
        -- files
        PackageDescription -> [String]
dataFiles      :: [FilePath],
        PackageDescription -> String
dataDir        :: FilePath,
        PackageDescription -> [String]
extraSrcFiles  :: [FilePath],
        PackageDescription -> [String]
extraTmpFiles  :: [FilePath],
        PackageDescription -> [String]
extraDocFiles  :: [FilePath]
    }
    deriving (forall x. Rep PackageDescription x -> PackageDescription
forall x. PackageDescription -> Rep PackageDescription x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep PackageDescription x -> PackageDescription
$cfrom :: forall x. PackageDescription -> Rep PackageDescription x
Generic, Int -> PackageDescription -> ShowS
[PackageDescription] -> ShowS
PackageDescription -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PackageDescription] -> ShowS
$cshowList :: [PackageDescription] -> ShowS
show :: PackageDescription -> String
$cshow :: PackageDescription -> String
showsPrec :: Int -> PackageDescription -> ShowS
$cshowsPrec :: Int -> PackageDescription -> ShowS
Show, ReadPrec [PackageDescription]
ReadPrec PackageDescription
Int -> ReadS PackageDescription
ReadS [PackageDescription]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [PackageDescription]
$creadListPrec :: ReadPrec [PackageDescription]
readPrec :: ReadPrec PackageDescription
$creadPrec :: ReadPrec PackageDescription
readList :: ReadS [PackageDescription]
$creadList :: ReadS [PackageDescription]
readsPrec :: Int -> ReadS PackageDescription
$creadsPrec :: Int -> ReadS PackageDescription
Read, PackageDescription -> PackageDescription -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PackageDescription -> PackageDescription -> Bool
$c/= :: PackageDescription -> PackageDescription -> Bool
== :: PackageDescription -> PackageDescription -> Bool
$c== :: PackageDescription -> PackageDescription -> Bool
Eq, Eq PackageDescription
PackageDescription -> PackageDescription -> Bool
PackageDescription -> PackageDescription -> Ordering
PackageDescription -> PackageDescription -> PackageDescription
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: PackageDescription -> PackageDescription -> PackageDescription
$cmin :: PackageDescription -> PackageDescription -> PackageDescription
max :: PackageDescription -> PackageDescription -> PackageDescription
$cmax :: PackageDescription -> PackageDescription -> PackageDescription
>= :: PackageDescription -> PackageDescription -> Bool
$c>= :: PackageDescription -> PackageDescription -> Bool
> :: PackageDescription -> PackageDescription -> Bool
$c> :: PackageDescription -> PackageDescription -> Bool
<= :: PackageDescription -> PackageDescription -> Bool
$c<= :: PackageDescription -> PackageDescription -> Bool
< :: PackageDescription -> PackageDescription -> Bool
$c< :: PackageDescription -> PackageDescription -> Bool
compare :: PackageDescription -> PackageDescription -> Ordering
$ccompare :: PackageDescription -> PackageDescription -> Ordering
Ord, Typeable, Typeable PackageDescription
PackageDescription -> DataType
PackageDescription -> Constr
(forall b. Data b => b -> b)
-> PackageDescription -> PackageDescription
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int -> (forall d. Data d => d -> u) -> PackageDescription -> u
forall u. (forall d. Data d => d -> u) -> PackageDescription -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> PackageDescription -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PackageDescription -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> PackageDescription -> m PackageDescription
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> PackageDescription -> m PackageDescription
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c PackageDescription
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> PackageDescription
-> c PackageDescription
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c PackageDescription)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c PackageDescription)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> PackageDescription -> m PackageDescription
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> PackageDescription -> m PackageDescription
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> PackageDescription -> m PackageDescription
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> PackageDescription -> m PackageDescription
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> PackageDescription -> m PackageDescription
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> PackageDescription -> m PackageDescription
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> PackageDescription -> u
$cgmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> PackageDescription -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> PackageDescription -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> PackageDescription -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PackageDescription -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> PackageDescription -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> PackageDescription -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> PackageDescription -> r
gmapT :: (forall b. Data b => b -> b)
-> PackageDescription -> PackageDescription
$cgmapT :: (forall b. Data b => b -> b)
-> PackageDescription -> PackageDescription
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c PackageDescription)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c PackageDescription)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c PackageDescription)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c PackageDescription)
dataTypeOf :: PackageDescription -> DataType
$cdataTypeOf :: PackageDescription -> DataType
toConstr :: PackageDescription -> Constr
$ctoConstr :: PackageDescription -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c PackageDescription
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c PackageDescription
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> PackageDescription
-> c PackageDescription
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> PackageDescription
-> c PackageDescription
Data)

instance Binary PackageDescription
instance Structured PackageDescription

instance NFData PackageDescription where rnf :: PackageDescription -> ()
rnf = forall a. (Generic a, GNFData (Rep a)) => a -> ()
genericRnf

instance Package PackageDescription where
  packageId :: PackageDescription -> PackageIdentifier
packageId = PackageDescription -> PackageIdentifier
package

-- | The SPDX 'LicenseExpression' of the package.
--
-- @since 2.2.0.0
license :: PackageDescription -> SPDX.License
license :: PackageDescription -> License
license = Either License License -> License
license' forall b c a. (b -> c) -> (a -> b) -> a -> c
. PackageDescription -> Either License License
licenseRaw

-- | See 'license'.
--
-- @since 2.2.0.0
license' :: Either SPDX.License License -> SPDX.License
license' :: Either License License -> License
license' = forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either forall a. a -> a
id License -> License
licenseToSPDX

-- | 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
buildType :: PackageDescription -> BuildType
buildType :: PackageDescription -> BuildType
buildType PackageDescription
pkg
  | PackageDescription -> CabalSpecVersion
specVersion PackageDescription
pkg forall a. Ord a => a -> a -> Bool
>= CabalSpecVersion
CabalSpecV2_2
    = forall a. a -> Maybe a -> a
fromMaybe BuildType
newDefault (PackageDescription -> Maybe BuildType
buildTypeRaw PackageDescription
pkg)
  | Bool
otherwise -- cabal-version < 2.1
    = forall a. a -> Maybe a -> a
fromMaybe BuildType
Custom (PackageDescription -> Maybe BuildType
buildTypeRaw PackageDescription
pkg)
  where
    newDefault :: BuildType
newDefault | forall a. Maybe a -> Bool
isNothing (PackageDescription -> Maybe SetupBuildInfo
setupBuildInfo PackageDescription
pkg) = BuildType
Simple
               | Bool
otherwise                      = BuildType
Custom

emptyPackageDescription :: PackageDescription
emptyPackageDescription :: PackageDescription
emptyPackageDescription
    =  PackageDescription {
                      package :: PackageIdentifier
package      = PackageName -> Version -> PackageIdentifier
PackageIdentifier (String -> PackageName
mkPackageName String
"")
                                                       Version
nullVersion,
                      licenseRaw :: Either License License
licenseRaw   = forall a b. b -> Either a b
Right License
UnspecifiedLicense, -- TODO:
                      licenseFiles :: [SymbolicPath PackageDir LicenseFile]
licenseFiles = [],
                      specVersion :: CabalSpecVersion
specVersion  = CabalSpecVersion
CabalSpecV1_0,
                      buildTypeRaw :: Maybe BuildType
buildTypeRaw = forall a. Maybe a
Nothing,
                      copyright :: ShortText
copyright    = forall a. Monoid a => a
mempty,
                      maintainer :: ShortText
maintainer   = forall a. Monoid a => a
mempty,
                      author :: ShortText
author       = forall a. Monoid a => a
mempty,
                      stability :: ShortText
stability    = forall a. Monoid a => a
mempty,
                      testedWith :: [(CompilerFlavor, VersionRange)]
testedWith   = [],
                      homepage :: ShortText
homepage     = forall a. Monoid a => a
mempty,
                      pkgUrl :: ShortText
pkgUrl       = forall a. Monoid a => a
mempty,
                      bugReports :: ShortText
bugReports   = forall a. Monoid a => a
mempty,
                      sourceRepos :: [SourceRepo]
sourceRepos  = [],
                      synopsis :: ShortText
synopsis     = forall a. Monoid a => a
mempty,
                      description :: ShortText
description  = forall a. Monoid a => a
mempty,
                      category :: ShortText
category     = forall a. Monoid a => a
mempty,
                      customFieldsPD :: [(String, String)]
customFieldsPD = [],
                      setupBuildInfo :: Maybe SetupBuildInfo
setupBuildInfo = forall a. Maybe a
Nothing,
                      library :: Maybe Library
library      = forall a. Maybe a
Nothing,
                      subLibraries :: [Library]
subLibraries = [],
                      foreignLibs :: [ForeignLib]
foreignLibs  = [],
                      executables :: [Executable]
executables  = [],
                      testSuites :: [TestSuite]
testSuites   = [],
                      benchmarks :: [Benchmark]
benchmarks   = [],
                      dataFiles :: [String]
dataFiles    = [],
                      dataDir :: String
dataDir      = String
".",
                      extraSrcFiles :: [String]
extraSrcFiles = [],
                      extraTmpFiles :: [String]
extraTmpFiles = [],
                      extraDocFiles :: [String]
extraDocFiles = []
                     }

-- ---------------------------------------------------------------------------
-- The Library type

-- | Does this package have a buildable PUBLIC library?
hasPublicLib :: PackageDescription -> Bool
hasPublicLib :: PackageDescription -> Bool
hasPublicLib PackageDescription
p =
    case PackageDescription -> Maybe Library
library PackageDescription
p of
        Just Library
lib -> BuildInfo -> Bool
buildable (Library -> BuildInfo
libBuildInfo Library
lib)
        Maybe Library
Nothing  -> Bool
False

-- | Does this package have any libraries?
hasLibs :: PackageDescription -> Bool
hasLibs :: PackageDescription -> Bool
hasLibs PackageDescription
p = forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (BuildInfo -> Bool
buildable forall b c a. (b -> c) -> (a -> b) -> a -> c
. Library -> BuildInfo
libBuildInfo) (PackageDescription -> [Library]
allLibraries PackageDescription
p)

allLibraries :: PackageDescription -> [Library]
allLibraries :: PackageDescription -> [Library]
allLibraries PackageDescription
p = forall a. Maybe a -> [a]
maybeToList (PackageDescription -> Maybe Library
library PackageDescription
p) forall a. [a] -> [a] -> [a]
++ PackageDescription -> [Library]
subLibraries PackageDescription
p

-- | 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#buildable_vs_enabled_components"
-- for more information.
withLib :: PackageDescription -> (Library -> IO ()) -> IO ()
withLib :: PackageDescription -> (Library -> IO ()) -> IO ()
withLib PackageDescription
pkg_descr Library -> IO ()
f =
   forall (t :: * -> *) (m :: * -> *) a.
(Foldable t, Monad m) =>
t (m a) -> m ()
sequence_ [Library -> IO ()
f Library
lib | Library
lib <- PackageDescription -> [Library]
allLibraries PackageDescription
pkg_descr, BuildInfo -> Bool
buildable (Library -> BuildInfo
libBuildInfo Library
lib)]

-- ---------------------------------------------------------------------------
-- The Executable type

-- |does this package have any executables?
hasExes :: PackageDescription -> Bool
hasExes :: PackageDescription -> Bool
hasExes PackageDescription
p = forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (BuildInfo -> Bool
buildable forall b c a. (b -> c) -> (a -> b) -> a -> c
. Executable -> BuildInfo
buildInfo) (PackageDescription -> [Executable]
executables PackageDescription
p)

-- | 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#buildable_vs_enabled_components"
-- for more information.
withExe :: PackageDescription -> (Executable -> IO ()) -> IO ()
withExe :: PackageDescription -> (Executable -> IO ()) -> IO ()
withExe PackageDescription
pkg_descr Executable -> IO ()
f =
  forall (t :: * -> *) (m :: * -> *) a.
(Foldable t, Monad m) =>
t (m a) -> m ()
sequence_ [Executable -> IO ()
f Executable
exe | Executable
exe <- PackageDescription -> [Executable]
executables PackageDescription
pkg_descr, BuildInfo -> Bool
buildable (Executable -> BuildInfo
buildInfo Executable
exe)]

-- ---------------------------------------------------------------------------
-- The TestSuite type

-- | Does this package have any test suites?
hasTests :: PackageDescription -> Bool
hasTests :: PackageDescription -> Bool
hasTests = forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (BuildInfo -> Bool
buildable forall b c a. (b -> c) -> (a -> b) -> a -> c
. TestSuite -> BuildInfo
testBuildInfo) forall b c a. (b -> c) -> (a -> b) -> a -> c
. PackageDescription -> [TestSuite]
testSuites

-- | 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#buildable_vs_enabled_components"
-- for more information.

withTest :: PackageDescription -> (TestSuite -> IO ()) -> IO ()
withTest :: PackageDescription -> (TestSuite -> IO ()) -> IO ()
withTest PackageDescription
pkg_descr TestSuite -> IO ()
f =
    forall (t :: * -> *) (m :: * -> *) a.
(Foldable t, Monad m) =>
t (m a) -> m ()
sequence_ [ TestSuite -> IO ()
f TestSuite
test | TestSuite
test <- PackageDescription -> [TestSuite]
testSuites PackageDescription
pkg_descr, BuildInfo -> Bool
buildable (TestSuite -> BuildInfo
testBuildInfo TestSuite
test) ]

-- ---------------------------------------------------------------------------
-- The Benchmark type

-- | Does this package have any benchmarks?
hasBenchmarks :: PackageDescription -> Bool
hasBenchmarks :: PackageDescription -> Bool
hasBenchmarks = forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (BuildInfo -> Bool
buildable forall b c a. (b -> c) -> (a -> b) -> a -> c
. Benchmark -> BuildInfo
benchmarkBuildInfo) forall b c a. (b -> c) -> (a -> b) -> a -> c
. PackageDescription -> [Benchmark]
benchmarks

-- | 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#buildable_vs_enabled_components"
-- for more information.

withBenchmark :: PackageDescription -> (Benchmark -> IO ()) -> IO ()
withBenchmark :: PackageDescription -> (Benchmark -> IO ()) -> IO ()
withBenchmark PackageDescription
pkg_descr Benchmark -> IO ()
f =
    forall (t :: * -> *) (m :: * -> *) a.
(Foldable t, Monad m) =>
t (m a) -> m ()
sequence_ [Benchmark -> IO ()
f Benchmark
bench | Benchmark
bench <- PackageDescription -> [Benchmark]
benchmarks PackageDescription
pkg_descr, BuildInfo -> Bool
buildable (Benchmark -> BuildInfo
benchmarkBuildInfo Benchmark
bench)]

-- ---------------------------------------------------------------------------
-- The ForeignLib type

-- | Does this package have any foreign libraries?
hasForeignLibs :: PackageDescription -> Bool
hasForeignLibs :: PackageDescription -> Bool
hasForeignLibs PackageDescription
p = forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any (BuildInfo -> Bool
buildable forall b c a. (b -> c) -> (a -> b) -> a -> c
. ForeignLib -> BuildInfo
foreignLibBuildInfo) (PackageDescription -> [ForeignLib]
foreignLibs PackageDescription
p)

-- | Perform the action on each buildable 'ForeignLib' in the package
-- description.
withForeignLib :: PackageDescription -> (ForeignLib -> IO ()) -> IO ()
withForeignLib :: PackageDescription -> (ForeignLib -> IO ()) -> IO ()
withForeignLib PackageDescription
pkg_descr ForeignLib -> IO ()
f =
  forall (t :: * -> *) (m :: * -> *) a.
(Foldable t, Monad m) =>
t (m a) -> m ()
sequence_ [ ForeignLib -> IO ()
f ForeignLib
flib
            | ForeignLib
flib <- PackageDescription -> [ForeignLib]
foreignLibs PackageDescription
pkg_descr
            , BuildInfo -> Bool
buildable (ForeignLib -> BuildInfo
foreignLibBuildInfo ForeignLib
flib)
            ]

-- ---------------------------------------------------------------------------
-- The BuildInfo type

-- | All 'BuildInfo' in the 'PackageDescription':
-- libraries, executables, test-suites and benchmarks.
--
-- Useful for implementing package checks.
allBuildInfo :: PackageDescription -> [BuildInfo]
allBuildInfo :: PackageDescription -> [BuildInfo]
allBuildInfo PackageDescription
pkg_descr = [ BuildInfo
bi | Library
lib <- PackageDescription -> [Library]
allLibraries PackageDescription
pkg_descr
                               , let bi :: BuildInfo
bi = Library -> BuildInfo
libBuildInfo Library
lib ]
                       forall a. [a] -> [a] -> [a]
++ [ BuildInfo
bi | ForeignLib
flib <- PackageDescription -> [ForeignLib]
foreignLibs PackageDescription
pkg_descr
                               , let bi :: BuildInfo
bi = ForeignLib -> BuildInfo
foreignLibBuildInfo ForeignLib
flib ]
                       forall a. [a] -> [a] -> [a]
++ [ BuildInfo
bi | Executable
exe <- PackageDescription -> [Executable]
executables PackageDescription
pkg_descr
                               , let bi :: BuildInfo
bi = Executable -> BuildInfo
buildInfo Executable
exe ]
                       forall a. [a] -> [a] -> [a]
++ [ BuildInfo
bi | TestSuite
tst <- PackageDescription -> [TestSuite]
testSuites PackageDescription
pkg_descr
                               , let bi :: BuildInfo
bi = TestSuite -> BuildInfo
testBuildInfo TestSuite
tst ]
                       forall a. [a] -> [a] -> [a]
++ [ BuildInfo
bi | Benchmark
tst <- PackageDescription -> [Benchmark]
benchmarks PackageDescription
pkg_descr
                               , let bi :: BuildInfo
bi = Benchmark -> BuildInfo
benchmarkBuildInfo Benchmark
tst ]

-- | Return all of the 'BuildInfo's of enabled components, i.e., all of
-- the ones that would be built if you run @./Setup build@.
enabledBuildInfos :: PackageDescription -> ComponentRequestedSpec -> [BuildInfo]
enabledBuildInfos :: PackageDescription -> ComponentRequestedSpec -> [BuildInfo]
enabledBuildInfos PackageDescription
pkg ComponentRequestedSpec
enabled =
    [ Component -> BuildInfo
componentBuildInfo Component
comp
    | Component
comp <- PackageDescription -> ComponentRequestedSpec -> [Component]
enabledComponents PackageDescription
pkg ComponentRequestedSpec
enabled ]


-- ------------------------------------------------------------
-- * Utils
-- ------------------------------------------------------------

-- | Get the combined build-depends entries of all components.
allBuildDepends :: PackageDescription -> [Dependency]
allBuildDepends :: PackageDescription -> [Dependency]
allBuildDepends = BuildInfo -> [Dependency]
targetBuildDepends forall (m :: * -> *) b c a.
Monad m =>
(b -> m c) -> (a -> m b) -> a -> m c
<=< PackageDescription -> [BuildInfo]
allBuildInfo

-- | Get the combined build-depends entries of all enabled components, per the
-- given request spec.
enabledBuildDepends :: PackageDescription -> ComponentRequestedSpec -> [Dependency]
enabledBuildDepends :: PackageDescription -> ComponentRequestedSpec -> [Dependency]
enabledBuildDepends PackageDescription
spec ComponentRequestedSpec
pd = BuildInfo -> [Dependency]
targetBuildDepends forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< PackageDescription -> ComponentRequestedSpec -> [BuildInfo]
enabledBuildInfos PackageDescription
spec ComponentRequestedSpec
pd


updatePackageDescription :: HookedBuildInfo -> PackageDescription -> PackageDescription
updatePackageDescription :: HookedBuildInfo -> PackageDescription -> PackageDescription
updatePackageDescription (Maybe BuildInfo
mb_lib_bi, [(UnqualComponentName, BuildInfo)]
exe_bi) PackageDescription
p
    = PackageDescription
p{ executables :: [Executable]
executables = [(UnqualComponentName, BuildInfo)] -> [Executable] -> [Executable]
updateExecutables [(UnqualComponentName, BuildInfo)]
exe_bi    (PackageDescription -> [Executable]
executables PackageDescription
p)
       , library :: Maybe Library
library     = Maybe BuildInfo -> Maybe Library -> Maybe Library
updateLibrary     Maybe BuildInfo
mb_lib_bi (PackageDescription -> Maybe Library
library     PackageDescription
p) }
    where
      updateLibrary :: Maybe BuildInfo -> Maybe Library -> Maybe Library
      updateLibrary :: Maybe BuildInfo -> Maybe Library -> Maybe Library
updateLibrary (Just BuildInfo
bi) (Just Library
lib) = forall a. a -> Maybe a
Just (Library
lib{libBuildInfo :: BuildInfo
libBuildInfo = BuildInfo
bi forall a. Monoid a => a -> a -> a
`mappend` Library -> BuildInfo
libBuildInfo Library
lib})
      updateLibrary Maybe BuildInfo
Nothing   Maybe Library
mb_lib     = Maybe Library
mb_lib
      updateLibrary (Just BuildInfo
_)  Maybe Library
Nothing    = forall a. Maybe a
Nothing

      updateExecutables :: [(UnqualComponentName, BuildInfo)] -- ^[(exeName, new buildinfo)]
        -> [Executable]                                       -- ^list of executables to update
        -> [Executable]                                       -- ^list with exeNames updated
      updateExecutables :: [(UnqualComponentName, BuildInfo)] -> [Executable] -> [Executable]
updateExecutables [(UnqualComponentName, BuildInfo)]
exe_bi' [Executable]
executables' = forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr (UnqualComponentName, BuildInfo) -> [Executable] -> [Executable]
updateExecutable [Executable]
executables' [(UnqualComponentName, BuildInfo)]
exe_bi'

      updateExecutable :: (UnqualComponentName, BuildInfo) -- ^(exeName, new buildinfo)
                       -> [Executable]                     -- ^list of executables to update
                       -> [Executable]                     -- ^list with exeName updated
      updateExecutable :: (UnqualComponentName, BuildInfo) -> [Executable] -> [Executable]
updateExecutable (UnqualComponentName, BuildInfo)
_                 []         = []
      updateExecutable exe_bi' :: (UnqualComponentName, BuildInfo)
exe_bi'@(UnqualComponentName
name,BuildInfo
bi) (Executable
exe:[Executable]
exes)
        | Executable -> UnqualComponentName
exeName Executable
exe forall a. Eq a => a -> a -> Bool
== UnqualComponentName
name = Executable
exe{buildInfo :: BuildInfo
buildInfo = BuildInfo
bi forall a. Monoid a => a -> a -> a
`mappend` Executable -> BuildInfo
buildInfo Executable
exe} forall a. a -> [a] -> [a]
: [Executable]
exes
        | Bool
otherwise           = Executable
exe forall a. a -> [a] -> [a]
: (UnqualComponentName, BuildInfo) -> [Executable] -> [Executable]
updateExecutable (UnqualComponentName, BuildInfo)
exe_bi' [Executable]
exes

-- -----------------------------------------------------------------------------
-- Source-representation of buildable components

-- | All the components in the package.
--
pkgComponents :: PackageDescription -> [Component]
pkgComponents :: PackageDescription -> [Component]
pkgComponents PackageDescription
pkg =
    [ Library -> Component
CLib  Library
lib | Library
lib <- PackageDescription -> [Library]
allLibraries PackageDescription
pkg ]
 forall a. [a] -> [a] -> [a]
++ [ ForeignLib -> Component
CFLib ForeignLib
flib | ForeignLib
flib <- PackageDescription -> [ForeignLib]
foreignLibs PackageDescription
pkg ]
 forall a. [a] -> [a] -> [a]
++ [ Executable -> Component
CExe  Executable
exe | Executable
exe <- PackageDescription -> [Executable]
executables PackageDescription
pkg ]
 forall a. [a] -> [a] -> [a]
++ [ TestSuite -> Component
CTest TestSuite
tst | TestSuite
tst <- PackageDescription -> [TestSuite]
testSuites  PackageDescription
pkg ]
 forall a. [a] -> [a] -> [a]
++ [ Benchmark -> Component
CBench Benchmark
bm | Benchmark
bm  <- PackageDescription -> [Benchmark]
benchmarks  PackageDescription
pkg ]

-- | 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
--
pkgBuildableComponents :: PackageDescription -> [Component]
pkgBuildableComponents :: PackageDescription -> [Component]
pkgBuildableComponents = forall a. (a -> Bool) -> [a] -> [a]
filter Component -> Bool
componentBuildable forall b c a. (b -> c) -> (a -> b) -> a -> c
. PackageDescription -> [Component]
pkgComponents

-- | A list of all components in the package that are enabled.
--
-- @since 2.0.0.2
--
enabledComponents :: PackageDescription -> ComponentRequestedSpec -> [Component]
enabledComponents :: PackageDescription -> ComponentRequestedSpec -> [Component]
enabledComponents PackageDescription
pkg ComponentRequestedSpec
enabled = forall a. (a -> Bool) -> [a] -> [a]
filter (ComponentRequestedSpec -> Component -> Bool
componentEnabled ComponentRequestedSpec
enabled) forall a b. (a -> b) -> a -> b
$ PackageDescription -> [Component]
pkgBuildableComponents PackageDescription
pkg

lookupComponent :: PackageDescription -> ComponentName -> Maybe Component
lookupComponent :: PackageDescription -> ComponentName -> Maybe Component
lookupComponent PackageDescription
pkg (CLibName LibraryName
name) =
    forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Library -> Component
CLib forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
find ((LibraryName
name forall a. Eq a => a -> a -> Bool
==) forall b c a. (b -> c) -> (a -> b) -> a -> c
. Library -> LibraryName
libName) (PackageDescription -> [Library]
allLibraries PackageDescription
pkg)
lookupComponent PackageDescription
pkg (CFLibName UnqualComponentName
name) =
    forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ForeignLib -> Component
CFLib forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
find ((UnqualComponentName
name forall a. Eq a => a -> a -> Bool
==) forall b c a. (b -> c) -> (a -> b) -> a -> c
. ForeignLib -> UnqualComponentName
foreignLibName) (PackageDescription -> [ForeignLib]
foreignLibs PackageDescription
pkg)
lookupComponent PackageDescription
pkg (CExeName UnqualComponentName
name) =
    forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Executable -> Component
CExe forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
find ((UnqualComponentName
name forall a. Eq a => a -> a -> Bool
==) forall b c a. (b -> c) -> (a -> b) -> a -> c
. Executable -> UnqualComponentName
exeName) (PackageDescription -> [Executable]
executables PackageDescription
pkg)
lookupComponent PackageDescription
pkg (CTestName UnqualComponentName
name) =
    forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap TestSuite -> Component
CTest forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
find ((UnqualComponentName
name forall a. Eq a => a -> a -> Bool
==) forall b c a. (b -> c) -> (a -> b) -> a -> c
. TestSuite -> UnqualComponentName
testName) (PackageDescription -> [TestSuite]
testSuites PackageDescription
pkg)
lookupComponent PackageDescription
pkg (CBenchName UnqualComponentName
name) =
    forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Benchmark -> Component
CBench forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Maybe a
find ((UnqualComponentName
name forall a. Eq a => a -> a -> Bool
==) forall b c a. (b -> c) -> (a -> b) -> a -> c
. Benchmark -> UnqualComponentName
benchmarkName) (PackageDescription -> [Benchmark]
benchmarks PackageDescription
pkg)

getComponent :: PackageDescription -> ComponentName -> Component
getComponent :: PackageDescription -> ComponentName -> Component
getComponent PackageDescription
pkg ComponentName
cname =
    case PackageDescription -> ComponentName -> Maybe Component
lookupComponent PackageDescription
pkg ComponentName
cname of
      Just Component
cpnt -> Component
cpnt
      Maybe Component
Nothing   -> forall {a}. a
missingComponent
  where
    missingComponent :: a
missingComponent =
      forall a. HasCallStack => String -> a
error forall a b. (a -> b) -> a -> b
$ String
"internal error: the package description contains no "
           forall a. [a] -> [a] -> [a]
++ String
"component corresponding to " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show ComponentName
cname

-- -----------------------------------------------------------------------------
-- Traversal Instances

instance L.HasBuildInfos PackageDescription where
  traverseBuildInfos :: Traversal' PackageDescription BuildInfo
traverseBuildInfos BuildInfo -> f BuildInfo
f (PackageDescription CabalSpecVersion
a1 PackageIdentifier
a2 Either License License
a3 [SymbolicPath PackageDir LicenseFile]
a4 ShortText
a5 ShortText
a6 ShortText
a7 ShortText
a8 [(CompilerFlavor, VersionRange)]
a9 ShortText
a10 ShortText
a11 ShortText
a12 [SourceRepo]
a13 ShortText
a14 ShortText
a15 ShortText
a16 [(String, String)]
a17 Maybe BuildType
a18 Maybe SetupBuildInfo
a19
                                   Maybe Library
x1 [Library]
x2 [Executable]
x3 [ForeignLib]
x4 [TestSuite]
x5 [Benchmark]
x6
                                   [String]
a20 String
a21 [String]
a22 [String]
a23 [String]
a24) =
    CabalSpecVersion
-> PackageIdentifier
-> Either License License
-> [SymbolicPath PackageDir LicenseFile]
-> ShortText
-> ShortText
-> ShortText
-> ShortText
-> [(CompilerFlavor, VersionRange)]
-> ShortText
-> ShortText
-> ShortText
-> [SourceRepo]
-> ShortText
-> ShortText
-> ShortText
-> [(String, String)]
-> Maybe BuildType
-> Maybe SetupBuildInfo
-> Maybe Library
-> [Library]
-> [Executable]
-> [ForeignLib]
-> [TestSuite]
-> [Benchmark]
-> [String]
-> String
-> [String]
-> [String]
-> [String]
-> PackageDescription
PackageDescription CabalSpecVersion
a1 PackageIdentifier
a2 Either License License
a3 [SymbolicPath PackageDir LicenseFile]
a4 ShortText
a5 ShortText
a6 ShortText
a7 ShortText
a8 [(CompilerFlavor, VersionRange)]
a9 ShortText
a10 ShortText
a11 ShortText
a12 [SourceRepo]
a13 ShortText
a14 ShortText
a15 ShortText
a16 [(String, String)]
a17 Maybe BuildType
a18 Maybe SetupBuildInfo
a19
        forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. HasBuildInfo a => Lens' a BuildInfo
L.buildInfo) BuildInfo -> f BuildInfo
f Maybe Library
x1 -- library
        forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. HasBuildInfo a => Lens' a BuildInfo
L.buildInfo) BuildInfo -> f BuildInfo
f [Library]
x2 -- sub libraries
        forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. HasBuildInfo a => Lens' a BuildInfo
L.buildInfo) BuildInfo -> f BuildInfo
f [Executable]
x3 -- executables
        forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. HasBuildInfo a => Lens' a BuildInfo
L.buildInfo) BuildInfo -> f BuildInfo
f [ForeignLib]
x4 -- foreign libs
        forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. HasBuildInfo a => Lens' a BuildInfo
L.buildInfo) BuildInfo -> f BuildInfo
f [TestSuite]
x5 -- test suites
        forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. HasBuildInfo a => Lens' a BuildInfo
L.buildInfo) BuildInfo -> f BuildInfo
f [Benchmark]
x6 -- benchmarks
        forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (f :: * -> *) a. Applicative f => a -> f a
pure [String]
a20                      -- data files
        forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (f :: * -> *) a. Applicative f => a -> f a
pure String
a21                      -- data dir
        forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (f :: * -> *) a. Applicative f => a -> f a
pure [String]
a22                      -- extra src files
        forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (f :: * -> *) a. Applicative f => a -> f a
pure [String]
a23                      -- extra temp files
        forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (f :: * -> *) a. Applicative f => a -> f a
pure [String]
a24                      -- extra doc files