{-# LANGUAGE Rank2Types #-}
module Distribution.Types.GenericPackageDescription.Lens (
    GenericPackageDescription,
    PackageFlag,
    FlagName,
    ConfVar (..),
    module Distribution.Types.GenericPackageDescription.Lens,
    ) where
import Prelude()
import Distribution.Compat.Prelude
import Distribution.Compat.Lens
import qualified Distribution.Types.GenericPackageDescription as T
import Distribution.Types.CondTree (CondTree)
import Distribution.Types.Dependency (Dependency)
import Distribution.Types.Executable (Executable)
import Distribution.Types.PackageDescription (PackageDescription)
import Distribution.Types.Benchmark (Benchmark)
import Distribution.Types.ForeignLib (ForeignLib)
import Distribution.Types.GenericPackageDescription (GenericPackageDescription(GenericPackageDescription) )
import Distribution.Types.Flag (PackageFlag(MkPackageFlag), FlagName)
import Distribution.Types.ConfVar (ConfVar (..))
import Distribution.Types.Library (Library)
import Distribution.Types.TestSuite (TestSuite)
import Distribution.Types.UnqualComponentName (UnqualComponentName)
import Distribution.System (Arch, OS)
import Distribution.Compiler (CompilerFlavor)
import Distribution.Version (Version, VersionRange)
packageDescription :: Lens' GenericPackageDescription PackageDescription
packageDescription :: Lens' GenericPackageDescription PackageDescription
packageDescription PackageDescription -> f PackageDescription
f GenericPackageDescription
s = (PackageDescription -> GenericPackageDescription)
-> f PackageDescription -> f GenericPackageDescription
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\PackageDescription
x -> GenericPackageDescription
s { packageDescription :: PackageDescription
T.packageDescription = PackageDescription
x }) (PackageDescription -> f PackageDescription
f (GenericPackageDescription -> PackageDescription
T.packageDescription GenericPackageDescription
s))
{-# INLINE packageDescription #-}
gpdScannedVersion :: Lens' GenericPackageDescription (Maybe Version)
gpdScannedVersion :: Lens' GenericPackageDescription (Maybe Version)
gpdScannedVersion Maybe Version -> f (Maybe Version)
f GenericPackageDescription
s = (Maybe Version -> GenericPackageDescription)
-> f (Maybe Version) -> f GenericPackageDescription
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\Maybe Version
x -> GenericPackageDescription
s { gpdScannedVersion :: Maybe Version
T.gpdScannedVersion = Maybe Version
x }) (Maybe Version -> f (Maybe Version)
f (GenericPackageDescription -> Maybe Version
T.gpdScannedVersion GenericPackageDescription
s))
{-# INLINE gpdScannedVersion #-}
genPackageFlags :: Lens' GenericPackageDescription [PackageFlag]
genPackageFlags :: Lens' GenericPackageDescription [PackageFlag]
genPackageFlags [PackageFlag] -> f [PackageFlag]
f GenericPackageDescription
s = ([PackageFlag] -> GenericPackageDescription)
-> f [PackageFlag] -> f GenericPackageDescription
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\[PackageFlag]
x -> GenericPackageDescription
s { genPackageFlags :: [PackageFlag]
T.genPackageFlags = [PackageFlag]
x }) ([PackageFlag] -> f [PackageFlag]
f (GenericPackageDescription -> [PackageFlag]
T.genPackageFlags GenericPackageDescription
s))
{-# INLINE genPackageFlags #-}
condLibrary :: Lens' GenericPackageDescription (Maybe (CondTree ConfVar [Dependency] Library))
condLibrary :: Lens'
  GenericPackageDescription
  (Maybe (CondTree ConfVar [Dependency] Library))
condLibrary Maybe (CondTree ConfVar [Dependency] Library)
-> f (Maybe (CondTree ConfVar [Dependency] Library))
f GenericPackageDescription
s = (Maybe (CondTree ConfVar [Dependency] Library)
 -> GenericPackageDescription)
-> f (Maybe (CondTree ConfVar [Dependency] Library))
-> f GenericPackageDescription
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\Maybe (CondTree ConfVar [Dependency] Library)
x -> GenericPackageDescription
s { condLibrary :: Maybe (CondTree ConfVar [Dependency] Library)
T.condLibrary = Maybe (CondTree ConfVar [Dependency] Library)
x }) (Maybe (CondTree ConfVar [Dependency] Library)
-> f (Maybe (CondTree ConfVar [Dependency] Library))
f (GenericPackageDescription
-> Maybe (CondTree ConfVar [Dependency] Library)
T.condLibrary GenericPackageDescription
s))
{-# INLINE condLibrary #-}
condSubLibraries :: Lens' GenericPackageDescription [(UnqualComponentName,(CondTree ConfVar [Dependency] Library))]
condSubLibraries :: Lens'
  GenericPackageDescription
  [(UnqualComponentName, CondTree ConfVar [Dependency] Library)]
condSubLibraries [(UnqualComponentName, CondTree ConfVar [Dependency] Library)]
-> f [(UnqualComponentName, CondTree ConfVar [Dependency] Library)]
f GenericPackageDescription
s = ([(UnqualComponentName, CondTree ConfVar [Dependency] Library)]
 -> GenericPackageDescription)
-> f [(UnqualComponentName, CondTree ConfVar [Dependency] Library)]
-> f GenericPackageDescription
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\[(UnqualComponentName, CondTree ConfVar [Dependency] Library)]
x -> GenericPackageDescription
s { condSubLibraries :: [(UnqualComponentName, CondTree ConfVar [Dependency] Library)]
T.condSubLibraries = [(UnqualComponentName, CondTree ConfVar [Dependency] Library)]
x }) ([(UnqualComponentName, CondTree ConfVar [Dependency] Library)]
-> f [(UnqualComponentName, CondTree ConfVar [Dependency] Library)]
f (GenericPackageDescription
-> [(UnqualComponentName, CondTree ConfVar [Dependency] Library)]
T.condSubLibraries GenericPackageDescription
s))
{-# INLINE condSubLibraries #-}
condForeignLibs :: Lens' GenericPackageDescription [(UnqualComponentName,(CondTree ConfVar [Dependency] ForeignLib))]
condForeignLibs :: Lens'
  GenericPackageDescription
  [(UnqualComponentName, CondTree ConfVar [Dependency] ForeignLib)]
condForeignLibs [(UnqualComponentName, CondTree ConfVar [Dependency] ForeignLib)]
-> f [(UnqualComponentName,
       CondTree ConfVar [Dependency] ForeignLib)]
f GenericPackageDescription
s = ([(UnqualComponentName, CondTree ConfVar [Dependency] ForeignLib)]
 -> GenericPackageDescription)
-> f [(UnqualComponentName,
       CondTree ConfVar [Dependency] ForeignLib)]
-> f GenericPackageDescription
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\[(UnqualComponentName, CondTree ConfVar [Dependency] ForeignLib)]
x -> GenericPackageDescription
s { condForeignLibs :: [(UnqualComponentName, CondTree ConfVar [Dependency] ForeignLib)]
T.condForeignLibs = [(UnqualComponentName, CondTree ConfVar [Dependency] ForeignLib)]
x }) ([(UnqualComponentName, CondTree ConfVar [Dependency] ForeignLib)]
-> f [(UnqualComponentName,
       CondTree ConfVar [Dependency] ForeignLib)]
f (GenericPackageDescription
-> [(UnqualComponentName,
     CondTree ConfVar [Dependency] ForeignLib)]
T.condForeignLibs GenericPackageDescription
s))
{-# INLINE condForeignLibs #-}
condExecutables :: Lens' GenericPackageDescription [(UnqualComponentName,(CondTree ConfVar [Dependency] Executable))]
condExecutables :: Lens'
  GenericPackageDescription
  [(UnqualComponentName, CondTree ConfVar [Dependency] Executable)]
condExecutables [(UnqualComponentName, CondTree ConfVar [Dependency] Executable)]
-> f [(UnqualComponentName,
       CondTree ConfVar [Dependency] Executable)]
f GenericPackageDescription
s = ([(UnqualComponentName, CondTree ConfVar [Dependency] Executable)]
 -> GenericPackageDescription)
-> f [(UnqualComponentName,
       CondTree ConfVar [Dependency] Executable)]
-> f GenericPackageDescription
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\[(UnqualComponentName, CondTree ConfVar [Dependency] Executable)]
x -> GenericPackageDescription
s { condExecutables :: [(UnqualComponentName, CondTree ConfVar [Dependency] Executable)]
T.condExecutables = [(UnqualComponentName, CondTree ConfVar [Dependency] Executable)]
x }) ([(UnqualComponentName, CondTree ConfVar [Dependency] Executable)]
-> f [(UnqualComponentName,
       CondTree ConfVar [Dependency] Executable)]
f (GenericPackageDescription
-> [(UnqualComponentName,
     CondTree ConfVar [Dependency] Executable)]
T.condExecutables GenericPackageDescription
s))
{-# INLINE condExecutables #-}
condTestSuites :: Lens' GenericPackageDescription [(UnqualComponentName,(CondTree ConfVar [Dependency] TestSuite))]
condTestSuites :: Lens'
  GenericPackageDescription
  [(UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)]
condTestSuites [(UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)]
-> f [(UnqualComponentName,
       CondTree ConfVar [Dependency] TestSuite)]
f GenericPackageDescription
s = ([(UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)]
 -> GenericPackageDescription)
-> f [(UnqualComponentName,
       CondTree ConfVar [Dependency] TestSuite)]
-> f GenericPackageDescription
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\[(UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)]
x -> GenericPackageDescription
s { condTestSuites :: [(UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)]
T.condTestSuites = [(UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)]
x }) ([(UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)]
-> f [(UnqualComponentName,
       CondTree ConfVar [Dependency] TestSuite)]
f (GenericPackageDescription
-> [(UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)]
T.condTestSuites GenericPackageDescription
s))
{-# INLINE condTestSuites #-}
condBenchmarks :: Lens' GenericPackageDescription [(UnqualComponentName,(CondTree ConfVar [Dependency] Benchmark))]
condBenchmarks :: Lens'
  GenericPackageDescription
  [(UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)]
condBenchmarks [(UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)]
-> f [(UnqualComponentName,
       CondTree ConfVar [Dependency] Benchmark)]
f GenericPackageDescription
s = ([(UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)]
 -> GenericPackageDescription)
-> f [(UnqualComponentName,
       CondTree ConfVar [Dependency] Benchmark)]
-> f GenericPackageDescription
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\[(UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)]
x -> GenericPackageDescription
s { condBenchmarks :: [(UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)]
T.condBenchmarks = [(UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)]
x }) ([(UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)]
-> f [(UnqualComponentName,
       CondTree ConfVar [Dependency] Benchmark)]
f (GenericPackageDescription
-> [(UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)]
T.condBenchmarks GenericPackageDescription
s))
{-# INLINE condBenchmarks #-}
allCondTrees
  :: Applicative f
  => (forall a. CondTree ConfVar [Dependency] a
          -> f (CondTree ConfVar [Dependency] a))
  -> GenericPackageDescription
  -> f GenericPackageDescription
allCondTrees :: forall (f :: * -> *).
Applicative f =>
(forall a.
 CondTree ConfVar [Dependency] a
 -> f (CondTree ConfVar [Dependency] a))
-> GenericPackageDescription -> f GenericPackageDescription
allCondTrees forall a.
CondTree ConfVar [Dependency] a
-> f (CondTree ConfVar [Dependency] a)
f (GenericPackageDescription PackageDescription
p Maybe Version
v [PackageFlag]
a1 Maybe (CondTree ConfVar [Dependency] Library)
x1 [(UnqualComponentName, CondTree ConfVar [Dependency] Library)]
x2 [(UnqualComponentName, CondTree ConfVar [Dependency] ForeignLib)]
x3 [(UnqualComponentName, CondTree ConfVar [Dependency] Executable)]
x4 [(UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)]
x5 [(UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)]
x6) =
    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
p
        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
v
        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]
