{-# LANGUAGE Rank2Types #-}
module CabalLenses.Traversals.BuildInfo
( allBuildInfo
, buildInfo
, buildInfoIf
) where
import CabalLenses.Section (Section(..))
import CabalLenses.Traversals.Internal (traverseData, traverseDataIf)
import CabalLenses.CondVars (CondVars)
import CabalLenses.PackageDescription
import Control.Lens
import Distribution.PackageDescription (GenericPackageDescription(GenericPackageDescription), BuildInfo)
import Distribution.Types.UnqualComponentName (unUnqualComponentName)
allBuildInfo :: Traversal' GenericPackageDescription BuildInfo
allBuildInfo :: Traversal' GenericPackageDescription BuildInfo
allBuildInfo BuildInfo -> f BuildInfo
f (GenericPackageDescription PackageDescription
descrp Maybe Version
gpdVers [PackageFlag]
flags Maybe (CondTree ConfVar [Dependency] Library)
lib [(UnqualComponentName, CondTree ConfVar [Dependency] Library)]
subLibs [(UnqualComponentName, CondTree ConfVar [Dependency] ForeignLib)]
foreignLibs [(UnqualComponentName, CondTree ConfVar [Dependency] Executable)]
exes [(UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)]
tests [(UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)]
benchs) =
PackageDescription
-> Maybe Version
-> [PackageFlag]
-> Maybe (CondTree ConfVar [Dependency] Library)
-> [(UnqualComponentName, CondTree ConfVar [Dependency] Library)]
-> [(UnqualComponentName,
CondTree ConfVar [Dependency] ForeignLib)]
-> [(UnqualComponentName,
CondTree ConfVar [Dependency] Executable)]
-> [(UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)]
-> [(UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)]
-> GenericPackageDescription
GenericPackageDescription (PackageDescription
-> Maybe Version
-> [PackageFlag]
-> Maybe (CondTree ConfVar [Dependency] Library)
-> [(UnqualComponentName, CondTree ConfVar [Dependency] Library)]
-> [(UnqualComponentName,
CondTree ConfVar [Dependency] ForeignLib)]
-> [(UnqualComponentName,
CondTree ConfVar [Dependency] Executable)]
-> [(UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)]
-> [(UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)]
-> GenericPackageDescription)
-> f PackageDescription
-> f (Maybe Version
-> [PackageFlag]
-> Maybe (CondTree ConfVar [Dependency] Library)
-> [(UnqualComponentName, CondTree ConfVar [Dependency] Library)]
-> [(UnqualComponentName,
CondTree ConfVar [Dependency] ForeignLib)]
-> [(UnqualComponentName,
CondTree ConfVar [Dependency] Executable)]
-> [(UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)]
-> [(UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)]
-> GenericPackageDescription)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> PackageDescription -> f PackageDescription
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure PackageDescription
descrp
f (Maybe Version
-> [PackageFlag]
-> Maybe (CondTree ConfVar [Dependency] Library)
-> [(UnqualComponentName, CondTree ConfVar [Dependency] Library)]
-> [(UnqualComponentName,
CondTree ConfVar [Dependency] ForeignLib)]
-> [(UnqualComponentName,
CondTree ConfVar [Dependency] Executable)]
-> [(UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)]
-> [(UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)]
-> GenericPackageDescription)
-> f (Maybe Version)
-> f ([PackageFlag]
-> Maybe (CondTree ConfVar [Dependency] Library)
-> [(UnqualComponentName, CondTree ConfVar [Dependency] Library)]
-> [(UnqualComponentName,
CondTree ConfVar [Dependency] ForeignLib)]
-> [(UnqualComponentName,
CondTree ConfVar [Dependency] Executable)]
-> [(UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)]
-> [(UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)]
-> GenericPackageDescription)
forall a b. f (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Maybe Version -> f (Maybe Version)
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe Version
gpdVers
f ([PackageFlag]
-> Maybe (CondTree ConfVar [Dependency] Library)
-> [(UnqualComponentName, CondTree ConfVar [Dependency] Library)]
-> [(UnqualComponentName,
CondTree ConfVar [Dependency] ForeignLib)]
-> [(UnqualComponentName,
CondTree ConfVar [Dependency] Executable)]
-> [(UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)]
-> [(UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)]
-> GenericPackageDescription)
-> f [PackageFlag]
-> f (Maybe (CondTree ConfVar [Dependency] Library)
-> [(UnqualComponentName, CondTree ConfVar [Dependency] Library)]
-> [(UnqualComponentName,
CondTree ConfVar [Dependency] ForeignLib)]
-> [(UnqualComponentName,
CondTree ConfVar [Dependency] Executable)]
-> [(UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)]
-> [(UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)]
-> GenericPackageDescription)
forall a b. f (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> [PackageFlag] -> f [PackageFlag]
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure [PackageFlag]
flags
f (Maybe (CondTree ConfVar [Dependency] Library)
-> [(UnqualComponentName, CondTree ConfVar [Dependency] Library)]
-> [(UnqualComponentName,
CondTree ConfVar [Dependency] ForeignLib)]
-> [(UnqualComponentName,
CondTree ConfVar [Dependency] Executable)]
-> [(UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)]
-> [(UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)]
-> GenericPackageDescription)
-> f (Maybe (CondTree ConfVar [Dependency] Library))
-> f ([(UnqualComponentName,
CondTree ConfVar [Dependency] Library)]
-> [(UnqualComponentName,
CondTree ConfVar [Dependency] ForeignLib)]
-> [(UnqualComponentName,
CondTree ConfVar [Dependency] Executable)]
-> [(UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)]
-> [(UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)]
-> GenericPackageDescription)
forall a b. f (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ((CondTree ConfVar [Dependency] Library
-> f (CondTree ConfVar [Dependency] Library))
-> Maybe (CondTree ConfVar [Dependency] Library)
-> f (Maybe (CondTree ConfVar [Dependency] Library))
forall a b (p :: * -> * -> *) (f :: * -> *).
(Choice p, Applicative f) =>
p a (f b) -> p (Maybe a) (f (Maybe b))
_Just ((CondTree ConfVar [Dependency] Library
-> f (CondTree ConfVar [Dependency] Library))
-> Maybe (CondTree ConfVar [Dependency] Library)
-> f (Maybe (CondTree ConfVar [Dependency] Library)))
-> ((BuildInfo -> f BuildInfo)
-> CondTree ConfVar [Dependency] Library
-> f (CondTree ConfVar [Dependency] Library))
-> (BuildInfo -> f BuildInfo)
-> Maybe (CondTree ConfVar [Dependency] Library)
-> f (Maybe (CondTree ConfVar [Dependency] Library))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Library -> f Library)
-> CondTree ConfVar [Dependency] Library
-> f (CondTree ConfVar [Dependency] Library)
forall dat (f :: * -> *).
Applicative f =>
(dat -> f dat) -> CondTree' dat -> f (CondTree' dat)
traverseData ((Library -> f Library)
-> CondTree ConfVar [Dependency] Library
-> f (CondTree ConfVar [Dependency] Library))
-> ((BuildInfo -> f BuildInfo) -> Library -> f Library)
-> (BuildInfo -> f BuildInfo)
-> CondTree ConfVar [Dependency] Library
-> f (CondTree ConfVar [Dependency] Library)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (BuildInfo -> f BuildInfo) -> Library -> f Library
Lens' Library BuildInfo
libBuildInfoL) BuildInfo -> f BuildInfo
f Maybe (CondTree ConfVar [Dependency] Library)
lib
f ([(UnqualComponentName, CondTree ConfVar [Dependency] Library)]
-> [(UnqualComponentName,
CondTree ConfVar [Dependency] ForeignLib)]
-> [(UnqualComponentName,
CondTree ConfVar [Dependency] Executable)]
-> [(UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)]
-> [(UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)]
-> GenericPackageDescription)
-> f [(UnqualComponentName, CondTree ConfVar [Dependency] Library)]
-> f ([(UnqualComponentName,
CondTree ConfVar [Dependency] ForeignLib)]
-> [(UnqualComponentName,
CondTree ConfVar [Dependency] Executable)]
-> [(UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)]
-> [(UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)]
-> GenericPackageDescription)
forall a b. f (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> [(UnqualComponentName, CondTree ConfVar [Dependency] Library)]
-> f [(UnqualComponentName, CondTree ConfVar [Dependency] Library)]
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure [(UnqualComponentName, CondTree ConfVar [Dependency] Library)]
subLibs
f ([(UnqualComponentName,
CondTree ConfVar [Dependency] ForeignLib)]
-> [(UnqualComponentName,
CondTree ConfVar [Dependency] Executable)]
-> [(UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)]
-> [(UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)]
-> GenericPackageDescription)
-> f [(UnqualComponentName,
CondTree ConfVar [Dependency] ForeignLib)]
-> f ([(UnqualComponentName,
CondTree ConfVar [Dependency] Executable)]
-> [(UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)]
-> [(UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)]
-> GenericPackageDescription)
forall a b. f (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> [(UnqualComponentName, CondTree ConfVar [Dependency] ForeignLib)]
-> f [(UnqualComponentName,
CondTree ConfVar [Dependency] ForeignLib)]
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure [(UnqualComponentName, CondTree ConfVar [Dependency] ForeignLib)]
foreignLibs
f ([(UnqualComponentName,
CondTree ConfVar [Dependency] Executable)]
-> [(UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)]
-> [(UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)]
-> GenericPackageDescription)
-> f [(UnqualComponentName,
CondTree ConfVar [Dependency] Executable)]
-> f ([(UnqualComponentName,
CondTree ConfVar [Dependency] TestSuite)]
-> [(UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)]
-> GenericPackageDescription)
forall a b. f (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (((UnqualComponentName, CondTree ConfVar [Dependency] Executable)
-> f (UnqualComponentName,
CondTree ConfVar [Dependency] Executable))
-> [(UnqualComponentName,
CondTree ConfVar [Dependency] Executable)]
-> f [(UnqualComponentName,
CondTree ConfVar [Dependency] Executable)]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> [a] -> f [b]
traverse (((UnqualComponentName, CondTree ConfVar [Dependency] Executable)
-> f (UnqualComponentName,
CondTree ConfVar [Dependency] Executable))
-> [(UnqualComponentName,
CondTree ConfVar [Dependency] Executable)]
-> f [(UnqualComponentName,
CondTree ConfVar [Dependency] Executable)])
-> ((BuildInfo -> f BuildInfo)
-> (UnqualComponentName, CondTree ConfVar [Dependency] Executable)
-> f (UnqualComponentName,
CondTree ConfVar [Dependency] Executable))
-> (BuildInfo -> f BuildInfo)
-> [(UnqualComponentName,
CondTree ConfVar [Dependency] Executable)]
-> f [(UnqualComponentName,
CondTree ConfVar [Dependency] Executable)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (CondTree ConfVar [Dependency] Executable
-> f (CondTree ConfVar [Dependency] Executable))
-> (UnqualComponentName, CondTree ConfVar [Dependency] Executable)
-> f (UnqualComponentName,
CondTree ConfVar [Dependency] Executable)
forall s t a b. Field2 s t a b => Lens s t a b
Lens
(UnqualComponentName, CondTree ConfVar [Dependency] Executable)
(UnqualComponentName, CondTree ConfVar [Dependency] Executable)
(CondTree ConfVar [Dependency] Executable)
(CondTree ConfVar [Dependency] Executable)
_2 ((CondTree ConfVar [Dependency] Executable
-> f (CondTree ConfVar [Dependency] Executable))
-> (UnqualComponentName, CondTree ConfVar [Dependency] Executable)
-> f (UnqualComponentName,
CondTree ConfVar [Dependency] Executable))
-> ((BuildInfo -> f BuildInfo)
-> CondTree ConfVar [Dependency] Executable
-> f (CondTree ConfVar [Dependency] Executable))
-> (BuildInfo -> f BuildInfo)
-> (UnqualComponentName, CondTree ConfVar [Dependency] Executable)
-> f (UnqualComponentName,
CondTree ConfVar [Dependency] Executable)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Executable -> f Executable)
-> CondTree ConfVar [Dependency] Executable
-> f (CondTree ConfVar [Dependency] Executable)
forall dat (f :: * -> *).
Applicative f =>
(dat -> f dat) -> CondTree' dat -> f (CondTree' dat)
traverseData ((Executable -> f Executable)
-> CondTree ConfVar [Dependency] Executable
-> f (CondTree ConfVar [Dependency] Executable))
-> ((BuildInfo -> f BuildInfo) -> Executable -> f Executable)
-> (BuildInfo -> f BuildInfo)
-> CondTree ConfVar [Dependency] Executable
-> f (CondTree ConfVar [Dependency] Executable)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (BuildInfo -> f BuildInfo) -> Executable -> f Executable
Lens' Executable BuildInfo
buildInfoL) BuildInfo -> f BuildInfo
f [(UnqualComponentName, CondTree ConfVar [Dependency] Executable)]
exes
f ([(UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)]
-> [(UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)]
-> GenericPackageDescription)
-> f [(UnqualComponentName,
CondTree ConfVar [Dependency] TestSuite)]
-> f ([(UnqualComponentName,
CondTree ConfVar [Dependency] Benchmark)]
-> GenericPackageDescription)
forall a b. f (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (((UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)
-> f (UnqualComponentName,
CondTree ConfVar [Dependency] TestSuite))
-> [(UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)]
-> f [(UnqualComponentName,
CondTree ConfVar [Dependency] TestSuite)]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> [a] -> f [b]
traverse (((UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)
-> f (UnqualComponentName,
CondTree ConfVar [Dependency] TestSuite))
-> [(UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)]
-> f [(UnqualComponentName,
CondTree ConfVar [Dependency] TestSuite)])
-> ((BuildInfo -> f BuildInfo)
-> (UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)
-> f (UnqualComponentName,
CondTree ConfVar [Dependency] TestSuite))
-> (BuildInfo -> f BuildInfo)
-> [(UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)]
-> f [(UnqualComponentName,
CondTree ConfVar [Dependency] TestSuite)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (CondTree ConfVar [Dependency] TestSuite
-> f (CondTree ConfVar [Dependency] TestSuite))
-> (UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)
-> f (UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)
forall s t a b. Field2 s t a b => Lens s t a b
Lens
(UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)
(UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)
(CondTree ConfVar [Dependency] TestSuite)
(CondTree ConfVar [Dependency] TestSuite)
_2 ((CondTree ConfVar [Dependency] TestSuite
-> f (CondTree ConfVar [Dependency] TestSuite))
-> (UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)
-> f (UnqualComponentName,
CondTree ConfVar [Dependency] TestSuite))
-> ((BuildInfo -> f BuildInfo)
-> CondTree ConfVar [Dependency] TestSuite
-> f (CondTree ConfVar [Dependency] TestSuite))
-> (BuildInfo -> f BuildInfo)
-> (UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)
-> f (UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (TestSuite -> f TestSuite)
-> CondTree ConfVar [Dependency] TestSuite
-> f (CondTree ConfVar [Dependency] TestSuite)
forall dat (f :: * -> *).
Applicative f =>
(dat -> f dat) -> CondTree' dat -> f (CondTree' dat)
traverseData ((TestSuite -> f TestSuite)
-> CondTree ConfVar [Dependency] TestSuite
-> f (CondTree ConfVar [Dependency] TestSuite))
-> ((BuildInfo -> f BuildInfo) -> TestSuite -> f TestSuite)
-> (BuildInfo -> f BuildInfo)
-> CondTree ConfVar [Dependency] TestSuite
-> f (CondTree ConfVar [Dependency] TestSuite)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (BuildInfo -> f BuildInfo) -> TestSuite -> f TestSuite
Lens' TestSuite BuildInfo
testBuildInfoL) BuildInfo -> f BuildInfo
f [(UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)]
tests
f ([(UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)]
-> GenericPackageDescription)
-> f [(UnqualComponentName,
CondTree ConfVar [Dependency] Benchmark)]
-> f GenericPackageDescription
forall a b. f (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (((UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)
-> f (UnqualComponentName,
CondTree ConfVar [Dependency] Benchmark))
-> [(UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)]
-> f [(UnqualComponentName,
CondTree ConfVar [Dependency] Benchmark)]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> [a] -> f [b]
traverse (((UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)
-> f (UnqualComponentName,
CondTree ConfVar [Dependency] Benchmark))
-> [(UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)]
-> f [(UnqualComponentName,
CondTree ConfVar [Dependency] Benchmark)])
-> ((BuildInfo -> f BuildInfo)
-> (UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)
-> f (UnqualComponentName,
CondTree ConfVar [Dependency] Benchmark))
-> (BuildInfo -> f BuildInfo)
-> [(UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)]
-> f [(UnqualComponentName,
CondTree ConfVar [Dependency] Benchmark)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (CondTree ConfVar [Dependency] Benchmark
-> f (CondTree ConfVar [Dependency] Benchmark))
-> (UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)
-> f (UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)
forall s t a b. Field2 s t a b => Lens s t a b
Lens
(UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)
(UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)
(CondTree ConfVar [Dependency] Benchmark)
(CondTree ConfVar [Dependency] Benchmark)
_2 ((CondTree ConfVar [Dependency] Benchmark
-> f (CondTree ConfVar [Dependency] Benchmark))
-> (UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)
-> f (UnqualComponentName,
CondTree ConfVar [Dependency] Benchmark))
-> ((BuildInfo -> f BuildInfo)
-> CondTree ConfVar [Dependency] Benchmark
-> f (CondTree ConfVar [Dependency] Benchmark))
-> (BuildInfo -> f BuildInfo)
-> (UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)
-> f (UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Benchmark -> f Benchmark)
-> CondTree ConfVar [Dependency] Benchmark
-> f (CondTree ConfVar [Dependency] Benchmark)
forall dat (f :: * -> *).
Applicative f =>
(dat -> f dat) -> CondTree' dat -> f (CondTree' dat)
traverseData ((Benchmark -> f Benchmark)
-> CondTree ConfVar [Dependency] Benchmark
-> f (CondTree ConfVar [Dependency] Benchmark))
-> ((BuildInfo -> f BuildInfo) -> Benchmark -> f Benchmark)
-> (BuildInfo -> f BuildInfo)
-> CondTree ConfVar [Dependency] Benchmark
-> f (CondTree ConfVar [Dependency] Benchmark)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (BuildInfo -> f BuildInfo) -> Benchmark -> f Benchmark
Lens' Benchmark BuildInfo
benchmarkBuildInfoL) BuildInfo -> f BuildInfo
f [(UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)]
benchs
buildInfo :: Section -> Traversal' GenericPackageDescription BuildInfo
buildInfo :: Section -> Traversal' GenericPackageDescription BuildInfo
buildInfo Section
Library = (Maybe (CondTree ConfVar [Dependency] Library)
-> f (Maybe (CondTree ConfVar [Dependency] Library)))
-> GenericPackageDescription -> f GenericPackageDescription
Lens'
GenericPackageDescription
(Maybe (CondTree ConfVar [Dependency] Library))
condLibraryL ((Maybe (CondTree ConfVar [Dependency] Library)
-> f (Maybe (CondTree ConfVar [Dependency] Library)))
-> GenericPackageDescription -> f GenericPackageDescription)
-> ((BuildInfo -> f BuildInfo)
-> Maybe (CondTree ConfVar [Dependency] Library)
-> f (Maybe (CondTree ConfVar [Dependency] Library)))
-> (BuildInfo -> f BuildInfo)
-> GenericPackageDescription
-> f GenericPackageDescription
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (CondTree ConfVar [Dependency] Library
-> f (CondTree ConfVar [Dependency] Library))
-> Maybe (CondTree ConfVar [Dependency] Library)
-> f (Maybe (CondTree ConfVar [Dependency] Library))
forall a b (p :: * -> * -> *) (f :: * -> *).
(Choice p, Applicative f) =>
p a (f b) -> p (Maybe a) (f (Maybe b))
_Just ((CondTree ConfVar [Dependency] Library
-> f (CondTree ConfVar [Dependency] Library))
-> Maybe (CondTree ConfVar [Dependency] Library)
-> f (Maybe (CondTree ConfVar [Dependency] Library)))
-> ((BuildInfo -> f BuildInfo)
-> CondTree ConfVar [Dependency] Library
-> f (CondTree ConfVar [Dependency] Library))
-> (BuildInfo -> f BuildInfo)
-> Maybe (CondTree ConfVar [Dependency] Library)
-> f (Maybe (CondTree ConfVar [Dependency] Library))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Library -> f Library)
-> CondTree ConfVar [Dependency] Library
-> f (CondTree ConfVar [Dependency] Library)
forall dat (f :: * -> *).
Applicative f =>
(dat -> f dat) -> CondTree' dat -> f (CondTree' dat)
traverseData ((Library -> f Library)
-> CondTree ConfVar [Dependency] Library
-> f (CondTree ConfVar [Dependency] Library))
-> ((BuildInfo -> f BuildInfo) -> Library -> f Library)
-> (BuildInfo -> f BuildInfo)
-> CondTree ConfVar [Dependency] Library
-> f (CondTree ConfVar [Dependency] Library)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (BuildInfo -> f BuildInfo) -> Library -> f Library
Lens' Library BuildInfo
libBuildInfoL
buildInfo (Executable Name
name) = ([(UnqualComponentName, CondTree ConfVar [Dependency] Executable)]
-> f [(UnqualComponentName,
CondTree ConfVar [Dependency] Executable)])
-> GenericPackageDescription -> f GenericPackageDescription
Lens'
GenericPackageDescription
[(UnqualComponentName, CondTree ConfVar [Dependency] Executable)]
condExecutablesL (([(UnqualComponentName, CondTree ConfVar [Dependency] Executable)]
-> f [(UnqualComponentName,
CondTree ConfVar [Dependency] Executable)])
-> GenericPackageDescription -> f GenericPackageDescription)
-> ((BuildInfo -> f BuildInfo)
-> [(UnqualComponentName,
CondTree ConfVar [Dependency] Executable)]
-> f [(UnqualComponentName,
CondTree ConfVar [Dependency] Executable)])
-> (BuildInfo -> f BuildInfo)
-> GenericPackageDescription
-> f GenericPackageDescription
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((UnqualComponentName, CondTree ConfVar [Dependency] Executable)
-> f (UnqualComponentName,
CondTree ConfVar [Dependency] Executable))
-> [(UnqualComponentName,
CondTree ConfVar [Dependency] Executable)]
-> f [(UnqualComponentName,
CondTree ConfVar [Dependency] Executable)]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> [a] -> f [b]
traverse (((UnqualComponentName, CondTree ConfVar [Dependency] Executable)
-> f (UnqualComponentName,
CondTree ConfVar [Dependency] Executable))
-> [(UnqualComponentName,
CondTree ConfVar [Dependency] Executable)]
-> f [(UnqualComponentName,
CondTree ConfVar [Dependency] Executable)])
-> ((BuildInfo -> f BuildInfo)
-> (UnqualComponentName, CondTree ConfVar [Dependency] Executable)
-> f (UnqualComponentName,
CondTree ConfVar [Dependency] Executable))
-> (BuildInfo -> f BuildInfo)
-> [(UnqualComponentName,
CondTree ConfVar [Dependency] Executable)]
-> f [(UnqualComponentName,
CondTree ConfVar [Dependency] Executable)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Name
-> ((UnqualComponentName, CondTree ConfVar [Dependency] Executable)
-> f (UnqualComponentName,
CondTree ConfVar [Dependency] Executable))
-> (UnqualComponentName, CondTree ConfVar [Dependency] Executable)
-> f (UnqualComponentName,
CondTree ConfVar [Dependency] Executable)
forall {p :: * -> * -> *} {f :: * -> *} {b}.
(Choice p, Applicative f) =>
Name
-> Optic' p f (UnqualComponentName, b) (UnqualComponentName, b)
having Name
name (((UnqualComponentName, CondTree ConfVar [Dependency] Executable)
-> f (UnqualComponentName,
CondTree ConfVar [Dependency] Executable))
-> (UnqualComponentName, CondTree ConfVar [Dependency] Executable)
-> f (UnqualComponentName,
CondTree ConfVar [Dependency] Executable))
-> ((BuildInfo -> f BuildInfo)
-> (UnqualComponentName, CondTree ConfVar [Dependency] Executable)
-> f (UnqualComponentName,
CondTree ConfVar [Dependency] Executable))
-> (BuildInfo -> f BuildInfo)
-> (UnqualComponentName, CondTree ConfVar [Dependency] Executable)
-> f (UnqualComponentName,
CondTree ConfVar [Dependency] Executable)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (CondTree ConfVar [Dependency] Executable
-> f (CondTree ConfVar [Dependency] Executable))
-> (UnqualComponentName, CondTree ConfVar [Dependency] Executable)
-> f (UnqualComponentName,
CondTree ConfVar [Dependency] Executable)
forall s t a b. Field2 s t a b => Lens s t a b
Lens
(UnqualComponentName, CondTree ConfVar [Dependency] Executable)
(UnqualComponentName, CondTree ConfVar [Dependency] Executable)
(CondTree ConfVar [Dependency] Executable)
(CondTree ConfVar [Dependency] Executable)
_2 ((CondTree ConfVar [Dependency] Executable
-> f (CondTree ConfVar [Dependency] Executable))
-> (UnqualComponentName, CondTree ConfVar [Dependency] Executable)
-> f (UnqualComponentName,
CondTree ConfVar [Dependency] Executable))
-> ((BuildInfo -> f BuildInfo)
-> CondTree ConfVar [Dependency] Executable
-> f (CondTree ConfVar [Dependency] Executable))
-> (BuildInfo -> f BuildInfo)
-> (UnqualComponentName, CondTree ConfVar [Dependency] Executable)
-> f (UnqualComponentName,
CondTree ConfVar [Dependency] Executable)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Executable -> f Executable)
-> CondTree ConfVar [Dependency] Executable
-> f (CondTree ConfVar [Dependency] Executable)
forall dat (f :: * -> *).
Applicative f =>
(dat -> f dat) -> CondTree' dat -> f (CondTree' dat)
traverseData ((Executable -> f Executable)
-> CondTree ConfVar [Dependency] Executable
-> f (CondTree ConfVar [Dependency] Executable))
-> ((BuildInfo -> f BuildInfo) -> Executable -> f Executable)
-> (BuildInfo -> f BuildInfo)
-> CondTree ConfVar [Dependency] Executable
-> f (CondTree ConfVar [Dependency] Executable)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (BuildInfo -> f BuildInfo) -> Executable -> f Executable
Lens' Executable BuildInfo
buildInfoL
buildInfo (TestSuite Name
name) = ([(UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)]
-> f [(UnqualComponentName,
CondTree ConfVar [Dependency] TestSuite)])
-> GenericPackageDescription -> f GenericPackageDescription
Lens'
GenericPackageDescription
[(UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)]
condTestSuitesL (([(UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)]
-> f [(UnqualComponentName,
CondTree ConfVar [Dependency] TestSuite)])
-> GenericPackageDescription -> f GenericPackageDescription)
-> ((BuildInfo -> f BuildInfo)
-> [(UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)]
-> f [(UnqualComponentName,
CondTree ConfVar [Dependency] TestSuite)])
-> (BuildInfo -> f BuildInfo)
-> GenericPackageDescription
-> f GenericPackageDescription
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)
-> f (UnqualComponentName,
CondTree ConfVar [Dependency] TestSuite))
-> [(UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)]
-> f [(UnqualComponentName,
CondTree ConfVar [Dependency] TestSuite)]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> [a] -> f [b]
traverse (((UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)
-> f (UnqualComponentName,
CondTree ConfVar [Dependency] TestSuite))
-> [(UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)]
-> f [(UnqualComponentName,
CondTree ConfVar [Dependency] TestSuite)])
-> ((BuildInfo -> f BuildInfo)
-> (UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)
-> f (UnqualComponentName,
CondTree ConfVar [Dependency] TestSuite))
-> (BuildInfo -> f BuildInfo)
-> [(UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)]
-> f [(UnqualComponentName,
CondTree ConfVar [Dependency] TestSuite)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Name
-> ((UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)
-> f (UnqualComponentName,
CondTree ConfVar [Dependency] TestSuite))
-> (UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)
-> f (UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)
forall {p :: * -> * -> *} {f :: * -> *} {b}.
(Choice p, Applicative f) =>
Name
-> Optic' p f (UnqualComponentName, b) (UnqualComponentName, b)
having Name
name (((UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)
-> f (UnqualComponentName,
CondTree ConfVar [Dependency] TestSuite))
-> (UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)
-> f (UnqualComponentName,
CondTree ConfVar [Dependency] TestSuite))
-> ((BuildInfo -> f BuildInfo)
-> (UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)
-> f (UnqualComponentName,
CondTree ConfVar [Dependency] TestSuite))
-> (BuildInfo -> f BuildInfo)
-> (UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)
-> f (UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (CondTree ConfVar [Dependency] TestSuite
-> f (CondTree ConfVar [Dependency] TestSuite))
-> (UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)
-> f (UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)
forall s t a b. Field2 s t a b => Lens s t a b
Lens
(UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)
(UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)
(CondTree ConfVar [Dependency] TestSuite)
(CondTree ConfVar [Dependency] TestSuite)
_2 ((CondTree ConfVar [Dependency] TestSuite
-> f (CondTree ConfVar [Dependency] TestSuite))
-> (UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)
-> f (UnqualComponentName,
CondTree ConfVar [Dependency] TestSuite))
-> ((BuildInfo -> f BuildInfo)
-> CondTree ConfVar [Dependency] TestSuite
-> f (CondTree ConfVar [Dependency] TestSuite))
-> (BuildInfo -> f BuildInfo)
-> (UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)
-> f (UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (TestSuite -> f TestSuite)
-> CondTree ConfVar [Dependency] TestSuite
-> f (CondTree ConfVar [Dependency] TestSuite)
forall dat (f :: * -> *).
Applicative f =>
(dat -> f dat) -> CondTree' dat -> f (CondTree' dat)
traverseData ((TestSuite -> f TestSuite)
-> CondTree ConfVar [Dependency] TestSuite
-> f (CondTree ConfVar [Dependency] TestSuite))
-> ((BuildInfo -> f BuildInfo) -> TestSuite -> f TestSuite)
-> (BuildInfo -> f BuildInfo)
-> CondTree ConfVar [Dependency] TestSuite
-> f (CondTree ConfVar [Dependency] TestSuite)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (BuildInfo -> f BuildInfo) -> TestSuite -> f TestSuite
Lens' TestSuite BuildInfo
testBuildInfoL
buildInfo (Benchmark Name
name) = ([(UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)]
-> f [(UnqualComponentName,
CondTree ConfVar [Dependency] Benchmark)])
-> GenericPackageDescription -> f GenericPackageDescription
Lens'
GenericPackageDescription
[(UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)]
condBenchmarksL (([(UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)]
-> f [(UnqualComponentName,
CondTree ConfVar [Dependency] Benchmark)])
-> GenericPackageDescription -> f GenericPackageDescription)
-> ((BuildInfo -> f BuildInfo)
-> [(UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)]
-> f [(UnqualComponentName,
CondTree ConfVar [Dependency] Benchmark)])
-> (BuildInfo -> f BuildInfo)
-> GenericPackageDescription
-> f GenericPackageDescription
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)
-> f (UnqualComponentName,
CondTree ConfVar [Dependency] Benchmark))
-> [(UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)]
-> f [(UnqualComponentName,
CondTree ConfVar [Dependency] Benchmark)]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> [a] -> f [b]
traverse (((UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)
-> f (UnqualComponentName,
CondTree ConfVar [Dependency] Benchmark))
-> [(UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)]
-> f [(UnqualComponentName,
CondTree ConfVar [Dependency] Benchmark)])
-> ((BuildInfo -> f BuildInfo)
-> (UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)
-> f (UnqualComponentName,
CondTree ConfVar [Dependency] Benchmark))
-> (BuildInfo -> f BuildInfo)
-> [(UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)]
-> f [(UnqualComponentName,
CondTree ConfVar [Dependency] Benchmark)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Name
-> ((UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)
-> f (UnqualComponentName,
CondTree ConfVar [Dependency] Benchmark))
-> (UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)
-> f (UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)
forall {p :: * -> * -> *} {f :: * -> *} {b}.
(Choice p, Applicative f) =>
Name
-> Optic' p f (UnqualComponentName, b) (UnqualComponentName, b)
having Name
name (((UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)
-> f (UnqualComponentName,
CondTree ConfVar [Dependency] Benchmark))
-> (UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)
-> f (UnqualComponentName,
CondTree ConfVar [Dependency] Benchmark))
-> ((BuildInfo -> f BuildInfo)
-> (UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)
-> f (UnqualComponentName,
CondTree ConfVar [Dependency] Benchmark))
-> (BuildInfo -> f BuildInfo)
-> (UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)
-> f (UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (CondTree ConfVar [Dependency] Benchmark
-> f (CondTree ConfVar [Dependency] Benchmark))
-> (UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)
-> f (UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)
forall s t a b. Field2 s t a b => Lens s t a b
Lens
(UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)
(UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)
(CondTree ConfVar [Dependency] Benchmark)
(CondTree ConfVar [Dependency] Benchmark)
_2 ((CondTree ConfVar [Dependency] Benchmark
-> f (CondTree ConfVar [Dependency] Benchmark))
-> (UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)
-> f (UnqualComponentName,
CondTree ConfVar [Dependency] Benchmark))
-> ((BuildInfo -> f BuildInfo)
-> CondTree ConfVar [Dependency] Benchmark
-> f (CondTree ConfVar [Dependency] Benchmark))
-> (BuildInfo -> f BuildInfo)
-> (UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)
-> f (UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Benchmark -> f Benchmark)
-> CondTree ConfVar [Dependency] Benchmark
-> f (CondTree ConfVar [Dependency] Benchmark)
forall dat (f :: * -> *).
Applicative f =>
(dat -> f dat) -> CondTree' dat -> f (CondTree' dat)
traverseData ((Benchmark -> f Benchmark)
-> CondTree ConfVar [Dependency] Benchmark
-> f (CondTree ConfVar [Dependency] Benchmark))
-> ((BuildInfo -> f BuildInfo) -> Benchmark -> f Benchmark)
-> (BuildInfo -> f BuildInfo)
-> CondTree ConfVar [Dependency] Benchmark
-> f (CondTree ConfVar [Dependency] Benchmark)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (BuildInfo -> f BuildInfo) -> Benchmark -> f Benchmark
Lens' Benchmark BuildInfo
benchmarkBuildInfoL
buildInfoIf :: CondVars -> Section -> Traversal' GenericPackageDescription BuildInfo
buildInfoIf :: CondVars
-> Section -> Traversal' GenericPackageDescription BuildInfo
buildInfoIf CondVars
condVars Section
Library = (Maybe (CondTree ConfVar [Dependency] Library)
-> f (Maybe (CondTree ConfVar [Dependency] Library)))
-> GenericPackageDescription -> f GenericPackageDescription
Lens'
GenericPackageDescription
(Maybe (CondTree ConfVar [Dependency] Library))
condLibraryL ((Maybe (CondTree ConfVar [Dependency] Library)
-> f (Maybe (CondTree ConfVar [Dependency] Library)))
-> GenericPackageDescription -> f GenericPackageDescription)
-> ((BuildInfo -> f BuildInfo)
-> Maybe (CondTree ConfVar [Dependency] Library)
-> f (Maybe (CondTree ConfVar [Dependency] Library)))
-> (BuildInfo -> f BuildInfo)
-> GenericPackageDescription
-> f GenericPackageDescription
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (CondTree ConfVar [Dependency] Library
-> f (CondTree ConfVar [Dependency] Library))
-> Maybe (CondTree ConfVar [Dependency] Library)
-> f (Maybe (CondTree ConfVar [Dependency] Library))
forall a b (p :: * -> * -> *) (f :: * -> *).
(Choice p, Applicative f) =>
p a (f b) -> p (Maybe a) (f (Maybe b))
_Just ((CondTree ConfVar [Dependency] Library
-> f (CondTree ConfVar [Dependency] Library))
-> Maybe (CondTree ConfVar [Dependency] Library)
-> f (Maybe (CondTree ConfVar [Dependency] Library)))
-> ((BuildInfo -> f BuildInfo)
-> CondTree ConfVar [Dependency] Library
-> f (CondTree ConfVar [Dependency] Library))
-> (BuildInfo -> f BuildInfo)
-> Maybe (CondTree ConfVar [Dependency] Library)
-> f (Maybe (CondTree ConfVar [Dependency] Library))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CondVars
-> Traversal' (CondTree ConfVar [Dependency] Library) Library
forall dat. CondVars -> Traversal' (CondTree' dat) dat
traverseDataIf CondVars
condVars ((Library -> f Library)
-> CondTree ConfVar [Dependency] Library
-> f (CondTree ConfVar [Dependency] Library))
-> ((BuildInfo -> f BuildInfo) -> Library -> f Library)
-> (BuildInfo -> f BuildInfo)
-> CondTree ConfVar [Dependency] Library
-> f (CondTree ConfVar [Dependency] Library)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (BuildInfo -> f BuildInfo) -> Library -> f Library
Lens' Library BuildInfo
libBuildInfoL
buildInfoIf CondVars
condVars (Executable Name
name) = ([(UnqualComponentName, CondTree ConfVar [Dependency] Executable)]
-> f [(UnqualComponentName,
CondTree ConfVar [Dependency] Executable)])
-> GenericPackageDescription -> f GenericPackageDescription
Lens'
GenericPackageDescription
[(UnqualComponentName, CondTree ConfVar [Dependency] Executable)]
condExecutablesL (([(UnqualComponentName, CondTree ConfVar [Dependency] Executable)]
-> f [(UnqualComponentName,
CondTree ConfVar [Dependency] Executable)])
-> GenericPackageDescription -> f GenericPackageDescription)
-> ((BuildInfo -> f BuildInfo)
-> [(UnqualComponentName,
CondTree ConfVar [Dependency] Executable)]
-> f [(UnqualComponentName,
CondTree ConfVar [Dependency] Executable)])
-> (BuildInfo -> f BuildInfo)
-> GenericPackageDescription
-> f GenericPackageDescription
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((UnqualComponentName, CondTree ConfVar [Dependency] Executable)
-> f (UnqualComponentName,
CondTree ConfVar [Dependency] Executable))
-> [(UnqualComponentName,
CondTree ConfVar [Dependency] Executable)]
-> f [(UnqualComponentName,
CondTree ConfVar [Dependency] Executable)]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> [a] -> f [b]
traverse (((UnqualComponentName, CondTree ConfVar [Dependency] Executable)
-> f (UnqualComponentName,
CondTree ConfVar [Dependency] Executable))
-> [(UnqualComponentName,
CondTree ConfVar [Dependency] Executable)]
-> f [(UnqualComponentName,
CondTree ConfVar [Dependency] Executable)])
-> ((BuildInfo -> f BuildInfo)
-> (UnqualComponentName, CondTree ConfVar [Dependency] Executable)
-> f (UnqualComponentName,
CondTree ConfVar [Dependency] Executable))
-> (BuildInfo -> f BuildInfo)
-> [(UnqualComponentName,
CondTree ConfVar [Dependency] Executable)]
-> f [(UnqualComponentName,
CondTree ConfVar [Dependency] Executable)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Name
-> ((UnqualComponentName, CondTree ConfVar [Dependency] Executable)
-> f (UnqualComponentName,
CondTree ConfVar [Dependency] Executable))
-> (UnqualComponentName, CondTree ConfVar [Dependency] Executable)
-> f (UnqualComponentName,
CondTree ConfVar [Dependency] Executable)
forall {p :: * -> * -> *} {f :: * -> *} {b}.
(Choice p, Applicative f) =>
Name
-> Optic' p f (UnqualComponentName, b) (UnqualComponentName, b)
having Name
name (((UnqualComponentName, CondTree ConfVar [Dependency] Executable)
-> f (UnqualComponentName,
CondTree ConfVar [Dependency] Executable))
-> (UnqualComponentName, CondTree ConfVar [Dependency] Executable)
-> f (UnqualComponentName,
CondTree ConfVar [Dependency] Executable))
-> ((BuildInfo -> f BuildInfo)
-> (UnqualComponentName, CondTree ConfVar [Dependency] Executable)
-> f (UnqualComponentName,
CondTree ConfVar [Dependency] Executable))
-> (BuildInfo -> f BuildInfo)
-> (UnqualComponentName, CondTree ConfVar [Dependency] Executable)
-> f (UnqualComponentName,
CondTree ConfVar [Dependency] Executable)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (CondTree ConfVar [Dependency] Executable
-> f (CondTree ConfVar [Dependency] Executable))
-> (UnqualComponentName, CondTree ConfVar [Dependency] Executable)
-> f (UnqualComponentName,
CondTree ConfVar [Dependency] Executable)
forall s t a b. Field2 s t a b => Lens s t a b
Lens
(UnqualComponentName, CondTree ConfVar [Dependency] Executable)
(UnqualComponentName, CondTree ConfVar [Dependency] Executable)
(CondTree ConfVar [Dependency] Executable)
(CondTree ConfVar [Dependency] Executable)
_2 ((CondTree ConfVar [Dependency] Executable
-> f (CondTree ConfVar [Dependency] Executable))
-> (UnqualComponentName, CondTree ConfVar [Dependency] Executable)
-> f (UnqualComponentName,
CondTree ConfVar [Dependency] Executable))
-> ((BuildInfo -> f BuildInfo)
-> CondTree ConfVar [Dependency] Executable
-> f (CondTree ConfVar [Dependency] Executable))
-> (BuildInfo -> f BuildInfo)
-> (UnqualComponentName, CondTree ConfVar [Dependency] Executable)
-> f (UnqualComponentName,
CondTree ConfVar [Dependency] Executable)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CondVars
-> Traversal' (CondTree ConfVar [Dependency] Executable) Executable
forall dat. CondVars -> Traversal' (CondTree' dat) dat
traverseDataIf CondVars
condVars ((Executable -> f Executable)
-> CondTree ConfVar [Dependency] Executable
-> f (CondTree ConfVar [Dependency] Executable))
-> ((BuildInfo -> f BuildInfo) -> Executable -> f Executable)
-> (BuildInfo -> f BuildInfo)
-> CondTree ConfVar [Dependency] Executable
-> f (CondTree ConfVar [Dependency] Executable)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (BuildInfo -> f BuildInfo) -> Executable -> f Executable
Lens' Executable BuildInfo
buildInfoL
buildInfoIf CondVars
condVars (TestSuite Name
name) = ([(UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)]
-> f [(UnqualComponentName,
CondTree ConfVar [Dependency] TestSuite)])
-> GenericPackageDescription -> f GenericPackageDescription
Lens'
GenericPackageDescription
[(UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)]
condTestSuitesL (([(UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)]
-> f [(UnqualComponentName,
CondTree ConfVar [Dependency] TestSuite)])
-> GenericPackageDescription -> f GenericPackageDescription)
-> ((BuildInfo -> f BuildInfo)
-> [(UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)]
-> f [(UnqualComponentName,
CondTree ConfVar [Dependency] TestSuite)])
-> (BuildInfo -> f BuildInfo)
-> GenericPackageDescription
-> f GenericPackageDescription
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)
-> f (UnqualComponentName,
CondTree ConfVar [Dependency] TestSuite))
-> [(UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)]
-> f [(UnqualComponentName,
CondTree ConfVar [Dependency] TestSuite)]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> [a] -> f [b]
traverse (((UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)
-> f (UnqualComponentName,
CondTree ConfVar [Dependency] TestSuite))
-> [(UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)]
-> f [(UnqualComponentName,
CondTree ConfVar [Dependency] TestSuite)])
-> ((BuildInfo -> f BuildInfo)
-> (UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)
-> f (UnqualComponentName,
CondTree ConfVar [Dependency] TestSuite))
-> (BuildInfo -> f BuildInfo)
-> [(UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)]
-> f [(UnqualComponentName,
CondTree ConfVar [Dependency] TestSuite)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Name
-> ((UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)
-> f (UnqualComponentName,
CondTree ConfVar [Dependency] TestSuite))
-> (UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)
-> f (UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)
forall {p :: * -> * -> *} {f :: * -> *} {b}.
(Choice p, Applicative f) =>
Name
-> Optic' p f (UnqualComponentName, b) (UnqualComponentName, b)
having Name
name (((UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)
-> f (UnqualComponentName,
CondTree ConfVar [Dependency] TestSuite))
-> (UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)
-> f (UnqualComponentName,
CondTree ConfVar [Dependency] TestSuite))
-> ((BuildInfo -> f BuildInfo)
-> (UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)
-> f (UnqualComponentName,
CondTree ConfVar [Dependency] TestSuite))
-> (BuildInfo -> f BuildInfo)
-> (UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)
-> f (UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (CondTree ConfVar [Dependency] TestSuite
-> f (CondTree ConfVar [Dependency] TestSuite))
-> (UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)
-> f (UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)
forall s t a b. Field2 s t a b => Lens s t a b
Lens
(UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)
(UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)
(CondTree ConfVar [Dependency] TestSuite)
(CondTree ConfVar [Dependency] TestSuite)
_2 ((CondTree ConfVar [Dependency] TestSuite
-> f (CondTree ConfVar [Dependency] TestSuite))
-> (UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)
-> f (UnqualComponentName,
CondTree ConfVar [Dependency] TestSuite))
-> ((BuildInfo -> f BuildInfo)
-> CondTree ConfVar [Dependency] TestSuite
-> f (CondTree ConfVar [Dependency] TestSuite))
-> (BuildInfo -> f BuildInfo)
-> (UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)
-> f (UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CondVars
-> Traversal' (CondTree ConfVar [Dependency] TestSuite) TestSuite
forall dat. CondVars -> Traversal' (CondTree' dat) dat
traverseDataIf CondVars
condVars ((TestSuite -> f TestSuite)
-> CondTree ConfVar [Dependency] TestSuite
-> f (CondTree ConfVar [Dependency] TestSuite))
-> ((BuildInfo -> f BuildInfo) -> TestSuite -> f TestSuite)
-> (BuildInfo -> f BuildInfo)
-> CondTree ConfVar [Dependency] TestSuite
-> f (CondTree ConfVar [Dependency] TestSuite)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (BuildInfo -> f BuildInfo) -> TestSuite -> f TestSuite
Lens' TestSuite BuildInfo
testBuildInfoL
buildInfoIf CondVars
condVars (Benchmark Name
name) = ([(UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)]
-> f [(UnqualComponentName,
CondTree ConfVar [Dependency] Benchmark)])
-> GenericPackageDescription -> f GenericPackageDescription
Lens'
GenericPackageDescription
[(UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)]
condBenchmarksL (([(UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)]
-> f [(UnqualComponentName,
CondTree ConfVar [Dependency] Benchmark)])
-> GenericPackageDescription -> f GenericPackageDescription)
-> ((BuildInfo -> f BuildInfo)
-> [(UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)]
-> f [(UnqualComponentName,
CondTree ConfVar [Dependency] Benchmark)])
-> (BuildInfo -> f BuildInfo)
-> GenericPackageDescription
-> f GenericPackageDescription
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)
-> f (UnqualComponentName,
CondTree ConfVar [Dependency] Benchmark))
-> [(UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)]
-> f [(UnqualComponentName,
CondTree ConfVar [Dependency] Benchmark)]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> [a] -> f [b]
traverse (((UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)
-> f (UnqualComponentName,
CondTree ConfVar [Dependency] Benchmark))
-> [(UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)]
-> f [(UnqualComponentName,
CondTree ConfVar [Dependency] Benchmark)])
-> ((BuildInfo -> f BuildInfo)
-> (UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)
-> f (UnqualComponentName,
CondTree ConfVar [Dependency] Benchmark))
-> (BuildInfo -> f BuildInfo)
-> [(UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)]
-> f [(UnqualComponentName,
CondTree ConfVar [Dependency] Benchmark)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Name
-> ((UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)
-> f (UnqualComponentName,
CondTree ConfVar [Dependency] Benchmark))
-> (UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)
-> f (UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)
forall {p :: * -> * -> *} {f :: * -> *} {b}.
(Choice p, Applicative f) =>
Name
-> Optic' p f (UnqualComponentName, b) (UnqualComponentName, b)
having Name
name (((UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)
-> f (UnqualComponentName,
CondTree ConfVar [Dependency] Benchmark))
-> (UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)
-> f (UnqualComponentName,
CondTree ConfVar [Dependency] Benchmark))
-> ((BuildInfo -> f BuildInfo)
-> (UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)
-> f (UnqualComponentName,
CondTree ConfVar [Dependency] Benchmark))
-> (BuildInfo -> f BuildInfo)
-> (UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)
-> f (UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (CondTree ConfVar [Dependency] Benchmark
-> f (CondTree ConfVar [Dependency] Benchmark))
-> (UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)
-> f (UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)
forall s t a b. Field2 s t a b => Lens s t a b
Lens
(UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)
(UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)
(CondTree ConfVar [Dependency] Benchmark)
(CondTree ConfVar [Dependency] Benchmark)
_2 ((CondTree ConfVar [Dependency] Benchmark
-> f (CondTree ConfVar [Dependency] Benchmark))
-> (UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)
-> f (UnqualComponentName,
CondTree ConfVar [Dependency] Benchmark))
-> ((BuildInfo -> f BuildInfo)
-> CondTree ConfVar [Dependency] Benchmark
-> f (CondTree ConfVar [Dependency] Benchmark))
-> (BuildInfo -> f BuildInfo)
-> (UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)
-> f (UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CondVars
-> Traversal' (CondTree ConfVar [Dependency] Benchmark) Benchmark
forall dat. CondVars -> Traversal' (CondTree' dat) dat
traverseDataIf CondVars
condVars ((Benchmark -> f Benchmark)
-> CondTree ConfVar [Dependency] Benchmark
-> f (CondTree ConfVar [Dependency] Benchmark))
-> ((BuildInfo -> f BuildInfo) -> Benchmark -> f Benchmark)
-> (BuildInfo -> f BuildInfo)
-> CondTree ConfVar [Dependency] Benchmark
-> f (CondTree ConfVar [Dependency] Benchmark)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (BuildInfo -> f BuildInfo) -> Benchmark -> f Benchmark
Lens' Benchmark BuildInfo
benchmarkBuildInfoL
having :: Name
-> Optic' p f (UnqualComponentName, b) (UnqualComponentName, b)
having Name
name = ((UnqualComponentName, b) -> Bool)
-> Optic' p f (UnqualComponentName, b) (UnqualComponentName, b)
forall (p :: * -> * -> *) (f :: * -> *) a.
(Choice p, Applicative f) =>
(a -> Bool) -> Optic' p f a a
filtered ((Name -> Name -> Bool
forall a. Eq a => a -> a -> Bool
== Name
name) (Name -> Bool)
-> ((UnqualComponentName, b) -> Name)
-> (UnqualComponentName, b)
-> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. UnqualComponentName -> Name
unUnqualComponentName (UnqualComponentName -> Name)
-> ((UnqualComponentName, b) -> UnqualComponentName)
-> (UnqualComponentName, b)
-> Name
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (UnqualComponentName, b) -> UnqualComponentName
forall a b. (a, b) -> a
fst)