{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RankNTypes #-}
module Distribution.Types.PackageDescription.Lens (
PackageDescription,
module Distribution.Types.PackageDescription.Lens,
) where
import Distribution.Compat.Lens
import Distribution.Compat.Prelude
import Prelude ()
import Distribution.Compiler (CompilerFlavor)
import Distribution.License (License)
import Distribution.ModuleName (ModuleName)
import Distribution.Types.Benchmark (Benchmark, benchmarkModules)
import Distribution.Types.Benchmark.Lens (benchmarkBuildInfo, benchmarkName)
import Distribution.Types.BuildInfo (BuildInfo)
import Distribution.Types.BuildType (BuildType)
import Distribution.Types.ComponentName (ComponentName (..))
import Distribution.Types.Executable (Executable, exeModules)
import Distribution.Types.Executable.Lens (exeBuildInfo, exeName)
import Distribution.Types.ForeignLib (ForeignLib, foreignLibModules)
import Distribution.Types.ForeignLib.Lens (foreignLibBuildInfo, foreignLibName)
import Distribution.Types.Library (Library, explicitLibModules)
import Distribution.Types.Library.Lens (libBuildInfo, libName)
import Distribution.Types.PackageDescription (PackageDescription)
import Distribution.Types.PackageId (PackageIdentifier)
import Distribution.Types.SetupBuildInfo (SetupBuildInfo)
import Distribution.Types.SourceRepo (SourceRepo)
import Distribution.Types.TestSuite (TestSuite, testModules)
import Distribution.Types.TestSuite.Lens (testBuildInfo, testName)
import Distribution.Utils.ShortText (ShortText)
import Distribution.Version (Version, VersionRange)
import qualified Distribution.SPDX as SPDX
import qualified Distribution.Types.PackageDescription as T
package :: Lens' PackageDescription PackageIdentifier
package :: LensLike
f
PackageDescription
PackageDescription
PackageIdentifier
PackageIdentifier
package PackageIdentifier -> f PackageIdentifier
f PackageDescription
s = (PackageIdentifier -> PackageDescription)
-> f PackageIdentifier -> f PackageDescription
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Functor f
fmap (\PackageIdentifier
x -> PackageDescription
s { package :: PackageIdentifier
T.package = PackageIdentifier
x }) (PackageIdentifier -> f PackageIdentifier
f (PackageDescription -> PackageIdentifier
T.package PackageDescription
s))
{-# INLINE package #-}
licenseRaw :: Lens' PackageDescription (Either SPDX.License License)
licenseRaw :: LensLike
f
PackageDescription
PackageDescription
(Either License License)
(Either License License)
licenseRaw Either License License -> f (Either License License)
f PackageDescription
s = (Either License License -> PackageDescription)
-> f (Either License License) -> f PackageDescription
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Functor f
fmap (\Either License License
x -> PackageDescription
s { licenseRaw :: Either License License
T.licenseRaw = Either License License
x }) (Either License License -> f (Either License License)
f (PackageDescription -> Either License License
T.licenseRaw PackageDescription
s))
{-# INLINE licenseRaw #-}
licenseFiles :: Lens' PackageDescription [FilePath]
licenseFiles :: LensLike
f PackageDescription PackageDescription [FilePath] [FilePath]
licenseFiles [FilePath] -> f [FilePath]
f PackageDescription
s = ([FilePath] -> PackageDescription)
-> f [FilePath] -> f PackageDescription
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Functor f
fmap (\[FilePath]
x -> PackageDescription
s { licenseFiles :: [FilePath]
T.licenseFiles = [FilePath]
x }) ([FilePath] -> f [FilePath]
f (PackageDescription -> [FilePath]
T.licenseFiles PackageDescription
s))
{-# INLINE licenseFiles #-}
copyright :: Lens' PackageDescription ShortText
copyright :: LensLike
f PackageDescription PackageDescription ShortText ShortText
copyright ShortText -> f ShortText
f PackageDescription
s = (ShortText -> PackageDescription)
-> f ShortText -> f PackageDescription
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Functor f
fmap (\ShortText
x -> PackageDescription
s { copyright :: ShortText
T.copyright = ShortText
x }) (ShortText -> f ShortText
f (PackageDescription -> ShortText
T.copyright PackageDescription
s))
{-# INLINE copyright #-}
maintainer :: Lens' PackageDescription ShortText
maintainer :: LensLike
f PackageDescription PackageDescription ShortText ShortText
maintainer ShortText -> f ShortText
f PackageDescription
s = (ShortText -> PackageDescription)
-> f ShortText -> f PackageDescription
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Functor f
fmap (\ShortText
x -> PackageDescription
s { maintainer :: ShortText
T.maintainer = ShortText
x }) (ShortText -> f ShortText
f (PackageDescription -> ShortText
T.maintainer PackageDescription
s))
{-# INLINE maintainer #-}
author :: Lens' PackageDescription ShortText
author :: LensLike
f PackageDescription PackageDescription ShortText ShortText
author ShortText -> f ShortText
f PackageDescription
s = (ShortText -> PackageDescription)
-> f ShortText -> f PackageDescription
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Functor f
fmap (\ShortText
x -> PackageDescription
s { author :: ShortText
T.author = ShortText
x }) (ShortText -> f ShortText
f (PackageDescription -> ShortText
T.author PackageDescription
s))
{-# INLINE author #-}
stability :: Lens' PackageDescription ShortText
stability :: LensLike
f PackageDescription PackageDescription ShortText ShortText
stability ShortText -> f ShortText
f PackageDescription
s = (ShortText -> PackageDescription)
-> f ShortText -> f PackageDescription
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Functor f
fmap (\ShortText
x -> PackageDescription
s { stability :: ShortText
T.stability = ShortText
x }) (ShortText -> f ShortText
f (PackageDescription -> ShortText
T.stability PackageDescription
s))
{-# INLINE stability #-}
testedWith :: Lens' PackageDescription [(CompilerFlavor,VersionRange)]
testedWith :: LensLike
f
PackageDescription
PackageDescription
[(CompilerFlavor, VersionRange)]
[(CompilerFlavor, VersionRange)]
testedWith [(CompilerFlavor, VersionRange)]
-> f [(CompilerFlavor, VersionRange)]
f PackageDescription
s = ([(CompilerFlavor, VersionRange)] -> PackageDescription)
-> f [(CompilerFlavor, VersionRange)] -> f PackageDescription
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Functor f
fmap (\[(CompilerFlavor, VersionRange)]
x -> PackageDescription
s { testedWith :: [(CompilerFlavor, VersionRange)]
T.testedWith = [(CompilerFlavor, VersionRange)]
x }) ([(CompilerFlavor, VersionRange)]
-> f [(CompilerFlavor, VersionRange)]
f (PackageDescription -> [(CompilerFlavor, VersionRange)]
T.testedWith PackageDescription
s))
{-# INLINE testedWith #-}
homepage :: Lens' PackageDescription ShortText
homepage :: LensLike
f PackageDescription PackageDescription ShortText ShortText
homepage ShortText -> f ShortText
f PackageDescription
s = (ShortText -> PackageDescription)
-> f ShortText -> f PackageDescription
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Functor f
fmap (\ShortText
x -> PackageDescription
s { homepage :: ShortText
T.homepage = ShortText
x }) (ShortText -> f ShortText
f (PackageDescription -> ShortText
T.homepage PackageDescription
s))
{-# INLINE homepage #-}
pkgUrl :: Lens' PackageDescription ShortText
pkgUrl :: LensLike
f PackageDescription PackageDescription ShortText ShortText
pkgUrl ShortText -> f ShortText
f PackageDescription
s = (ShortText -> PackageDescription)
-> f ShortText -> f PackageDescription
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Functor f
fmap (\ShortText
x -> PackageDescription
s { pkgUrl :: ShortText
T.pkgUrl = ShortText
x }) (ShortText -> f ShortText
f (PackageDescription -> ShortText
T.pkgUrl PackageDescription
s))
{-# INLINE pkgUrl #-}
bugReports :: Lens' PackageDescription ShortText
bugReports :: LensLike
f PackageDescription PackageDescription ShortText ShortText
bugReports ShortText -> f ShortText
f PackageDescription
s = (ShortText -> PackageDescription)
-> f ShortText -> f PackageDescription
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Functor f
fmap (\ShortText
x -> PackageDescription
s { bugReports :: ShortText
T.bugReports = ShortText
x }) (ShortText -> f ShortText
f (PackageDescription -> ShortText
T.bugReports PackageDescription
s))
{-# INLINE bugReports #-}
sourceRepos :: Lens' PackageDescription [SourceRepo]
sourceRepos :: LensLike
f PackageDescription PackageDescription [SourceRepo] [SourceRepo]
sourceRepos [SourceRepo] -> f [SourceRepo]
f PackageDescription
s = ([SourceRepo] -> PackageDescription)
-> f [SourceRepo] -> f PackageDescription
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Functor f
fmap (\[SourceRepo]
x -> PackageDescription
s { sourceRepos :: [SourceRepo]
T.sourceRepos = [SourceRepo]
x }) ([SourceRepo] -> f [SourceRepo]
f (PackageDescription -> [SourceRepo]
T.sourceRepos PackageDescription
s))
{-# INLINE sourceRepos #-}
synopsis :: Lens' PackageDescription ShortText
synopsis :: LensLike
f PackageDescription PackageDescription ShortText ShortText
synopsis ShortText -> f ShortText
f PackageDescription
s = (ShortText -> PackageDescription)
-> f ShortText -> f PackageDescription
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Functor f
fmap (\ShortText
x -> PackageDescription
s { synopsis :: ShortText
T.synopsis = ShortText
x }) (ShortText -> f ShortText
f (PackageDescription -> ShortText
T.synopsis PackageDescription
s))
{-# INLINE synopsis #-}
description :: Lens' PackageDescription ShortText
description :: LensLike
f PackageDescription PackageDescription ShortText ShortText
description ShortText -> f ShortText
f PackageDescription
s = (ShortText -> PackageDescription)
-> f ShortText -> f PackageDescription
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Functor f
fmap (\ShortText
x -> PackageDescription
s { description :: ShortText
T.description = ShortText
x }) (ShortText -> f ShortText
f (PackageDescription -> ShortText
T.description PackageDescription
s))
{-# INLINE description #-}
category :: Lens' PackageDescription ShortText
category :: LensLike
f PackageDescription PackageDescription ShortText ShortText
category ShortText -> f ShortText
f PackageDescription
s = (ShortText -> PackageDescription)
-> f ShortText -> f PackageDescription
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Functor f
fmap (\ShortText
x -> PackageDescription
s { category :: ShortText
T.category = ShortText
x }) (ShortText -> f ShortText
f (PackageDescription -> ShortText
T.category PackageDescription
s))
{-# INLINE category #-}
customFieldsPD :: Lens' PackageDescription [(String,String)]
customFieldsPD :: LensLike
f
PackageDescription
PackageDescription
[(FilePath, FilePath)]
[(FilePath, FilePath)]
customFieldsPD [(FilePath, FilePath)] -> f [(FilePath, FilePath)]
f PackageDescription
s = ([(FilePath, FilePath)] -> PackageDescription)
-> f [(FilePath, FilePath)] -> f PackageDescription
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Functor f
fmap (\[(FilePath, FilePath)]
x -> PackageDescription
s { customFieldsPD :: [(FilePath, FilePath)]
T.customFieldsPD = [(FilePath, FilePath)]
x }) ([(FilePath, FilePath)] -> f [(FilePath, FilePath)]
f (PackageDescription -> [(FilePath, FilePath)]
T.customFieldsPD PackageDescription
s))
{-# INLINE customFieldsPD #-}
specVersionRaw :: Lens' PackageDescription (Either Version VersionRange)
specVersionRaw :: LensLike
f
PackageDescription
PackageDescription
(Either Version VersionRange)
(Either Version VersionRange)
specVersionRaw Either Version VersionRange -> f (Either Version VersionRange)
f PackageDescription
s = (Either Version VersionRange -> PackageDescription)
-> f (Either Version VersionRange) -> f PackageDescription
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Functor f
fmap (\Either Version VersionRange
x -> PackageDescription
s { specVersionRaw :: Either Version VersionRange
T.specVersionRaw = Either Version VersionRange
x }) (Either Version VersionRange -> f (Either Version VersionRange)
f (PackageDescription -> Either Version VersionRange
T.specVersionRaw PackageDescription
s))
{-# INLINE specVersionRaw #-}
buildTypeRaw :: Lens' PackageDescription (Maybe BuildType)
buildTypeRaw :: LensLike
f
PackageDescription
PackageDescription
(Maybe BuildType)
(Maybe BuildType)
buildTypeRaw Maybe BuildType -> f (Maybe BuildType)
f PackageDescription
s = (Maybe BuildType -> PackageDescription)
-> f (Maybe BuildType) -> f PackageDescription
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Functor f
fmap (\Maybe BuildType
x -> PackageDescription
s { buildTypeRaw :: Maybe BuildType
T.buildTypeRaw = Maybe BuildType
x }) (Maybe BuildType -> f (Maybe BuildType)
f (PackageDescription -> Maybe BuildType
T.buildTypeRaw PackageDescription
s))
{-# INLINE buildTypeRaw #-}
setupBuildInfo :: Lens' PackageDescription (Maybe SetupBuildInfo)
setupBuildInfo :: LensLike
f
PackageDescription
PackageDescription
(Maybe SetupBuildInfo)
(Maybe SetupBuildInfo)
setupBuildInfo Maybe SetupBuildInfo -> f (Maybe SetupBuildInfo)
f PackageDescription
s = (Maybe SetupBuildInfo -> PackageDescription)
-> f (Maybe SetupBuildInfo) -> f PackageDescription
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Functor f
fmap (\Maybe SetupBuildInfo
x -> PackageDescription
s { setupBuildInfo :: Maybe SetupBuildInfo
T.setupBuildInfo = Maybe SetupBuildInfo
x }) (Maybe SetupBuildInfo -> f (Maybe SetupBuildInfo)
f (PackageDescription -> Maybe SetupBuildInfo
T.setupBuildInfo PackageDescription
s))
{-# INLINE setupBuildInfo #-}
library :: Lens' PackageDescription (Maybe Library)
library :: LensLike
f
PackageDescription
PackageDescription
(Maybe Library)
(Maybe Library)
library Maybe Library -> f (Maybe Library)
f PackageDescription
s = (Maybe Library -> PackageDescription)
-> f (Maybe Library) -> f PackageDescription
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Functor f
fmap (\Maybe Library
x -> PackageDescription
s { library :: Maybe Library
T.library = Maybe Library
x }) (Maybe Library -> f (Maybe Library)
f (PackageDescription -> Maybe Library
T.library PackageDescription
s))
{-# INLINE library #-}
subLibraries :: Lens' PackageDescription [Library]
subLibraries :: LensLike
f PackageDescription PackageDescription [Library] [Library]
subLibraries [Library] -> f [Library]
f PackageDescription
s = ([Library] -> PackageDescription)
-> f [Library] -> f PackageDescription
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Functor f
fmap (\[Library]
x -> PackageDescription
s { subLibraries :: [Library]
T.subLibraries = [Library]
x }) ([Library] -> f [Library]
f (PackageDescription -> [Library]
T.subLibraries PackageDescription
s))
{-# INLINE subLibraries #-}
executables :: Lens' PackageDescription [Executable]
executables :: LensLike
f PackageDescription PackageDescription [Executable] [Executable]
executables [Executable] -> f [Executable]
f PackageDescription
s = ([Executable] -> PackageDescription)
-> f [Executable] -> f PackageDescription
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Functor f
fmap (\[Executable]
x -> PackageDescription
s { executables :: [Executable]
T.executables = [Executable]
x }) ([Executable] -> f [Executable]
f (PackageDescription -> [Executable]
T.executables PackageDescription
s))
{-# INLINE executables #-}
foreignLibs :: Lens' PackageDescription [ForeignLib]
foreignLibs :: LensLike
f PackageDescription PackageDescription [ForeignLib] [ForeignLib]
foreignLibs [ForeignLib] -> f [ForeignLib]
f PackageDescription
s = ([ForeignLib] -> PackageDescription)
-> f [ForeignLib] -> f PackageDescription
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Functor f
fmap (\[ForeignLib]
x -> PackageDescription
s { foreignLibs :: [ForeignLib]
T.foreignLibs = [ForeignLib]
x }) ([ForeignLib] -> f [ForeignLib]
f (PackageDescription -> [ForeignLib]
T.foreignLibs PackageDescription
s))
{-# INLINE foreignLibs #-}
testSuites :: Lens' PackageDescription [TestSuite]
testSuites :: LensLike
f PackageDescription PackageDescription [TestSuite] [TestSuite]
testSuites [TestSuite] -> f [TestSuite]
f PackageDescription
s = ([TestSuite] -> PackageDescription)
-> f [TestSuite] -> f PackageDescription
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Functor f
fmap (\[TestSuite]
x -> PackageDescription
s { testSuites :: [TestSuite]
T.testSuites = [TestSuite]
x }) ([TestSuite] -> f [TestSuite]
f (PackageDescription -> [TestSuite]
T.testSuites PackageDescription
s))
{-# INLINE testSuites #-}
benchmarks :: Lens' PackageDescription [Benchmark]
benchmarks :: LensLike
f PackageDescription PackageDescription [Benchmark] [Benchmark]
benchmarks [Benchmark] -> f [Benchmark]
f PackageDescription
s = ([Benchmark] -> PackageDescription)
-> f [Benchmark] -> f PackageDescription
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Functor f
fmap (\[Benchmark]
x -> PackageDescription
s { benchmarks :: [Benchmark]
T.benchmarks = [Benchmark]
x }) ([Benchmark] -> f [Benchmark]
f (PackageDescription -> [Benchmark]
T.benchmarks PackageDescription
s))
{-# INLINE benchmarks #-}
dataFiles :: Lens' PackageDescription [FilePath]
dataFiles :: LensLike
f PackageDescription PackageDescription [FilePath] [FilePath]
dataFiles [FilePath] -> f [FilePath]
f PackageDescription
s = ([FilePath] -> PackageDescription)
-> f [FilePath] -> f PackageDescription
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Functor f
fmap (\[FilePath]
x -> PackageDescription
s { dataFiles :: [FilePath]
T.dataFiles = [FilePath]
x }) ([FilePath] -> f [FilePath]
f (PackageDescription -> [FilePath]
T.dataFiles PackageDescription
s))
{-# INLINE dataFiles #-}
dataDir :: Lens' PackageDescription FilePath
dataDir :: LensLike f PackageDescription PackageDescription FilePath FilePath
dataDir FilePath -> f FilePath
f PackageDescription
s = (FilePath -> PackageDescription)
-> f FilePath -> f PackageDescription
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Functor f
fmap (\FilePath
x -> PackageDescription
s { dataDir :: FilePath
T.dataDir = FilePath
x }) (FilePath -> f FilePath
f (PackageDescription -> FilePath
T.dataDir PackageDescription
s))
{-# INLINE dataDir #-}
extraSrcFiles :: Lens' PackageDescription [String]
[FilePath] -> f [FilePath]
f PackageDescription
s = ([FilePath] -> PackageDescription)
-> f [FilePath] -> f PackageDescription
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Functor f
fmap (\[FilePath]
x -> PackageDescription
s { extraSrcFiles :: [FilePath]
T.extraSrcFiles = [FilePath]
x }) ([FilePath] -> f [FilePath]
f (PackageDescription -> [FilePath]
T.extraSrcFiles PackageDescription
s))
{-# INLINE extraSrcFiles #-}
extraTmpFiles :: Lens' PackageDescription [String]
[FilePath] -> f [FilePath]
f PackageDescription
s = ([FilePath] -> PackageDescription)
-> f [FilePath] -> f PackageDescription
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Functor f
fmap (\[FilePath]
x -> PackageDescription
s { extraTmpFiles :: [FilePath]
T.extraTmpFiles = [FilePath]
x }) ([FilePath] -> f [FilePath]
f (PackageDescription -> [FilePath]
T.extraTmpFiles PackageDescription
s))
{-# INLINE extraTmpFiles #-}
extraDocFiles :: Lens' PackageDescription [String]
[FilePath] -> f [FilePath]
f PackageDescription
s = ([FilePath] -> PackageDescription)
-> f [FilePath] -> f PackageDescription
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Functor f
fmap (\[FilePath]
x -> PackageDescription
s { extraDocFiles :: [FilePath]
T.extraDocFiles = [FilePath]
x }) ([FilePath] -> f [FilePath]
f (PackageDescription -> [FilePath]
T.extraDocFiles PackageDescription
s))
{-# INLINE extraDocFiles #-}
allLibraries :: Traversal' PackageDescription Library
allLibraries :: LensLike f PackageDescription PackageDescription Library Library
allLibraries Library -> f Library
f PackageDescription
pd = Maybe Library -> [Library] -> PackageDescription
mk (Maybe Library -> [Library] -> PackageDescription)
-> f (Maybe Library) -> f ([Library] -> PackageDescription)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type forall (f :: * -> *). Applicative f => Functor f
Evidence bound by a type signature of the constraint type Applicative f
<$> (Library -> f Library) -> Maybe Library -> f (Maybe Library)
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
Evidence bound by a type signature of the constraint type Applicative f
External instance of the constraint type Traversable Maybe
traverse Library -> f Library
f (PackageDescription -> Maybe Library
T.library PackageDescription
pd) f ([Library] -> PackageDescription)
-> f [Library] -> f PackageDescription
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Applicative f
<*> (Library -> f Library) -> [Library] -> f [Library]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
Evidence bound by a type signature of the constraint type Applicative f
External instance of the constraint type Traversable []
traverse Library -> f Library
f (PackageDescription -> [Library]
T.subLibraries PackageDescription
pd)
where
mk :: Maybe Library -> [Library] -> PackageDescription
mk Maybe Library
l [Library]
ls = PackageDescription
pd { library :: Maybe Library
T.library = Maybe Library
l, subLibraries :: [Library]
T.subLibraries = [Library]
ls }
componentModules :: Monoid r => ComponentName -> Getting r PackageDescription [ModuleName]
componentModules :: ComponentName -> Getting r PackageDescription [ModuleName]
componentModules ComponentName
cname = case ComponentName
cname of
CLibName LibraryName
name ->
LibraryName
-> Traversal' PackageDescription Library
-> Lens' Library LibraryName
-> (Library -> [ModuleName])
-> Getting r PackageDescription [ModuleName]
forall name r a.
(Eq name, Monoid r) =>
name
-> Traversal' PackageDescription a
-> Lens' a name
-> (a -> [ModuleName])
-> Getting r PackageDescription [ModuleName]
Evidence bound by a type signature of the constraint type Monoid r
External instance of the constraint type Eq LibraryName
componentModules' LibraryName
name Traversal' PackageDescription Library
Evidence bound by a HsWrapper of the constraint type Applicative f
Evidence bound by a HsWrapper of the constraint type Applicative f
allLibraries Lens' Library LibraryName
Evidence bound by a HsWrapper of the constraint type Functor f
Evidence bound by a HsWrapper of the constraint type Functor f
libName Library -> [ModuleName]
explicitLibModules
CFLibName UnqualComponentName
name ->
UnqualComponentName
-> Traversal' PackageDescription ForeignLib
-> Lens' ForeignLib UnqualComponentName
-> (ForeignLib -> [ModuleName])
-> Getting r PackageDescription [ModuleName]
forall name r a.
(Eq name, Monoid r) =>
name
-> Traversal' PackageDescription a
-> Lens' a name
-> (a -> [ModuleName])
-> Getting r PackageDescription [ModuleName]
Evidence bound by a type signature of the constraint type Monoid r
External instance of the constraint type Eq UnqualComponentName
componentModules' UnqualComponentName
name (LensLike
f PackageDescription PackageDescription [ForeignLib] [ForeignLib]
Lens' PackageDescription [ForeignLib]
External instance of the constraint type forall (f :: * -> *). Applicative f => Functor f
Evidence bound by a HsWrapper of the constraint type Applicative f
foreignLibs LensLike
f PackageDescription PackageDescription [ForeignLib] [ForeignLib]
-> ((ForeignLib -> f ForeignLib) -> [ForeignLib] -> f [ForeignLib])
-> (ForeignLib -> f ForeignLib)
-> PackageDescription
-> f PackageDescription
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ForeignLib -> f ForeignLib) -> [ForeignLib] -> f [ForeignLib]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
Evidence bound by a HsWrapper of the constraint type Applicative f
External instance of the constraint type Traversable []
traverse) Lens' ForeignLib UnqualComponentName
Evidence bound by a HsWrapper of the constraint type Functor f
Evidence bound by a HsWrapper of the constraint type Functor f
foreignLibName ForeignLib -> [ModuleName]
foreignLibModules
CExeName UnqualComponentName
name ->
UnqualComponentName
-> Traversal' PackageDescription Executable
-> Lens' Executable UnqualComponentName
-> (Executable -> [ModuleName])
-> Getting r PackageDescription [ModuleName]
forall name r a.
(Eq name, Monoid r) =>
name
-> Traversal' PackageDescription a
-> Lens' a name
-> (a -> [ModuleName])
-> Getting r PackageDescription [ModuleName]
Evidence bound by a type signature of the constraint type Monoid r
External instance of the constraint type Eq UnqualComponentName
componentModules' UnqualComponentName
name (LensLike
f PackageDescription PackageDescription [Executable] [Executable]
Lens' PackageDescription [Executable]
External instance of the constraint type forall (f :: * -> *). Applicative f => Functor f
Evidence bound by a HsWrapper of the constraint type Applicative f
executables LensLike
f PackageDescription PackageDescription [Executable] [Executable]
-> ((Executable -> f Executable) -> [Executable] -> f [Executable])
-> (Executable -> f Executable)
-> PackageDescription
-> f PackageDescription
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Executable -> f Executable) -> [Executable] -> f [Executable]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
Evidence bound by a HsWrapper of the constraint type Applicative f
External instance of the constraint type Traversable []
traverse) Lens' Executable UnqualComponentName
Evidence bound by a HsWrapper of the constraint type Functor f
Evidence bound by a HsWrapper of the constraint type Functor f
exeName Executable -> [ModuleName]
exeModules
CTestName UnqualComponentName
name ->
UnqualComponentName
-> Traversal' PackageDescription TestSuite
-> Lens' TestSuite UnqualComponentName
-> (TestSuite -> [ModuleName])
-> Getting r PackageDescription [ModuleName]
forall name r a.
(Eq name, Monoid r) =>
name
-> Traversal' PackageDescription a
-> Lens' a name
-> (a -> [ModuleName])
-> Getting r PackageDescription [ModuleName]
Evidence bound by a type signature of the constraint type Monoid r
External instance of the constraint type Eq UnqualComponentName
componentModules' UnqualComponentName
name (LensLike
f PackageDescription PackageDescription [TestSuite] [TestSuite]
Lens' PackageDescription [TestSuite]
External instance of the constraint type forall (f :: * -> *). Applicative f => Functor f
Evidence bound by a HsWrapper of the constraint type Applicative f
testSuites LensLike
f PackageDescription PackageDescription [TestSuite] [TestSuite]
-> ((TestSuite -> f TestSuite) -> [TestSuite] -> f [TestSuite])
-> (TestSuite -> f TestSuite)
-> PackageDescription
-> f PackageDescription
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (TestSuite -> f TestSuite) -> [TestSuite] -> f [TestSuite]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
Evidence bound by a HsWrapper of the constraint type Applicative f
External instance of the constraint type Traversable []
traverse) Lens' TestSuite UnqualComponentName
Evidence bound by a HsWrapper of the constraint type Functor f
Evidence bound by a HsWrapper of the constraint type Functor f
testName TestSuite -> [ModuleName]
testModules
CBenchName UnqualComponentName
name ->
UnqualComponentName
-> Traversal' PackageDescription Benchmark
-> Lens' Benchmark UnqualComponentName
-> (Benchmark -> [ModuleName])
-> Getting r PackageDescription [ModuleName]
forall name r a.
(Eq name, Monoid r) =>
name
-> Traversal' PackageDescription a
-> Lens' a name
-> (a -> [ModuleName])
-> Getting r PackageDescription [ModuleName]
Evidence bound by a type signature of the constraint type Monoid r
External instance of the constraint type Eq UnqualComponentName
componentModules' UnqualComponentName
name (LensLike
f PackageDescription PackageDescription [Benchmark] [Benchmark]
Lens' PackageDescription [Benchmark]
External instance of the constraint type forall (f :: * -> *). Applicative f => Functor f
Evidence bound by a HsWrapper of the constraint type Applicative f
benchmarks LensLike
f PackageDescription PackageDescription [Benchmark] [Benchmark]
-> ((Benchmark -> f Benchmark) -> [Benchmark] -> f [Benchmark])
-> (Benchmark -> f Benchmark)
-> PackageDescription
-> f PackageDescription
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Benchmark -> f Benchmark) -> [Benchmark] -> f [Benchmark]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
Evidence bound by a HsWrapper of the constraint type Applicative f
External instance of the constraint type Traversable []
traverse) Lens' Benchmark UnqualComponentName
Evidence bound by a HsWrapper of the constraint type Functor f
Evidence bound by a HsWrapper of the constraint type Functor f
benchmarkName Benchmark -> [ModuleName]
benchmarkModules
where
componentModules'
:: (Eq name, Monoid r)
=> name
-> Traversal' PackageDescription a
-> Lens' a name
-> (a -> [ModuleName])
-> Getting r PackageDescription [ModuleName]
componentModules' :: name
-> Traversal' PackageDescription a
-> Lens' a name
-> (a -> [ModuleName])
-> Getting r PackageDescription [ModuleName]
componentModules' name
name Traversal' PackageDescription a
pdL Lens' a name
nameL a -> [ModuleName]
modules =
LensLike (Const r) PackageDescription PackageDescription a a
Traversal' PackageDescription a
External instance of the constraint type forall m. Monoid m => Applicative (Const m)
Evidence bound by a type signature of the constraint type Monoid r
pdL
LensLike (Const r) PackageDescription PackageDescription a a
-> (([ModuleName] -> Const r [ModuleName]) -> a -> Const r a)
-> Getting r PackageDescription [ModuleName]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> Bool) -> Traversal' a a
forall a. (a -> Bool) -> Traversal' a a
filtered ((name -> name -> Bool
forall a. Eq a => a -> a -> Bool
Evidence bound by a type signature of the constraint type Eq name
== name
name) (name -> Bool) -> (a -> name) -> a -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Getting name a name -> a -> name
forall a s. Getting a s a -> s -> a
view Getting name a name
Lens' a name
External instance of the constraint type forall m. Functor (Const m)
nameL)
LensLike (Const r) a a a a
-> (([ModuleName] -> Const r [ModuleName]) -> a -> Const r a)
-> ([ModuleName] -> Const r [ModuleName])
-> a
-> Const r a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> [ModuleName])
-> ([ModuleName] -> Const r [ModuleName]) -> a -> Const r a
forall s a r. (s -> a) -> Getting r s a
getting a -> [ModuleName]
modules
filtered :: (a -> Bool) -> Traversal' a a
filtered :: (a -> Bool) -> Traversal' a a
filtered a -> Bool
p a -> f a
f a
s = if a -> Bool
p a
s then a -> f a
f a
s else a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
Evidence bound by a HsWrapper of the constraint type Applicative f
pure a
s
componentBuildInfo :: ComponentName -> Traversal' PackageDescription BuildInfo
componentBuildInfo :: ComponentName -> Traversal' PackageDescription BuildInfo
componentBuildInfo ComponentName
cname = case ComponentName
cname of
CLibName LibraryName
name ->
LibraryName
-> Traversal' PackageDescription Library
-> Lens' Library LibraryName
-> Traversal' Library BuildInfo
-> Traversal' PackageDescription BuildInfo
forall name a.
Eq name =>
name
-> Traversal' PackageDescription a
-> Lens' a name
-> Traversal' a BuildInfo
-> Traversal' PackageDescription BuildInfo
External instance of the constraint type Eq LibraryName
componentBuildInfo' LibraryName
name Traversal' PackageDescription Library
Evidence bound by a HsWrapper of the constraint type Applicative f
Evidence bound by a HsWrapper of the constraint type Applicative f
allLibraries Lens' Library LibraryName
Evidence bound by a HsWrapper of the constraint type Functor f
Evidence bound by a HsWrapper of the constraint type Functor f
libName Lens' Library BuildInfo
Traversal' Library BuildInfo
External instance of the constraint type forall (f :: * -> *). Applicative f => Functor f
Evidence bound by a HsWrapper of the constraint type Applicative f
External instance of the constraint type forall (f :: * -> *). Applicative f => Functor f
Evidence bound by a HsWrapper of the constraint type Applicative f
Evidence bound by a HsWrapper of the constraint type Applicative f
External instance of the constraint type forall (f :: * -> *). Applicative f => Functor f
libBuildInfo
CFLibName UnqualComponentName
name ->
UnqualComponentName
-> Traversal' PackageDescription ForeignLib
-> Lens' ForeignLib UnqualComponentName
-> Traversal' ForeignLib BuildInfo
-> Traversal' PackageDescription BuildInfo
forall name a.
Eq name =>
name
-> Traversal' PackageDescription a
-> Lens' a name
-> Traversal' a BuildInfo
-> Traversal' PackageDescription BuildInfo
External instance of the constraint type Eq UnqualComponentName
componentBuildInfo' UnqualComponentName
name (LensLike
f PackageDescription PackageDescription [ForeignLib] [ForeignLib]
Lens' PackageDescription [ForeignLib]
External instance of the constraint type forall (f :: * -> *). Applicative f => Functor f
Evidence bound by a HsWrapper of the constraint type Applicative f
foreignLibs LensLike
f PackageDescription PackageDescription [ForeignLib] [ForeignLib]
-> ((ForeignLib -> f ForeignLib) -> [ForeignLib] -> f [ForeignLib])
-> (ForeignLib -> f ForeignLib)
-> PackageDescription
-> f PackageDescription
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ForeignLib -> f ForeignLib) -> [ForeignLib] -> f [ForeignLib]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
Evidence bound by a HsWrapper of the constraint type Applicative f
External instance of the constraint type Traversable []
traverse) Lens' ForeignLib UnqualComponentName
Evidence bound by a HsWrapper of the constraint type Functor f
Evidence bound by a HsWrapper of the constraint type Functor f
foreignLibName Lens' ForeignLib BuildInfo
Traversal' ForeignLib BuildInfo
External instance of the constraint type forall (f :: * -> *). Applicative f => Functor f
Evidence bound by a HsWrapper of the constraint type Applicative f
External instance of the constraint type forall (f :: * -> *). Applicative f => Functor f
Evidence bound by a HsWrapper of the constraint type Applicative f
Evidence bound by a HsWrapper of the constraint type Applicative f
External instance of the constraint type forall (f :: * -> *). Applicative f => Functor f
foreignLibBuildInfo
CExeName UnqualComponentName
name ->
UnqualComponentName
-> Traversal' PackageDescription Executable
-> Lens' Executable UnqualComponentName
-> Traversal' Executable BuildInfo
-> Traversal' PackageDescription BuildInfo
forall name a.
Eq name =>
name
-> Traversal' PackageDescription a
-> Lens' a name
-> Traversal' a BuildInfo
-> Traversal' PackageDescription BuildInfo
External instance of the constraint type Eq UnqualComponentName
componentBuildInfo' UnqualComponentName
name (LensLike
f PackageDescription PackageDescription [Executable] [Executable]
Lens' PackageDescription [Executable]
External instance of the constraint type forall (f :: * -> *). Applicative f => Functor f
Evidence bound by a HsWrapper of the constraint type Applicative f
executables LensLike
f PackageDescription PackageDescription [Executable] [Executable]
-> ((Executable -> f Executable) -> [Executable] -> f [Executable])
-> (Executable -> f Executable)
-> PackageDescription
-> f PackageDescription
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Executable -> f Executable) -> [Executable] -> f [Executable]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
Evidence bound by a HsWrapper of the constraint type Applicative f
External instance of the constraint type Traversable []
traverse) Lens' Executable UnqualComponentName
Evidence bound by a HsWrapper of the constraint type Functor f
Evidence bound by a HsWrapper of the constraint type Functor f
exeName Lens' Executable BuildInfo
Traversal' Executable BuildInfo
External instance of the constraint type forall (f :: * -> *). Applicative f => Functor f
Evidence bound by a HsWrapper of the constraint type Applicative f
External instance of the constraint type forall (f :: * -> *). Applicative f => Functor f
Evidence bound by a HsWrapper of the constraint type Applicative f
Evidence bound by a HsWrapper of the constraint type Applicative f
External instance of the constraint type forall (f :: * -> *). Applicative f => Functor f
exeBuildInfo
CTestName UnqualComponentName
name ->
UnqualComponentName
-> Traversal' PackageDescription TestSuite
-> Lens' TestSuite UnqualComponentName
-> Traversal' TestSuite BuildInfo
-> Traversal' PackageDescription BuildInfo
forall name a.
Eq name =>
name
-> Traversal' PackageDescription a
-> Lens' a name
-> Traversal' a BuildInfo
-> Traversal' PackageDescription BuildInfo
External instance of the constraint type Eq UnqualComponentName
componentBuildInfo' UnqualComponentName
name (LensLike
f PackageDescription PackageDescription [TestSuite] [TestSuite]
Lens' PackageDescription [TestSuite]
External instance of the constraint type forall (f :: * -> *). Applicative f => Functor f
Evidence bound by a HsWrapper of the constraint type Applicative f
testSuites LensLike
f PackageDescription PackageDescription [TestSuite] [TestSuite]
-> ((TestSuite -> f TestSuite) -> [TestSuite] -> f [TestSuite])
-> (TestSuite -> f TestSuite)
-> PackageDescription
-> f PackageDescription
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (TestSuite -> f TestSuite) -> [TestSuite] -> f [TestSuite]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
Evidence bound by a HsWrapper of the constraint type Applicative f
External instance of the constraint type Traversable []
traverse) Lens' TestSuite UnqualComponentName
Evidence bound by a HsWrapper of the constraint type Functor f
Evidence bound by a HsWrapper of the constraint type Functor f
testName Lens' TestSuite BuildInfo
Traversal' TestSuite BuildInfo
External instance of the constraint type forall (f :: * -> *). Applicative f => Functor f
Evidence bound by a HsWrapper of the constraint type Applicative f
External instance of the constraint type forall (f :: * -> *). Applicative f => Functor f
Evidence bound by a HsWrapper of the constraint type Applicative f
Evidence bound by a HsWrapper of the constraint type Applicative f
External instance of the constraint type forall (f :: * -> *). Applicative f => Functor f
testBuildInfo
CBenchName UnqualComponentName
name ->
UnqualComponentName
-> Traversal' PackageDescription Benchmark
-> Lens' Benchmark UnqualComponentName
-> Traversal' Benchmark BuildInfo
-> Traversal' PackageDescription BuildInfo
forall name a.
Eq name =>
name
-> Traversal' PackageDescription a
-> Lens' a name
-> Traversal' a BuildInfo
-> Traversal' PackageDescription BuildInfo
External instance of the constraint type Eq UnqualComponentName
componentBuildInfo' UnqualComponentName
name (LensLike
f PackageDescription PackageDescription [Benchmark] [Benchmark]
Lens' PackageDescription [Benchmark]
External instance of the constraint type forall (f :: * -> *). Applicative f => Functor f
Evidence bound by a HsWrapper of the constraint type Applicative f
benchmarks LensLike
f PackageDescription PackageDescription [Benchmark] [Benchmark]
-> ((Benchmark -> f Benchmark) -> [Benchmark] -> f [Benchmark])
-> (Benchmark -> f Benchmark)
-> PackageDescription
-> f PackageDescription
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Benchmark -> f Benchmark) -> [Benchmark] -> f [Benchmark]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
Evidence bound by a HsWrapper of the constraint type Applicative f
External instance of the constraint type Traversable []
traverse) Lens' Benchmark UnqualComponentName
Evidence bound by a HsWrapper of the constraint type Functor f
Evidence bound by a HsWrapper of the constraint type Functor f
benchmarkName Lens' Benchmark BuildInfo
Traversal' Benchmark BuildInfo
External instance of the constraint type forall (f :: * -> *). Applicative f => Functor f
Evidence bound by a HsWrapper of the constraint type Applicative f
External instance of the constraint type forall (f :: * -> *). Applicative f => Functor f
Evidence bound by a HsWrapper of the constraint type Applicative f
Evidence bound by a HsWrapper of the constraint type Applicative f
External instance of the constraint type forall (f :: * -> *). Applicative f => Functor f
benchmarkBuildInfo
where
componentBuildInfo' :: Eq name
=> name
-> Traversal' PackageDescription a
-> Lens' a name
-> Traversal' a BuildInfo
-> Traversal' PackageDescription BuildInfo
componentBuildInfo' :: name
-> Traversal' PackageDescription a
-> Lens' a name
-> Traversal' a BuildInfo
-> Traversal' PackageDescription BuildInfo
componentBuildInfo' name
name Traversal' PackageDescription a
pdL Lens' a name
nameL Traversal' a BuildInfo
biL =
LensLike f PackageDescription PackageDescription a a
Traversal' PackageDescription a
Evidence bound by a HsWrapper of the constraint type Applicative f
pdL
LensLike f PackageDescription PackageDescription a a
-> ((BuildInfo -> f BuildInfo) -> a -> f a)
-> (BuildInfo -> f BuildInfo)
-> PackageDescription
-> f PackageDescription
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> Bool) -> Traversal' a a
forall a. (a -> Bool) -> Traversal' a a
filtered ((name -> name -> Bool
forall a. Eq a => a -> a -> Bool
Evidence bound by a type signature of the constraint type Eq name
== name
name) (name -> Bool) -> (a -> name) -> a -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Getting name a name -> a -> name
forall a s. Getting a s a -> s -> a
view Getting name a name
Lens' a name
External instance of the constraint type forall m. Functor (Const m)
nameL)
LensLike f a a a a
-> ((BuildInfo -> f BuildInfo) -> a -> f a)
-> (BuildInfo -> f BuildInfo)
-> a
-> f a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (BuildInfo -> f BuildInfo) -> a -> f a
Traversal' a BuildInfo
Evidence bound by a HsWrapper of the constraint type Applicative f
biL
filtered :: (a -> Bool) -> Traversal' a a
filtered :: (a -> Bool) -> Traversal' a a
filtered a -> Bool
p a -> f a
f a
s = if a -> Bool
p a
s then a -> f a
f a
s else a -> f a
forall (f :: * -> *) a. Applicative f => a -> f a
Evidence bound by a HsWrapper of the constraint type Applicative f
pure a
s