a1
        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 (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) -> Maybe a -> f (Maybe b)
traverse CondTree ConfVar [Dependency] Library
-> f (CondTree ConfVar [Dependency] Library)
forall a.
CondTree ConfVar [Dependency] a
-> f (CondTree ConfVar [Dependency] a)
f Maybe (CondTree ConfVar [Dependency] Library)
x1
        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))
-> [(UnqualComponentName, CondTree ConfVar [Dependency] Library)]
-> f [(UnqualComponentName, CondTree ConfVar [Dependency] Library)]
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] Library)
  -> f (UnqualComponentName, CondTree ConfVar [Dependency] Library))
 -> [(UnqualComponentName, CondTree ConfVar [Dependency] Library)]
 -> f [(UnqualComponentName,
        CondTree ConfVar [Dependency] Library)])
-> ((CondTree ConfVar [Dependency] Library
     -> f (CondTree ConfVar [Dependency] Library))
    -> (UnqualComponentName, CondTree ConfVar [Dependency] Library)
    -> f (UnqualComponentName, CondTree ConfVar [Dependency] Library))
-> (CondTree ConfVar [Dependency] Library
    -> f (CondTree ConfVar [Dependency] Library))
-> [(UnqualComponentName, CondTree ConfVar [Dependency] Library)]
-> f [(UnqualComponentName, CondTree ConfVar [Dependency] Library)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (CondTree ConfVar [Dependency] Library
 -> f (CondTree ConfVar [Dependency] Library))
-> (UnqualComponentName, CondTree ConfVar [Dependency] Library)
-> f (UnqualComponentName, CondTree ConfVar [Dependency] Library)
forall c a b (f :: * -> *).
Functor f =>
LensLike f (c, a) (c, b) a b
_2) CondTree ConfVar [Dependency] Library
-> f (CondTree ConfVar [Dependency] Library)
forall a.
CondTree ConfVar [Dependency] a
-> f (CondTree ConfVar [Dependency] a)
f [(UnqualComponentName, CondTree ConfVar [Dependency] Library)]
x2
        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))
-> [(UnqualComponentName,
     CondTree ConfVar [Dependency] ForeignLib)]
-> f [(UnqualComponentName,
       CondTree ConfVar [Dependency] ForeignLib)]
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] ForeignLib)
  -> f (UnqualComponentName,
        CondTree ConfVar [Dependency] ForeignLib))
 -> [(UnqualComponentName,
      CondTree ConfVar [Dependency] ForeignLib)]
 -> f [(UnqualComponentName,
        CondTree ConfVar [Dependency] ForeignLib)])
-> ((CondTree ConfVar [Dependency] ForeignLib
     -> f (CondTree ConfVar [Dependency] ForeignLib))
    -> (UnqualComponentName, CondTree ConfVar [Dependency] ForeignLib)
    -> f (UnqualComponentName,
          CondTree ConfVar [Dependency] ForeignLib))
-> (CondTree ConfVar [Dependency] ForeignLib
    -> f (CondTree ConfVar [Dependency] ForeignLib))
-> [(UnqualComponentName,
     CondTree ConfVar [Dependency] ForeignLib)]
-> f [(UnqualComponentName,
       CondTree ConfVar [Dependency] ForeignLib)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (CondTree ConfVar [Dependency] ForeignLib
 -> f (CondTree ConfVar [Dependency] ForeignLib))
-> (UnqualComponentName, CondTree ConfVar [Dependency] ForeignLib)
-> f (UnqualComponentName,
      CondTree ConfVar [Dependency] ForeignLib)
forall c a b (f :: * -> *).
Functor f =>
LensLike f (c, a) (c, b) a b
_2) CondTree ConfVar [Dependency] ForeignLib
-> f (CondTree ConfVar [Dependency] ForeignLib)
forall a.
CondTree ConfVar [Dependency] a
-> f (CondTree ConfVar [Dependency] a)
f [(UnqualComponentName, CondTree ConfVar [Dependency] ForeignLib)]
x3
        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)])
-> ((CondTree ConfVar [Dependency] Executable
     -> f (CondTree ConfVar [Dependency] Executable))
    -> (UnqualComponentName, CondTree ConfVar [Dependency] Executable)
    -> f (UnqualComponentName,
          CondTree ConfVar [Dependency] Executable))
-> (CondTree ConfVar [Dependency] Executable
    -> f (CondTree ConfVar [Dependency] Executable))
-> [(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 c a b (f :: * -> *).
Functor f =>
LensLike f (c, a) (c, b) a b
_2) CondTree ConfVar [Dependency] Executable
-> f (CondTree ConfVar [Dependency] Executable)
forall a.
CondTree ConfVar [Dependency] a
-> f (CondTree ConfVar [Dependency] a)
f [(UnqualComponentName, CondTree ConfVar [Dependency] Executable)]
x4
        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)])
-> ((CondTree ConfVar [Dependency] TestSuite
     -> f (CondTree ConfVar [Dependency] TestSuite))
    -> (UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)
    -> f (UnqualComponentName,
          CondTree ConfVar [Dependency] TestSuite))
-> (CondTree ConfVar [Dependency] TestSuite
    -> f (CondTree ConfVar [Dependency] TestSuite))
-> [(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 c a b (f :: * -> *).
Functor f =>
LensLike f (c, a) (c, b) a b
_2) CondTree ConfVar [Dependency] TestSuite
-> f (CondTree ConfVar [Dependency] TestSuite)
forall a.
CondTree ConfVar [Dependency] a
-> f (CondTree ConfVar [Dependency] a)
f [(UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)]
x5
        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)])
-> ((CondTree ConfVar [Dependency] Benchmark
     -> f (CondTree ConfVar [Dependency] Benchmark))
    -> (UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)
    -> f (UnqualComponentName,
          CondTree ConfVar [Dependency] Benchmark))
-> (CondTree ConfVar [Dependency] Benchmark
    -> f (CondTree ConfVar [Dependency] Benchmark))
-> [(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 c a b (f :: * -> *).
Functor f =>
LensLike f (c, a) (c, b) a b
_2) CondTree ConfVar [Dependency] Benchmark
-> f (CondTree ConfVar [Dependency] Benchmark)
forall a.
CondTree ConfVar [Dependency] a
-> f (CondTree ConfVar [Dependency] a)
f [(UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)]
x6
flagName :: Lens' PackageFlag FlagName
flagName :: Lens' PackageFlag FlagName
flagName FlagName -> f FlagName
f (MkPackageFlag FlagName
x1 String
x2 Bool
x3 Bool
x4) = (FlagName -> PackageFlag) -> f FlagName -> f PackageFlag
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\FlagName
y1 -> FlagName -> String -> Bool -> Bool -> PackageFlag
MkPackageFlag FlagName
y1 String
x2 Bool
x3 Bool
x4) (FlagName -> f FlagName
f FlagName
x1)
{-# INLINE flagName #-}
flagDescription :: Lens' PackageFlag String
flagDescription :: Lens' PackageFlag String
flagDescription String -> f String
f (MkPackageFlag FlagName
x1 String
x2 Bool
x3 Bool
x4) = (String -> PackageFlag) -> f String -> f PackageFlag
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\String
y1 -> FlagName -> String -> Bool -> Bool -> PackageFlag
MkPackageFlag FlagName
x1 String
y1 Bool
x3 Bool
x4) (String -> f String
f String
x2)
{-# INLINE flagDescription #-}
flagDefault :: Lens' PackageFlag Bool
flagDefault :: Lens' PackageFlag Bool
flagDefault Bool -> f Bool
f (MkPackageFlag FlagName
x1 String
x2 Bool
x3 Bool
x4) = (Bool -> PackageFlag) -> f Bool -> f PackageFlag
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\Bool
y1 -> FlagName -> String -> Bool -> Bool -> PackageFlag
MkPackageFlag FlagName
x1 String
x2 Bool
y1 Bool
x4) (Bool -> f Bool
f Bool
x3)
{-# INLINE flagDefault #-}
flagManual :: Lens' PackageFlag Bool
flagManual :: Lens' PackageFlag Bool
flagManual Bool -> f Bool
f (MkPackageFlag FlagName
x1 String
x2 Bool
x3 Bool
x4) = (Bool -> PackageFlag) -> f Bool -> f PackageFlag
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\Bool
y1 -> FlagName -> String -> Bool -> Bool -> PackageFlag
MkPackageFlag FlagName
x1 String
x2 Bool
x3 Bool
y1) (Bool -> f Bool
f Bool
x4)
{-# INLINE flagManual #-}
_OS :: Traversal' ConfVar OS
_OS :: Traversal' ConfVar OS
_OS OS -> f OS
f (OS OS
os) = OS -> ConfVar
OS (OS -> ConfVar) -> f OS -> f ConfVar
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> OS -> f OS
f OS
os
_OS OS -> f OS
_ ConfVar
x       = ConfVar -> f ConfVar
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ConfVar
x
_Arch :: Traversal' ConfVar Arch
_Arch :: Traversal' ConfVar Arch
_Arch Arch -> f Arch
f (Arch Arch
arch) = Arch -> ConfVar
Arch (Arch -> ConfVar) -> f Arch -> f ConfVar
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Arch -> f Arch
f Arch
arch
_Arch Arch -> f Arch
_ ConfVar
x           = ConfVar -> f ConfVar
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ConfVar
x
_PackageFlag :: Traversal' ConfVar FlagName
_PackageFlag :: Traversal' ConfVar FlagName
_PackageFlag FlagName -> f FlagName
f (PackageFlag FlagName
flag) = FlagName -> ConfVar
PackageFlag (FlagName -> ConfVar) -> f FlagName -> f ConfVar
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> FlagName -> f FlagName
f FlagName
flag
_PackageFlag FlagName -> f FlagName
_ ConfVar
x                  = ConfVar -> f ConfVar
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ConfVar
x
_Impl :: Traversal' ConfVar (CompilerFlavor, VersionRange)
_Impl :: Traversal' ConfVar (CompilerFlavor, VersionRange)
_Impl (CompilerFlavor, VersionRange) -> f (CompilerFlavor, VersionRange)
f (Impl CompilerFlavor
cf VersionRange
vr) = (CompilerFlavor -> VersionRange -> ConfVar)
-> (CompilerFlavor, VersionRange) -> ConfVar
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry CompilerFlavor -> VersionRange -> ConfVar
Impl ((CompilerFlavor, VersionRange) -> ConfVar)
-> f (CompilerFlavor, VersionRange) -> f ConfVar
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (CompilerFlavor, VersionRange) -> f (CompilerFlavor, VersionRange)
f (CompilerFlavor
cf, VersionRange
vr)
_Impl (CompilerFlavor, VersionRange) -> f (CompilerFlavor, VersionRange)
_ ConfVar
x            = ConfVar -> f ConfVar
forall a. a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
pure ConfVar
x