{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE QuantifiedConstraints #-}
module Distribution.PackageDescription.FieldGrammar
(
packageDescriptionFieldGrammar
, CompatDataDir (..)
, CompatLicenseFile (..)
, libraryFieldGrammar
, foreignLibFieldGrammar
, executableFieldGrammar
, TestSuiteStanza (..)
, testSuiteFieldGrammar
, validateTestSuite
, unvalidateTestSuite
, testStanzaTestType
, testStanzaMainIs
, testStanzaTestModule
, testStanzaBuildInfo
, BenchmarkStanza (..)
, benchmarkFieldGrammar
, validateBenchmark
, unvalidateBenchmark
, formatDependencyList
, formatExposedModules
, formatExtraSourceFiles
, formatHsSourceDirs
, formatMixinList
, formatOtherExtensions
, formatOtherModules
, benchmarkStanzaBenchmarkType
, benchmarkStanzaMainIs
, benchmarkStanzaBenchmarkModule
, benchmarkStanzaBuildInfo
, flagFieldGrammar
, sourceRepoFieldGrammar
, setupBInfoFieldGrammar
, buildInfoFieldGrammar
) where
import Distribution.Compat.Lens
import Distribution.Compat.Prelude
import Language.Haskell.Extension
import Prelude ()
import Distribution.CabalSpecVersion
import Distribution.Compat.Newtype (Newtype, pack', unpack')
import Distribution.Compiler (CompilerFlavor (..), PerCompilerFlavor (..))
import Distribution.FieldGrammar
import Distribution.Fields
import Distribution.ModuleName (ModuleName)
import Distribution.Package
import Distribution.PackageDescription
import Distribution.Parsec
import Distribution.Pretty (Pretty (..), prettyShow, showToken)
import Distribution.Utils.Path
import Distribution.Version (Version, VersionRange)
import qualified Data.ByteString.Char8 as BS8
import qualified Distribution.Compat.CharParsing as P
import qualified Distribution.SPDX as SPDX
import qualified Distribution.Types.Lens as L
packageDescriptionFieldGrammar
:: ( FieldGrammar c g
, Applicative (g PackageDescription)
, Applicative (g PackageIdentifier)
, c (Identity BuildType)
, c (Identity PackageName)
, c (Identity Version)
, forall from to. c (List FSep (RelativePathNT from to) (RelativePath from to))
, forall from to. c (List VCat (RelativePathNT from to) (RelativePath from to))
, c (List FSep TestedWith (CompilerFlavor, VersionRange))
, c CompatLicenseFile
, c CompatDataDir
)
=> g PackageDescription PackageDescription
packageDescriptionFieldGrammar :: forall (c :: * -> Constraint) (g :: * -> * -> *).
(FieldGrammar c g, Applicative (g PackageDescription),
Applicative (g PackageIdentifier), c (Identity BuildType),
c (Identity PackageName), c (Identity Version),
forall from (to :: FileOrDir).
c (List FSep (RelativePathNT from to) (RelativePath from to)),
forall from (to :: FileOrDir).
c (List VCat (RelativePathNT from to) (RelativePath from to)),
c (List FSep TestedWith (CompilerFlavor, VersionRange)),
c CompatLicenseFile, c CompatDataDir) =>
g PackageDescription PackageDescription
packageDescriptionFieldGrammar =
CabalSpecVersion
-> PackageIdentifier
-> Either License License
-> [RelativePath Pkg 'File]
-> ShortText
-> ShortText
-> ShortText
-> ShortText
-> [(CompilerFlavor, VersionRange)]
-> ShortText
-> ShortText
-> ShortText
-> [SourceRepo]
-> ShortText
-> ShortText
-> ShortText
-> [(String, String)]
-> Maybe BuildType
-> Maybe SetupBuildInfo
-> Maybe Library
-> [Library]
-> [Executable]
-> [ForeignLib]
-> [TestSuite]
-> [Benchmark]
-> [RelativePath DataDir 'File]
-> SymbolicPath Pkg ('Dir DataDir)
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> PackageDescription
PackageDescription
(CabalSpecVersion
-> PackageIdentifier
-> Either License License
-> [RelativePath Pkg 'File]
-> ShortText
-> ShortText
-> ShortText
-> ShortText
-> [(CompilerFlavor, VersionRange)]
-> ShortText
-> ShortText
-> ShortText
-> [SourceRepo]
-> ShortText
-> ShortText
-> ShortText
-> [(String, String)]
-> Maybe BuildType
-> Maybe SetupBuildInfo
-> Maybe Library
-> [Library]
-> [Executable]
-> [ForeignLib]
-> [TestSuite]
-> [Benchmark]
-> [RelativePath DataDir 'File]
-> SymbolicPath Pkg ('Dir DataDir)
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> PackageDescription)
-> g PackageDescription CabalSpecVersion
-> g PackageDescription
(PackageIdentifier
-> Either License License
-> [RelativePath Pkg 'File]
-> ShortText
-> ShortText
-> ShortText
-> ShortText
-> [(CompilerFlavor, VersionRange)]
-> ShortText
-> ShortText
-> ShortText
-> [SourceRepo]
-> ShortText
-> ShortText
-> ShortText
-> [(String, String)]
-> Maybe BuildType
-> Maybe SetupBuildInfo
-> Maybe Library
-> [Library]
-> [Executable]
-> [ForeignLib]
-> [TestSuite]
-> [Benchmark]
-> [RelativePath DataDir 'File]
-> SymbolicPath Pkg ('Dir DataDir)
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> PackageDescription)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> FieldName
-> (CabalSpecVersion -> SpecVersion)
-> ALens' PackageDescription CabalSpecVersion
-> CabalSpecVersion
-> g PackageDescription CabalSpecVersion
forall b a s.
(c b, Newtype a b, Eq a) =>
FieldName -> (a -> b) -> ALens' s a -> a -> g s a
forall (c :: * -> Constraint) (g :: * -> * -> *) b a s.
(FieldGrammar c g, c b, Newtype a b, Eq a) =>
FieldName -> (a -> b) -> ALens' s a -> a -> g s a
optionalFieldDefAla FieldName
"cabal-version" CabalSpecVersion -> SpecVersion
SpecVersion ALens' PackageDescription CabalSpecVersion
Lens' PackageDescription CabalSpecVersion
L.specVersion CabalSpecVersion
CabalSpecV1_0
g PackageDescription
(PackageIdentifier
-> Either License License
-> [RelativePath Pkg 'File]
-> ShortText
-> ShortText
-> ShortText
-> ShortText
-> [(CompilerFlavor, VersionRange)]
-> ShortText
-> ShortText
-> ShortText
-> [SourceRepo]
-> ShortText
-> ShortText
-> ShortText
-> [(String, String)]
-> Maybe BuildType
-> Maybe SetupBuildInfo
-> Maybe Library
-> [Library]
-> [Executable]
-> [ForeignLib]
-> [TestSuite]
-> [Benchmark]
-> [RelativePath DataDir 'File]
-> SymbolicPath Pkg ('Dir DataDir)
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> PackageDescription)
-> g PackageDescription PackageIdentifier
-> g PackageDescription
(Either License License
-> [RelativePath Pkg 'File]
-> ShortText
-> ShortText
-> ShortText
-> ShortText
-> [(CompilerFlavor, VersionRange)]
-> ShortText
-> ShortText
-> ShortText
-> [SourceRepo]
-> ShortText
-> ShortText
-> ShortText
-> [(String, String)]
-> Maybe BuildType
-> Maybe SetupBuildInfo
-> Maybe Library
-> [Library]
-> [Executable]
-> [ForeignLib]
-> [TestSuite]
-> [Benchmark]
-> [RelativePath DataDir 'File]
-> SymbolicPath Pkg ('Dir DataDir)
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> PackageDescription)
forall a b.
g PackageDescription (a -> b)
-> g PackageDescription a -> g PackageDescription b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ALens' PackageDescription PackageIdentifier
-> g PackageIdentifier PackageIdentifier
-> g PackageDescription PackageIdentifier
forall a b d. ALens' a b -> g b d -> g a d
forall (c :: * -> Constraint) (g :: * -> * -> *) a b d.
FieldGrammar c g =>
ALens' a b -> g b d -> g a d
blurFieldGrammar ALens' PackageDescription PackageIdentifier
Lens' PackageDescription PackageIdentifier
L.package g PackageIdentifier PackageIdentifier
packageIdentifierGrammar
g PackageDescription
(Either License License
-> [RelativePath Pkg 'File]
-> ShortText
-> ShortText
-> ShortText
-> ShortText
-> [(CompilerFlavor, VersionRange)]
-> ShortText
-> ShortText
-> ShortText
-> [SourceRepo]
-> ShortText
-> ShortText
-> ShortText
-> [(String, String)]
-> Maybe BuildType
-> Maybe SetupBuildInfo
-> Maybe Library
-> [Library]
-> [Executable]
-> [ForeignLib]
-> [TestSuite]
-> [Benchmark]
-> [RelativePath DataDir 'File]
-> SymbolicPath Pkg ('Dir DataDir)
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> PackageDescription)
-> g PackageDescription (Either License License)
-> g PackageDescription
([RelativePath Pkg 'File]
-> ShortText
-> ShortText
-> ShortText
-> ShortText
-> [(CompilerFlavor, VersionRange)]
-> ShortText
-> ShortText
-> ShortText
-> [SourceRepo]
-> ShortText
-> ShortText
-> ShortText
-> [(String, String)]
-> Maybe BuildType
-> Maybe SetupBuildInfo
-> Maybe Library
-> [Library]
-> [Executable]
-> [ForeignLib]
-> [TestSuite]
-> [Benchmark]
-> [RelativePath DataDir 'File]
-> SymbolicPath Pkg ('Dir DataDir)
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> PackageDescription)
forall a b.
g PackageDescription (a -> b)
-> g PackageDescription a -> g PackageDescription b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> FieldName
-> (Either License License -> SpecLicense)
-> ALens' PackageDescription (Either License License)
-> Either License License
-> g PackageDescription (Either License License)
forall b a s.
(c b, Newtype a b, Eq a) =>
FieldName -> (a -> b) -> ALens' s a -> a -> g s a
forall (c :: * -> Constraint) (g :: * -> * -> *) b a s.
(FieldGrammar c g, c b, Newtype a b, Eq a) =>
FieldName -> (a -> b) -> ALens' s a -> a -> g s a
optionalFieldDefAla FieldName
"license" Either License License -> SpecLicense
SpecLicense ALens' PackageDescription (Either License License)
Lens' PackageDescription (Either License License)
L.licenseRaw (License -> Either License License
forall a b. a -> Either a b
Left License
SPDX.NONE)
g PackageDescription
([RelativePath Pkg 'File]
-> ShortText
-> ShortText
-> ShortText
-> ShortText
-> [(CompilerFlavor, VersionRange)]
-> ShortText
-> ShortText
-> ShortText
-> [SourceRepo]
-> ShortText
-> ShortText
-> ShortText
-> [(String, String)]
-> Maybe BuildType
-> Maybe SetupBuildInfo
-> Maybe Library
-> [Library]
-> [Executable]
-> [ForeignLib]
-> [TestSuite]
-> [Benchmark]
-> [RelativePath DataDir 'File]
-> SymbolicPath Pkg ('Dir DataDir)
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> PackageDescription)
-> g PackageDescription [RelativePath Pkg 'File]
-> g PackageDescription
(ShortText
-> ShortText
-> ShortText
-> ShortText
-> [(CompilerFlavor, VersionRange)]
-> ShortText
-> ShortText
-> ShortText
-> [SourceRepo]
-> ShortText
-> ShortText
-> ShortText
-> [(String, String)]
-> Maybe BuildType
-> Maybe SetupBuildInfo
-> Maybe Library
-> [Library]
-> [Executable]
-> [ForeignLib]
-> [TestSuite]
-> [Benchmark]
-> [RelativePath DataDir 'File]
-> SymbolicPath Pkg ('Dir DataDir)
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> PackageDescription)
forall a b.
g PackageDescription (a -> b)
-> g PackageDescription a -> g PackageDescription b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> g PackageDescription [RelativePath Pkg 'File]
licenseFilesGrammar
g PackageDescription
(ShortText
-> ShortText
-> ShortText
-> ShortText
-> [(CompilerFlavor, VersionRange)]
-> ShortText
-> ShortText
-> ShortText
-> [SourceRepo]
-> ShortText
-> ShortText
-> ShortText
-> [(String, String)]
-> Maybe BuildType
-> Maybe SetupBuildInfo
-> Maybe Library
-> [Library]
-> [Executable]
-> [ForeignLib]
-> [TestSuite]
-> [Benchmark]
-> [RelativePath DataDir 'File]
-> SymbolicPath Pkg ('Dir DataDir)
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> PackageDescription)
-> g PackageDescription ShortText
-> g PackageDescription
(ShortText
-> ShortText
-> ShortText
-> [(CompilerFlavor, VersionRange)]
-> ShortText
-> ShortText
-> ShortText
-> [SourceRepo]
-> ShortText
-> ShortText
-> ShortText
-> [(String, String)]
-> Maybe BuildType
-> Maybe SetupBuildInfo
-> Maybe Library
-> [Library]
-> [Executable]
-> [ForeignLib]
-> [TestSuite]
-> [Benchmark]
-> [RelativePath DataDir 'File]
-> SymbolicPath Pkg ('Dir DataDir)
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> PackageDescription)
forall a b.
g PackageDescription (a -> b)
-> g PackageDescription a -> g PackageDescription b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> FieldName
-> ALens' PackageDescription ShortText
-> g PackageDescription ShortText
forall s. FieldName -> ALens' s ShortText -> g s ShortText
forall (c :: * -> Constraint) (g :: * -> * -> *) s.
FieldGrammar c g =>
FieldName -> ALens' s ShortText -> g s ShortText
freeTextFieldDefST FieldName
"copyright" ALens' PackageDescription ShortText
Lens' PackageDescription ShortText
L.copyright
g PackageDescription
(ShortText
-> ShortText
-> ShortText
-> [(CompilerFlavor, VersionRange)]
-> ShortText
-> ShortText
-> ShortText
-> [SourceRepo]
-> ShortText
-> ShortText
-> ShortText
-> [(String, String)]
-> Maybe BuildType
-> Maybe SetupBuildInfo
-> Maybe Library
-> [Library]
-> [Executable]
-> [ForeignLib]
-> [TestSuite]
-> [Benchmark]
-> [RelativePath DataDir 'File]
-> SymbolicPath Pkg ('Dir DataDir)
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> PackageDescription)
-> g PackageDescription ShortText
-> g PackageDescription
(ShortText
-> ShortText
-> [(CompilerFlavor, VersionRange)]
-> ShortText
-> ShortText
-> ShortText
-> [SourceRepo]
-> ShortText
-> ShortText
-> ShortText
-> [(String, String)]
-> Maybe BuildType
-> Maybe SetupBuildInfo
-> Maybe Library
-> [Library]
-> [Executable]
-> [ForeignLib]
-> [TestSuite]
-> [Benchmark]
-> [RelativePath DataDir 'File]
-> SymbolicPath Pkg ('Dir DataDir)
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> PackageDescription)
forall a b.
g PackageDescription (a -> b)
-> g PackageDescription a -> g PackageDescription b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> FieldName
-> ALens' PackageDescription ShortText
-> g PackageDescription ShortText
forall s. FieldName -> ALens' s ShortText -> g s ShortText
forall (c :: * -> Constraint) (g :: * -> * -> *) s.
FieldGrammar c g =>
FieldName -> ALens' s ShortText -> g s ShortText
freeTextFieldDefST FieldName
"maintainer" ALens' PackageDescription ShortText
Lens' PackageDescription ShortText
L.maintainer
g PackageDescription
(ShortText
-> ShortText
-> [(CompilerFlavor, VersionRange)]
-> ShortText
-> ShortText
-> ShortText
-> [SourceRepo]
-> ShortText
-> ShortText
-> ShortText
-> [(String, String)]
-> Maybe BuildType
-> Maybe SetupBuildInfo
-> Maybe Library
-> [Library]
-> [Executable]
-> [ForeignLib]
-> [TestSuite]
-> [Benchmark]
-> [RelativePath DataDir 'File]
-> SymbolicPath Pkg ('Dir DataDir)
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> PackageDescription)
-> g PackageDescription ShortText
-> g PackageDescription
(ShortText
-> [(CompilerFlavor, VersionRange)]
-> ShortText
-> ShortText
-> ShortText
-> [SourceRepo]
-> ShortText
-> ShortText
-> ShortText
-> [(String, String)]
-> Maybe BuildType
-> Maybe SetupBuildInfo
-> Maybe Library
-> [Library]
-> [Executable]
-> [ForeignLib]
-> [TestSuite]
-> [Benchmark]
-> [RelativePath DataDir 'File]
-> SymbolicPath Pkg ('Dir DataDir)
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> PackageDescription)
forall a b.
g PackageDescription (a -> b)
-> g PackageDescription a -> g PackageDescription b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> FieldName
-> ALens' PackageDescription ShortText
-> g PackageDescription ShortText
forall s. FieldName -> ALens' s ShortText -> g s ShortText
forall (c :: * -> Constraint) (g :: * -> * -> *) s.
FieldGrammar c g =>
FieldName -> ALens' s ShortText -> g s ShortText
freeTextFieldDefST FieldName
"author" ALens' PackageDescription ShortText
Lens' PackageDescription ShortText
L.author
g PackageDescription
(ShortText
-> [(CompilerFlavor, VersionRange)]
-> ShortText
-> ShortText
-> ShortText
-> [SourceRepo]
-> ShortText
-> ShortText
-> ShortText
-> [(String, String)]
-> Maybe BuildType
-> Maybe SetupBuildInfo
-> Maybe Library
-> [Library]
-> [Executable]
-> [ForeignLib]
-> [TestSuite]
-> [Benchmark]
-> [RelativePath DataDir 'File]
-> SymbolicPath Pkg ('Dir DataDir)
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> PackageDescription)
-> g PackageDescription ShortText
-> g PackageDescription
([(CompilerFlavor, VersionRange)]
-> ShortText
-> ShortText
-> ShortText
-> [SourceRepo]
-> ShortText
-> ShortText
-> ShortText
-> [(String, String)]
-> Maybe BuildType
-> Maybe SetupBuildInfo
-> Maybe Library
-> [Library]
-> [Executable]
-> [ForeignLib]
-> [TestSuite]
-> [Benchmark]
-> [RelativePath DataDir 'File]
-> SymbolicPath Pkg ('Dir DataDir)
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> PackageDescription)
forall a b.
g PackageDescription (a -> b)
-> g PackageDescription a -> g PackageDescription b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> FieldName
-> ALens' PackageDescription ShortText
-> g PackageDescription ShortText
forall s. FieldName -> ALens' s ShortText -> g s ShortText
forall (c :: * -> Constraint) (g :: * -> * -> *) s.
FieldGrammar c g =>
FieldName -> ALens' s ShortText -> g s ShortText
freeTextFieldDefST FieldName
"stability" ALens' PackageDescription ShortText
Lens' PackageDescription ShortText
L.stability
g PackageDescription
([(CompilerFlavor, VersionRange)]
-> ShortText
-> ShortText
-> ShortText
-> [SourceRepo]
-> ShortText
-> ShortText
-> ShortText
-> [(String, String)]
-> Maybe BuildType
-> Maybe SetupBuildInfo
-> Maybe Library
-> [Library]
-> [Executable]
-> [ForeignLib]
-> [TestSuite]
-> [Benchmark]
-> [RelativePath DataDir 'File]
-> SymbolicPath Pkg ('Dir DataDir)
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> PackageDescription)
-> g PackageDescription [(CompilerFlavor, VersionRange)]
-> g PackageDescription
(ShortText
-> ShortText
-> ShortText
-> [SourceRepo]
-> ShortText
-> ShortText
-> ShortText
-> [(String, String)]
-> Maybe BuildType
-> Maybe SetupBuildInfo
-> Maybe Library
-> [Library]
-> [Executable]
-> [ForeignLib]
-> [TestSuite]
-> [Benchmark]
-> [RelativePath DataDir 'File]
-> SymbolicPath Pkg ('Dir DataDir)
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> PackageDescription)
forall a b.
g PackageDescription (a -> b)
-> g PackageDescription a -> g PackageDescription b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> FieldName
-> ([(CompilerFlavor, VersionRange)]
-> List FSep TestedWith (CompilerFlavor, VersionRange))
-> ALens' PackageDescription [(CompilerFlavor, VersionRange)]
-> g PackageDescription [(CompilerFlavor, VersionRange)]
forall b a s.
(c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
forall (c :: * -> Constraint) (g :: * -> * -> *) b a s.
(FieldGrammar c g, c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
monoidalFieldAla FieldName
"tested-with" (FSep
-> ((CompilerFlavor, VersionRange) -> TestedWith)
-> [(CompilerFlavor, VersionRange)]
-> List FSep TestedWith (CompilerFlavor, VersionRange)
forall sep a b. sep -> (a -> b) -> [a] -> List sep b a
alaList' FSep
FSep (CompilerFlavor, VersionRange) -> TestedWith
TestedWith) ALens' PackageDescription [(CompilerFlavor, VersionRange)]
Lens' PackageDescription [(CompilerFlavor, VersionRange)]
L.testedWith
g PackageDescription
(ShortText
-> ShortText
-> ShortText
-> [SourceRepo]
-> ShortText
-> ShortText
-> ShortText
-> [(String, String)]
-> Maybe BuildType
-> Maybe SetupBuildInfo
-> Maybe Library
-> [Library]
-> [Executable]
-> [ForeignLib]
-> [TestSuite]
-> [Benchmark]
-> [RelativePath DataDir 'File]
-> SymbolicPath Pkg ('Dir DataDir)
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> PackageDescription)
-> g PackageDescription ShortText
-> g PackageDescription
(ShortText
-> ShortText
-> [SourceRepo]
-> ShortText
-> ShortText
-> ShortText
-> [(String, String)]
-> Maybe BuildType
-> Maybe SetupBuildInfo
-> Maybe Library
-> [Library]
-> [Executable]
-> [ForeignLib]
-> [TestSuite]
-> [Benchmark]
-> [RelativePath DataDir 'File]
-> SymbolicPath Pkg ('Dir DataDir)
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> PackageDescription)
forall a b.
g PackageDescription (a -> b)
-> g PackageDescription a -> g PackageDescription b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> FieldName
-> ALens' PackageDescription ShortText
-> g PackageDescription ShortText
forall s. FieldName -> ALens' s ShortText -> g s ShortText
forall (c :: * -> Constraint) (g :: * -> * -> *) s.
FieldGrammar c g =>
FieldName -> ALens' s ShortText -> g s ShortText
freeTextFieldDefST FieldName
"homepage" ALens' PackageDescription ShortText
Lens' PackageDescription ShortText
L.homepage
g PackageDescription
(ShortText
-> ShortText
-> [SourceRepo]
-> ShortText
-> ShortText
-> ShortText
-> [(String, String)]
-> Maybe BuildType
-> Maybe SetupBuildInfo
-> Maybe Library
-> [Library]
-> [Executable]
-> [ForeignLib]
-> [TestSuite]
-> [Benchmark]
-> [RelativePath DataDir 'File]
-> SymbolicPath Pkg ('Dir DataDir)
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> PackageDescription)
-> g PackageDescription ShortText
-> g PackageDescription
(ShortText
-> [SourceRepo]
-> ShortText
-> ShortText
-> ShortText
-> [(String, String)]
-> Maybe BuildType
-> Maybe SetupBuildInfo
-> Maybe Library
-> [Library]
-> [Executable]
-> [ForeignLib]
-> [TestSuite]
-> [Benchmark]
-> [RelativePath DataDir 'File]
-> SymbolicPath Pkg ('Dir DataDir)
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> PackageDescription)
forall a b.
g PackageDescription (a -> b)
-> g PackageDescription a -> g PackageDescription b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> FieldName
-> ALens' PackageDescription ShortText
-> g PackageDescription ShortText
forall s. FieldName -> ALens' s ShortText -> g s ShortText
forall (c :: * -> Constraint) (g :: * -> * -> *) s.
FieldGrammar c g =>
FieldName -> ALens' s ShortText -> g s ShortText
freeTextFieldDefST FieldName
"package-url" ALens' PackageDescription ShortText
Lens' PackageDescription ShortText
L.pkgUrl
g PackageDescription
(ShortText
-> [SourceRepo]
-> ShortText
-> ShortText
-> ShortText
-> [(String, String)]
-> Maybe BuildType
-> Maybe SetupBuildInfo
-> Maybe Library
-> [Library]
-> [Executable]
-> [ForeignLib]
-> [TestSuite]
-> [Benchmark]
-> [RelativePath DataDir 'File]
-> SymbolicPath Pkg ('Dir DataDir)
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> PackageDescription)
-> g PackageDescription ShortText
-> g PackageDescription
([SourceRepo]
-> ShortText
-> ShortText
-> ShortText
-> [(String, String)]
-> Maybe BuildType
-> Maybe SetupBuildInfo
-> Maybe Library
-> [Library]
-> [Executable]
-> [ForeignLib]
-> [TestSuite]
-> [Benchmark]
-> [RelativePath DataDir 'File]
-> SymbolicPath Pkg ('Dir DataDir)
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> PackageDescription)
forall a b.
g PackageDescription (a -> b)
-> g PackageDescription a -> g PackageDescription b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> FieldName
-> ALens' PackageDescription ShortText
-> g PackageDescription ShortText
forall s. FieldName -> ALens' s ShortText -> g s ShortText
forall (c :: * -> Constraint) (g :: * -> * -> *) s.
FieldGrammar c g =>
FieldName -> ALens' s ShortText -> g s ShortText
freeTextFieldDefST FieldName
"bug-reports" ALens' PackageDescription ShortText
Lens' PackageDescription ShortText
L.bugReports
g PackageDescription
([SourceRepo]
-> ShortText
-> ShortText
-> ShortText
-> [(String, String)]
-> Maybe BuildType
-> Maybe SetupBuildInfo
-> Maybe Library
-> [Library]
-> [Executable]
-> [ForeignLib]
-> [TestSuite]
-> [Benchmark]
-> [RelativePath DataDir 'File]
-> SymbolicPath Pkg ('Dir DataDir)
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> PackageDescription)
-> g PackageDescription [SourceRepo]
-> g PackageDescription
(ShortText
-> ShortText
-> ShortText
-> [(String, String)]
-> Maybe BuildType
-> Maybe SetupBuildInfo
-> Maybe Library
-> [Library]
-> [Executable]
-> [ForeignLib]
-> [TestSuite]
-> [Benchmark]
-> [RelativePath DataDir 'File]
-> SymbolicPath Pkg ('Dir DataDir)
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> PackageDescription)
forall a b.
g PackageDescription (a -> b)
-> g PackageDescription a -> g PackageDescription b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> [SourceRepo] -> g PackageDescription [SourceRepo]
forall a. a -> g PackageDescription a
forall (f :: * -> *) a. Applicative f => a -> f a
pure []
g PackageDescription
(ShortText
-> ShortText
-> ShortText
-> [(String, String)]
-> Maybe BuildType
-> Maybe SetupBuildInfo
-> Maybe Library
-> [Library]
-> [Executable]
-> [ForeignLib]
-> [TestSuite]
-> [Benchmark]
-> [RelativePath DataDir 'File]
-> SymbolicPath Pkg ('Dir DataDir)
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> PackageDescription)
-> g PackageDescription ShortText
-> g PackageDescription
(ShortText
-> ShortText
-> [(String, String)]
-> Maybe BuildType
-> Maybe SetupBuildInfo
-> Maybe Library
-> [Library]
-> [Executable]
-> [ForeignLib]
-> [TestSuite]
-> [Benchmark]
-> [RelativePath DataDir 'File]
-> SymbolicPath Pkg ('Dir DataDir)
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> PackageDescription)
forall a b.
g PackageDescription (a -> b)
-> g PackageDescription a -> g PackageDescription b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> FieldName
-> ALens' PackageDescription ShortText
-> g PackageDescription ShortText
forall s. FieldName -> ALens' s ShortText -> g s ShortText
forall (c :: * -> Constraint) (g :: * -> * -> *) s.
FieldGrammar c g =>
FieldName -> ALens' s ShortText -> g s ShortText
freeTextFieldDefST FieldName
"synopsis" ALens' PackageDescription ShortText
Lens' PackageDescription ShortText
L.synopsis
g PackageDescription
(ShortText
-> ShortText
-> [(String, String)]
-> Maybe BuildType
-> Maybe SetupBuildInfo
-> Maybe Library
-> [Library]
-> [Executable]
-> [ForeignLib]
-> [TestSuite]
-> [Benchmark]
-> [RelativePath DataDir 'File]
-> SymbolicPath Pkg ('Dir DataDir)
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> PackageDescription)
-> g PackageDescription ShortText
-> g PackageDescription
(ShortText
-> [(String, String)]
-> Maybe BuildType
-> Maybe SetupBuildInfo
-> Maybe Library
-> [Library]
-> [Executable]
-> [ForeignLib]
-> [TestSuite]
-> [Benchmark]
-> [RelativePath DataDir 'File]
-> SymbolicPath Pkg ('Dir DataDir)
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> PackageDescription)
forall a b.
g PackageDescription (a -> b)
-> g PackageDescription a -> g PackageDescription b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> FieldName
-> ALens' PackageDescription ShortText
-> g PackageDescription ShortText
forall s. FieldName -> ALens' s ShortText -> g s ShortText
forall (c :: * -> Constraint) (g :: * -> * -> *) s.
FieldGrammar c g =>
FieldName -> ALens' s ShortText -> g s ShortText
freeTextFieldDefST FieldName
"description" ALens' PackageDescription ShortText
Lens' PackageDescription ShortText
L.description
g PackageDescription
(ShortText
-> [(String, String)]
-> Maybe BuildType
-> Maybe SetupBuildInfo
-> Maybe Library
-> [Library]
-> [Executable]
-> [ForeignLib]
-> [TestSuite]
-> [Benchmark]
-> [RelativePath DataDir 'File]
-> SymbolicPath Pkg ('Dir DataDir)
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> PackageDescription)
-> g PackageDescription ShortText
-> g PackageDescription
([(String, String)]
-> Maybe BuildType
-> Maybe SetupBuildInfo
-> Maybe Library
-> [Library]
-> [Executable]
-> [ForeignLib]
-> [TestSuite]
-> [Benchmark]
-> [RelativePath DataDir 'File]
-> SymbolicPath Pkg ('Dir DataDir)
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> PackageDescription)
forall a b.
g PackageDescription (a -> b)
-> g PackageDescription a -> g PackageDescription b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> FieldName
-> ALens' PackageDescription ShortText
-> g PackageDescription ShortText
forall s. FieldName -> ALens' s ShortText -> g s ShortText
forall (c :: * -> Constraint) (g :: * -> * -> *) s.
FieldGrammar c g =>
FieldName -> ALens' s ShortText -> g s ShortText
freeTextFieldDefST FieldName
"category" ALens' PackageDescription ShortText
Lens' PackageDescription ShortText
L.category
g PackageDescription
([(String, String)]
-> Maybe BuildType
-> Maybe SetupBuildInfo
-> Maybe Library
-> [Library]
-> [Executable]
-> [ForeignLib]
-> [TestSuite]
-> [Benchmark]
-> [RelativePath DataDir 'File]
-> SymbolicPath Pkg ('Dir DataDir)
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> PackageDescription)
-> g PackageDescription [(String, String)]
-> g PackageDescription
(Maybe BuildType
-> Maybe SetupBuildInfo
-> Maybe Library
-> [Library]
-> [Executable]
-> [ForeignLib]
-> [TestSuite]
-> [Benchmark]
-> [RelativePath DataDir 'File]
-> SymbolicPath Pkg ('Dir DataDir)
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> PackageDescription)
forall a b.
g PackageDescription (a -> b)
-> g PackageDescription a -> g PackageDescription b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> FieldName
-> ALens' PackageDescription [(String, String)]
-> g PackageDescription [(String, String)]
forall s.
FieldName -> ALens' s [(String, String)] -> g s [(String, String)]
forall (c :: * -> Constraint) (g :: * -> * -> *) s.
FieldGrammar c g =>
FieldName -> ALens' s [(String, String)] -> g s [(String, String)]
prefixedFields FieldName
"x-" ALens' PackageDescription [(String, String)]
Lens' PackageDescription [(String, String)]
L.customFieldsPD
g PackageDescription
(Maybe BuildType
-> Maybe SetupBuildInfo
-> Maybe Library
-> [Library]
-> [Executable]
-> [ForeignLib]
-> [TestSuite]
-> [Benchmark]
-> [RelativePath DataDir 'File]
-> SymbolicPath Pkg ('Dir DataDir)
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> PackageDescription)
-> g PackageDescription (Maybe BuildType)
-> g PackageDescription
(Maybe SetupBuildInfo
-> Maybe Library
-> [Library]
-> [Executable]
-> [ForeignLib]
-> [TestSuite]
-> [Benchmark]
-> [RelativePath DataDir 'File]
-> SymbolicPath Pkg ('Dir DataDir)
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> PackageDescription)
forall a b.
g PackageDescription (a -> b)
-> g PackageDescription a -> g PackageDescription b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> FieldName
-> ALens' PackageDescription (Maybe BuildType)
-> g PackageDescription (Maybe BuildType)
forall (c :: * -> Constraint) (g :: * -> * -> *) a s.
(FieldGrammar c g, c (Identity a)) =>
FieldName -> ALens' s (Maybe a) -> g s (Maybe a)
optionalField FieldName
"build-type" ALens' PackageDescription (Maybe BuildType)
Lens' PackageDescription (Maybe BuildType)
L.buildTypeRaw
g PackageDescription
(Maybe SetupBuildInfo
-> Maybe Library
-> [Library]
-> [Executable]
-> [ForeignLib]
-> [TestSuite]
-> [Benchmark]
-> [RelativePath DataDir 'File]
-> SymbolicPath Pkg ('Dir DataDir)
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> PackageDescription)
-> g PackageDescription (Maybe SetupBuildInfo)
-> g PackageDescription
(Maybe Library
-> [Library]
-> [Executable]
-> [ForeignLib]
-> [TestSuite]
-> [Benchmark]
-> [RelativePath DataDir 'File]
-> SymbolicPath Pkg ('Dir DataDir)
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> PackageDescription)
forall a b.
g PackageDescription (a -> b)
-> g PackageDescription a -> g PackageDescription b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Maybe SetupBuildInfo -> g PackageDescription (Maybe SetupBuildInfo)
forall a. a -> g PackageDescription a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe SetupBuildInfo
forall a. Maybe a
Nothing
g PackageDescription
(Maybe Library
-> [Library]
-> [Executable]
-> [ForeignLib]
-> [TestSuite]
-> [Benchmark]
-> [RelativePath DataDir 'File]
-> SymbolicPath Pkg ('Dir DataDir)
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> PackageDescription)
-> g PackageDescription (Maybe Library)
-> g PackageDescription
([Library]
-> [Executable]
-> [ForeignLib]
-> [TestSuite]
-> [Benchmark]
-> [RelativePath DataDir 'File]
-> SymbolicPath Pkg ('Dir DataDir)
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> PackageDescription)
forall a b.
g PackageDescription (a -> b)
-> g PackageDescription a -> g PackageDescription b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Maybe Library -> g PackageDescription (Maybe Library)
forall a. a -> g PackageDescription a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe Library
forall a. Maybe a
Nothing
g PackageDescription
([Library]
-> [Executable]
-> [ForeignLib]
-> [TestSuite]
-> [Benchmark]
-> [RelativePath DataDir 'File]
-> SymbolicPath Pkg ('Dir DataDir)
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> PackageDescription)
-> g PackageDescription [Library]
-> g PackageDescription
([Executable]
-> [ForeignLib]
-> [TestSuite]
-> [Benchmark]
-> [RelativePath DataDir 'File]
-> SymbolicPath Pkg ('Dir DataDir)
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> PackageDescription)
forall a b.
g PackageDescription (a -> b)
-> g PackageDescription a -> g PackageDescription b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> [Library] -> g PackageDescription [Library]
forall a. a -> g PackageDescription a
forall (f :: * -> *) a. Applicative f => a -> f a
pure []
g PackageDescription
([Executable]
-> [ForeignLib]
-> [TestSuite]
-> [Benchmark]
-> [RelativePath DataDir 'File]
-> SymbolicPath Pkg ('Dir DataDir)
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> PackageDescription)
-> g PackageDescription [Executable]
-> g PackageDescription
([ForeignLib]
-> [TestSuite]
-> [Benchmark]
-> [RelativePath DataDir 'File]
-> SymbolicPath Pkg ('Dir DataDir)
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> PackageDescription)
forall a b.
g PackageDescription (a -> b)
-> g PackageDescription a -> g PackageDescription b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> [Executable] -> g PackageDescription [Executable]
forall a. a -> g PackageDescription a
forall (f :: * -> *) a. Applicative f => a -> f a
pure []
g PackageDescription
([ForeignLib]
-> [TestSuite]
-> [Benchmark]
-> [RelativePath DataDir 'File]
-> SymbolicPath Pkg ('Dir DataDir)
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> PackageDescription)
-> g PackageDescription [ForeignLib]
-> g PackageDescription
([TestSuite]
-> [Benchmark]
-> [RelativePath DataDir 'File]
-> SymbolicPath Pkg ('Dir DataDir)
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> PackageDescription)
forall a b.
g PackageDescription (a -> b)
-> g PackageDescription a -> g PackageDescription b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> [ForeignLib] -> g PackageDescription [ForeignLib]
forall a. a -> g PackageDescription a
forall (f :: * -> *) a. Applicative f => a -> f a
pure []
g PackageDescription
([TestSuite]
-> [Benchmark]
-> [RelativePath DataDir 'File]
-> SymbolicPath Pkg ('Dir DataDir)
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> PackageDescription)
-> g PackageDescription [TestSuite]
-> g PackageDescription
([Benchmark]
-> [RelativePath DataDir 'File]
-> SymbolicPath Pkg ('Dir DataDir)
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> PackageDescription)
forall a b.
g PackageDescription (a -> b)
-> g PackageDescription a -> g PackageDescription b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> [TestSuite] -> g PackageDescription [TestSuite]
forall a. a -> g PackageDescription a
forall (f :: * -> *) a. Applicative f => a -> f a
pure []
g PackageDescription
([Benchmark]
-> [RelativePath DataDir 'File]
-> SymbolicPath Pkg ('Dir DataDir)
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> PackageDescription)
-> g PackageDescription [Benchmark]
-> g PackageDescription
([RelativePath DataDir 'File]
-> SymbolicPath Pkg ('Dir DataDir)
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> PackageDescription)
forall a b.
g PackageDescription (a -> b)
-> g PackageDescription a -> g PackageDescription b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> [Benchmark] -> g PackageDescription [Benchmark]
forall a. a -> g PackageDescription a
forall (f :: * -> *) a. Applicative f => a -> f a
pure []
g PackageDescription
([RelativePath DataDir 'File]
-> SymbolicPath Pkg ('Dir DataDir)
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> PackageDescription)
-> g PackageDescription [RelativePath DataDir 'File]
-> g PackageDescription
(SymbolicPath Pkg ('Dir DataDir)
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> PackageDescription)
forall a b.
g PackageDescription (a -> b)
-> g PackageDescription a -> g PackageDescription b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> FieldName
-> ([RelativePath DataDir 'File]
-> List
VCat (RelativePathNT DataDir 'File) (RelativePath DataDir 'File))
-> ALens' PackageDescription [RelativePath DataDir 'File]
-> g PackageDescription [RelativePath DataDir 'File]
forall b a s.
(c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
forall (c :: * -> Constraint) (g :: * -> * -> *) b a s.
(FieldGrammar c g, c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
monoidalFieldAla FieldName
"data-files" (VCat
-> (RelativePath DataDir 'File -> RelativePathNT DataDir 'File)
-> [RelativePath DataDir 'File]
-> List
VCat (RelativePathNT DataDir 'File) (RelativePath DataDir 'File)
forall sep a b. sep -> (a -> b) -> [a] -> List sep b a
alaList' VCat
VCat RelativePath DataDir 'File -> RelativePathNT DataDir 'File
forall from (to :: FileOrDir).
RelativePath from to -> RelativePathNT from to
RelativePathNT) ALens' PackageDescription [RelativePath DataDir 'File]
Lens' PackageDescription [RelativePath DataDir 'File]
L.dataFiles
g PackageDescription
(SymbolicPath Pkg ('Dir DataDir)
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> PackageDescription)
-> g PackageDescription (SymbolicPath Pkg ('Dir DataDir))
-> g PackageDescription
([RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> PackageDescription)
forall a b.
g PackageDescription (a -> b)
-> g PackageDescription a -> g PackageDescription b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> FieldName
-> (SymbolicPath Pkg ('Dir DataDir) -> CompatDataDir)
-> ALens' PackageDescription (SymbolicPath Pkg ('Dir DataDir))
-> SymbolicPath Pkg ('Dir DataDir)
-> g PackageDescription (SymbolicPath Pkg ('Dir DataDir))
forall b a s.
(c b, Newtype a b, Eq a) =>
FieldName -> (a -> b) -> ALens' s a -> a -> g s a
forall (c :: * -> Constraint) (g :: * -> * -> *) b a s.
(FieldGrammar c g, c b, Newtype a b, Eq a) =>
FieldName -> (a -> b) -> ALens' s a -> a -> g s a
optionalFieldDefAla FieldName
"data-dir" SymbolicPath Pkg ('Dir DataDir) -> CompatDataDir
CompatDataDir ALens' PackageDescription (SymbolicPath Pkg ('Dir DataDir))
Lens' PackageDescription (SymbolicPath Pkg ('Dir DataDir))
L.dataDir SymbolicPath Pkg ('Dir DataDir)
forall (allowAbsolute :: AllowAbsolute) from to.
SymbolicPathX allowAbsolute from ('Dir to)
sameDirectory
g PackageDescription (SymbolicPath Pkg ('Dir DataDir))
-> (g PackageDescription (SymbolicPath Pkg ('Dir DataDir))
-> g PackageDescription (SymbolicPath Pkg ('Dir DataDir)))
-> g PackageDescription (SymbolicPath Pkg ('Dir DataDir))
forall a b. a -> (a -> b) -> b
^^^ (SymbolicPath Pkg ('Dir DataDir)
-> SymbolicPath Pkg ('Dir DataDir))
-> g PackageDescription (SymbolicPath Pkg ('Dir DataDir))
-> g PackageDescription (SymbolicPath Pkg ('Dir DataDir))
forall a b.
(a -> b) -> g PackageDescription a -> g PackageDescription b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\SymbolicPath Pkg ('Dir DataDir)
x -> if String -> Bool
forall a. [a] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null (SymbolicPath Pkg ('Dir DataDir) -> String
forall (allowAbsolute :: AllowAbsolute) from (to :: FileOrDir).
SymbolicPathX allowAbsolute from to -> String
getSymbolicPath SymbolicPath Pkg ('Dir DataDir)
x) then SymbolicPath Pkg ('Dir DataDir)
forall (allowAbsolute :: AllowAbsolute) from to.
SymbolicPathX allowAbsolute from ('Dir to)
sameDirectory else SymbolicPath Pkg ('Dir DataDir)
x)
g PackageDescription
([RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> PackageDescription)
-> g PackageDescription [RelativePath Pkg 'File]
-> g PackageDescription
([RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> PackageDescription)
forall a b.
g PackageDescription (a -> b)
-> g PackageDescription a -> g PackageDescription b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> FieldName
-> ([RelativePath Pkg 'File]
-> List VCat (RelativePathNT Pkg 'File) (RelativePath Pkg 'File))
-> ALens' PackageDescription [RelativePath Pkg 'File]
-> g PackageDescription [RelativePath Pkg 'File]
forall b a s.
(c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
forall (c :: * -> Constraint) (g :: * -> * -> *) b a s.
(FieldGrammar c g, c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
monoidalFieldAla FieldName
"extra-source-files" [RelativePath Pkg 'File]
-> List VCat (RelativePathNT Pkg 'File) (RelativePath Pkg 'File)
formatExtraSourceFiles ALens' PackageDescription [RelativePath Pkg 'File]
Lens' PackageDescription [RelativePath Pkg 'File]
L.extraSrcFiles
g PackageDescription
([RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> [RelativePath Pkg 'File]
-> PackageDescription)
-> g PackageDescription [RelativePath Pkg 'File]
-> g PackageDescription
([RelativePath Pkg 'File]
-> [RelativePath Pkg 'File] -> PackageDescription)
forall a b.
g PackageDescription (a -> b)
-> g PackageDescription a -> g PackageDescription b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> FieldName
-> ([RelativePath Pkg 'File]
-> List VCat (RelativePathNT Pkg 'File) (RelativePath Pkg 'File))
-> ALens' PackageDescription [RelativePath Pkg 'File]
-> g PackageDescription [RelativePath Pkg 'File]
forall b a s.
(c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
forall (c :: * -> Constraint) (g :: * -> * -> *) b a s.
(FieldGrammar c g, c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
monoidalFieldAla FieldName
"extra-tmp-files" (VCat
-> (RelativePath Pkg 'File -> RelativePathNT Pkg 'File)
-> [RelativePath Pkg 'File]
-> List VCat (RelativePathNT Pkg 'File) (RelativePath Pkg 'File)
forall sep a b. sep -> (a -> b) -> [a] -> List sep b a
alaList' VCat
VCat RelativePath Pkg 'File -> RelativePathNT Pkg 'File
forall from (to :: FileOrDir).
RelativePath from to -> RelativePathNT from to
RelativePathNT) ALens' PackageDescription [RelativePath Pkg 'File]
Lens' PackageDescription [RelativePath Pkg 'File]
L.extraTmpFiles
g PackageDescription
([RelativePath Pkg 'File]
-> [RelativePath Pkg 'File] -> PackageDescription)
-> g PackageDescription [RelativePath Pkg 'File]
-> g PackageDescription
([RelativePath Pkg 'File] -> PackageDescription)
forall a b.
g PackageDescription (a -> b)
-> g PackageDescription a -> g PackageDescription b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> FieldName
-> ([RelativePath Pkg 'File]
-> List VCat (RelativePathNT Pkg 'File) (RelativePath Pkg 'File))
-> ALens' PackageDescription [RelativePath Pkg 'File]
-> g PackageDescription [RelativePath Pkg 'File]
forall b a s.
(c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
forall (c :: * -> Constraint) (g :: * -> * -> *) b a s.
(FieldGrammar c g, c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
monoidalFieldAla FieldName
"extra-doc-files" [RelativePath Pkg 'File]
-> List VCat (RelativePathNT Pkg 'File) (RelativePath Pkg 'File)
formatExtraSourceFiles ALens' PackageDescription [RelativePath Pkg 'File]
Lens' PackageDescription [RelativePath Pkg 'File]
L.extraDocFiles
g PackageDescription
([RelativePath Pkg 'File] -> PackageDescription)
-> g PackageDescription [RelativePath Pkg 'File]
-> g PackageDescription PackageDescription
forall a b.
g PackageDescription (a -> b)
-> g PackageDescription a -> g PackageDescription b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> FieldName
-> ([RelativePath Pkg 'File]
-> List VCat (RelativePathNT Pkg 'File) (RelativePath Pkg 'File))
-> ALens' PackageDescription [RelativePath Pkg 'File]
-> g PackageDescription [RelativePath Pkg 'File]
forall b a s.
(c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
forall (c :: * -> Constraint) (g :: * -> * -> *) b a s.
(FieldGrammar c g, c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
monoidalFieldAla FieldName
"extra-files" [RelativePath Pkg 'File]
-> List VCat (RelativePathNT Pkg 'File) (RelativePath Pkg 'File)
formatExtraSourceFiles ALens' PackageDescription [RelativePath Pkg 'File]
Lens' PackageDescription [RelativePath Pkg 'File]
L.extraFiles
g PackageDescription [RelativePath Pkg 'File]
-> (g PackageDescription [RelativePath Pkg 'File]
-> g PackageDescription [RelativePath Pkg 'File])
-> g PackageDescription [RelativePath Pkg 'File]
forall a b. a -> (a -> b) -> b
^^^ CabalSpecVersion
-> [RelativePath Pkg 'File]
-> g PackageDescription [RelativePath Pkg 'File]
-> g PackageDescription [RelativePath Pkg 'File]
forall a s. CabalSpecVersion -> a -> g s a -> g s a
forall (c :: * -> Constraint) (g :: * -> * -> *) a s.
FieldGrammar c g =>
CabalSpecVersion -> a -> g s a -> g s a
availableSince CabalSpecVersion
CabalSpecV3_14 []
where
packageIdentifierGrammar :: g PackageIdentifier PackageIdentifier
packageIdentifierGrammar =
PackageName -> Version -> PackageIdentifier
PackageIdentifier
(PackageName -> Version -> PackageIdentifier)
-> g PackageIdentifier PackageName
-> g PackageIdentifier (Version -> PackageIdentifier)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> FieldName
-> ALens' PackageIdentifier PackageName
-> g PackageIdentifier PackageName
forall (c :: * -> Constraint) (g :: * -> * -> *) a s.
(FieldGrammar c g, c (Identity a)) =>
FieldName -> ALens' s a -> g s a
uniqueField FieldName
"name" ALens' PackageIdentifier PackageName
Lens' PackageIdentifier PackageName
L.pkgName
g PackageIdentifier (Version -> PackageIdentifier)
-> g PackageIdentifier Version
-> g PackageIdentifier PackageIdentifier
forall a b.
g PackageIdentifier (a -> b)
-> g PackageIdentifier a -> g PackageIdentifier b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> FieldName
-> ALens' PackageIdentifier Version -> g PackageIdentifier Version
forall (c :: * -> Constraint) (g :: * -> * -> *) a s.
(FieldGrammar c g, c (Identity a)) =>
FieldName -> ALens' s a -> g s a
uniqueField FieldName
"version" ALens' PackageIdentifier Version
Lens' PackageIdentifier Version
L.pkgVersion
licenseFilesGrammar :: g PackageDescription [RelativePath Pkg 'File]
licenseFilesGrammar =
[RelativePath Pkg 'File]
-> [RelativePath Pkg 'File] -> [RelativePath Pkg 'File]
forall a. [a] -> [a] -> [a]
(++)
([RelativePath Pkg 'File]
-> [RelativePath Pkg 'File] -> [RelativePath Pkg 'File])
-> g PackageDescription [RelativePath Pkg 'File]
-> g PackageDescription
([RelativePath Pkg 'File] -> [RelativePath Pkg 'File])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> FieldName
-> ([RelativePath Pkg 'File] -> CompatLicenseFile)
-> ALens' PackageDescription [RelativePath Pkg 'File]
-> g PackageDescription [RelativePath Pkg 'File]
forall b a s.
(c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
forall (c :: * -> Constraint) (g :: * -> * -> *) b a s.
(FieldGrammar c g, c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
monoidalFieldAla FieldName
"license-file" [RelativePath Pkg 'File] -> CompatLicenseFile
CompatLicenseFile ALens' PackageDescription [RelativePath Pkg 'File]
Lens' PackageDescription [RelativePath Pkg 'File]
L.licenseFiles
g PackageDescription
([RelativePath Pkg 'File] -> [RelativePath Pkg 'File])
-> g PackageDescription [RelativePath Pkg 'File]
-> g PackageDescription [RelativePath Pkg 'File]
forall a b.
g PackageDescription (a -> b)
-> g PackageDescription a -> g PackageDescription b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> FieldName
-> ([RelativePath Pkg 'File]
-> List FSep (RelativePathNT Pkg 'File) (RelativePath Pkg 'File))
-> ALens' PackageDescription [RelativePath Pkg 'File]
-> g PackageDescription [RelativePath Pkg 'File]
forall b a s.
(c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
forall (c :: * -> Constraint) (g :: * -> * -> *) b a s.
(FieldGrammar c g, c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
monoidalFieldAla FieldName
"license-files" (FSep
-> (RelativePath Pkg 'File -> RelativePathNT Pkg 'File)
-> [RelativePath Pkg 'File]
-> List FSep (RelativePathNT Pkg 'File) (RelativePath Pkg 'File)
forall sep a b. sep -> (a -> b) -> [a] -> List sep b a
alaList' FSep
FSep RelativePath Pkg 'File -> RelativePathNT Pkg 'File
forall from (to :: FileOrDir).
RelativePath from to -> RelativePathNT from to
RelativePathNT) ALens' PackageDescription [RelativePath Pkg 'File]
Lens' PackageDescription [RelativePath Pkg 'File]
L.licenseFiles
g PackageDescription [RelativePath Pkg 'File]
-> (g PackageDescription [RelativePath Pkg 'File]
-> g PackageDescription [RelativePath Pkg 'File])
-> g PackageDescription [RelativePath Pkg 'File]
forall a b. a -> (a -> b) -> b
^^^ g PackageDescription [RelativePath Pkg 'File]
-> g PackageDescription [RelativePath Pkg 'File]
forall s a. g s a -> g s a
forall (c :: * -> Constraint) (g :: * -> * -> *) s a.
FieldGrammar c g =>
g s a -> g s a
hiddenField
libraryFieldGrammar
:: ( FieldGrammar c g
, Applicative (g Library)
, Applicative (g BuildInfo)
, c (Identity LibraryVisibility)
, c (List CommaFSep (Identity ExeDependency) ExeDependency)
, c (List CommaFSep (Identity LegacyExeDependency) LegacyExeDependency)
, c (List CommaFSep (Identity PkgconfigDependency) PkgconfigDependency)
, c (List CommaVCat (Identity Dependency) Dependency)
, c (List CommaVCat (Identity Mixin) Mixin)
, c (List CommaVCat (Identity ModuleReexport) ModuleReexport)
, c (List FSep (MQuoted Extension) Extension)
, c (List FSep (MQuoted Language) Language)
, c (List FSep Token String)
, c (List NoCommaFSep Token' String)
, c (List VCat (MQuoted ModuleName) ModuleName)
, forall from to. c (List FSep (SymbolicPathNT from to) (SymbolicPath from to))
, forall from to. c (List FSep (RelativePathNT from to) (RelativePath from to))
, forall from to. c (List VCat (SymbolicPathNT from to) (SymbolicPath from to))
, c (List VCat Token String)
, c (MQuoted Language)
)
=> LibraryName
-> g Library Library
libraryFieldGrammar :: forall (c :: * -> Constraint) (g :: * -> * -> *).
(FieldGrammar c g, Applicative (g Library),
Applicative (g BuildInfo), c (Identity LibraryVisibility),
c (List CommaFSep (Identity ExeDependency) ExeDependency),
c (List
CommaFSep (Identity LegacyExeDependency) LegacyExeDependency),
c (List
CommaFSep (Identity PkgconfigDependency) PkgconfigDependency),
c (List CommaVCat (Identity Dependency) Dependency),
c (List CommaVCat (Identity Mixin) Mixin),
c (List CommaVCat (Identity ModuleReexport) ModuleReexport),
c (List FSep (MQuoted Extension) Extension),
c (List FSep (MQuoted Language) Language),
c (List FSep Token String), c (List NoCommaFSep Token' String),
c (List VCat (MQuoted ModuleName) ModuleName),
forall from (to :: FileOrDir).
c (List FSep (SymbolicPathNT from to) (SymbolicPath from to)),
forall from (to :: FileOrDir).
c (List FSep (RelativePathNT from to) (RelativePath from to)),
forall from (to :: FileOrDir).
c (List VCat (SymbolicPathNT from to) (SymbolicPath from to)),
c (List VCat Token String), c (MQuoted Language)) =>
LibraryName -> g Library Library
libraryFieldGrammar LibraryName
n =
LibraryName
-> [ModuleName]
-> [ModuleReexport]
-> [ModuleName]
-> Bool
-> LibraryVisibility
-> BuildInfo
-> Library
Library LibraryName
n
([ModuleName]
-> [ModuleReexport]
-> [ModuleName]
-> Bool
-> LibraryVisibility
-> BuildInfo
-> Library)
-> g Library [ModuleName]
-> g Library
([ModuleReexport]
-> [ModuleName]
-> Bool
-> LibraryVisibility
-> BuildInfo
-> Library)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> FieldName
-> ([ModuleName] -> List VCat (MQuoted ModuleName) ModuleName)
-> ALens' Library [ModuleName]
-> g Library [ModuleName]
forall b a s.
(c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
forall (c :: * -> Constraint) (g :: * -> * -> *) b a s.
(FieldGrammar c g, c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
monoidalFieldAla FieldName
"exposed-modules" [ModuleName] -> List VCat (MQuoted ModuleName) ModuleName
formatExposedModules ALens' Library [ModuleName]
Lens' Library [ModuleName]
L.exposedModules
g Library
([ModuleReexport]
-> [ModuleName]
-> Bool
-> LibraryVisibility
-> BuildInfo
-> Library)
-> g Library [ModuleReexport]
-> g Library
([ModuleName] -> Bool -> LibraryVisibility -> BuildInfo -> Library)
forall a b. g Library (a -> b) -> g Library a -> g Library b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> FieldName
-> ([ModuleReexport]
-> List CommaVCat (Identity ModuleReexport) ModuleReexport)
-> ALens' Library [ModuleReexport]
-> g Library [ModuleReexport]
forall b a s.
(c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
forall (c :: * -> Constraint) (g :: * -> * -> *) b a s.
(FieldGrammar c g, c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
monoidalFieldAla FieldName
"reexported-modules" (CommaVCat
-> [ModuleReexport]
-> List CommaVCat (Identity ModuleReexport) ModuleReexport
forall sep a. sep -> [a] -> List sep (Identity a) a
alaList CommaVCat
CommaVCat) ALens' Library [ModuleReexport]
Lens' Library [ModuleReexport]
L.reexportedModules
g Library
([ModuleName] -> Bool -> LibraryVisibility -> BuildInfo -> Library)
-> g Library [ModuleName]
-> g Library (Bool -> LibraryVisibility -> BuildInfo -> Library)
forall a b. g Library (a -> b) -> g Library a -> g Library b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> FieldName
-> ([ModuleName] -> List VCat (MQuoted ModuleName) ModuleName)
-> ALens' Library [ModuleName]
-> g Library [ModuleName]
forall b a s.
(c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
forall (c :: * -> Constraint) (g :: * -> * -> *) b a s.
(FieldGrammar c g, c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
monoidalFieldAla FieldName
"signatures" (VCat
-> (ModuleName -> MQuoted ModuleName)
-> [ModuleName]
-> List VCat (MQuoted ModuleName) ModuleName
forall sep a b. sep -> (a -> b) -> [a] -> List sep b a
alaList' VCat
VCat ModuleName -> MQuoted ModuleName
forall a. a -> MQuoted a
MQuoted) ALens' Library [ModuleName]
Lens' Library [ModuleName]
L.signatures
g Library [ModuleName]
-> (g Library [ModuleName] -> g Library [ModuleName])
-> g Library [ModuleName]
forall a b. a -> (a -> b) -> b
^^^ CabalSpecVersion
-> [ModuleName] -> g Library [ModuleName] -> g Library [ModuleName]
forall a s. CabalSpecVersion -> a -> g s a -> g s a
forall (c :: * -> Constraint) (g :: * -> * -> *) a s.
FieldGrammar c g =>
CabalSpecVersion -> a -> g s a -> g s a
availableSince CabalSpecVersion
CabalSpecV2_0 []
g Library (Bool -> LibraryVisibility -> BuildInfo -> Library)
-> g Library Bool
-> g Library (LibraryVisibility -> BuildInfo -> Library)
forall a b. g Library (a -> b) -> g Library a -> g Library b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> FieldName -> ALens' Library Bool -> Bool -> g Library Bool
forall s. FieldName -> ALens' s Bool -> Bool -> g s Bool
forall (c :: * -> Constraint) (g :: * -> * -> *) s.
FieldGrammar c g =>
FieldName -> ALens' s Bool -> Bool -> g s Bool
booleanFieldDef FieldName
"exposed" ALens' Library Bool
Lens' Library Bool
L.libExposed Bool
True
g Library (LibraryVisibility -> BuildInfo -> Library)
-> g Library LibraryVisibility -> g Library (BuildInfo -> Library)
forall a b. g Library (a -> b) -> g Library a -> g Library b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> g Library LibraryVisibility
visibilityField
g Library (BuildInfo -> Library)
-> g Library BuildInfo -> g Library Library
forall a b. g Library (a -> b) -> g Library a -> g Library b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ALens' Library BuildInfo
-> g BuildInfo BuildInfo -> g Library BuildInfo
forall a b d. ALens' a b -> g b d -> g a d
forall (c :: * -> Constraint) (g :: * -> * -> *) a b d.
FieldGrammar c g =>
ALens' a b -> g b d -> g a d
blurFieldGrammar ALens' Library BuildInfo
Lens' Library BuildInfo
L.libBuildInfo g BuildInfo BuildInfo
forall (c :: * -> Constraint) (g :: * -> * -> *).
(FieldGrammar c g, Applicative (g BuildInfo),
c (List CommaFSep (Identity ExeDependency) ExeDependency),
c (List
CommaFSep (Identity LegacyExeDependency) LegacyExeDependency),
c (List
CommaFSep (Identity PkgconfigDependency) PkgconfigDependency),
c (List CommaVCat (Identity Dependency) Dependency),
c (List CommaVCat (Identity Mixin) Mixin),
c (List FSep (MQuoted Extension) Extension),
c (List FSep (MQuoted Language) Language),
c (List FSep Token String), c (List NoCommaFSep Token' String),
c (List VCat (MQuoted ModuleName) ModuleName),
forall from (to :: FileOrDir).
c (List FSep (SymbolicPathNT from to) (SymbolicPath from to)),
forall from (to :: FileOrDir).
c (List FSep (RelativePathNT from to) (RelativePath from to)),
forall from (to :: FileOrDir).
c (List VCat (SymbolicPathNT from to) (SymbolicPath from to)),
c (List VCat Token String), c (MQuoted Language)) =>
g BuildInfo BuildInfo
buildInfoFieldGrammar
where
visibilityField :: g Library LibraryVisibility
visibilityField = case LibraryName
n of
LibraryName
LMainLibName -> LibraryVisibility -> g Library LibraryVisibility
forall a. a -> g Library a
forall (f :: * -> *) a. Applicative f => a -> f a
pure LibraryVisibility
LibraryVisibilityPublic
LSubLibName UnqualComponentName
_ ->
FieldName
-> ALens' Library LibraryVisibility
-> LibraryVisibility
-> g Library LibraryVisibility
forall (c :: * -> Constraint) (g :: * -> * -> *) s a.
(FieldGrammar c g, Functor (g s), c (Identity a), Eq a) =>
FieldName -> ALens' s a -> a -> g s a
optionalFieldDef FieldName
"visibility" ALens' Library LibraryVisibility
Lens' Library LibraryVisibility
L.libVisibility LibraryVisibility
LibraryVisibilityPrivate
g Library LibraryVisibility
-> (g Library LibraryVisibility -> g Library LibraryVisibility)
-> g Library LibraryVisibility
forall a b. a -> (a -> b) -> b
^^^ CabalSpecVersion
-> LibraryVisibility
-> g Library LibraryVisibility
-> g Library LibraryVisibility
forall a s. CabalSpecVersion -> a -> g s a -> g s a
forall (c :: * -> Constraint) (g :: * -> * -> *) a s.
FieldGrammar c g =>
CabalSpecVersion -> a -> g s a -> g s a
availableSince CabalSpecVersion
CabalSpecV3_0 LibraryVisibility
LibraryVisibilityPrivate
{-# SPECIALIZE libraryFieldGrammar :: LibraryName -> ParsecFieldGrammar' Library #-}
{-# SPECIALIZE libraryFieldGrammar :: LibraryName -> PrettyFieldGrammar' Library #-}
foreignLibFieldGrammar
:: ( FieldGrammar c g
, Applicative (g ForeignLib)
, Applicative (g BuildInfo)
, c (Identity ForeignLibType)
, c (Identity LibVersionInfo)
, c (Identity Version)
, c (List CommaFSep (Identity ExeDependency) ExeDependency)
, c (List CommaFSep (Identity LegacyExeDependency) LegacyExeDependency)
, c (List CommaFSep (Identity PkgconfigDependency) PkgconfigDependency)
, c (List CommaVCat (Identity Dependency) Dependency)
, c (List CommaVCat (Identity Mixin) Mixin)
, c (List FSep (Identity ForeignLibOption) ForeignLibOption)
, c (List FSep (MQuoted Extension) Extension)
, c (List FSep (MQuoted Language) Language)
, c (List FSep Token String)
, forall from to. c (List FSep (SymbolicPathNT from to) (SymbolicPath from to))
, forall from to. c (List FSep (RelativePathNT from to) (RelativePath from to))
, forall from to. c (List VCat (SymbolicPathNT from to) (SymbolicPath from to))
, c (List NoCommaFSep Token' String)
, c (List VCat (MQuoted ModuleName) ModuleName)
, c (List VCat Token String)
, c (MQuoted Language)
)
=> UnqualComponentName
-> g ForeignLib ForeignLib
foreignLibFieldGrammar :: forall (c :: * -> Constraint) (g :: * -> * -> *).
(FieldGrammar c g, Applicative (g ForeignLib),
Applicative (g BuildInfo), c (Identity ForeignLibType),
c (Identity LibVersionInfo), c (Identity Version),
c (List CommaFSep (Identity ExeDependency) ExeDependency),
c (List
CommaFSep (Identity LegacyExeDependency) LegacyExeDependency),
c (List
CommaFSep (Identity PkgconfigDependency) PkgconfigDependency),
c (List CommaVCat (Identity Dependency) Dependency),
c (List CommaVCat (Identity Mixin) Mixin),
c (List FSep (Identity ForeignLibOption) ForeignLibOption),
c (List FSep (MQuoted Extension) Extension),
c (List FSep (MQuoted Language) Language),
c (List FSep Token String),
forall from (to :: FileOrDir).
c (List FSep (SymbolicPathNT from to) (SymbolicPath from to)),
forall from (to :: FileOrDir).
c (List FSep (RelativePathNT from to) (RelativePath from to)),
forall from (to :: FileOrDir).
c (List VCat (SymbolicPathNT from to) (SymbolicPath from to)),
c (List NoCommaFSep Token' String),
c (List VCat (MQuoted ModuleName) ModuleName),
c (List VCat Token String), c (MQuoted Language)) =>
UnqualComponentName -> g ForeignLib ForeignLib
foreignLibFieldGrammar UnqualComponentName
n =
UnqualComponentName
-> ForeignLibType
-> [ForeignLibOption]
-> BuildInfo
-> Maybe LibVersionInfo
-> Maybe Version
-> [RelativePath Source 'File]
-> ForeignLib
ForeignLib UnqualComponentName
n
(ForeignLibType
-> [ForeignLibOption]
-> BuildInfo
-> Maybe LibVersionInfo
-> Maybe Version
-> [RelativePath Source 'File]
-> ForeignLib)
-> g ForeignLib ForeignLibType
-> g ForeignLib
([ForeignLibOption]
-> BuildInfo
-> Maybe LibVersionInfo
-> Maybe Version
-> [RelativePath Source 'File]
-> ForeignLib)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> FieldName
-> ALens' ForeignLib ForeignLibType
-> ForeignLibType
-> g ForeignLib ForeignLibType
forall (c :: * -> Constraint) (g :: * -> * -> *) s a.
(FieldGrammar c g, Functor (g s), c (Identity a), Eq a) =>
FieldName -> ALens' s a -> a -> g s a
optionalFieldDef FieldName
"type" ALens' ForeignLib ForeignLibType
Lens' ForeignLib ForeignLibType
L.foreignLibType ForeignLibType
ForeignLibTypeUnknown
g ForeignLib
([ForeignLibOption]
-> BuildInfo
-> Maybe LibVersionInfo
-> Maybe Version
-> [RelativePath Source 'File]
-> ForeignLib)
-> g ForeignLib [ForeignLibOption]
-> g ForeignLib
(BuildInfo
-> Maybe LibVersionInfo
-> Maybe Version
-> [RelativePath Source 'File]
-> ForeignLib)
forall a b.
g ForeignLib (a -> b) -> g ForeignLib a -> g ForeignLib b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> FieldName
-> ([ForeignLibOption]
-> List FSep (Identity ForeignLibOption) ForeignLibOption)
-> ALens' ForeignLib [ForeignLibOption]
-> g ForeignLib [ForeignLibOption]
forall b a s.
(c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
forall (c :: * -> Constraint) (g :: * -> * -> *) b a s.
(FieldGrammar c g, c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
monoidalFieldAla FieldName
"options" (FSep
-> [ForeignLibOption]
-> List FSep (Identity ForeignLibOption) ForeignLibOption
forall sep a. sep -> [a] -> List sep (Identity a) a
alaList FSep
FSep) ALens' ForeignLib [ForeignLibOption]
Lens' ForeignLib [ForeignLibOption]
L.foreignLibOptions
g ForeignLib
(BuildInfo
-> Maybe LibVersionInfo
-> Maybe Version
-> [RelativePath Source 'File]
-> ForeignLib)
-> g ForeignLib BuildInfo
-> g ForeignLib
(Maybe LibVersionInfo
-> Maybe Version -> [RelativePath Source 'File] -> ForeignLib)
forall a b.
g ForeignLib (a -> b) -> g ForeignLib a -> g ForeignLib b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ALens' ForeignLib BuildInfo
-> g BuildInfo BuildInfo -> g ForeignLib BuildInfo
forall a b d. ALens' a b -> g b d -> g a d
forall (c :: * -> Constraint) (g :: * -> * -> *) a b d.
FieldGrammar c g =>
ALens' a b -> g b d -> g a d
blurFieldGrammar ALens' ForeignLib BuildInfo
Lens' ForeignLib BuildInfo
L.foreignLibBuildInfo g BuildInfo BuildInfo
forall (c :: * -> Constraint) (g :: * -> * -> *).
(FieldGrammar c g, Applicative (g BuildInfo),
c (List CommaFSep (Identity ExeDependency) ExeDependency),
c (List
CommaFSep (Identity LegacyExeDependency) LegacyExeDependency),
c (List
CommaFSep (Identity PkgconfigDependency) PkgconfigDependency),
c (List CommaVCat (Identity Dependency) Dependency),
c (List CommaVCat (Identity Mixin) Mixin),
c (List FSep (MQuoted Extension) Extension),
c (List FSep (MQuoted Language) Language),
c (List FSep Token String), c (List NoCommaFSep Token' String),
c (List VCat (MQuoted ModuleName) ModuleName),
forall from (to :: FileOrDir).
c (List FSep (SymbolicPathNT from to) (SymbolicPath from to)),
forall from (to :: FileOrDir).
c (List FSep (RelativePathNT from to) (RelativePath from to)),
forall from (to :: FileOrDir).
c (List VCat (SymbolicPathNT from to) (SymbolicPath from to)),
c (List VCat Token String), c (MQuoted Language)) =>
g BuildInfo BuildInfo
buildInfoFieldGrammar
g ForeignLib
(Maybe LibVersionInfo
-> Maybe Version -> [RelativePath Source 'File] -> ForeignLib)
-> g ForeignLib (Maybe LibVersionInfo)
-> g ForeignLib
(Maybe Version -> [RelativePath Source 'File] -> ForeignLib)
forall a b.
g ForeignLib (a -> b) -> g ForeignLib a -> g ForeignLib b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> FieldName
-> ALens' ForeignLib (Maybe LibVersionInfo)
-> g ForeignLib (Maybe LibVersionInfo)
forall (c :: * -> Constraint) (g :: * -> * -> *) a s.
(FieldGrammar c g, c (Identity a)) =>
FieldName -> ALens' s (Maybe a) -> g s (Maybe a)
optionalField FieldName
"lib-version-info" ALens' ForeignLib (Maybe LibVersionInfo)
Lens' ForeignLib (Maybe LibVersionInfo)
L.foreignLibVersionInfo
g ForeignLib
(Maybe Version -> [RelativePath Source 'File] -> ForeignLib)
-> g ForeignLib (Maybe Version)
-> g ForeignLib ([RelativePath Source 'File] -> ForeignLib)
forall a b.
g ForeignLib (a -> b) -> g ForeignLib a -> g ForeignLib b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> FieldName
-> ALens' ForeignLib (Maybe Version)
-> g ForeignLib (Maybe Version)
forall (c :: * -> Constraint) (g :: * -> * -> *) a s.
(FieldGrammar c g, c (Identity a)) =>
FieldName -> ALens' s (Maybe a) -> g s (Maybe a)
optionalField FieldName
"lib-version-linux" ALens' ForeignLib (Maybe Version)
Lens' ForeignLib (Maybe Version)
L.foreignLibVersionLinux
g ForeignLib ([RelativePath Source 'File] -> ForeignLib)
-> g ForeignLib [RelativePath Source 'File]
-> g ForeignLib ForeignLib
forall a b.
g ForeignLib (a -> b) -> g ForeignLib a -> g ForeignLib b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> FieldName
-> ([RelativePath Source 'File]
-> List
FSep (RelativePathNT Source 'File) (RelativePath Source 'File))
-> ALens' ForeignLib [RelativePath Source 'File]
-> g ForeignLib [RelativePath Source 'File]
forall b a s.
(c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
forall (c :: * -> Constraint) (g :: * -> * -> *) b a s.
(FieldGrammar c g, c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
monoidalFieldAla FieldName
"mod-def-file" (FSep
-> (RelativePath Source 'File -> RelativePathNT Source 'File)
-> [RelativePath Source 'File]
-> List
FSep (RelativePathNT Source 'File) (RelativePath Source 'File)
forall sep a b. sep -> (a -> b) -> [a] -> List sep b a
alaList' FSep
FSep RelativePath Source 'File -> RelativePathNT Source 'File
forall from (to :: FileOrDir).
RelativePath from to -> RelativePathNT from to
RelativePathNT) ALens' ForeignLib [RelativePath Source 'File]
Lens' ForeignLib [RelativePath Source 'File]
L.foreignLibModDefFile
{-# SPECIALIZE foreignLibFieldGrammar :: UnqualComponentName -> ParsecFieldGrammar' ForeignLib #-}
{-# SPECIALIZE foreignLibFieldGrammar :: UnqualComponentName -> PrettyFieldGrammar' ForeignLib #-}
executableFieldGrammar
:: ( FieldGrammar c g
, Applicative (g Executable)
, Applicative (g BuildInfo)
, c (Identity ExecutableScope)
, c (List CommaFSep (Identity ExeDependency) ExeDependency)
, c (List CommaFSep (Identity LegacyExeDependency) LegacyExeDependency)
, c (List CommaFSep (Identity PkgconfigDependency) PkgconfigDependency)
, c (List CommaVCat (Identity Dependency) Dependency)
, c (List CommaVCat (Identity Mixin) Mixin)
, c (List FSep (MQuoted Extension) Extension)
, c (List FSep (MQuoted Language) Language)
, c (List FSep Token String)
, forall from to. c (List FSep (SymbolicPathNT from to) (SymbolicPath from to))
, forall from to. c (List FSep (RelativePathNT from to) (RelativePath from to))
, forall from to. c (List FSep (SymbolicPathNT from to) (SymbolicPath from to))
, forall from to. c (List FSep (RelativePathNT from to) (RelativePath from to))
, forall from to. c (List VCat (SymbolicPathNT from to) (SymbolicPath from to))
, forall from to. c (SymbolicPathNT from to)
, forall from to. c (RelativePathNT from to)
, c (List NoCommaFSep Token' String)
, c (List VCat (MQuoted ModuleName) ModuleName)
, c (List VCat Token String)
, c (MQuoted Language)
)
=> UnqualComponentName
-> g Executable Executable
executableFieldGrammar :: forall (c :: * -> Constraint) (g :: * -> * -> *).
(FieldGrammar c g, Applicative (g Executable),
Applicative (g BuildInfo), c (Identity ExecutableScope),
c (List CommaFSep (Identity ExeDependency) ExeDependency),
c (List
CommaFSep (Identity LegacyExeDependency) LegacyExeDependency),
c (List
CommaFSep (Identity PkgconfigDependency) PkgconfigDependency),
c (List CommaVCat (Identity Dependency) Dependency),
c (List CommaVCat (Identity Mixin) Mixin),
c (List FSep (MQuoted Extension) Extension),
c (List FSep (MQuoted Language) Language),
c (List FSep Token String),
forall from (to :: FileOrDir).
c (List FSep (SymbolicPathNT from to) (SymbolicPath from to)),
forall from (to :: FileOrDir).
c (List FSep (RelativePathNT from to) (RelativePath from to)),
forall from (to :: FileOrDir).
c (List FSep (SymbolicPathNT from to) (SymbolicPath from to)),
forall from (to :: FileOrDir).
c (List FSep (RelativePathNT from to) (RelativePath from to)),
forall from (to :: FileOrDir).
c (List VCat (SymbolicPathNT from to) (SymbolicPath from to)),
forall from (to :: FileOrDir). c (SymbolicPathNT from to),
forall from (to :: FileOrDir). c (RelativePathNT from to),
c (List NoCommaFSep Token' String),
c (List VCat (MQuoted ModuleName) ModuleName),
c (List VCat Token String), c (MQuoted Language)) =>
UnqualComponentName -> g Executable Executable
executableFieldGrammar UnqualComponentName
n =
UnqualComponentName
-> RelativePath Source 'File
-> ExecutableScope
-> BuildInfo
-> Executable
Executable UnqualComponentName
n
(RelativePath Source 'File
-> ExecutableScope -> BuildInfo -> Executable)
-> g Executable (RelativePath Source 'File)
-> g Executable (ExecutableScope -> BuildInfo -> Executable)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> FieldName
-> (RelativePath Source 'File -> RelativePathNT Source 'File)
-> ALens' Executable (RelativePath Source 'File)
-> RelativePath Source 'File
-> g Executable (RelativePath Source 'File)
forall b a s.
(c b, Newtype a b, Eq a) =>
FieldName -> (a -> b) -> ALens' s a -> a -> g s a
forall (c :: * -> Constraint) (g :: * -> * -> *) b a s.
(FieldGrammar c g, c b, Newtype a b, Eq a) =>
FieldName -> (a -> b) -> ALens' s a -> a -> g s a
optionalFieldDefAla FieldName
"main-is" RelativePath Source 'File -> RelativePathNT Source 'File
forall from (to :: FileOrDir).
RelativePath from to -> RelativePathNT from to
RelativePathNT ALens' Executable (RelativePath Source 'File)
Lens' Executable (RelativePath Source 'File)
L.modulePath (Executable -> RelativePath Source 'File
modulePath Executable
forall a. Monoid a => a
mempty)
g Executable (ExecutableScope -> BuildInfo -> Executable)
-> g Executable ExecutableScope
-> g Executable (BuildInfo -> Executable)
forall a b.
g Executable (a -> b) -> g Executable a -> g Executable b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> FieldName
-> ALens' Executable ExecutableScope
-> ExecutableScope
-> g Executable ExecutableScope
forall (c :: * -> Constraint) (g :: * -> * -> *) s a.
(FieldGrammar c g, Functor (g s), c (Identity a), Eq a) =>
FieldName -> ALens' s a -> a -> g s a
optionalFieldDef FieldName
"scope" ALens' Executable ExecutableScope
Lens' Executable ExecutableScope
L.exeScope ExecutableScope
ExecutablePublic
g Executable ExecutableScope
-> (g Executable ExecutableScope -> g Executable ExecutableScope)
-> g Executable ExecutableScope
forall a b. a -> (a -> b) -> b
^^^ CabalSpecVersion
-> ExecutableScope
-> g Executable ExecutableScope
-> g Executable ExecutableScope
forall a s. CabalSpecVersion -> a -> g s a -> g s a
forall (c :: * -> Constraint) (g :: * -> * -> *) a s.
FieldGrammar c g =>
CabalSpecVersion -> a -> g s a -> g s a
availableSince CabalSpecVersion
CabalSpecV2_0 ExecutableScope
ExecutablePublic
g Executable (BuildInfo -> Executable)
-> g Executable BuildInfo -> g Executable Executable
forall a b.
g Executable (a -> b) -> g Executable a -> g Executable b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ALens' Executable BuildInfo
-> g BuildInfo BuildInfo -> g Executable BuildInfo
forall a b d. ALens' a b -> g b d -> g a d
forall (c :: * -> Constraint) (g :: * -> * -> *) a b d.
FieldGrammar c g =>
ALens' a b -> g b d -> g a d
blurFieldGrammar ALens' Executable BuildInfo
forall a. HasBuildInfo a => Lens' a BuildInfo
Lens' Executable BuildInfo
L.buildInfo g BuildInfo BuildInfo
forall (c :: * -> Constraint) (g :: * -> * -> *).
(FieldGrammar c g, Applicative (g BuildInfo),
c (List CommaFSep (Identity ExeDependency) ExeDependency),
c (List
CommaFSep (Identity LegacyExeDependency) LegacyExeDependency),
c (List
CommaFSep (Identity PkgconfigDependency) PkgconfigDependency),
c (List CommaVCat (Identity Dependency) Dependency),
c (List CommaVCat (Identity Mixin) Mixin),
c (List FSep (MQuoted Extension) Extension),
c (List FSep (MQuoted Language) Language),
c (List FSep Token String), c (List NoCommaFSep Token' String),
c (List VCat (MQuoted ModuleName) ModuleName),
forall from (to :: FileOrDir).
c (List FSep (SymbolicPathNT from to) (SymbolicPath from to)),
forall from (to :: FileOrDir).
c (List FSep (RelativePathNT from to) (RelativePath from to)),
forall from (to :: FileOrDir).
c (List VCat (SymbolicPathNT from to) (SymbolicPath from to)),
c (List VCat Token String), c (MQuoted Language)) =>
g BuildInfo BuildInfo
buildInfoFieldGrammar
{-# SPECIALIZE executableFieldGrammar :: UnqualComponentName -> ParsecFieldGrammar' Executable #-}
{-# SPECIALIZE executableFieldGrammar :: UnqualComponentName -> PrettyFieldGrammar' Executable #-}
data TestSuiteStanza = TestSuiteStanza
{ TestSuiteStanza -> Maybe TestType
_testStanzaTestType :: Maybe TestType
, TestSuiteStanza -> Maybe (RelativePath Source 'File)
_testStanzaMainIs :: Maybe (RelativePath Source File)
, TestSuiteStanza -> Maybe ModuleName
_testStanzaTestModule :: Maybe ModuleName
, TestSuiteStanza -> BuildInfo
_testStanzaBuildInfo :: BuildInfo
, TestSuiteStanza -> [String]
_testStanzaCodeGenerators :: [String]
}
instance L.HasBuildInfo TestSuiteStanza where
buildInfo :: Lens' TestSuiteStanza BuildInfo
buildInfo = LensLike f TestSuiteStanza TestSuiteStanza BuildInfo BuildInfo
Lens' TestSuiteStanza BuildInfo
testStanzaBuildInfo
testStanzaTestType :: Lens' TestSuiteStanza (Maybe TestType)
testStanzaTestType :: Lens' TestSuiteStanza (Maybe TestType)
testStanzaTestType Maybe TestType -> f (Maybe TestType)
f TestSuiteStanza
s = (Maybe TestType -> TestSuiteStanza)
-> f (Maybe TestType) -> f TestSuiteStanza
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\Maybe TestType
x -> TestSuiteStanza
s{_testStanzaTestType = x}) (Maybe TestType -> f (Maybe TestType)
f (TestSuiteStanza -> Maybe TestType
_testStanzaTestType TestSuiteStanza
s))
{-# INLINE testStanzaTestType #-}
testStanzaMainIs :: Lens' TestSuiteStanza (Maybe (RelativePath Source File))
testStanzaMainIs :: Lens' TestSuiteStanza (Maybe (RelativePath Source 'File))
testStanzaMainIs Maybe (RelativePath Source 'File)
-> f (Maybe (RelativePath Source 'File))
f TestSuiteStanza
s = (Maybe (RelativePath Source 'File) -> TestSuiteStanza)
-> f (Maybe (RelativePath Source 'File)) -> f TestSuiteStanza
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\Maybe (RelativePath Source 'File)
x -> TestSuiteStanza
s{_testStanzaMainIs = x}) (Maybe (RelativePath Source 'File)
-> f (Maybe (RelativePath Source 'File))
f (TestSuiteStanza -> Maybe (RelativePath Source 'File)
_testStanzaMainIs TestSuiteStanza
s))
{-# INLINE testStanzaMainIs #-}
testStanzaTestModule :: Lens' TestSuiteStanza (Maybe ModuleName)
testStanzaTestModule :: Lens' TestSuiteStanza (Maybe ModuleName)
testStanzaTestModule Maybe ModuleName -> f (Maybe ModuleName)
f TestSuiteStanza
s = (Maybe ModuleName -> TestSuiteStanza)
-> f (Maybe ModuleName) -> f TestSuiteStanza
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\Maybe ModuleName
x -> TestSuiteStanza
s{_testStanzaTestModule = x}) (Maybe ModuleName -> f (Maybe ModuleName)
f (TestSuiteStanza -> Maybe ModuleName
_testStanzaTestModule TestSuiteStanza
s))
{-# INLINE testStanzaTestModule #-}
testStanzaBuildInfo :: Lens' TestSuiteStanza BuildInfo
testStanzaBuildInfo :: Lens' TestSuiteStanza BuildInfo
testStanzaBuildInfo BuildInfo -> f BuildInfo
f TestSuiteStanza
s = (BuildInfo -> TestSuiteStanza) -> f BuildInfo -> f TestSuiteStanza
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\BuildInfo
x -> TestSuiteStanza
s{_testStanzaBuildInfo = x}) (BuildInfo -> f BuildInfo
f (TestSuiteStanza -> BuildInfo
_testStanzaBuildInfo TestSuiteStanza
s))
{-# INLINE testStanzaBuildInfo #-}
testStanzaCodeGenerators :: Lens' TestSuiteStanza [String]
testStanzaCodeGenerators :: Lens' TestSuiteStanza [String]
testStanzaCodeGenerators [String] -> f [String]
f TestSuiteStanza
s = ([String] -> TestSuiteStanza) -> f [String] -> f TestSuiteStanza
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\[String]
x -> TestSuiteStanza
s{_testStanzaCodeGenerators = x}) ([String] -> f [String]
f (TestSuiteStanza -> [String]
_testStanzaCodeGenerators TestSuiteStanza
s))
{-# INLINE testStanzaCodeGenerators #-}
testSuiteFieldGrammar
:: ( FieldGrammar c g
, Applicative (g TestSuiteStanza)
, Applicative (g BuildInfo)
, c (Identity ModuleName)
, c (Identity TestType)
, c (List CommaFSep (Identity ExeDependency) ExeDependency)
, c (List CommaFSep (Identity LegacyExeDependency) LegacyExeDependency)
, c (List CommaFSep (Identity PkgconfigDependency) PkgconfigDependency)
, c (List CommaFSep Token String)
, c (List CommaVCat (Identity Dependency) Dependency)
, c (List CommaVCat (Identity Mixin) Mixin)
, c (List FSep (MQuoted Extension) Extension)
, c (List FSep (MQuoted Language) Language)
, c (List FSep Token String)
, c (List NoCommaFSep Token' String)
, c (List VCat (MQuoted ModuleName) ModuleName)
, forall from to. c (List FSep (SymbolicPathNT from to) (SymbolicPath from to))
, forall from to. c (List FSep (RelativePathNT from to) (RelativePath from to))
, forall from to. c (List VCat (SymbolicPathNT from to) (SymbolicPath from to))
, forall from to. c (RelativePathNT from to)
, c (List VCat Token String)
, c (MQuoted Language)
)
=> g TestSuiteStanza TestSuiteStanza
testSuiteFieldGrammar :: forall (c :: * -> Constraint) (g :: * -> * -> *).
(FieldGrammar c g, Applicative (g TestSuiteStanza),
Applicative (g BuildInfo), c (Identity ModuleName),
c (Identity TestType),
c (List CommaFSep (Identity ExeDependency) ExeDependency),
c (List
CommaFSep (Identity LegacyExeDependency) LegacyExeDependency),
c (List
CommaFSep (Identity PkgconfigDependency) PkgconfigDependency),
c (List CommaFSep Token String),
c (List CommaVCat (Identity Dependency) Dependency),
c (List CommaVCat (Identity Mixin) Mixin),
c (List FSep (MQuoted Extension) Extension),
c (List FSep (MQuoted Language) Language),
c (List FSep Token String), c (List NoCommaFSep Token' String),
c (List VCat (MQuoted ModuleName) ModuleName),
forall from (to :: FileOrDir).
c (List FSep (SymbolicPathNT from to) (SymbolicPath from to)),
forall from (to :: FileOrDir).
c (List FSep (RelativePathNT from to) (RelativePath from to)),
forall from (to :: FileOrDir).
c (List VCat (SymbolicPathNT from to) (SymbolicPath from to)),
forall from (to :: FileOrDir). c (RelativePathNT from to),
c (List VCat Token String), c (MQuoted Language)) =>
g TestSuiteStanza TestSuiteStanza
testSuiteFieldGrammar =
Maybe TestType
-> Maybe (RelativePath Source 'File)
-> Maybe ModuleName
-> BuildInfo
-> [String]
-> TestSuiteStanza
TestSuiteStanza
(Maybe TestType
-> Maybe (RelativePath Source 'File)
-> Maybe ModuleName
-> BuildInfo
-> [String]
-> TestSuiteStanza)
-> g TestSuiteStanza (Maybe TestType)
-> g TestSuiteStanza
(Maybe (RelativePath Source 'File)
-> Maybe ModuleName -> BuildInfo -> [String] -> TestSuiteStanza)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> FieldName
-> ALens' TestSuiteStanza (Maybe TestType)
-> g TestSuiteStanza (Maybe TestType)
forall (c :: * -> Constraint) (g :: * -> * -> *) a s.
(FieldGrammar c g, c (Identity a)) =>
FieldName -> ALens' s (Maybe a) -> g s (Maybe a)
optionalField FieldName
"type" ALens' TestSuiteStanza (Maybe TestType)
Lens' TestSuiteStanza (Maybe TestType)
testStanzaTestType
g TestSuiteStanza
(Maybe (RelativePath Source 'File)
-> Maybe ModuleName -> BuildInfo -> [String] -> TestSuiteStanza)
-> g TestSuiteStanza (Maybe (RelativePath Source 'File))
-> g TestSuiteStanza
(Maybe ModuleName -> BuildInfo -> [String] -> TestSuiteStanza)
forall a b.
g TestSuiteStanza (a -> b)
-> g TestSuiteStanza a -> g TestSuiteStanza b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> FieldName
-> (RelativePath Source 'File -> RelativePathNT Source 'File)
-> ALens' TestSuiteStanza (Maybe (RelativePath Source 'File))
-> g TestSuiteStanza (Maybe (RelativePath Source 'File))
forall b a s.
(c b, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s (Maybe a) -> g s (Maybe a)
forall (c :: * -> Constraint) (g :: * -> * -> *) b a s.
(FieldGrammar c g, c b, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s (Maybe a) -> g s (Maybe a)
optionalFieldAla FieldName
"main-is" RelativePath Source 'File -> RelativePathNT Source 'File
forall from (to :: FileOrDir).
RelativePath from to -> RelativePathNT from to
RelativePathNT ALens' TestSuiteStanza (Maybe (RelativePath Source 'File))
Lens' TestSuiteStanza (Maybe (RelativePath Source 'File))
testStanzaMainIs
g TestSuiteStanza
(Maybe ModuleName -> BuildInfo -> [String] -> TestSuiteStanza)
-> g TestSuiteStanza (Maybe ModuleName)
-> g TestSuiteStanza (BuildInfo -> [String] -> TestSuiteStanza)
forall a b.
g TestSuiteStanza (a -> b)
-> g TestSuiteStanza a -> g TestSuiteStanza b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> FieldName
-> ALens' TestSuiteStanza (Maybe ModuleName)
-> g TestSuiteStanza (Maybe ModuleName)
forall (c :: * -> Constraint) (g :: * -> * -> *) a s.
(FieldGrammar c g, c (Identity a)) =>
FieldName -> ALens' s (Maybe a) -> g s (Maybe a)
optionalField FieldName
"test-module" ALens' TestSuiteStanza (Maybe ModuleName)
Lens' TestSuiteStanza (Maybe ModuleName)
testStanzaTestModule
g TestSuiteStanza (BuildInfo -> [String] -> TestSuiteStanza)
-> g TestSuiteStanza BuildInfo
-> g TestSuiteStanza ([String] -> TestSuiteStanza)
forall a b.
g TestSuiteStanza (a -> b)
-> g TestSuiteStanza a -> g TestSuiteStanza b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ALens' TestSuiteStanza BuildInfo
-> g BuildInfo BuildInfo -> g TestSuiteStanza BuildInfo
forall a b d. ALens' a b -> g b d -> g a d
forall (c :: * -> Constraint) (g :: * -> * -> *) a b d.
FieldGrammar c g =>
ALens' a b -> g b d -> g a d
blurFieldGrammar ALens' TestSuiteStanza BuildInfo
Lens' TestSuiteStanza BuildInfo
testStanzaBuildInfo g BuildInfo BuildInfo
forall (c :: * -> Constraint) (g :: * -> * -> *).
(FieldGrammar c g, Applicative (g BuildInfo),
c (List CommaFSep (Identity ExeDependency) ExeDependency),
c (List
CommaFSep (Identity LegacyExeDependency) LegacyExeDependency),
c (List
CommaFSep (Identity PkgconfigDependency) PkgconfigDependency),
c (List CommaVCat (Identity Dependency) Dependency),
c (List CommaVCat (Identity Mixin) Mixin),
c (List FSep (MQuoted Extension) Extension),
c (List FSep (MQuoted Language) Language),
c (List FSep Token String), c (List NoCommaFSep Token' String),
c (List VCat (MQuoted ModuleName) ModuleName),
forall from (to :: FileOrDir).
c (List FSep (SymbolicPathNT from to) (SymbolicPath from to)),
forall from (to :: FileOrDir).
c (List FSep (RelativePathNT from to) (RelativePath from to)),
forall from (to :: FileOrDir).
c (List VCat (SymbolicPathNT from to) (SymbolicPath from to)),
c (List VCat Token String), c (MQuoted Language)) =>
g BuildInfo BuildInfo
buildInfoFieldGrammar
g TestSuiteStanza ([String] -> TestSuiteStanza)
-> g TestSuiteStanza [String] -> g TestSuiteStanza TestSuiteStanza
forall a b.
g TestSuiteStanza (a -> b)
-> g TestSuiteStanza a -> g TestSuiteStanza b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> FieldName
-> ([String] -> List CommaFSep Token String)
-> ALens' TestSuiteStanza [String]
-> g TestSuiteStanza [String]
forall b a s.
(c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
forall (c :: * -> Constraint) (g :: * -> * -> *) b a s.
(FieldGrammar c g, c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
monoidalFieldAla FieldName
"code-generators" (CommaFSep
-> (String -> Token) -> [String] -> List CommaFSep Token String
forall sep a b. sep -> (a -> b) -> [a] -> List sep b a
alaList' CommaFSep
CommaFSep String -> Token
Token) ALens' TestSuiteStanza [String]
Lens' TestSuiteStanza [String]
testStanzaCodeGenerators
g TestSuiteStanza [String]
-> (g TestSuiteStanza [String] -> g TestSuiteStanza [String])
-> g TestSuiteStanza [String]
forall a b. a -> (a -> b) -> b
^^^ CabalSpecVersion
-> [String]
-> g TestSuiteStanza [String]
-> g TestSuiteStanza [String]
forall a s. CabalSpecVersion -> a -> g s a -> g s a
forall (c :: * -> Constraint) (g :: * -> * -> *) a s.
FieldGrammar c g =>
CabalSpecVersion -> a -> g s a -> g s a
availableSince CabalSpecVersion
CabalSpecV3_8 []
validateTestSuite :: CabalSpecVersion -> Position -> TestSuiteStanza -> ParseResult TestSuite
validateTestSuite :: CabalSpecVersion
-> Position -> TestSuiteStanza -> ParseResult TestSuite
validateTestSuite CabalSpecVersion
cabalSpecVersion Position
pos TestSuiteStanza
stanza = case Maybe TestType
testSuiteType of
Maybe TestType
Nothing -> TestSuite -> ParseResult TestSuite
forall a. a -> ParseResult a
forall (f :: * -> *) a. Applicative f => a -> f a
pure TestSuite
basicTestSuite
Just tt :: TestType
tt@(TestTypeUnknown String
_ Version
_) ->
TestSuite -> ParseResult TestSuite
forall a. a -> ParseResult a
forall (f :: * -> *) a. Applicative f => a -> f a
pure
TestSuite
basicTestSuite
{ testInterface = TestSuiteUnsupported tt
}
Just TestType
tt
| TestType
tt TestType -> [TestType] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`notElem` [TestType]
knownTestTypes ->
TestSuite -> ParseResult TestSuite
forall a. a -> ParseResult a
forall (f :: * -> *) a. Applicative f => a -> f a
pure
TestSuite
basicTestSuite
{ testInterface = TestSuiteUnsupported tt
}
Just tt :: TestType
tt@(TestTypeExe Version
ver) -> case TestSuiteStanza -> Maybe (RelativePath Source 'File)
_testStanzaMainIs TestSuiteStanza
stanza of
Maybe (RelativePath Source 'File)
Nothing -> do
Position -> String -> ParseResult ()
parseFailure Position
pos (String -> TestType -> String
forall {a}. Pretty a => String -> a -> String
missingField String
"main-is" TestType
tt)
TestSuite -> ParseResult TestSuite
forall a. a -> ParseResult a
forall (f :: * -> *) a. Applicative f => a -> f a
pure TestSuite
emptyTestSuite
Just RelativePath Source 'File
file -> do
Bool -> ParseResult () -> ParseResult ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Maybe ModuleName -> Bool
forall a. Maybe a -> Bool
isJust (TestSuiteStanza -> Maybe ModuleName
_testStanzaTestModule TestSuiteStanza
stanza)) (ParseResult () -> ParseResult ())
-> ParseResult () -> ParseResult ()
forall a b. (a -> b) -> a -> b
$
Position -> PWarnType -> String -> ParseResult ()
parseWarning Position
pos PWarnType
PWTExtraBenchmarkModule (String -> TestType -> String
forall {a}. Pretty a => String -> a -> String
extraField String
"test-module" TestType
tt)
TestSuite -> ParseResult TestSuite
forall a. a -> ParseResult a
forall (f :: * -> *) a. Applicative f => a -> f a
pure
TestSuite
basicTestSuite
{ testInterface = TestSuiteExeV10 ver file
}
Just tt :: TestType
tt@(TestTypeLib Version
ver) -> case TestSuiteStanza -> Maybe ModuleName
_testStanzaTestModule TestSuiteStanza
stanza of
Maybe ModuleName
Nothing -> do
Position -> String -> ParseResult ()
parseFailure Position
pos (String -> TestType -> String
forall {a}. Pretty a => String -> a -> String
missingField String
"test-module" TestType
tt)
TestSuite -> ParseResult TestSuite
forall a. a -> ParseResult a
forall (f :: * -> *) a. Applicative f => a -> f a
pure TestSuite
emptyTestSuite
Just ModuleName
module_ -> do
Bool -> ParseResult () -> ParseResult ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Maybe (RelativePath Source 'File) -> Bool
forall a. Maybe a -> Bool
isJust (TestSuiteStanza -> Maybe (RelativePath Source 'File)
_testStanzaMainIs TestSuiteStanza
stanza)) (ParseResult () -> ParseResult ())
-> ParseResult () -> ParseResult ()
forall a b. (a -> b) -> a -> b
$
Position -> PWarnType -> String -> ParseResult ()
parseWarning Position
pos PWarnType
PWTExtraMainIs (String -> TestType -> String
forall {a}. Pretty a => String -> a -> String
extraField String
"main-is" TestType
tt)
TestSuite -> ParseResult TestSuite
forall a. a -> ParseResult a
forall (f :: * -> *) a. Applicative f => a -> f a
pure
TestSuite
basicTestSuite
{ testInterface = TestSuiteLibV09 ver module_
}
where
testSuiteType :: Maybe TestType
testSuiteType =
TestSuiteStanza -> Maybe TestType
_testStanzaTestType TestSuiteStanza
stanza
Maybe TestType -> Maybe TestType -> Maybe TestType
forall a. Maybe a -> Maybe a -> Maybe a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> do
Bool -> Maybe ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (CabalSpecVersion
cabalSpecVersion CabalSpecVersion -> CabalSpecVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= CabalSpecVersion
CabalSpecV3_8)
TestType
testTypeExe TestType -> Maybe (RelativePath Source 'File) -> Maybe TestType
forall a b. a -> Maybe b -> Maybe a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ TestSuiteStanza -> Maybe (RelativePath Source 'File)
_testStanzaMainIs TestSuiteStanza
stanza
Maybe TestType -> Maybe TestType -> Maybe TestType
forall a. Maybe a -> Maybe a -> Maybe a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> TestType
testTypeLib TestType -> Maybe ModuleName -> Maybe TestType
forall a b. a -> Maybe b -> Maybe a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ TestSuiteStanza -> Maybe ModuleName
_testStanzaTestModule TestSuiteStanza
stanza
missingField :: String -> a -> String
missingField String
name a
tt =
String
"The '"
String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
name
String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"' field is required for the "
String -> String -> String
forall a. [a] -> [a] -> [a]
++ a -> String
forall a. Pretty a => a -> String
prettyShow a
tt
String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" test suite type."
extraField :: String -> a -> String
extraField String
name a
tt =
String
"The '"
String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
name
String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"' field is not used for the '"
String -> String -> String
forall a. [a] -> [a] -> [a]
++ a -> String
forall a. Pretty a => a -> String
prettyShow a
tt
String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"' test suite type."
basicTestSuite :: TestSuite
basicTestSuite =
TestSuite
emptyTestSuite
{ testBuildInfo = _testStanzaBuildInfo stanza
, testCodeGenerators = _testStanzaCodeGenerators stanza
}
unvalidateTestSuite :: TestSuite -> TestSuiteStanza
unvalidateTestSuite :: TestSuite -> TestSuiteStanza
unvalidateTestSuite TestSuite
t =
TestSuiteStanza
{ _testStanzaTestType :: Maybe TestType
_testStanzaTestType = Maybe TestType
ty
, _testStanzaMainIs :: Maybe (RelativePath Source 'File)
_testStanzaMainIs = Maybe (RelativePath Source 'File)
ma
, _testStanzaTestModule :: Maybe ModuleName
_testStanzaTestModule = Maybe ModuleName
mo
, _testStanzaBuildInfo :: BuildInfo
_testStanzaBuildInfo = TestSuite -> BuildInfo
testBuildInfo TestSuite
t
, _testStanzaCodeGenerators :: [String]
_testStanzaCodeGenerators = TestSuite -> [String]
testCodeGenerators TestSuite
t
}
where
(Maybe TestType
ty, Maybe (RelativePath Source 'File)
ma, Maybe ModuleName
mo) = case TestSuite -> TestSuiteInterface
testInterface TestSuite
t of
TestSuiteExeV10 Version
ver RelativePath Source 'File
file -> (TestType -> Maybe TestType
forall a. a -> Maybe a
Just (TestType -> Maybe TestType) -> TestType -> Maybe TestType
forall a b. (a -> b) -> a -> b
$ Version -> TestType
TestTypeExe Version
ver, RelativePath Source 'File -> Maybe (RelativePath Source 'File)
forall a. a -> Maybe a
Just RelativePath Source 'File
file, Maybe ModuleName
forall a. Maybe a
Nothing)
TestSuiteLibV09 Version
ver ModuleName
modu -> (TestType -> Maybe TestType
forall a. a -> Maybe a
Just (TestType -> Maybe TestType) -> TestType -> Maybe TestType
forall a b. (a -> b) -> a -> b
$ Version -> TestType
TestTypeLib Version
ver, Maybe (RelativePath Source 'File)
forall a. Maybe a
Nothing, ModuleName -> Maybe ModuleName
forall a. a -> Maybe a
Just ModuleName
modu)
TestSuiteInterface
_ -> (Maybe TestType
forall a. Maybe a
Nothing, Maybe (RelativePath Source 'File)
forall a. Maybe a
Nothing, Maybe ModuleName
forall a. Maybe a
Nothing)
data BenchmarkStanza = BenchmarkStanza
{ BenchmarkStanza -> Maybe BenchmarkType
_benchmarkStanzaBenchmarkType :: Maybe BenchmarkType
, BenchmarkStanza -> Maybe (RelativePath Source 'File)
_benchmarkStanzaMainIs :: Maybe (RelativePath Source File)
, BenchmarkStanza -> Maybe ModuleName
_benchmarkStanzaBenchmarkModule :: Maybe ModuleName
, BenchmarkStanza -> BuildInfo
_benchmarkStanzaBuildInfo :: BuildInfo
}
instance L.HasBuildInfo BenchmarkStanza where
buildInfo :: Lens' BenchmarkStanza BuildInfo
buildInfo = LensLike f BenchmarkStanza BenchmarkStanza BuildInfo BuildInfo
Lens' BenchmarkStanza BuildInfo
benchmarkStanzaBuildInfo
benchmarkStanzaBenchmarkType :: Lens' BenchmarkStanza (Maybe BenchmarkType)
benchmarkStanzaBenchmarkType :: Lens' BenchmarkStanza (Maybe BenchmarkType)
benchmarkStanzaBenchmarkType Maybe BenchmarkType -> f (Maybe BenchmarkType)
f BenchmarkStanza
s = (Maybe BenchmarkType -> BenchmarkStanza)
-> f (Maybe BenchmarkType) -> f BenchmarkStanza
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\Maybe BenchmarkType
x -> BenchmarkStanza
s{_benchmarkStanzaBenchmarkType = x}) (Maybe BenchmarkType -> f (Maybe BenchmarkType)
f (BenchmarkStanza -> Maybe BenchmarkType
_benchmarkStanzaBenchmarkType BenchmarkStanza
s))
{-# INLINE benchmarkStanzaBenchmarkType #-}
benchmarkStanzaMainIs :: Lens' BenchmarkStanza (Maybe (RelativePath Source File))
benchmarkStanzaMainIs :: Lens' BenchmarkStanza (Maybe (RelativePath Source 'File))
benchmarkStanzaMainIs Maybe (RelativePath Source 'File)
-> f (Maybe (RelativePath Source 'File))
f BenchmarkStanza
s = (Maybe (RelativePath Source 'File) -> BenchmarkStanza)
-> f (Maybe (RelativePath Source 'File)) -> f BenchmarkStanza
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\Maybe (RelativePath Source 'File)
x -> BenchmarkStanza
s{_benchmarkStanzaMainIs = x}) (Maybe (RelativePath Source 'File)
-> f (Maybe (RelativePath Source 'File))
f (BenchmarkStanza -> Maybe (RelativePath Source 'File)
_benchmarkStanzaMainIs BenchmarkStanza
s))
{-# INLINE benchmarkStanzaMainIs #-}
benchmarkStanzaBenchmarkModule :: Lens' BenchmarkStanza (Maybe ModuleName)
benchmarkStanzaBenchmarkModule :: Lens' BenchmarkStanza (Maybe ModuleName)
benchmarkStanzaBenchmarkModule Maybe ModuleName -> f (Maybe ModuleName)
f BenchmarkStanza
s = (Maybe ModuleName -> BenchmarkStanza)
-> f (Maybe ModuleName) -> f BenchmarkStanza
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\Maybe ModuleName
x -> BenchmarkStanza
s{_benchmarkStanzaBenchmarkModule = x}) (Maybe ModuleName -> f (Maybe ModuleName)
f (BenchmarkStanza -> Maybe ModuleName
_benchmarkStanzaBenchmarkModule BenchmarkStanza
s))
{-# INLINE benchmarkStanzaBenchmarkModule #-}
benchmarkStanzaBuildInfo :: Lens' BenchmarkStanza BuildInfo
benchmarkStanzaBuildInfo :: Lens' BenchmarkStanza BuildInfo
benchmarkStanzaBuildInfo BuildInfo -> f BuildInfo
f BenchmarkStanza
s = (BuildInfo -> BenchmarkStanza) -> f BuildInfo -> f BenchmarkStanza
forall a b. (a -> b) -> f a -> f b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\BuildInfo
x -> BenchmarkStanza
s{_benchmarkStanzaBuildInfo = x}) (BuildInfo -> f BuildInfo
f (BenchmarkStanza -> BuildInfo
_benchmarkStanzaBuildInfo BenchmarkStanza
s))
{-# INLINE benchmarkStanzaBuildInfo #-}
benchmarkFieldGrammar
:: ( FieldGrammar c g
, Applicative (g BenchmarkStanza)
, Applicative (g BuildInfo)
, c (Identity BenchmarkType)
, c (Identity ModuleName)
, c (List CommaFSep (Identity ExeDependency) ExeDependency)
, c (List CommaFSep (Identity LegacyExeDependency) LegacyExeDependency)
, c (List CommaFSep (Identity PkgconfigDependency) PkgconfigDependency)
, c (List CommaVCat (Identity Dependency) Dependency)
, c (List CommaVCat (Identity Mixin) Mixin)
, c (List FSep (MQuoted Extension) Extension)
, c (List FSep (MQuoted Language) Language)
, c (List FSep Token String)
, c (List NoCommaFSep Token' String)
, c (List VCat (MQuoted ModuleName) ModuleName)
, forall from to. c (List FSep (SymbolicPathNT from to) (SymbolicPath from to))
, forall from to. c (List FSep (RelativePathNT from to) (RelativePath from to))
, forall from to. c (List VCat (SymbolicPathNT from to) (SymbolicPath from to))
, forall from to. c (RelativePathNT from to)
, c (List VCat Token String)
, c (MQuoted Language)
)
=> g BenchmarkStanza BenchmarkStanza
benchmarkFieldGrammar :: forall (c :: * -> Constraint) (g :: * -> * -> *).
(FieldGrammar c g, Applicative (g BenchmarkStanza),
Applicative (g BuildInfo), c (Identity BenchmarkType),
c (Identity ModuleName),
c (List CommaFSep (Identity ExeDependency) ExeDependency),
c (List
CommaFSep (Identity LegacyExeDependency) LegacyExeDependency),
c (List
CommaFSep (Identity PkgconfigDependency) PkgconfigDependency),
c (List CommaVCat (Identity Dependency) Dependency),
c (List CommaVCat (Identity Mixin) Mixin),
c (List FSep (MQuoted Extension) Extension),
c (List FSep (MQuoted Language) Language),
c (List FSep Token String), c (List NoCommaFSep Token' String),
c (List VCat (MQuoted ModuleName) ModuleName),
forall from (to :: FileOrDir).
c (List FSep (SymbolicPathNT from to) (SymbolicPath from to)),
forall from (to :: FileOrDir).
c (List FSep (RelativePathNT from to) (RelativePath from to)),
forall from (to :: FileOrDir).
c (List VCat (SymbolicPathNT from to) (SymbolicPath from to)),
forall from (to :: FileOrDir). c (RelativePathNT from to),
c (List VCat Token String), c (MQuoted Language)) =>
g BenchmarkStanza BenchmarkStanza
benchmarkFieldGrammar =
Maybe BenchmarkType
-> Maybe (RelativePath Source 'File)
-> Maybe ModuleName
-> BuildInfo
-> BenchmarkStanza
BenchmarkStanza
(Maybe BenchmarkType
-> Maybe (RelativePath Source 'File)
-> Maybe ModuleName
-> BuildInfo
-> BenchmarkStanza)
-> g BenchmarkStanza (Maybe BenchmarkType)
-> g BenchmarkStanza
(Maybe (RelativePath Source 'File)
-> Maybe ModuleName -> BuildInfo -> BenchmarkStanza)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> FieldName
-> ALens' BenchmarkStanza (Maybe BenchmarkType)
-> g BenchmarkStanza (Maybe BenchmarkType)
forall (c :: * -> Constraint) (g :: * -> * -> *) a s.
(FieldGrammar c g, c (Identity a)) =>
FieldName -> ALens' s (Maybe a) -> g s (Maybe a)
optionalField FieldName
"type" ALens' BenchmarkStanza (Maybe BenchmarkType)
Lens' BenchmarkStanza (Maybe BenchmarkType)
benchmarkStanzaBenchmarkType
g BenchmarkStanza
(Maybe (RelativePath Source 'File)
-> Maybe ModuleName -> BuildInfo -> BenchmarkStanza)
-> g BenchmarkStanza (Maybe (RelativePath Source 'File))
-> g BenchmarkStanza
(Maybe ModuleName -> BuildInfo -> BenchmarkStanza)
forall a b.
g BenchmarkStanza (a -> b)
-> g BenchmarkStanza a -> g BenchmarkStanza b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> FieldName
-> (RelativePath Source 'File -> RelativePathNT Source 'File)
-> ALens' BenchmarkStanza (Maybe (RelativePath Source 'File))
-> g BenchmarkStanza (Maybe (RelativePath Source 'File))
forall b a s.
(c b, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s (Maybe a) -> g s (Maybe a)
forall (c :: * -> Constraint) (g :: * -> * -> *) b a s.
(FieldGrammar c g, c b, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s (Maybe a) -> g s (Maybe a)
optionalFieldAla FieldName
"main-is" RelativePath Source 'File -> RelativePathNT Source 'File
forall from (to :: FileOrDir).
RelativePath from to -> RelativePathNT from to
RelativePathNT ALens' BenchmarkStanza (Maybe (RelativePath Source 'File))
Lens' BenchmarkStanza (Maybe (RelativePath Source 'File))
benchmarkStanzaMainIs
g BenchmarkStanza
(Maybe ModuleName -> BuildInfo -> BenchmarkStanza)
-> g BenchmarkStanza (Maybe ModuleName)
-> g BenchmarkStanza (BuildInfo -> BenchmarkStanza)
forall a b.
g BenchmarkStanza (a -> b)
-> g BenchmarkStanza a -> g BenchmarkStanza b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> FieldName
-> ALens' BenchmarkStanza (Maybe ModuleName)
-> g BenchmarkStanza (Maybe ModuleName)
forall (c :: * -> Constraint) (g :: * -> * -> *) a s.
(FieldGrammar c g, c (Identity a)) =>
FieldName -> ALens' s (Maybe a) -> g s (Maybe a)
optionalField FieldName
"benchmark-module" ALens' BenchmarkStanza (Maybe ModuleName)
Lens' BenchmarkStanza (Maybe ModuleName)
benchmarkStanzaBenchmarkModule
g BenchmarkStanza (BuildInfo -> BenchmarkStanza)
-> g BenchmarkStanza BuildInfo -> g BenchmarkStanza BenchmarkStanza
forall a b.
g BenchmarkStanza (a -> b)
-> g BenchmarkStanza a -> g BenchmarkStanza b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ALens' BenchmarkStanza BuildInfo
-> g BuildInfo BuildInfo -> g BenchmarkStanza BuildInfo
forall a b d. ALens' a b -> g b d -> g a d
forall (c :: * -> Constraint) (g :: * -> * -> *) a b d.
FieldGrammar c g =>
ALens' a b -> g b d -> g a d
blurFieldGrammar ALens' BenchmarkStanza BuildInfo
Lens' BenchmarkStanza BuildInfo
benchmarkStanzaBuildInfo g BuildInfo BuildInfo
forall (c :: * -> Constraint) (g :: * -> * -> *).
(FieldGrammar c g, Applicative (g BuildInfo),
c (List CommaFSep (Identity ExeDependency) ExeDependency),
c (List
CommaFSep (Identity LegacyExeDependency) LegacyExeDependency),
c (List
CommaFSep (Identity PkgconfigDependency) PkgconfigDependency),
c (List CommaVCat (Identity Dependency) Dependency),
c (List CommaVCat (Identity Mixin) Mixin),
c (List FSep (MQuoted Extension) Extension),
c (List FSep (MQuoted Language) Language),
c (List FSep Token String), c (List NoCommaFSep Token' String),
c (List VCat (MQuoted ModuleName) ModuleName),
forall from (to :: FileOrDir).
c (List FSep (SymbolicPathNT from to) (SymbolicPath from to)),
forall from (to :: FileOrDir).
c (List FSep (RelativePathNT from to) (RelativePath from to)),
forall from (to :: FileOrDir).
c (List VCat (SymbolicPathNT from to) (SymbolicPath from to)),
c (List VCat Token String), c (MQuoted Language)) =>
g BuildInfo BuildInfo
buildInfoFieldGrammar
validateBenchmark :: CabalSpecVersion -> Position -> BenchmarkStanza -> ParseResult Benchmark
validateBenchmark :: CabalSpecVersion
-> Position -> BenchmarkStanza -> ParseResult Benchmark
validateBenchmark CabalSpecVersion
cabalSpecVersion Position
pos BenchmarkStanza
stanza = case Maybe BenchmarkType
benchmarkStanzaType of
Maybe BenchmarkType
Nothing ->
Benchmark -> ParseResult Benchmark
forall a. a -> ParseResult a
forall (f :: * -> *) a. Applicative f => a -> f a
pure
Benchmark
emptyBenchmark
{ benchmarkBuildInfo = _benchmarkStanzaBuildInfo stanza
}
Just tt :: BenchmarkType
tt@(BenchmarkTypeUnknown String
_ Version
_) ->
Benchmark -> ParseResult Benchmark
forall a. a -> ParseResult a
forall (f :: * -> *) a. Applicative f => a -> f a
pure
Benchmark
emptyBenchmark
{ benchmarkInterface = BenchmarkUnsupported tt
, benchmarkBuildInfo = _benchmarkStanzaBuildInfo stanza
}
Just BenchmarkType
tt
| BenchmarkType
tt BenchmarkType -> [BenchmarkType] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`notElem` [BenchmarkType]
knownBenchmarkTypes ->
Benchmark -> ParseResult Benchmark
forall a. a -> ParseResult a
forall (f :: * -> *) a. Applicative f => a -> f a
pure
Benchmark
emptyBenchmark
{ benchmarkInterface = BenchmarkUnsupported tt
, benchmarkBuildInfo = _benchmarkStanzaBuildInfo stanza
}
Just tt :: BenchmarkType
tt@(BenchmarkTypeExe Version
ver) -> case BenchmarkStanza -> Maybe (RelativePath Source 'File)
_benchmarkStanzaMainIs BenchmarkStanza
stanza of
Maybe (RelativePath Source 'File)
Nothing -> do
Position -> String -> ParseResult ()
parseFailure Position
pos (String -> BenchmarkType -> String
forall {a}. Pretty a => String -> a -> String
missingField String
"main-is" BenchmarkType
tt)
Benchmark -> ParseResult Benchmark
forall a. a -> ParseResult a
forall (f :: * -> *) a. Applicative f => a -> f a
pure Benchmark
emptyBenchmark
Just RelativePath Source 'File
file -> do
Bool -> ParseResult () -> ParseResult ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Maybe ModuleName -> Bool
forall a. Maybe a -> Bool
isJust (BenchmarkStanza -> Maybe ModuleName
_benchmarkStanzaBenchmarkModule BenchmarkStanza
stanza)) (ParseResult () -> ParseResult ())
-> ParseResult () -> ParseResult ()
forall a b. (a -> b) -> a -> b
$
Position -> PWarnType -> String -> ParseResult ()
parseWarning Position
pos PWarnType
PWTExtraBenchmarkModule (String -> BenchmarkType -> String
forall {a}. Pretty a => String -> a -> String
extraField String
"benchmark-module" BenchmarkType
tt)
Benchmark -> ParseResult Benchmark
forall a. a -> ParseResult a
forall (f :: * -> *) a. Applicative f => a -> f a
pure
Benchmark
emptyBenchmark
{ benchmarkInterface = BenchmarkExeV10 ver file
, benchmarkBuildInfo = _benchmarkStanzaBuildInfo stanza
}
where
benchmarkStanzaType :: Maybe BenchmarkType
benchmarkStanzaType =
BenchmarkStanza -> Maybe BenchmarkType
_benchmarkStanzaBenchmarkType BenchmarkStanza
stanza Maybe BenchmarkType -> Maybe BenchmarkType -> Maybe BenchmarkType
forall a. Maybe a -> Maybe a -> Maybe a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> do
Bool -> Maybe ()
forall (f :: * -> *). Alternative f => Bool -> f ()
guard (CabalSpecVersion
cabalSpecVersion CabalSpecVersion -> CabalSpecVersion -> Bool
forall a. Ord a => a -> a -> Bool
>= CabalSpecVersion
CabalSpecV3_8)
BenchmarkType
benchmarkTypeExe BenchmarkType
-> Maybe (RelativePath Source 'File) -> Maybe BenchmarkType
forall a b. a -> Maybe b -> Maybe a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ BenchmarkStanza -> Maybe (RelativePath Source 'File)
_benchmarkStanzaMainIs BenchmarkStanza
stanza
missingField :: String -> a -> String
missingField String
name a
tt =
String
"The '"
String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
name
String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"' field is required for the "
String -> String -> String
forall a. [a] -> [a] -> [a]
++ a -> String
forall a. Pretty a => a -> String
prettyShow a
tt
String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
" benchmark type."
extraField :: String -> a -> String
extraField String
name a
tt =
String
"The '"
String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
name
String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"' field is not used for the '"
String -> String -> String
forall a. [a] -> [a] -> [a]
++ a -> String
forall a. Pretty a => a -> String
prettyShow a
tt
String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"' benchmark type."
unvalidateBenchmark :: Benchmark -> BenchmarkStanza
unvalidateBenchmark :: Benchmark -> BenchmarkStanza
unvalidateBenchmark Benchmark
b =
BenchmarkStanza
{ _benchmarkStanzaBenchmarkType :: Maybe BenchmarkType
_benchmarkStanzaBenchmarkType = Maybe BenchmarkType
ty
, _benchmarkStanzaMainIs :: Maybe (RelativePath Source 'File)
_benchmarkStanzaMainIs = Maybe (RelativePath Source 'File)
ma
, _benchmarkStanzaBenchmarkModule :: Maybe ModuleName
_benchmarkStanzaBenchmarkModule = Maybe ModuleName
forall a. Maybe a
mo
, _benchmarkStanzaBuildInfo :: BuildInfo
_benchmarkStanzaBuildInfo = Benchmark -> BuildInfo
benchmarkBuildInfo Benchmark
b
}
where
(Maybe BenchmarkType
ty, Maybe (RelativePath Source 'File)
ma, Maybe a
mo) = case Benchmark -> BenchmarkInterface
benchmarkInterface Benchmark
b of
BenchmarkExeV10 Version
ver RelativePath Source 'File
ma'
| RelativePath Source 'File -> String
forall (allowAbsolute :: AllowAbsolute) from (to :: FileOrDir).
SymbolicPathX allowAbsolute from to -> String
getSymbolicPath RelativePath Source 'File
ma' String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
"" ->
(BenchmarkType -> Maybe BenchmarkType
forall a. a -> Maybe a
Just (BenchmarkType -> Maybe BenchmarkType)
-> BenchmarkType -> Maybe BenchmarkType
forall a b. (a -> b) -> a -> b
$ Version -> BenchmarkType
BenchmarkTypeExe Version
ver, Maybe (RelativePath Source 'File)
forall a. Maybe a
Nothing, Maybe a
forall a. Maybe a
Nothing)
| Bool
otherwise ->
(BenchmarkType -> Maybe BenchmarkType
forall a. a -> Maybe a
Just (BenchmarkType -> Maybe BenchmarkType)
-> BenchmarkType -> Maybe BenchmarkType
forall a b. (a -> b) -> a -> b
$ Version -> BenchmarkType
BenchmarkTypeExe Version
ver, RelativePath Source 'File -> Maybe (RelativePath Source 'File)
forall a. a -> Maybe a
Just RelativePath Source 'File
ma', Maybe a
forall a. Maybe a
Nothing)
BenchmarkInterface
_ -> (Maybe BenchmarkType
forall a. Maybe a
Nothing, Maybe (RelativePath Source 'File)
forall a. Maybe a
Nothing, Maybe a
forall a. Maybe a
Nothing)
buildInfoFieldGrammar
:: ( FieldGrammar c g
, Applicative (g BuildInfo)
, c (List CommaFSep (Identity ExeDependency) ExeDependency)
, c (List CommaFSep (Identity LegacyExeDependency) LegacyExeDependency)
, c (List CommaFSep (Identity PkgconfigDependency) PkgconfigDependency)
, c (List CommaVCat (Identity Dependency) Dependency)
, c (List CommaVCat (Identity Mixin) Mixin)
, c (List FSep (MQuoted Extension) Extension)
, c (List FSep (MQuoted Language) Language)
, c (List FSep Token String)
, c (List NoCommaFSep Token' String)
, c (List VCat (MQuoted ModuleName) ModuleName)
, forall from to. c (List FSep (SymbolicPathNT from to) (SymbolicPath from to))
, forall from to. c (List FSep (RelativePathNT from to) (RelativePath from to))
, forall from to. c (List VCat (SymbolicPathNT from to) (SymbolicPath from to))
, c (List VCat Token String)
, c (MQuoted Language)
)
=> g BuildInfo BuildInfo
buildInfoFieldGrammar :: forall (c :: * -> Constraint) (g :: * -> * -> *).
(FieldGrammar c g, Applicative (g BuildInfo),
c (List CommaFSep (Identity ExeDependency) ExeDependency),
c (List
CommaFSep (Identity LegacyExeDependency) LegacyExeDependency),
c (List
CommaFSep (Identity PkgconfigDependency) PkgconfigDependency),
c (List CommaVCat (Identity Dependency) Dependency),
c (List CommaVCat (Identity Mixin) Mixin),
c (List FSep (MQuoted Extension) Extension),
c (List FSep (MQuoted Language) Language),
c (List FSep Token String), c (List NoCommaFSep Token' String),
c (List VCat (MQuoted ModuleName) ModuleName),
forall from (to :: FileOrDir).
c (List FSep (SymbolicPathNT from to) (SymbolicPath from to)),
forall from (to :: FileOrDir).
c (List FSep (RelativePathNT from to) (RelativePath from to)),
forall from (to :: FileOrDir).
c (List VCat (SymbolicPathNT from to) (SymbolicPath from to)),
c (List VCat Token String), c (MQuoted Language)) =>
g BuildInfo BuildInfo
buildInfoFieldGrammar =
Bool
-> [LegacyExeDependency]
-> [ExeDependency]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [PkgconfigDependency]
-> [RelativePath Framework 'File]
-> [SymbolicPath Pkg ('Dir Framework)]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg ('Dir Source)]
-> [ModuleName]
-> [ModuleName]
-> [ModuleName]
-> Maybe Language
-> [Language]
-> [Extension]
-> [Extension]
-> [Extension]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Include)]
-> [SymbolicPath Include 'File]
-> [RelativePath Include 'File]
-> [RelativePath Include 'File]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> [(String, String)]
-> [Dependency]
-> [Mixin]
-> BuildInfo
BuildInfo
(Bool
-> [LegacyExeDependency]
-> [ExeDependency]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [PkgconfigDependency]
-> [RelativePath Framework 'File]
-> [SymbolicPath Pkg ('Dir Framework)]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg ('Dir Source)]
-> [ModuleName]
-> [ModuleName]
-> [ModuleName]
-> Maybe Language
-> [Language]
-> [Extension]
-> [Extension]
-> [Extension]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Include)]
-> [SymbolicPath Include 'File]
-> [RelativePath Include 'File]
-> [RelativePath Include 'File]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> [(String, String)]
-> [Dependency]
-> [Mixin]
-> BuildInfo)
-> g BuildInfo Bool
-> g BuildInfo
([LegacyExeDependency]
-> [ExeDependency]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [PkgconfigDependency]
-> [RelativePath Framework 'File]
-> [SymbolicPath Pkg ('Dir Framework)]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg ('Dir Source)]
-> [ModuleName]
-> [ModuleName]
-> [ModuleName]
-> Maybe Language
-> [Language]
-> [Extension]
-> [Extension]
-> [Extension]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Include)]
-> [SymbolicPath Include 'File]
-> [RelativePath Include 'File]
-> [RelativePath Include 'File]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> [(String, String)]
-> [Dependency]
-> [Mixin]
-> BuildInfo)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> FieldName -> ALens' BuildInfo Bool -> Bool -> g BuildInfo Bool
forall s. FieldName -> ALens' s Bool -> Bool -> g s Bool
forall (c :: * -> Constraint) (g :: * -> * -> *) s.
FieldGrammar c g =>
FieldName -> ALens' s Bool -> Bool -> g s Bool
booleanFieldDef FieldName
"buildable" ALens' BuildInfo Bool
forall a. HasBuildInfo a => Lens' a Bool
Lens' BuildInfo Bool
L.buildable Bool
True
g BuildInfo
([LegacyExeDependency]
-> [ExeDependency]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [PkgconfigDependency]
-> [RelativePath Framework 'File]
-> [SymbolicPath Pkg ('Dir Framework)]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg ('Dir Source)]
-> [ModuleName]
-> [ModuleName]
-> [ModuleName]
-> Maybe Language
-> [Language]
-> [Extension]
-> [Extension]
-> [Extension]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Include)]
-> [SymbolicPath Include 'File]
-> [RelativePath Include 'File]
-> [RelativePath Include 'File]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> [(String, String)]
-> [Dependency]
-> [Mixin]
-> BuildInfo)
-> g BuildInfo [LegacyExeDependency]
-> g BuildInfo
([ExeDependency]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [PkgconfigDependency]
-> [RelativePath Framework 'File]
-> [SymbolicPath Pkg ('Dir Framework)]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg ('Dir Source)]
-> [ModuleName]
-> [ModuleName]
-> [ModuleName]
-> Maybe Language
-> [Language]
-> [Extension]
-> [Extension]
-> [Extension]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Include)]
-> [SymbolicPath Include 'File]
-> [RelativePath Include 'File]
-> [RelativePath Include 'File]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> [(String, String)]
-> [Dependency]
-> [Mixin]
-> BuildInfo)
forall a b. g BuildInfo (a -> b) -> g BuildInfo a -> g BuildInfo b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> FieldName
-> ([LegacyExeDependency]
-> List
CommaFSep (Identity LegacyExeDependency) LegacyExeDependency)
-> ALens' BuildInfo [LegacyExeDependency]
-> g BuildInfo [LegacyExeDependency]
forall b a s.
(c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
forall (c :: * -> Constraint) (g :: * -> * -> *) b a s.
(FieldGrammar c g, c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
monoidalFieldAla FieldName
"build-tools" (CommaFSep
-> [LegacyExeDependency]
-> List
CommaFSep (Identity LegacyExeDependency) LegacyExeDependency
forall sep a. sep -> [a] -> List sep (Identity a) a
alaList CommaFSep
CommaFSep) ALens' BuildInfo [LegacyExeDependency]
forall a. HasBuildInfo a => Lens' a [LegacyExeDependency]
Lens' BuildInfo [LegacyExeDependency]
L.buildTools
g BuildInfo [LegacyExeDependency]
-> (g BuildInfo [LegacyExeDependency]
-> g BuildInfo [LegacyExeDependency])
-> g BuildInfo [LegacyExeDependency]
forall a b. a -> (a -> b) -> b
^^^ CabalSpecVersion
-> String
-> g BuildInfo [LegacyExeDependency]
-> g BuildInfo [LegacyExeDependency]
forall s a. CabalSpecVersion -> String -> g s a -> g s a
forall (c :: * -> Constraint) (g :: * -> * -> *) s a.
FieldGrammar c g =>
CabalSpecVersion -> String -> g s a -> g s a
deprecatedSince
CabalSpecVersion
CabalSpecV2_0
String
"Please use 'build-tool-depends' field"
g BuildInfo [LegacyExeDependency]
-> (g BuildInfo [LegacyExeDependency]
-> g BuildInfo [LegacyExeDependency])
-> g BuildInfo [LegacyExeDependency]
forall a b. a -> (a -> b) -> b
^^^ CabalSpecVersion
-> String
-> g BuildInfo [LegacyExeDependency]
-> g BuildInfo [LegacyExeDependency]
forall s a. CabalSpecVersion -> String -> g s a -> g s a
forall (c :: * -> Constraint) (g :: * -> * -> *) s a.
FieldGrammar c g =>
CabalSpecVersion -> String -> g s a -> g s a
removedIn
CabalSpecVersion
CabalSpecV3_0
String
"Please use 'build-tool-depends' field."
g BuildInfo
([ExeDependency]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [PkgconfigDependency]
-> [RelativePath Framework 'File]
-> [SymbolicPath Pkg ('Dir Framework)]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg ('Dir Source)]
-> [ModuleName]
-> [ModuleName]
-> [ModuleName]
-> Maybe Language
-> [Language]
-> [Extension]
-> [Extension]
-> [Extension]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Include)]
-> [SymbolicPath Include 'File]
-> [RelativePath Include 'File]
-> [RelativePath Include 'File]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> [(String, String)]
-> [Dependency]
-> [Mixin]
-> BuildInfo)
-> g BuildInfo [ExeDependency]
-> g BuildInfo
([String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [PkgconfigDependency]
-> [RelativePath Framework 'File]
-> [SymbolicPath Pkg ('Dir Framework)]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg ('Dir Source)]
-> [ModuleName]
-> [ModuleName]
-> [ModuleName]
-> Maybe Language
-> [Language]
-> [Extension]
-> [Extension]
-> [Extension]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Include)]
-> [SymbolicPath Include 'File]
-> [RelativePath Include 'File]
-> [RelativePath Include 'File]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> [(String, String)]
-> [Dependency]
-> [Mixin]
-> BuildInfo)
forall a b. g BuildInfo (a -> b) -> g BuildInfo a -> g BuildInfo b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> FieldName
-> ([ExeDependency]
-> List CommaFSep (Identity ExeDependency) ExeDependency)
-> ALens' BuildInfo [ExeDependency]
-> g BuildInfo [ExeDependency]
forall b a s.
(c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
forall (c :: * -> Constraint) (g :: * -> * -> *) b a s.
(FieldGrammar c g, c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
monoidalFieldAla FieldName
"build-tool-depends" (CommaFSep
-> [ExeDependency]
-> List CommaFSep (Identity ExeDependency) ExeDependency
forall sep a. sep -> [a] -> List sep (Identity a) a
alaList CommaFSep
CommaFSep) ALens' BuildInfo [ExeDependency]
forall a. HasBuildInfo a => Lens' a [ExeDependency]
Lens' BuildInfo [ExeDependency]
L.buildToolDepends
g BuildInfo
([String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [PkgconfigDependency]
-> [RelativePath Framework 'File]
-> [SymbolicPath Pkg ('Dir Framework)]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg ('Dir Source)]
-> [ModuleName]
-> [ModuleName]
-> [ModuleName]
-> Maybe Language
-> [Language]
-> [Extension]
-> [Extension]
-> [Extension]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Include)]
-> [SymbolicPath Include 'File]
-> [RelativePath Include 'File]
-> [RelativePath Include 'File]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> [(String, String)]
-> [Dependency]
-> [Mixin]
-> BuildInfo)
-> g BuildInfo [String]
-> g BuildInfo
([String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [PkgconfigDependency]
-> [RelativePath Framework 'File]
-> [SymbolicPath Pkg ('Dir Framework)]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg ('Dir Source)]
-> [ModuleName]
-> [ModuleName]
-> [ModuleName]
-> Maybe Language
-> [Language]
-> [Extension]
-> [Extension]
-> [Extension]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Include)]
-> [SymbolicPath Include 'File]
-> [RelativePath Include 'File]
-> [RelativePath Include 'File]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> [(String, String)]
-> [Dependency]
-> [Mixin]
-> BuildInfo)
forall a b. g BuildInfo (a -> b) -> g BuildInfo a -> g BuildInfo b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> FieldName
-> ([String] -> List NoCommaFSep Token' String)
-> ALens' BuildInfo [String]
-> g BuildInfo [String]
forall b a s.
(c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
forall (c :: * -> Constraint) (g :: * -> * -> *) b a s.
(FieldGrammar c g, c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
monoidalFieldAla FieldName
"cpp-options" (NoCommaFSep
-> (String -> Token') -> [String] -> List NoCommaFSep Token' String
forall sep a b. sep -> (a -> b) -> [a] -> List sep b a
alaList' NoCommaFSep
NoCommaFSep String -> Token'
Token') ALens' BuildInfo [String]
forall a. HasBuildInfo a => Lens' a [String]
Lens' BuildInfo [String]
L.cppOptions
g BuildInfo
([String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [PkgconfigDependency]
-> [RelativePath Framework 'File]
-> [SymbolicPath Pkg ('Dir Framework)]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg ('Dir Source)]
-> [ModuleName]
-> [ModuleName]
-> [ModuleName]
-> Maybe Language
-> [Language]
-> [Extension]
-> [Extension]
-> [Extension]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Include)]
-> [SymbolicPath Include 'File]
-> [RelativePath Include 'File]
-> [RelativePath Include 'File]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> [(String, String)]
-> [Dependency]
-> [Mixin]
-> BuildInfo)
-> g BuildInfo [String]
-> g BuildInfo
([String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [PkgconfigDependency]
-> [RelativePath Framework 'File]
-> [SymbolicPath Pkg ('Dir Framework)]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg ('Dir Source)]
-> [ModuleName]
-> [ModuleName]
-> [ModuleName]
-> Maybe Language
-> [Language]
-> [Extension]
-> [Extension]
-> [Extension]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Include)]
-> [SymbolicPath Include 'File]
-> [RelativePath Include 'File]
-> [RelativePath Include 'File]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> [(String, String)]
-> [Dependency]
-> [Mixin]
-> BuildInfo)
forall a b. g BuildInfo (a -> b) -> g BuildInfo a -> g BuildInfo b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> FieldName
-> ([String] -> List NoCommaFSep Token' String)
-> ALens' BuildInfo [String]
-> g BuildInfo [String]
forall b a s.
(c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
forall (c :: * -> Constraint) (g :: * -> * -> *) b a s.
(FieldGrammar c g, c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
monoidalFieldAla FieldName
"asm-options" (NoCommaFSep
-> (String -> Token') -> [String] -> List NoCommaFSep Token' String
forall sep a b. sep -> (a -> b) -> [a] -> List sep b a
alaList' NoCommaFSep
NoCommaFSep String -> Token'
Token') ALens' BuildInfo [String]
forall a. HasBuildInfo a => Lens' a [String]
Lens' BuildInfo [String]
L.asmOptions
g BuildInfo [String]
-> (g BuildInfo [String] -> g BuildInfo [String])
-> g BuildInfo [String]
forall a b. a -> (a -> b) -> b
^^^ CabalSpecVersion
-> [String] -> g BuildInfo [String] -> g BuildInfo [String]
forall a s. CabalSpecVersion -> a -> g s a -> g s a
forall (c :: * -> Constraint) (g :: * -> * -> *) a s.
FieldGrammar c g =>
CabalSpecVersion -> a -> g s a -> g s a
availableSince CabalSpecVersion
CabalSpecV3_0 []
g BuildInfo
([String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [PkgconfigDependency]
-> [RelativePath Framework 'File]
-> [SymbolicPath Pkg ('Dir Framework)]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg ('Dir Source)]
-> [ModuleName]
-> [ModuleName]
-> [ModuleName]
-> Maybe Language
-> [Language]
-> [Extension]
-> [Extension]
-> [Extension]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Include)]
-> [SymbolicPath Include 'File]
-> [RelativePath Include 'File]
-> [RelativePath Include 'File]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> [(String, String)]
-> [Dependency]
-> [Mixin]
-> BuildInfo)
-> g BuildInfo [String]
-> g BuildInfo
([String]
-> [String]
-> [String]
-> [String]
-> [PkgconfigDependency]
-> [RelativePath Framework 'File]
-> [SymbolicPath Pkg ('Dir Framework)]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg ('Dir Source)]
-> [ModuleName]
-> [ModuleName]
-> [ModuleName]
-> Maybe Language
-> [Language]
-> [Extension]
-> [Extension]
-> [Extension]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Include)]
-> [SymbolicPath Include 'File]
-> [RelativePath Include 'File]
-> [RelativePath Include 'File]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> [(String, String)]
-> [Dependency]
-> [Mixin]
-> BuildInfo)
forall a b. g BuildInfo (a -> b) -> g BuildInfo a -> g BuildInfo b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> FieldName
-> ([String] -> List NoCommaFSep Token' String)
-> ALens' BuildInfo [String]
-> g BuildInfo [String]
forall b a s.
(c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
forall (c :: * -> Constraint) (g :: * -> * -> *) b a s.
(FieldGrammar c g, c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
monoidalFieldAla FieldName
"cmm-options" (NoCommaFSep
-> (String -> Token') -> [String] -> List NoCommaFSep Token' String
forall sep a b. sep -> (a -> b) -> [a] -> List sep b a
alaList' NoCommaFSep
NoCommaFSep String -> Token'
Token') ALens' BuildInfo [String]
forall a. HasBuildInfo a => Lens' a [String]
Lens' BuildInfo [String]
L.cmmOptions
g BuildInfo [String]
-> (g BuildInfo [String] -> g BuildInfo [String])
-> g BuildInfo [String]
forall a b. a -> (a -> b) -> b
^^^ CabalSpecVersion
-> [String] -> g BuildInfo [String] -> g BuildInfo [String]
forall a s. CabalSpecVersion -> a -> g s a -> g s a
forall (c :: * -> Constraint) (g :: * -> * -> *) a s.
FieldGrammar c g =>
CabalSpecVersion -> a -> g s a -> g s a
availableSince CabalSpecVersion
CabalSpecV3_0 []
g BuildInfo
([String]
-> [String]
-> [String]
-> [String]
-> [PkgconfigDependency]
-> [RelativePath Framework 'File]
-> [SymbolicPath Pkg ('Dir Framework)]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg ('Dir Source)]
-> [ModuleName]
-> [ModuleName]
-> [ModuleName]
-> Maybe Language
-> [Language]
-> [Extension]
-> [Extension]
-> [Extension]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Include)]
-> [SymbolicPath Include 'File]
-> [RelativePath Include 'File]
-> [RelativePath Include 'File]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> [(String, String)]
-> [Dependency]
-> [Mixin]
-> BuildInfo)
-> g BuildInfo [String]
-> g BuildInfo
([String]
-> [String]
-> [String]
-> [PkgconfigDependency]
-> [RelativePath Framework 'File]
-> [SymbolicPath Pkg ('Dir Framework)]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg ('Dir Source)]
-> [ModuleName]
-> [ModuleName]
-> [ModuleName]
-> Maybe Language
-> [Language]
-> [Extension]
-> [Extension]
-> [Extension]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Include)]
-> [SymbolicPath Include 'File]
-> [RelativePath Include 'File]
-> [RelativePath Include 'File]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> [(String, String)]
-> [Dependency]
-> [Mixin]
-> BuildInfo)
forall a b. g BuildInfo (a -> b) -> g BuildInfo a -> g BuildInfo b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> FieldName
-> ([String] -> List NoCommaFSep Token' String)
-> ALens' BuildInfo [String]
-> g BuildInfo [String]
forall b a s.
(c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
forall (c :: * -> Constraint) (g :: * -> * -> *) b a s.
(FieldGrammar c g, c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
monoidalFieldAla FieldName
"cc-options" (NoCommaFSep
-> (String -> Token') -> [String] -> List NoCommaFSep Token' String
forall sep a b. sep -> (a -> b) -> [a] -> List sep b a
alaList' NoCommaFSep
NoCommaFSep String -> Token'
Token') ALens' BuildInfo [String]
forall a. HasBuildInfo a => Lens' a [String]
Lens' BuildInfo [String]
L.ccOptions
g BuildInfo
([String]
-> [String]
-> [String]
-> [PkgconfigDependency]
-> [RelativePath Framework 'File]
-> [SymbolicPath Pkg ('Dir Framework)]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg ('Dir Source)]
-> [ModuleName]
-> [ModuleName]
-> [ModuleName]
-> Maybe Language
-> [Language]
-> [Extension]
-> [Extension]
-> [Extension]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Include)]
-> [SymbolicPath Include 'File]
-> [RelativePath Include 'File]
-> [RelativePath Include 'File]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> [(String, String)]
-> [Dependency]
-> [Mixin]
-> BuildInfo)
-> g BuildInfo [String]
-> g BuildInfo
([String]
-> [String]
-> [PkgconfigDependency]
-> [RelativePath Framework 'File]
-> [SymbolicPath Pkg ('Dir Framework)]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg ('Dir Source)]
-> [ModuleName]
-> [ModuleName]
-> [ModuleName]
-> Maybe Language
-> [Language]
-> [Extension]
-> [Extension]
-> [Extension]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Include)]
-> [SymbolicPath Include 'File]
-> [RelativePath Include 'File]
-> [RelativePath Include 'File]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> [(String, String)]
-> [Dependency]
-> [Mixin]
-> BuildInfo)
forall a b. g BuildInfo (a -> b) -> g BuildInfo a -> g BuildInfo b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> FieldName
-> ([String] -> List NoCommaFSep Token' String)
-> ALens' BuildInfo [String]
-> g BuildInfo [String]
forall b a s.
(c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
forall (c :: * -> Constraint) (g :: * -> * -> *) b a s.
(FieldGrammar c g, c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
monoidalFieldAla FieldName
"cxx-options" (NoCommaFSep
-> (String -> Token') -> [String] -> List NoCommaFSep Token' String
forall sep a b. sep -> (a -> b) -> [a] -> List sep b a
alaList' NoCommaFSep
NoCommaFSep String -> Token'
Token') ALens' BuildInfo [String]
forall a. HasBuildInfo a => Lens' a [String]
Lens' BuildInfo [String]
L.cxxOptions
g BuildInfo [String]
-> (g BuildInfo [String] -> g BuildInfo [String])
-> g BuildInfo [String]
forall a b. a -> (a -> b) -> b
^^^ CabalSpecVersion
-> [String] -> g BuildInfo [String] -> g BuildInfo [String]
forall a s. CabalSpecVersion -> a -> g s a -> g s a
forall (c :: * -> Constraint) (g :: * -> * -> *) a s.
FieldGrammar c g =>
CabalSpecVersion -> a -> g s a -> g s a
availableSince CabalSpecVersion
CabalSpecV2_2 []
g BuildInfo
([String]
-> [String]
-> [PkgconfigDependency]
-> [RelativePath Framework 'File]
-> [SymbolicPath Pkg ('Dir Framework)]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg ('Dir Source)]
-> [ModuleName]
-> [ModuleName]
-> [ModuleName]
-> Maybe Language
-> [Language]
-> [Extension]
-> [Extension]
-> [Extension]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Include)]
-> [SymbolicPath Include 'File]
-> [RelativePath Include 'File]
-> [RelativePath Include 'File]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> [(String, String)]
-> [Dependency]
-> [Mixin]
-> BuildInfo)
-> g BuildInfo [String]
-> g BuildInfo
([String]
-> [PkgconfigDependency]
-> [RelativePath Framework 'File]
-> [SymbolicPath Pkg ('Dir Framework)]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg ('Dir Source)]
-> [ModuleName]
-> [ModuleName]
-> [ModuleName]
-> Maybe Language
-> [Language]
-> [Extension]
-> [Extension]
-> [Extension]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Include)]
-> [SymbolicPath Include 'File]
-> [RelativePath Include 'File]
-> [RelativePath Include 'File]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> [(String, String)]
-> [Dependency]
-> [Mixin]
-> BuildInfo)
forall a b. g BuildInfo (a -> b) -> g BuildInfo a -> g BuildInfo b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> FieldName
-> ([String] -> List NoCommaFSep Token' String)
-> ALens' BuildInfo [String]
-> g BuildInfo [String]
forall b a s.
(c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
forall (c :: * -> Constraint) (g :: * -> * -> *) b a s.
(FieldGrammar c g, c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
monoidalFieldAla FieldName
"ld-options" (NoCommaFSep
-> (String -> Token') -> [String] -> List NoCommaFSep Token' String
forall sep a b. sep -> (a -> b) -> [a] -> List sep b a
alaList' NoCommaFSep
NoCommaFSep String -> Token'
Token') ALens' BuildInfo [String]
forall a. HasBuildInfo a => Lens' a [String]
Lens' BuildInfo [String]
L.ldOptions
g BuildInfo
([String]
-> [PkgconfigDependency]
-> [RelativePath Framework 'File]
-> [SymbolicPath Pkg ('Dir Framework)]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg ('Dir Source)]
-> [ModuleName]
-> [ModuleName]
-> [ModuleName]
-> Maybe Language
-> [Language]
-> [Extension]
-> [Extension]
-> [Extension]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Include)]
-> [SymbolicPath Include 'File]
-> [RelativePath Include 'File]
-> [RelativePath Include 'File]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> [(String, String)]
-> [Dependency]
-> [Mixin]
-> BuildInfo)
-> g BuildInfo [String]
-> g BuildInfo
([PkgconfigDependency]
-> [RelativePath Framework 'File]
-> [SymbolicPath Pkg ('Dir Framework)]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg ('Dir Source)]
-> [ModuleName]
-> [ModuleName]
-> [ModuleName]
-> Maybe Language
-> [Language]
-> [Extension]
-> [Extension]
-> [Extension]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Include)]
-> [SymbolicPath Include 'File]
-> [RelativePath Include 'File]
-> [RelativePath Include 'File]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> [(String, String)]
-> [Dependency]
-> [Mixin]
-> BuildInfo)
forall a b. g BuildInfo (a -> b) -> g BuildInfo a -> g BuildInfo b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> FieldName
-> ([String] -> List NoCommaFSep Token' String)
-> ALens' BuildInfo [String]
-> g BuildInfo [String]
forall b a s.
(c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
forall (c :: * -> Constraint) (g :: * -> * -> *) b a s.
(FieldGrammar c g, c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
monoidalFieldAla FieldName
"hsc2hs-options" (NoCommaFSep
-> (String -> Token') -> [String] -> List NoCommaFSep Token' String
forall sep a b. sep -> (a -> b) -> [a] -> List sep b a
alaList' NoCommaFSep
NoCommaFSep String -> Token'
Token') ALens' BuildInfo [String]
forall a. HasBuildInfo a => Lens' a [String]
Lens' BuildInfo [String]
L.hsc2hsOptions
g BuildInfo [String]
-> (g BuildInfo [String] -> g BuildInfo [String])
-> g BuildInfo [String]
forall a b. a -> (a -> b) -> b
^^^ CabalSpecVersion
-> [String] -> g BuildInfo [String] -> g BuildInfo [String]
forall a s. CabalSpecVersion -> a -> g s a -> g s a
forall (c :: * -> Constraint) (g :: * -> * -> *) a s.
FieldGrammar c g =>
CabalSpecVersion -> a -> g s a -> g s a
availableSince CabalSpecVersion
CabalSpecV3_6 []
g BuildInfo
([PkgconfigDependency]
-> [RelativePath Framework 'File]
-> [SymbolicPath Pkg ('Dir Framework)]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg ('Dir Source)]
-> [ModuleName]
-> [ModuleName]
-> [ModuleName]
-> Maybe Language
-> [Language]
-> [Extension]
-> [Extension]
-> [Extension]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Include)]
-> [SymbolicPath Include 'File]
-> [RelativePath Include 'File]
-> [RelativePath Include 'File]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> [(String, String)]
-> [Dependency]
-> [Mixin]
-> BuildInfo)
-> g BuildInfo [PkgconfigDependency]
-> g BuildInfo
([RelativePath Framework 'File]
-> [SymbolicPath Pkg ('Dir Framework)]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg ('Dir Source)]
-> [ModuleName]
-> [ModuleName]
-> [ModuleName]
-> Maybe Language
-> [Language]
-> [Extension]
-> [Extension]
-> [Extension]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Include)]
-> [SymbolicPath Include 'File]
-> [RelativePath Include 'File]
-> [RelativePath Include 'File]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> [(String, String)]
-> [Dependency]
-> [Mixin]
-> BuildInfo)
forall a b. g BuildInfo (a -> b) -> g BuildInfo a -> g BuildInfo b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> FieldName
-> ([PkgconfigDependency]
-> List
CommaFSep (Identity PkgconfigDependency) PkgconfigDependency)
-> ALens' BuildInfo [PkgconfigDependency]
-> g BuildInfo [PkgconfigDependency]
forall b a s.
(c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
forall (c :: * -> Constraint) (g :: * -> * -> *) b a s.
(FieldGrammar c g, c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
monoidalFieldAla FieldName
"pkgconfig-depends" (CommaFSep
-> [PkgconfigDependency]
-> List
CommaFSep (Identity PkgconfigDependency) PkgconfigDependency
forall sep a. sep -> [a] -> List sep (Identity a) a
alaList CommaFSep
CommaFSep) ALens' BuildInfo [PkgconfigDependency]
forall a. HasBuildInfo a => Lens' a [PkgconfigDependency]
Lens' BuildInfo [PkgconfigDependency]
L.pkgconfigDepends
g BuildInfo
([RelativePath Framework 'File]
-> [SymbolicPath Pkg ('Dir Framework)]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg ('Dir Source)]
-> [ModuleName]
-> [ModuleName]
-> [ModuleName]
-> Maybe Language
-> [Language]
-> [Extension]
-> [Extension]
-> [Extension]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Include)]
-> [SymbolicPath Include 'File]
-> [RelativePath Include 'File]
-> [RelativePath Include 'File]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> [(String, String)]
-> [Dependency]
-> [Mixin]
-> BuildInfo)
-> g BuildInfo [RelativePath Framework 'File]
-> g BuildInfo
([SymbolicPath Pkg ('Dir Framework)]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg ('Dir Source)]
-> [ModuleName]
-> [ModuleName]
-> [ModuleName]
-> Maybe Language
-> [Language]
-> [Extension]
-> [Extension]
-> [Extension]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Include)]
-> [SymbolicPath Include 'File]
-> [RelativePath Include 'File]
-> [RelativePath Include 'File]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> [(String, String)]
-> [Dependency]
-> [Mixin]
-> BuildInfo)
forall a b. g BuildInfo (a -> b) -> g BuildInfo a -> g BuildInfo b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> FieldName
-> ([RelativePath Framework 'File]
-> List
FSep
(RelativePathNT Framework 'File)
(RelativePath Framework 'File))
-> ALens' BuildInfo [RelativePath Framework 'File]
-> g BuildInfo [RelativePath Framework 'File]
forall b a s.
(c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
forall (c :: * -> Constraint) (g :: * -> * -> *) b a s.
(FieldGrammar c g, c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
monoidalFieldAla FieldName
"frameworks" (FSep
-> (RelativePath Framework 'File -> RelativePathNT Framework 'File)
-> [RelativePath Framework 'File]
-> List
FSep
(RelativePathNT Framework 'File)
(RelativePath Framework 'File)
forall sep a b. sep -> (a -> b) -> [a] -> List sep b a
alaList' FSep
FSep RelativePath Framework 'File -> RelativePathNT Framework 'File
forall from (to :: FileOrDir).
RelativePath from to -> RelativePathNT from to
RelativePathNT) ALens' BuildInfo [RelativePath Framework 'File]
forall a. HasBuildInfo a => Lens' a [RelativePath Framework 'File]
Lens' BuildInfo [RelativePath Framework 'File]
L.frameworks
g BuildInfo
([SymbolicPath Pkg ('Dir Framework)]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg ('Dir Source)]
-> [ModuleName]
-> [ModuleName]
-> [ModuleName]
-> Maybe Language
-> [Language]
-> [Extension]
-> [Extension]
-> [Extension]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Include)]
-> [SymbolicPath Include 'File]
-> [RelativePath Include 'File]
-> [RelativePath Include 'File]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> [(String, String)]
-> [Dependency]
-> [Mixin]
-> BuildInfo)
-> g BuildInfo [SymbolicPath Pkg ('Dir Framework)]
-> g BuildInfo
([SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg ('Dir Source)]
-> [ModuleName]
-> [ModuleName]
-> [ModuleName]
-> Maybe Language
-> [Language]
-> [Extension]
-> [Extension]
-> [Extension]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Include)]
-> [SymbolicPath Include 'File]
-> [RelativePath Include 'File]
-> [RelativePath Include 'File]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> [(String, String)]
-> [Dependency]
-> [Mixin]
-> BuildInfo)
forall a b. g BuildInfo (a -> b) -> g BuildInfo a -> g BuildInfo b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> FieldName
-> ([SymbolicPath Pkg ('Dir Framework)]
-> List
FSep
(SymbolicPathNT Pkg ('Dir Framework))
(SymbolicPath Pkg ('Dir Framework)))
-> ALens' BuildInfo [SymbolicPath Pkg ('Dir Framework)]
-> g BuildInfo [SymbolicPath Pkg ('Dir Framework)]
forall b a s.
(c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
forall (c :: * -> Constraint) (g :: * -> * -> *) b a s.
(FieldGrammar c g, c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
monoidalFieldAla FieldName
"extra-framework-dirs" (FSep
-> (SymbolicPath Pkg ('Dir Framework)
-> SymbolicPathNT Pkg ('Dir Framework))
-> [SymbolicPath Pkg ('Dir Framework)]
-> List
FSep
(SymbolicPathNT Pkg ('Dir Framework))
(SymbolicPath Pkg ('Dir Framework))
forall sep a b. sep -> (a -> b) -> [a] -> List sep b a
alaList' FSep
FSep SymbolicPath Pkg ('Dir Framework)
-> SymbolicPathNT Pkg ('Dir Framework)
forall from (to :: FileOrDir).
SymbolicPath from to -> SymbolicPathNT from to
SymbolicPathNT) ALens' BuildInfo [SymbolicPath Pkg ('Dir Framework)]
forall a.
HasBuildInfo a =>
Lens' a [SymbolicPath Pkg ('Dir Framework)]
Lens' BuildInfo [SymbolicPath Pkg ('Dir Framework)]
L.extraFrameworkDirs
g BuildInfo
([SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg ('Dir Source)]
-> [ModuleName]
-> [ModuleName]
-> [ModuleName]
-> Maybe Language
-> [Language]
-> [Extension]
-> [Extension]
-> [Extension]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Include)]
-> [SymbolicPath Include 'File]
-> [RelativePath Include 'File]
-> [RelativePath Include 'File]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> [(String, String)]
-> [Dependency]
-> [Mixin]
-> BuildInfo)
-> g BuildInfo [SymbolicPath Pkg 'File]
-> g BuildInfo
([SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg ('Dir Source)]
-> [ModuleName]
-> [ModuleName]
-> [ModuleName]
-> Maybe Language
-> [Language]
-> [Extension]
-> [Extension]
-> [Extension]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Include)]
-> [SymbolicPath Include 'File]
-> [RelativePath Include 'File]
-> [RelativePath Include 'File]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> [(String, String)]
-> [Dependency]
-> [Mixin]
-> BuildInfo)
forall a b. g BuildInfo (a -> b) -> g BuildInfo a -> g BuildInfo b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> FieldName
-> ([SymbolicPath Pkg 'File]
-> List VCat (SymbolicPathNT Pkg 'File) (SymbolicPath Pkg 'File))
-> ALens' BuildInfo [SymbolicPath Pkg 'File]
-> g BuildInfo [SymbolicPath Pkg 'File]
forall b a s.
(c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
forall (c :: * -> Constraint) (g :: * -> * -> *) b a s.
(FieldGrammar c g, c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
monoidalFieldAla FieldName
"asm-sources" (VCat
-> (SymbolicPath Pkg 'File -> SymbolicPathNT Pkg 'File)
-> [SymbolicPath Pkg 'File]
-> List VCat (SymbolicPathNT Pkg 'File) (SymbolicPath Pkg 'File)
forall sep a b. sep -> (a -> b) -> [a] -> List sep b a
alaList' VCat
VCat SymbolicPath Pkg 'File -> SymbolicPathNT Pkg 'File
forall from (to :: FileOrDir).
SymbolicPath from to -> SymbolicPathNT from to
SymbolicPathNT) ALens' BuildInfo [SymbolicPath Pkg 'File]
forall a. HasBuildInfo a => Lens' a [SymbolicPath Pkg 'File]
Lens' BuildInfo [SymbolicPath Pkg 'File]
L.asmSources
g BuildInfo [SymbolicPath Pkg 'File]
-> (g BuildInfo [SymbolicPath Pkg 'File]
-> g BuildInfo [SymbolicPath Pkg 'File])
-> g BuildInfo [SymbolicPath Pkg 'File]
forall a b. a -> (a -> b) -> b
^^^ CabalSpecVersion
-> [SymbolicPath Pkg 'File]
-> g BuildInfo [SymbolicPath Pkg 'File]
-> g BuildInfo [SymbolicPath Pkg 'File]
forall a s. CabalSpecVersion -> a -> g s a -> g s a
forall (c :: * -> Constraint) (g :: * -> * -> *) a s.
FieldGrammar c g =>
CabalSpecVersion -> a -> g s a -> g s a
availableSince CabalSpecVersion
CabalSpecV3_0 []
g BuildInfo
([SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg ('Dir Source)]
-> [ModuleName]
-> [ModuleName]
-> [ModuleName]
-> Maybe Language
-> [Language]
-> [Extension]
-> [Extension]
-> [Extension]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Include)]
-> [SymbolicPath Include 'File]
-> [RelativePath Include 'File]
-> [RelativePath Include 'File]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> [(String, String)]
-> [Dependency]
-> [Mixin]
-> BuildInfo)
-> g BuildInfo [SymbolicPath Pkg 'File]
-> g BuildInfo
([SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg ('Dir Source)]
-> [ModuleName]
-> [ModuleName]
-> [ModuleName]
-> Maybe Language
-> [Language]
-> [Extension]
-> [Extension]
-> [Extension]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Include)]
-> [SymbolicPath Include 'File]
-> [RelativePath Include 'File]
-> [RelativePath Include 'File]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> [(String, String)]
-> [Dependency]
-> [Mixin]
-> BuildInfo)
forall a b. g BuildInfo (a -> b) -> g BuildInfo a -> g BuildInfo b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> FieldName
-> ([SymbolicPath Pkg 'File]
-> List VCat (SymbolicPathNT Pkg 'File) (SymbolicPath Pkg 'File))
-> ALens' BuildInfo [SymbolicPath Pkg 'File]
-> g BuildInfo [SymbolicPath Pkg 'File]
forall b a s.
(c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
forall (c :: * -> Constraint) (g :: * -> * -> *) b a s.
(FieldGrammar c g, c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
monoidalFieldAla FieldName
"cmm-sources" (VCat
-> (SymbolicPath Pkg 'File -> SymbolicPathNT Pkg 'File)
-> [SymbolicPath Pkg 'File]
-> List VCat (SymbolicPathNT Pkg 'File) (SymbolicPath Pkg 'File)
forall sep a b. sep -> (a -> b) -> [a] -> List sep b a
alaList' VCat
VCat SymbolicPath Pkg 'File -> SymbolicPathNT Pkg 'File
forall from (to :: FileOrDir).
SymbolicPath from to -> SymbolicPathNT from to
SymbolicPathNT) ALens' BuildInfo [SymbolicPath Pkg 'File]
forall a. HasBuildInfo a => Lens' a [SymbolicPath Pkg 'File]
Lens' BuildInfo [SymbolicPath Pkg 'File]
L.cmmSources
g BuildInfo [SymbolicPath Pkg 'File]
-> (g BuildInfo [SymbolicPath Pkg 'File]
-> g BuildInfo [SymbolicPath Pkg 'File])
-> g BuildInfo [SymbolicPath Pkg 'File]
forall a b. a -> (a -> b) -> b
^^^ CabalSpecVersion
-> [SymbolicPath Pkg 'File]
-> g BuildInfo [SymbolicPath Pkg 'File]
-> g BuildInfo [SymbolicPath Pkg 'File]
forall a s. CabalSpecVersion -> a -> g s a -> g s a
forall (c :: * -> Constraint) (g :: * -> * -> *) a s.
FieldGrammar c g =>
CabalSpecVersion -> a -> g s a -> g s a
availableSince CabalSpecVersion
CabalSpecV3_0 []
g BuildInfo
([SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg ('Dir Source)]
-> [ModuleName]
-> [ModuleName]
-> [ModuleName]
-> Maybe Language
-> [Language]
-> [Extension]
-> [Extension]
-> [Extension]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Include)]
-> [SymbolicPath Include 'File]
-> [RelativePath Include 'File]
-> [RelativePath Include 'File]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> [(String, String)]
-> [Dependency]
-> [Mixin]
-> BuildInfo)
-> g BuildInfo [SymbolicPath Pkg 'File]
-> g BuildInfo
([SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg ('Dir Source)]
-> [ModuleName]
-> [ModuleName]
-> [ModuleName]
-> Maybe Language
-> [Language]
-> [Extension]
-> [Extension]
-> [Extension]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Include)]
-> [SymbolicPath Include 'File]
-> [RelativePath Include 'File]
-> [RelativePath Include 'File]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> [(String, String)]
-> [Dependency]
-> [Mixin]
-> BuildInfo)
forall a b. g BuildInfo (a -> b) -> g BuildInfo a -> g BuildInfo b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> FieldName
-> ([SymbolicPath Pkg 'File]
-> List VCat (SymbolicPathNT Pkg 'File) (SymbolicPath Pkg 'File))
-> ALens' BuildInfo [SymbolicPath Pkg 'File]
-> g BuildInfo [SymbolicPath Pkg 'File]
forall b a s.
(c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
forall (c :: * -> Constraint) (g :: * -> * -> *) b a s.
(FieldGrammar c g, c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
monoidalFieldAla FieldName
"c-sources" (VCat
-> (SymbolicPath Pkg 'File -> SymbolicPathNT Pkg 'File)
-> [SymbolicPath Pkg 'File]
-> List VCat (SymbolicPathNT Pkg 'File) (SymbolicPath Pkg 'File)
forall sep a b. sep -> (a -> b) -> [a] -> List sep b a
alaList' VCat
VCat SymbolicPath Pkg 'File -> SymbolicPathNT Pkg 'File
forall from (to :: FileOrDir).
SymbolicPath from to -> SymbolicPathNT from to
SymbolicPathNT) ALens' BuildInfo [SymbolicPath Pkg 'File]
forall a. HasBuildInfo a => Lens' a [SymbolicPath Pkg 'File]
Lens' BuildInfo [SymbolicPath Pkg 'File]
L.cSources
g BuildInfo
([SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg ('Dir Source)]
-> [ModuleName]
-> [ModuleName]
-> [ModuleName]
-> Maybe Language
-> [Language]
-> [Extension]
-> [Extension]
-> [Extension]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Include)]
-> [SymbolicPath Include 'File]
-> [RelativePath Include 'File]
-> [RelativePath Include 'File]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> [(String, String)]
-> [Dependency]
-> [Mixin]
-> BuildInfo)
-> g BuildInfo [SymbolicPath Pkg 'File]
-> g BuildInfo
([SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg ('Dir Source)]
-> [ModuleName]
-> [ModuleName]
-> [ModuleName]
-> Maybe Language
-> [Language]
-> [Extension]
-> [Extension]
-> [Extension]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Include)]
-> [SymbolicPath Include 'File]
-> [RelativePath Include 'File]
-> [RelativePath Include 'File]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> [(String, String)]
-> [Dependency]
-> [Mixin]
-> BuildInfo)
forall a b. g BuildInfo (a -> b) -> g BuildInfo a -> g BuildInfo b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> FieldName
-> ([SymbolicPath Pkg 'File]
-> List VCat (SymbolicPathNT Pkg 'File) (SymbolicPath Pkg 'File))
-> ALens' BuildInfo [SymbolicPath Pkg 'File]
-> g BuildInfo [SymbolicPath Pkg 'File]
forall b a s.
(c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
forall (c :: * -> Constraint) (g :: * -> * -> *) b a s.
(FieldGrammar c g, c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
monoidalFieldAla FieldName
"cxx-sources" (VCat
-> (SymbolicPath Pkg 'File -> SymbolicPathNT Pkg 'File)
-> [SymbolicPath Pkg 'File]
-> List VCat (SymbolicPathNT Pkg 'File) (SymbolicPath Pkg 'File)
forall sep a b. sep -> (a -> b) -> [a] -> List sep b a
alaList' VCat
VCat SymbolicPath Pkg 'File -> SymbolicPathNT Pkg 'File
forall from (to :: FileOrDir).
SymbolicPath from to -> SymbolicPathNT from to
SymbolicPathNT) ALens' BuildInfo [SymbolicPath Pkg 'File]
forall a. HasBuildInfo a => Lens' a [SymbolicPath Pkg 'File]
Lens' BuildInfo [SymbolicPath Pkg 'File]
L.cxxSources
g BuildInfo [SymbolicPath Pkg 'File]
-> (g BuildInfo [SymbolicPath Pkg 'File]
-> g BuildInfo [SymbolicPath Pkg 'File])
-> g BuildInfo [SymbolicPath Pkg 'File]
forall a b. a -> (a -> b) -> b
^^^ CabalSpecVersion
-> [SymbolicPath Pkg 'File]
-> g BuildInfo [SymbolicPath Pkg 'File]
-> g BuildInfo [SymbolicPath Pkg 'File]
forall a s. CabalSpecVersion -> a -> g s a -> g s a
forall (c :: * -> Constraint) (g :: * -> * -> *) a s.
FieldGrammar c g =>
CabalSpecVersion -> a -> g s a -> g s a
availableSince CabalSpecVersion
CabalSpecV2_2 []
g BuildInfo
([SymbolicPath Pkg 'File]
-> [SymbolicPath Pkg ('Dir Source)]
-> [ModuleName]
-> [ModuleName]
-> [ModuleName]
-> Maybe Language
-> [Language]
-> [Extension]
-> [Extension]
-> [Extension]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Include)]
-> [SymbolicPath Include 'File]
-> [RelativePath Include 'File]
-> [RelativePath Include 'File]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> [(String, String)]
-> [Dependency]
-> [Mixin]
-> BuildInfo)
-> g BuildInfo [SymbolicPath Pkg 'File]
-> g BuildInfo
([SymbolicPath Pkg ('Dir Source)]
-> [ModuleName]
-> [ModuleName]
-> [ModuleName]
-> Maybe Language
-> [Language]
-> [Extension]
-> [Extension]
-> [Extension]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Include)]
-> [SymbolicPath Include 'File]
-> [RelativePath Include 'File]
-> [RelativePath Include 'File]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> [(String, String)]
-> [Dependency]
-> [Mixin]
-> BuildInfo)
forall a b. g BuildInfo (a -> b) -> g BuildInfo a -> g BuildInfo b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> FieldName
-> ([SymbolicPath Pkg 'File]
-> List VCat (SymbolicPathNT Pkg 'File) (SymbolicPath Pkg 'File))
-> ALens' BuildInfo [SymbolicPath Pkg 'File]
-> g BuildInfo [SymbolicPath Pkg 'File]
forall b a s.
(c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
forall (c :: * -> Constraint) (g :: * -> * -> *) b a s.
(FieldGrammar c g, c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
monoidalFieldAla FieldName
"js-sources" (VCat
-> (SymbolicPath Pkg 'File -> SymbolicPathNT Pkg 'File)
-> [SymbolicPath Pkg 'File]
-> List VCat (SymbolicPathNT Pkg 'File) (SymbolicPath Pkg 'File)
forall sep a b. sep -> (a -> b) -> [a] -> List sep b a
alaList' VCat
VCat SymbolicPath Pkg 'File -> SymbolicPathNT Pkg 'File
forall from (to :: FileOrDir).
SymbolicPath from to -> SymbolicPathNT from to
SymbolicPathNT) ALens' BuildInfo [SymbolicPath Pkg 'File]
forall a. HasBuildInfo a => Lens' a [SymbolicPath Pkg 'File]
Lens' BuildInfo [SymbolicPath Pkg 'File]
L.jsSources
g BuildInfo
([SymbolicPath Pkg ('Dir Source)]
-> [ModuleName]
-> [ModuleName]
-> [ModuleName]
-> Maybe Language
-> [Language]
-> [Extension]
-> [Extension]
-> [Extension]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Include)]
-> [SymbolicPath Include 'File]
-> [RelativePath Include 'File]
-> [RelativePath Include 'File]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> [(String, String)]
-> [Dependency]
-> [Mixin]
-> BuildInfo)
-> g BuildInfo [SymbolicPath Pkg ('Dir Source)]
-> g BuildInfo
([ModuleName]
-> [ModuleName]
-> [ModuleName]
-> Maybe Language
-> [Language]
-> [Extension]
-> [Extension]
-> [Extension]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Include)]
-> [SymbolicPath Include 'File]
-> [RelativePath Include 'File]
-> [RelativePath Include 'File]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> [(String, String)]
-> [Dependency]
-> [Mixin]
-> BuildInfo)
forall a b. g BuildInfo (a -> b) -> g BuildInfo a -> g BuildInfo b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> g BuildInfo [SymbolicPath Pkg ('Dir Source)]
forall (c :: * -> Constraint) (g :: * -> * -> *).
(FieldGrammar c g, Applicative (g BuildInfo),
forall from (to :: FileOrDir).
c (List FSep (SymbolicPathNT from to) (SymbolicPath from to))) =>
g BuildInfo [SymbolicPath Pkg ('Dir Source)]
hsSourceDirsGrammar
g BuildInfo
([ModuleName]
-> [ModuleName]
-> [ModuleName]
-> Maybe Language
-> [Language]
-> [Extension]
-> [Extension]
-> [Extension]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Include)]
-> [SymbolicPath Include 'File]
-> [RelativePath Include 'File]
-> [RelativePath Include 'File]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> [(String, String)]
-> [Dependency]
-> [Mixin]
-> BuildInfo)
-> g BuildInfo [ModuleName]
-> g BuildInfo
([ModuleName]
-> [ModuleName]
-> Maybe Language
-> [Language]
-> [Extension]
-> [Extension]
-> [Extension]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Include)]
-> [SymbolicPath Include 'File]
-> [RelativePath Include 'File]
-> [RelativePath Include 'File]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> [(String, String)]
-> [Dependency]
-> [Mixin]
-> BuildInfo)
forall a b. g BuildInfo (a -> b) -> g BuildInfo a -> g BuildInfo b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> FieldName
-> ([ModuleName] -> List VCat (MQuoted ModuleName) ModuleName)
-> ALens' BuildInfo [ModuleName]
-> g BuildInfo [ModuleName]
forall b a s.
(c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
forall (c :: * -> Constraint) (g :: * -> * -> *) b a s.
(FieldGrammar c g, c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
monoidalFieldAla FieldName
"other-modules" [ModuleName] -> List VCat (MQuoted ModuleName) ModuleName
formatOtherModules ALens' BuildInfo [ModuleName]
forall a. HasBuildInfo a => Lens' a [ModuleName]
Lens' BuildInfo [ModuleName]
L.otherModules
g BuildInfo
([ModuleName]
-> [ModuleName]
-> Maybe Language
-> [Language]
-> [Extension]
-> [Extension]
-> [Extension]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Include)]
-> [SymbolicPath Include 'File]
-> [RelativePath Include 'File]
-> [RelativePath Include 'File]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> [(String, String)]
-> [Dependency]
-> [Mixin]
-> BuildInfo)
-> g BuildInfo [ModuleName]
-> g BuildInfo
([ModuleName]
-> Maybe Language
-> [Language]
-> [Extension]
-> [Extension]
-> [Extension]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Include)]
-> [SymbolicPath Include 'File]
-> [RelativePath Include 'File]
-> [RelativePath Include 'File]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> [(String, String)]
-> [Dependency]
-> [Mixin]
-> BuildInfo)
forall a b. g BuildInfo (a -> b) -> g BuildInfo a -> g BuildInfo b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> FieldName
-> ([ModuleName] -> List VCat (MQuoted ModuleName) ModuleName)
-> ALens' BuildInfo [ModuleName]
-> g BuildInfo [ModuleName]
forall b a s.
(c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
forall (c :: * -> Constraint) (g :: * -> * -> *) b a s.
(FieldGrammar c g, c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
monoidalFieldAla FieldName
"virtual-modules" (VCat
-> (ModuleName -> MQuoted ModuleName)
-> [ModuleName]
-> List VCat (MQuoted ModuleName) ModuleName
forall sep a b. sep -> (a -> b) -> [a] -> List sep b a
alaList' VCat
VCat ModuleName -> MQuoted ModuleName
forall a. a -> MQuoted a
MQuoted) ALens' BuildInfo [ModuleName]
forall a. HasBuildInfo a => Lens' a [ModuleName]
Lens' BuildInfo [ModuleName]
L.virtualModules
g BuildInfo [ModuleName]
-> (g BuildInfo [ModuleName] -> g BuildInfo [ModuleName])
-> g BuildInfo [ModuleName]
forall a b. a -> (a -> b) -> b
^^^ CabalSpecVersion
-> [ModuleName]
-> g BuildInfo [ModuleName]
-> g BuildInfo [ModuleName]
forall a s. CabalSpecVersion -> a -> g s a -> g s a
forall (c :: * -> Constraint) (g :: * -> * -> *) a s.
FieldGrammar c g =>
CabalSpecVersion -> a -> g s a -> g s a
availableSince CabalSpecVersion
CabalSpecV2_2 []
g BuildInfo
([ModuleName]
-> Maybe Language
-> [Language]
-> [Extension]
-> [Extension]
-> [Extension]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Include)]
-> [SymbolicPath Include 'File]
-> [RelativePath Include 'File]
-> [RelativePath Include 'File]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> [(String, String)]
-> [Dependency]
-> [Mixin]
-> BuildInfo)
-> g BuildInfo [ModuleName]
-> g BuildInfo
(Maybe Language
-> [Language]
-> [Extension]
-> [Extension]
-> [Extension]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Include)]
-> [SymbolicPath Include 'File]
-> [RelativePath Include 'File]
-> [RelativePath Include 'File]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> [(String, String)]
-> [Dependency]
-> [Mixin]
-> BuildInfo)
forall a b. g BuildInfo (a -> b) -> g BuildInfo a -> g BuildInfo b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> FieldName
-> ([ModuleName] -> List VCat (MQuoted ModuleName) ModuleName)
-> ALens' BuildInfo [ModuleName]
-> g BuildInfo [ModuleName]
forall b a s.
(c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
forall (c :: * -> Constraint) (g :: * -> * -> *) b a s.
(FieldGrammar c g, c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
monoidalFieldAla FieldName
"autogen-modules" (VCat
-> (ModuleName -> MQuoted ModuleName)
-> [ModuleName]
-> List VCat (MQuoted ModuleName) ModuleName
forall sep a b. sep -> (a -> b) -> [a] -> List sep b a
alaList' VCat
VCat ModuleName -> MQuoted ModuleName
forall a. a -> MQuoted a
MQuoted) ALens' BuildInfo [ModuleName]
forall a. HasBuildInfo a => Lens' a [ModuleName]
Lens' BuildInfo [ModuleName]
L.autogenModules
g BuildInfo [ModuleName]
-> (g BuildInfo [ModuleName] -> g BuildInfo [ModuleName])
-> g BuildInfo [ModuleName]
forall a b. a -> (a -> b) -> b
^^^ CabalSpecVersion
-> [ModuleName]
-> g BuildInfo [ModuleName]
-> g BuildInfo [ModuleName]
forall a s. CabalSpecVersion -> a -> g s a -> g s a
forall (c :: * -> Constraint) (g :: * -> * -> *) a s.
FieldGrammar c g =>
CabalSpecVersion -> a -> g s a -> g s a
availableSince CabalSpecVersion
CabalSpecV2_0 []
g BuildInfo
(Maybe Language
-> [Language]
-> [Extension]
-> [Extension]
-> [Extension]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Include)]
-> [SymbolicPath Include 'File]
-> [RelativePath Include 'File]
-> [RelativePath Include 'File]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> [(String, String)]
-> [Dependency]
-> [Mixin]
-> BuildInfo)
-> g BuildInfo (Maybe Language)
-> g BuildInfo
([Language]
-> [Extension]
-> [Extension]
-> [Extension]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Include)]
-> [SymbolicPath Include 'File]
-> [RelativePath Include 'File]
-> [RelativePath Include 'File]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> [(String, String)]
-> [Dependency]
-> [Mixin]
-> BuildInfo)
forall a b. g BuildInfo (a -> b) -> g BuildInfo a -> g BuildInfo b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> FieldName
-> (Language -> MQuoted Language)
-> ALens' BuildInfo (Maybe Language)
-> g BuildInfo (Maybe Language)
forall b a s.
(c b, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s (Maybe a) -> g s (Maybe a)
forall (c :: * -> Constraint) (g :: * -> * -> *) b a s.
(FieldGrammar c g, c b, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s (Maybe a) -> g s (Maybe a)
optionalFieldAla FieldName
"default-language" Language -> MQuoted Language
forall a. a -> MQuoted a
MQuoted ALens' BuildInfo (Maybe Language)
forall a. HasBuildInfo a => Lens' a (Maybe Language)
Lens' BuildInfo (Maybe Language)
L.defaultLanguage
g BuildInfo (Maybe Language)
-> (g BuildInfo (Maybe Language) -> g BuildInfo (Maybe Language))
-> g BuildInfo (Maybe Language)
forall a b. a -> (a -> b) -> b
^^^ CabalSpecVersion
-> Maybe Language
-> g BuildInfo (Maybe Language)
-> g BuildInfo (Maybe Language)
forall a s. CabalSpecVersion -> a -> g s a -> g s a
forall (c :: * -> Constraint) (g :: * -> * -> *) a s.
FieldGrammar c g =>
CabalSpecVersion -> a -> g s a -> g s a
availableSince CabalSpecVersion
CabalSpecV1_10 Maybe Language
forall a. Maybe a
Nothing
g BuildInfo
([Language]
-> [Extension]
-> [Extension]
-> [Extension]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Include)]
-> [SymbolicPath Include 'File]
-> [RelativePath Include 'File]
-> [RelativePath Include 'File]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> [(String, String)]
-> [Dependency]
-> [Mixin]
-> BuildInfo)
-> g BuildInfo [Language]
-> g BuildInfo
([Extension]
-> [Extension]
-> [Extension]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Include)]
-> [SymbolicPath Include 'File]
-> [RelativePath Include 'File]
-> [RelativePath Include 'File]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> [(String, String)]
-> [Dependency]
-> [Mixin]
-> BuildInfo)
forall a b. g BuildInfo (a -> b) -> g BuildInfo a -> g BuildInfo b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> FieldName
-> ([Language] -> List FSep (MQuoted Language) Language)
-> ALens' BuildInfo [Language]
-> g BuildInfo [Language]
forall b a s.
(c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
forall (c :: * -> Constraint) (g :: * -> * -> *) b a s.
(FieldGrammar c g, c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
monoidalFieldAla FieldName
"other-languages" (FSep
-> (Language -> MQuoted Language)
-> [Language]
-> List FSep (MQuoted Language) Language
forall sep a b. sep -> (a -> b) -> [a] -> List sep b a
alaList' FSep
FSep Language -> MQuoted Language
forall a. a -> MQuoted a
MQuoted) ALens' BuildInfo [Language]
forall a. HasBuildInfo a => Lens' a [Language]
Lens' BuildInfo [Language]
L.otherLanguages
g BuildInfo [Language]
-> (g BuildInfo [Language] -> g BuildInfo [Language])
-> g BuildInfo [Language]
forall a b. a -> (a -> b) -> b
^^^ CabalSpecVersion
-> [Language] -> g BuildInfo [Language] -> g BuildInfo [Language]
forall a s. CabalSpecVersion -> a -> g s a -> g s a
forall (c :: * -> Constraint) (g :: * -> * -> *) a s.
FieldGrammar c g =>
CabalSpecVersion -> a -> g s a -> g s a
availableSince CabalSpecVersion
CabalSpecV1_10 []
g BuildInfo
([Extension]
-> [Extension]
-> [Extension]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Include)]
-> [SymbolicPath Include 'File]
-> [RelativePath Include 'File]
-> [RelativePath Include 'File]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> [(String, String)]
-> [Dependency]
-> [Mixin]
-> BuildInfo)
-> g BuildInfo [Extension]
-> g BuildInfo
([Extension]
-> [Extension]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Include)]
-> [SymbolicPath Include 'File]
-> [RelativePath Include 'File]
-> [RelativePath Include 'File]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> [(String, String)]
-> [Dependency]
-> [Mixin]
-> BuildInfo)
forall a b. g BuildInfo (a -> b) -> g BuildInfo a -> g BuildInfo b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> FieldName
-> ([Extension] -> List FSep (MQuoted Extension) Extension)
-> ALens' BuildInfo [Extension]
-> g BuildInfo [Extension]
forall b a s.
(c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
forall (c :: * -> Constraint) (g :: * -> * -> *) b a s.
(FieldGrammar c g, c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
monoidalFieldAla FieldName
"default-extensions" (FSep
-> (Extension -> MQuoted Extension)
-> [Extension]
-> List FSep (MQuoted Extension) Extension
forall sep a b. sep -> (a -> b) -> [a] -> List sep b a
alaList' FSep
FSep Extension -> MQuoted Extension
forall a. a -> MQuoted a
MQuoted) ALens' BuildInfo [Extension]
forall a. HasBuildInfo a => Lens' a [Extension]
Lens' BuildInfo [Extension]
L.defaultExtensions
g BuildInfo [Extension]
-> (g BuildInfo [Extension] -> g BuildInfo [Extension])
-> g BuildInfo [Extension]
forall a b. a -> (a -> b) -> b
^^^ CabalSpecVersion
-> [Extension]
-> g BuildInfo [Extension]
-> g BuildInfo [Extension]
forall a s. CabalSpecVersion -> a -> g s a -> g s a
forall (c :: * -> Constraint) (g :: * -> * -> *) a s.
FieldGrammar c g =>
CabalSpecVersion -> a -> g s a -> g s a
availableSince CabalSpecVersion
CabalSpecV1_10 []
g BuildInfo
([Extension]
-> [Extension]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Include)]
-> [SymbolicPath Include 'File]
-> [RelativePath Include 'File]
-> [RelativePath Include 'File]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> [(String, String)]
-> [Dependency]
-> [Mixin]
-> BuildInfo)
-> g BuildInfo [Extension]
-> g BuildInfo
([Extension]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Include)]
-> [SymbolicPath Include 'File]
-> [RelativePath Include 'File]
-> [RelativePath Include 'File]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> [(String, String)]
-> [Dependency]
-> [Mixin]
-> BuildInfo)
forall a b. g BuildInfo (a -> b) -> g BuildInfo a -> g BuildInfo b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> FieldName
-> ([Extension] -> List FSep (MQuoted Extension) Extension)
-> ALens' BuildInfo [Extension]
-> g BuildInfo [Extension]
forall b a s.
(c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
forall (c :: * -> Constraint) (g :: * -> * -> *) b a s.
(FieldGrammar c g, c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
monoidalFieldAla FieldName
"other-extensions" [Extension] -> List FSep (MQuoted Extension) Extension
formatOtherExtensions ALens' BuildInfo [Extension]
forall a. HasBuildInfo a => Lens' a [Extension]
Lens' BuildInfo [Extension]
L.otherExtensions
g BuildInfo [Extension]
-> (g BuildInfo [Extension] -> g BuildInfo [Extension])
-> g BuildInfo [Extension]
forall a b. a -> (a -> b) -> b
^^^ CabalSpecVersion
-> g BuildInfo [Extension] -> g BuildInfo [Extension]
forall s a. CabalSpecVersion -> g s a -> g s a
forall (c :: * -> Constraint) (g :: * -> * -> *) s a.
FieldGrammar c g =>
CabalSpecVersion -> g s a -> g s a
availableSinceWarn CabalSpecVersion
CabalSpecV1_10
g BuildInfo
([Extension]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Include)]
-> [SymbolicPath Include 'File]
-> [RelativePath Include 'File]
-> [RelativePath Include 'File]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> [(String, String)]
-> [Dependency]
-> [Mixin]
-> BuildInfo)
-> g BuildInfo [Extension]
-> g BuildInfo
([String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Include)]
-> [SymbolicPath Include 'File]
-> [RelativePath Include 'File]
-> [RelativePath Include 'File]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> [(String, String)]
-> [Dependency]
-> [Mixin]
-> BuildInfo)
forall a b. g BuildInfo (a -> b) -> g BuildInfo a -> g BuildInfo b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> FieldName
-> ([Extension] -> List FSep (MQuoted Extension) Extension)
-> ALens' BuildInfo [Extension]
-> g BuildInfo [Extension]
forall b a s.
(c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
forall (c :: * -> Constraint) (g :: * -> * -> *) b a s.
(FieldGrammar c g, c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
monoidalFieldAla FieldName
"extensions" (FSep
-> (Extension -> MQuoted Extension)
-> [Extension]
-> List FSep (MQuoted Extension) Extension
forall sep a b. sep -> (a -> b) -> [a] -> List sep b a
alaList' FSep
FSep Extension -> MQuoted Extension
forall a. a -> MQuoted a
MQuoted) ALens' BuildInfo [Extension]
forall a. HasBuildInfo a => Lens' a [Extension]
Lens' BuildInfo [Extension]
L.oldExtensions
g BuildInfo [Extension]
-> (g BuildInfo [Extension] -> g BuildInfo [Extension])
-> g BuildInfo [Extension]
forall a b. a -> (a -> b) -> b
^^^ CabalSpecVersion
-> String -> g BuildInfo [Extension] -> g BuildInfo [Extension]
forall s a. CabalSpecVersion -> String -> g s a -> g s a
forall (c :: * -> Constraint) (g :: * -> * -> *) s a.
FieldGrammar c g =>
CabalSpecVersion -> String -> g s a -> g s a
deprecatedSince
CabalSpecVersion
CabalSpecV1_12
String
"Please use 'default-extensions' or 'other-extensions' fields."
g BuildInfo [Extension]
-> (g BuildInfo [Extension] -> g BuildInfo [Extension])
-> g BuildInfo [Extension]
forall a b. a -> (a -> b) -> b
^^^ CabalSpecVersion
-> String -> g BuildInfo [Extension] -> g BuildInfo [Extension]
forall s a. CabalSpecVersion -> String -> g s a -> g s a
forall (c :: * -> Constraint) (g :: * -> * -> *) s a.
FieldGrammar c g =>
CabalSpecVersion -> String -> g s a -> g s a
removedIn
CabalSpecVersion
CabalSpecV3_0
String
"Please use 'default-extensions' or 'other-extensions' fields."
g BuildInfo
([String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Include)]
-> [SymbolicPath Include 'File]
-> [RelativePath Include 'File]
-> [RelativePath Include 'File]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> [(String, String)]
-> [Dependency]
-> [Mixin]
-> BuildInfo)
-> g BuildInfo [String]
-> g BuildInfo
([String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Include)]
-> [SymbolicPath Include 'File]
-> [RelativePath Include 'File]
-> [RelativePath Include 'File]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> [(String, String)]
-> [Dependency]
-> [Mixin]
-> BuildInfo)
forall a b. g BuildInfo (a -> b) -> g BuildInfo a -> g BuildInfo b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> FieldName
-> ([String] -> List VCat Token String)
-> ALens' BuildInfo [String]
-> g BuildInfo [String]
forall b a s.
(c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
forall (c :: * -> Constraint) (g :: * -> * -> *) b a s.
(FieldGrammar c g, c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
monoidalFieldAla FieldName
"extra-libraries" (VCat -> (String -> Token) -> [String] -> List VCat Token String
forall sep a b. sep -> (a -> b) -> [a] -> List sep b a
alaList' VCat
VCat String -> Token
Token) ALens' BuildInfo [String]
forall a. HasBuildInfo a => Lens' a [String]
Lens' BuildInfo [String]
L.extraLibs
g BuildInfo
([String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Include)]
-> [SymbolicPath Include 'File]
-> [RelativePath Include 'File]
-> [RelativePath Include 'File]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> [(String, String)]
-> [Dependency]
-> [Mixin]
-> BuildInfo)
-> g BuildInfo [String]
-> g BuildInfo
([String]
-> [String]
-> [String]
-> [String]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Include)]
-> [SymbolicPath Include 'File]
-> [RelativePath Include 'File]
-> [RelativePath Include 'File]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> [(String, String)]
-> [Dependency]
-> [Mixin]
-> BuildInfo)
forall a b. g BuildInfo (a -> b) -> g BuildInfo a -> g BuildInfo b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> FieldName
-> ([String] -> List VCat Token String)
-> ALens' BuildInfo [String]
-> g BuildInfo [String]
forall b a s.
(c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
forall (c :: * -> Constraint) (g :: * -> * -> *) b a s.
(FieldGrammar c g, c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
monoidalFieldAla FieldName
"extra-libraries-static" (VCat -> (String -> Token) -> [String] -> List VCat Token String
forall sep a b. sep -> (a -> b) -> [a] -> List sep b a
alaList' VCat
VCat String -> Token
Token) ALens' BuildInfo [String]
forall a. HasBuildInfo a => Lens' a [String]
Lens' BuildInfo [String]
L.extraLibsStatic
g BuildInfo [String]
-> (g BuildInfo [String] -> g BuildInfo [String])
-> g BuildInfo [String]
forall a b. a -> (a -> b) -> b
^^^ CabalSpecVersion
-> [String] -> g BuildInfo [String] -> g BuildInfo [String]
forall a s. CabalSpecVersion -> a -> g s a -> g s a
forall (c :: * -> Constraint) (g :: * -> * -> *) a s.
FieldGrammar c g =>
CabalSpecVersion -> a -> g s a -> g s a
availableSince CabalSpecVersion
CabalSpecV3_8 []
g BuildInfo
([String]
-> [String]
-> [String]
-> [String]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Include)]
-> [SymbolicPath Include 'File]
-> [RelativePath Include 'File]
-> [RelativePath Include 'File]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> [(String, String)]
-> [Dependency]
-> [Mixin]
-> BuildInfo)
-> g BuildInfo [String]
-> g BuildInfo
([String]
-> [String]
-> [String]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Include)]
-> [SymbolicPath Include 'File]
-> [RelativePath Include 'File]
-> [RelativePath Include 'File]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> [(String, String)]
-> [Dependency]
-> [Mixin]
-> BuildInfo)
forall a b. g BuildInfo (a -> b) -> g BuildInfo a -> g BuildInfo b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> FieldName
-> ([String] -> List VCat Token String)
-> ALens' BuildInfo [String]
-> g BuildInfo [String]
forall b a s.
(c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
forall (c :: * -> Constraint) (g :: * -> * -> *) b a s.
(FieldGrammar c g, c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
monoidalFieldAla FieldName
"extra-ghci-libraries" (VCat -> (String -> Token) -> [String] -> List VCat Token String
forall sep a b. sep -> (a -> b) -> [a] -> List sep b a
alaList' VCat
VCat String -> Token
Token) ALens' BuildInfo [String]
forall a. HasBuildInfo a => Lens' a [String]
Lens' BuildInfo [String]
L.extraGHCiLibs
g BuildInfo
([String]
-> [String]
-> [String]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Include)]
-> [SymbolicPath Include 'File]
-> [RelativePath Include 'File]
-> [RelativePath Include 'File]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> [(String, String)]
-> [Dependency]
-> [Mixin]
-> BuildInfo)
-> g BuildInfo [String]
-> g BuildInfo
([String]
-> [String]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Include)]
-> [SymbolicPath Include 'File]
-> [RelativePath Include 'File]
-> [RelativePath Include 'File]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> [(String, String)]
-> [Dependency]
-> [Mixin]
-> BuildInfo)
forall a b. g BuildInfo (a -> b) -> g BuildInfo a -> g BuildInfo b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> FieldName
-> ([String] -> List VCat Token String)
-> ALens' BuildInfo [String]
-> g BuildInfo [String]
forall b a s.
(c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
forall (c :: * -> Constraint) (g :: * -> * -> *) b a s.
(FieldGrammar c g, c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
monoidalFieldAla FieldName
"extra-bundled-libraries" (VCat -> (String -> Token) -> [String] -> List VCat Token String
forall sep a b. sep -> (a -> b) -> [a] -> List sep b a
alaList' VCat
VCat String -> Token
Token) ALens' BuildInfo [String]
forall a. HasBuildInfo a => Lens' a [String]
Lens' BuildInfo [String]
L.extraBundledLibs
g BuildInfo
([String]
-> [String]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Include)]
-> [SymbolicPath Include 'File]
-> [RelativePath Include 'File]
-> [RelativePath Include 'File]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> [(String, String)]
-> [Dependency]
-> [Mixin]
-> BuildInfo)
-> g BuildInfo [String]
-> g BuildInfo
([String]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Include)]
-> [SymbolicPath Include 'File]
-> [RelativePath Include 'File]
-> [RelativePath Include 'File]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> [(String, String)]
-> [Dependency]
-> [Mixin]
-> BuildInfo)
forall a b. g BuildInfo (a -> b) -> g BuildInfo a -> g BuildInfo b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> FieldName
-> ([String] -> List VCat Token String)
-> ALens' BuildInfo [String]
-> g BuildInfo [String]
forall b a s.
(c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
forall (c :: * -> Constraint) (g :: * -> * -> *) b a s.
(FieldGrammar c g, c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
monoidalFieldAla FieldName
"extra-library-flavours" (VCat -> (String -> Token) -> [String] -> List VCat Token String
forall sep a b. sep -> (a -> b) -> [a] -> List sep b a
alaList' VCat
VCat String -> Token
Token) ALens' BuildInfo [String]
forall a. HasBuildInfo a => Lens' a [String]
Lens' BuildInfo [String]
L.extraLibFlavours
g BuildInfo
([String]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Include)]
-> [SymbolicPath Include 'File]
-> [RelativePath Include 'File]
-> [RelativePath Include 'File]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> [(String, String)]
-> [Dependency]
-> [Mixin]
-> BuildInfo)
-> g BuildInfo [String]
-> g BuildInfo
([SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Include)]
-> [SymbolicPath Include 'File]
-> [RelativePath Include 'File]
-> [RelativePath Include 'File]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> [(String, String)]
-> [Dependency]
-> [Mixin]
-> BuildInfo)
forall a b. g BuildInfo (a -> b) -> g BuildInfo a -> g BuildInfo b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> FieldName
-> ([String] -> List VCat Token String)
-> ALens' BuildInfo [String]
-> g BuildInfo [String]
forall b a s.
(c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
forall (c :: * -> Constraint) (g :: * -> * -> *) b a s.
(FieldGrammar c g, c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
monoidalFieldAla FieldName
"extra-dynamic-library-flavours" (VCat -> (String -> Token) -> [String] -> List VCat Token String
forall sep a b. sep -> (a -> b) -> [a] -> List sep b a
alaList' VCat
VCat String -> Token
Token) ALens' BuildInfo [String]
forall a. HasBuildInfo a => Lens' a [String]
Lens' BuildInfo [String]
L.extraDynLibFlavours
g BuildInfo [String]
-> (g BuildInfo [String] -> g BuildInfo [String])
-> g BuildInfo [String]
forall a b. a -> (a -> b) -> b
^^^ CabalSpecVersion
-> [String] -> g BuildInfo [String] -> g BuildInfo [String]
forall a s. CabalSpecVersion -> a -> g s a -> g s a
forall (c :: * -> Constraint) (g :: * -> * -> *) a s.
FieldGrammar c g =>
CabalSpecVersion -> a -> g s a -> g s a
availableSince CabalSpecVersion
CabalSpecV3_0 []
g BuildInfo
([SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Include)]
-> [SymbolicPath Include 'File]
-> [RelativePath Include 'File]
-> [RelativePath Include 'File]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> [(String, String)]
-> [Dependency]
-> [Mixin]
-> BuildInfo)
-> g BuildInfo [SymbolicPath Pkg ('Dir Lib)]
-> g BuildInfo
([SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Include)]
-> [SymbolicPath Include 'File]
-> [RelativePath Include 'File]
-> [RelativePath Include 'File]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> [(String, String)]
-> [Dependency]
-> [Mixin]
-> BuildInfo)
forall a b. g BuildInfo (a -> b) -> g BuildInfo a -> g BuildInfo b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> FieldName
-> ([SymbolicPath Pkg ('Dir Lib)]
-> List
FSep (SymbolicPathNT Pkg ('Dir Lib)) (SymbolicPath Pkg ('Dir Lib)))
-> ALens' BuildInfo [SymbolicPath Pkg ('Dir Lib)]
-> g BuildInfo [SymbolicPath Pkg ('Dir Lib)]
forall b a s.
(c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
forall (c :: * -> Constraint) (g :: * -> * -> *) b a s.
(FieldGrammar c g, c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
monoidalFieldAla FieldName
"extra-lib-dirs" (FSep
-> (SymbolicPath Pkg ('Dir Lib) -> SymbolicPathNT Pkg ('Dir Lib))
-> [SymbolicPath Pkg ('Dir Lib)]
-> List
FSep (SymbolicPathNT Pkg ('Dir Lib)) (SymbolicPath Pkg ('Dir Lib))
forall sep a b. sep -> (a -> b) -> [a] -> List sep b a
alaList' FSep
FSep SymbolicPath Pkg ('Dir Lib) -> SymbolicPathNT Pkg ('Dir Lib)
forall from (to :: FileOrDir).
SymbolicPath from to -> SymbolicPathNT from to
SymbolicPathNT) ALens' BuildInfo [SymbolicPath Pkg ('Dir Lib)]
forall a. HasBuildInfo a => Lens' a [SymbolicPath Pkg ('Dir Lib)]
Lens' BuildInfo [SymbolicPath Pkg ('Dir Lib)]
L.extraLibDirs
g BuildInfo
([SymbolicPath Pkg ('Dir Lib)]
-> [SymbolicPath Pkg ('Dir Include)]
-> [SymbolicPath Include 'File]
-> [RelativePath Include 'File]
-> [RelativePath Include 'File]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> [(String, String)]
-> [Dependency]
-> [Mixin]
-> BuildInfo)
-> g BuildInfo [SymbolicPath Pkg ('Dir Lib)]
-> g BuildInfo
([SymbolicPath Pkg ('Dir Include)]
-> [SymbolicPath Include 'File]
-> [RelativePath Include 'File]
-> [RelativePath Include 'File]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> [(String, String)]
-> [Dependency]
-> [Mixin]
-> BuildInfo)
forall a b. g BuildInfo (a -> b) -> g BuildInfo a -> g BuildInfo b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> FieldName
-> ([SymbolicPath Pkg ('Dir Lib)]
-> List
FSep (SymbolicPathNT Pkg ('Dir Lib)) (SymbolicPath Pkg ('Dir Lib)))
-> ALens' BuildInfo [SymbolicPath Pkg ('Dir Lib)]
-> g BuildInfo [SymbolicPath Pkg ('Dir Lib)]
forall b a s.
(c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
forall (c :: * -> Constraint) (g :: * -> * -> *) b a s.
(FieldGrammar c g, c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
monoidalFieldAla FieldName
"extra-lib-dirs-static" (FSep
-> (SymbolicPath Pkg ('Dir Lib) -> SymbolicPathNT Pkg ('Dir Lib))
-> [SymbolicPath Pkg ('Dir Lib)]
-> List
FSep (SymbolicPathNT Pkg ('Dir Lib)) (SymbolicPath Pkg ('Dir Lib))
forall sep a b. sep -> (a -> b) -> [a] -> List sep b a
alaList' FSep
FSep SymbolicPath Pkg ('Dir Lib) -> SymbolicPathNT Pkg ('Dir Lib)
forall from (to :: FileOrDir).
SymbolicPath from to -> SymbolicPathNT from to
SymbolicPathNT) ALens' BuildInfo [SymbolicPath Pkg ('Dir Lib)]
forall a. HasBuildInfo a => Lens' a [SymbolicPath Pkg ('Dir Lib)]
Lens' BuildInfo [SymbolicPath Pkg ('Dir Lib)]
L.extraLibDirsStatic
g BuildInfo [SymbolicPath Pkg ('Dir Lib)]
-> (g BuildInfo [SymbolicPath Pkg ('Dir Lib)]
-> g BuildInfo [SymbolicPath Pkg ('Dir Lib)])
-> g BuildInfo [SymbolicPath Pkg ('Dir Lib)]
forall a b. a -> (a -> b) -> b
^^^ CabalSpecVersion
-> [SymbolicPath Pkg ('Dir Lib)]
-> g BuildInfo [SymbolicPath Pkg ('Dir Lib)]
-> g BuildInfo [SymbolicPath Pkg ('Dir Lib)]
forall a s. CabalSpecVersion -> a -> g s a -> g s a
forall (c :: * -> Constraint) (g :: * -> * -> *) a s.
FieldGrammar c g =>
CabalSpecVersion -> a -> g s a -> g s a
availableSince CabalSpecVersion
CabalSpecV3_8 []
g BuildInfo
([SymbolicPath Pkg ('Dir Include)]
-> [SymbolicPath Include 'File]
-> [RelativePath Include 'File]
-> [RelativePath Include 'File]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> [(String, String)]
-> [Dependency]
-> [Mixin]
-> BuildInfo)
-> g BuildInfo [SymbolicPath Pkg ('Dir Include)]
-> g BuildInfo
([SymbolicPath Include 'File]
-> [RelativePath Include 'File]
-> [RelativePath Include 'File]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> [(String, String)]
-> [Dependency]
-> [Mixin]
-> BuildInfo)
forall a b. g BuildInfo (a -> b) -> g BuildInfo a -> g BuildInfo b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> FieldName
-> ([SymbolicPath Pkg ('Dir Include)]
-> List
FSep
(SymbolicPathNT Pkg ('Dir Include))
(SymbolicPath Pkg ('Dir Include)))
-> ALens' BuildInfo [SymbolicPath Pkg ('Dir Include)]
-> g BuildInfo [SymbolicPath Pkg ('Dir Include)]
forall b a s.
(c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
forall (c :: * -> Constraint) (g :: * -> * -> *) b a s.
(FieldGrammar c g, c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
monoidalFieldAla FieldName
"include-dirs" (FSep
-> (SymbolicPath Pkg ('Dir Include)
-> SymbolicPathNT Pkg ('Dir Include))
-> [SymbolicPath Pkg ('Dir Include)]
-> List
FSep
(SymbolicPathNT Pkg ('Dir Include))
(SymbolicPath Pkg ('Dir Include))
forall sep a b. sep -> (a -> b) -> [a] -> List sep b a
alaList' FSep
FSep SymbolicPath Pkg ('Dir Include)
-> SymbolicPathNT Pkg ('Dir Include)
forall from (to :: FileOrDir).
SymbolicPath from to -> SymbolicPathNT from to
SymbolicPathNT) ALens' BuildInfo [SymbolicPath Pkg ('Dir Include)]
forall a.
HasBuildInfo a =>
Lens' a [SymbolicPath Pkg ('Dir Include)]
Lens' BuildInfo [SymbolicPath Pkg ('Dir Include)]
L.includeDirs
g BuildInfo
([SymbolicPath Include 'File]
-> [RelativePath Include 'File]
-> [RelativePath Include 'File]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> [(String, String)]
-> [Dependency]
-> [Mixin]
-> BuildInfo)
-> g BuildInfo [SymbolicPath Include 'File]
-> g BuildInfo
([RelativePath Include 'File]
-> [RelativePath Include 'File]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> [(String, String)]
-> [Dependency]
-> [Mixin]
-> BuildInfo)
forall a b. g BuildInfo (a -> b) -> g BuildInfo a -> g BuildInfo b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> FieldName
-> ([SymbolicPath Include 'File]
-> List
FSep (SymbolicPathNT Include 'File) (SymbolicPath Include 'File))
-> ALens' BuildInfo [SymbolicPath Include 'File]
-> g BuildInfo [SymbolicPath Include 'File]
forall b a s.
(c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
forall (c :: * -> Constraint) (g :: * -> * -> *) b a s.
(FieldGrammar c g, c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
monoidalFieldAla FieldName
"includes" (FSep
-> (SymbolicPath Include 'File -> SymbolicPathNT Include 'File)
-> [SymbolicPath Include 'File]
-> List
FSep (SymbolicPathNT Include 'File) (SymbolicPath Include 'File)
forall sep a b. sep -> (a -> b) -> [a] -> List sep b a
alaList' FSep
FSep SymbolicPath Include 'File -> SymbolicPathNT Include 'File
forall from (to :: FileOrDir).
SymbolicPath from to -> SymbolicPathNT from to
SymbolicPathNT) ALens' BuildInfo [SymbolicPath Include 'File]
forall a. HasBuildInfo a => Lens' a [SymbolicPath Include 'File]
Lens' BuildInfo [SymbolicPath Include 'File]
L.includes
g BuildInfo
([RelativePath Include 'File]
-> [RelativePath Include 'File]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> [(String, String)]
-> [Dependency]
-> [Mixin]
-> BuildInfo)
-> g BuildInfo [RelativePath Include 'File]
-> g BuildInfo
([RelativePath Include 'File]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> [(String, String)]
-> [Dependency]
-> [Mixin]
-> BuildInfo)
forall a b. g BuildInfo (a -> b) -> g BuildInfo a -> g BuildInfo b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> FieldName
-> ([RelativePath Include 'File]
-> List
FSep (RelativePathNT Include 'File) (RelativePath Include 'File))
-> ALens' BuildInfo [RelativePath Include 'File]
-> g BuildInfo [RelativePath Include 'File]
forall b a s.
(c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
forall (c :: * -> Constraint) (g :: * -> * -> *) b a s.
(FieldGrammar c g, c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
monoidalFieldAla FieldName
"autogen-includes" (FSep
-> (RelativePath Include 'File -> RelativePathNT Include 'File)
-> [RelativePath Include 'File]
-> List
FSep (RelativePathNT Include 'File) (RelativePath Include 'File)
forall sep a b. sep -> (a -> b) -> [a] -> List sep b a
alaList' FSep
FSep RelativePath Include 'File -> RelativePathNT Include 'File
forall from (to :: FileOrDir).
RelativePath from to -> RelativePathNT from to
RelativePathNT) ALens' BuildInfo [RelativePath Include 'File]
forall a. HasBuildInfo a => Lens' a [RelativePath Include 'File]
Lens' BuildInfo [RelativePath Include 'File]
L.autogenIncludes
g BuildInfo [RelativePath Include 'File]
-> (g BuildInfo [RelativePath Include 'File]
-> g BuildInfo [RelativePath Include 'File])
-> g BuildInfo [RelativePath Include 'File]
forall a b. a -> (a -> b) -> b
^^^ CabalSpecVersion
-> [RelativePath Include 'File]
-> g BuildInfo [RelativePath Include 'File]
-> g BuildInfo [RelativePath Include 'File]
forall a s. CabalSpecVersion -> a -> g s a -> g s a
forall (c :: * -> Constraint) (g :: * -> * -> *) a s.
FieldGrammar c g =>
CabalSpecVersion -> a -> g s a -> g s a
availableSince CabalSpecVersion
CabalSpecV3_0 []
g BuildInfo
([RelativePath Include 'File]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> [(String, String)]
-> [Dependency]
-> [Mixin]
-> BuildInfo)
-> g BuildInfo [RelativePath Include 'File]
-> g BuildInfo
(PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> [(String, String)]
-> [Dependency]
-> [Mixin]
-> BuildInfo)
forall a b. g BuildInfo (a -> b) -> g BuildInfo a -> g BuildInfo b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> FieldName
-> ([RelativePath Include 'File]
-> List
FSep (RelativePathNT Include 'File) (RelativePath Include 'File))
-> ALens' BuildInfo [RelativePath Include 'File]
-> g BuildInfo [RelativePath Include 'File]
forall b a s.
(c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
forall (c :: * -> Constraint) (g :: * -> * -> *) b a s.
(FieldGrammar c g, c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
monoidalFieldAla FieldName
"install-includes" (FSep
-> (RelativePath Include 'File -> RelativePathNT Include 'File)
-> [RelativePath Include 'File]
-> List
FSep (RelativePathNT Include 'File) (RelativePath Include 'File)
forall sep a b. sep -> (a -> b) -> [a] -> List sep b a
alaList' FSep
FSep RelativePath Include 'File -> RelativePathNT Include 'File
forall from (to :: FileOrDir).
RelativePath from to -> RelativePathNT from to
RelativePathNT) ALens' BuildInfo [RelativePath Include 'File]
forall a. HasBuildInfo a => Lens' a [RelativePath Include 'File]
Lens' BuildInfo [RelativePath Include 'File]
L.installIncludes
g BuildInfo
(PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> [(String, String)]
-> [Dependency]
-> [Mixin]
-> BuildInfo)
-> g BuildInfo (PerCompilerFlavor [String])
-> g BuildInfo
(PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> [(String, String)]
-> [Dependency]
-> [Mixin]
-> BuildInfo)
forall a b. g BuildInfo (a -> b) -> g BuildInfo a -> g BuildInfo b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> g BuildInfo (PerCompilerFlavor [String])
forall (c :: * -> Constraint) (g :: * -> * -> *).
(FieldGrammar c g, Applicative (g BuildInfo),
c (List NoCommaFSep Token' String)) =>
g BuildInfo (PerCompilerFlavor [String])
optionsFieldGrammar
g BuildInfo
(PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> [(String, String)]
-> [Dependency]
-> [Mixin]
-> BuildInfo)
-> g BuildInfo (PerCompilerFlavor [String])
-> g BuildInfo
(PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> [(String, String)]
-> [Dependency]
-> [Mixin]
-> BuildInfo)
forall a b. g BuildInfo (a -> b) -> g BuildInfo a -> g BuildInfo b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> g BuildInfo (PerCompilerFlavor [String])
forall (c :: * -> Constraint) (g :: * -> * -> *).
(FieldGrammar c g, Applicative (g BuildInfo),
c (List NoCommaFSep Token' String)) =>
g BuildInfo (PerCompilerFlavor [String])
profOptionsFieldGrammar
g BuildInfo
(PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> [(String, String)]
-> [Dependency]
-> [Mixin]
-> BuildInfo)
-> g BuildInfo (PerCompilerFlavor [String])
-> g BuildInfo
(PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> [(String, String)]
-> [Dependency]
-> [Mixin]
-> BuildInfo)
forall a b. g BuildInfo (a -> b) -> g BuildInfo a -> g BuildInfo b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> g BuildInfo (PerCompilerFlavor [String])
forall (c :: * -> Constraint) (g :: * -> * -> *).
(FieldGrammar c g, Applicative (g BuildInfo),
c (List NoCommaFSep Token' String)) =>
g BuildInfo (PerCompilerFlavor [String])
sharedOptionsFieldGrammar
g BuildInfo
(PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> [(String, String)]
-> [Dependency]
-> [Mixin]
-> BuildInfo)
-> g BuildInfo (PerCompilerFlavor [String])
-> g BuildInfo
(PerCompilerFlavor [String]
-> [(String, String)] -> [Dependency] -> [Mixin] -> BuildInfo)
forall a b. g BuildInfo (a -> b) -> g BuildInfo a -> g BuildInfo b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> g BuildInfo (PerCompilerFlavor [String])
forall (c :: * -> Constraint) (g :: * -> * -> *).
(FieldGrammar c g, Applicative (g BuildInfo),
c (List NoCommaFSep Token' String)) =>
g BuildInfo (PerCompilerFlavor [String])
profSharedOptionsFieldGrammar
g BuildInfo
(PerCompilerFlavor [String]
-> [(String, String)] -> [Dependency] -> [Mixin] -> BuildInfo)
-> g BuildInfo (PerCompilerFlavor [String])
-> g BuildInfo
([(String, String)] -> [Dependency] -> [Mixin] -> BuildInfo)
forall a b. g BuildInfo (a -> b) -> g BuildInfo a -> g BuildInfo b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> PerCompilerFlavor [String]
-> g BuildInfo (PerCompilerFlavor [String])
forall a. a -> g BuildInfo a
forall (f :: * -> *) a. Applicative f => a -> f a
pure PerCompilerFlavor [String]
forall a. Monoid a => a
mempty
g BuildInfo
([(String, String)] -> [Dependency] -> [Mixin] -> BuildInfo)
-> g BuildInfo [(String, String)]
-> g BuildInfo ([Dependency] -> [Mixin] -> BuildInfo)
forall a b. g BuildInfo (a -> b) -> g BuildInfo a -> g BuildInfo b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> FieldName
-> ALens' BuildInfo [(String, String)]
-> g BuildInfo [(String, String)]
forall s.
FieldName -> ALens' s [(String, String)] -> g s [(String, String)]
forall (c :: * -> Constraint) (g :: * -> * -> *) s.
FieldGrammar c g =>
FieldName -> ALens' s [(String, String)] -> g s [(String, String)]
prefixedFields FieldName
"x-" ALens' BuildInfo [(String, String)]
forall a. HasBuildInfo a => Lens' a [(String, String)]
Lens' BuildInfo [(String, String)]
L.customFieldsBI
g BuildInfo ([Dependency] -> [Mixin] -> BuildInfo)
-> g BuildInfo [Dependency] -> g BuildInfo ([Mixin] -> BuildInfo)
forall a b. g BuildInfo (a -> b) -> g BuildInfo a -> g BuildInfo b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> FieldName
-> ([Dependency]
-> List CommaVCat (Identity Dependency) Dependency)
-> ALens' BuildInfo [Dependency]
-> g BuildInfo [Dependency]
forall b a s.
(c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
forall (c :: * -> Constraint) (g :: * -> * -> *) b a s.
(FieldGrammar c g, c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
monoidalFieldAla FieldName
"build-depends" [Dependency] -> List CommaVCat (Identity Dependency) Dependency
formatDependencyList ALens' BuildInfo [Dependency]
forall a. HasBuildInfo a => Lens' a [Dependency]
Lens' BuildInfo [Dependency]
L.targetBuildDepends
g BuildInfo ([Mixin] -> BuildInfo)
-> g BuildInfo [Mixin] -> g BuildInfo BuildInfo
forall a b. g BuildInfo (a -> b) -> g BuildInfo a -> g BuildInfo b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> FieldName
-> ([Mixin] -> List CommaVCat (Identity Mixin) Mixin)
-> ALens' BuildInfo [Mixin]
-> g BuildInfo [Mixin]
forall b a s.
(c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
forall (c :: * -> Constraint) (g :: * -> * -> *) b a s.
(FieldGrammar c g, c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
monoidalFieldAla FieldName
"mixins" [Mixin] -> List CommaVCat (Identity Mixin) Mixin
formatMixinList ALens' BuildInfo [Mixin]
forall a. HasBuildInfo a => Lens' a [Mixin]
Lens' BuildInfo [Mixin]
L.mixins
g BuildInfo [Mixin]
-> (g BuildInfo [Mixin] -> g BuildInfo [Mixin])
-> g BuildInfo [Mixin]
forall a b. a -> (a -> b) -> b
^^^ CabalSpecVersion
-> [Mixin] -> g BuildInfo [Mixin] -> g BuildInfo [Mixin]
forall a s. CabalSpecVersion -> a -> g s a -> g s a
forall (c :: * -> Constraint) (g :: * -> * -> *) a s.
FieldGrammar c g =>
CabalSpecVersion -> a -> g s a -> g s a
availableSince CabalSpecVersion
CabalSpecV2_0 []
{-# SPECIALIZE buildInfoFieldGrammar :: ParsecFieldGrammar' BuildInfo #-}
{-# SPECIALIZE buildInfoFieldGrammar :: PrettyFieldGrammar' BuildInfo #-}
hsSourceDirsGrammar
:: ( FieldGrammar c g
, Applicative (g BuildInfo)
, forall from to. c (List FSep (SymbolicPathNT from to) (SymbolicPath from to))
)
=> g BuildInfo [SymbolicPath Pkg (Dir Source)]
hsSourceDirsGrammar :: forall (c :: * -> Constraint) (g :: * -> * -> *).
(FieldGrammar c g, Applicative (g BuildInfo),
forall from (to :: FileOrDir).
c (List FSep (SymbolicPathNT from to) (SymbolicPath from to))) =>
g BuildInfo [SymbolicPath Pkg ('Dir Source)]
hsSourceDirsGrammar =
[SymbolicPath Pkg ('Dir Source)]
-> [SymbolicPath Pkg ('Dir Source)]
-> [SymbolicPath Pkg ('Dir Source)]
forall a. [a] -> [a] -> [a]
(++)
([SymbolicPath Pkg ('Dir Source)]
-> [SymbolicPath Pkg ('Dir Source)]
-> [SymbolicPath Pkg ('Dir Source)])
-> g BuildInfo [SymbolicPath Pkg ('Dir Source)]
-> g BuildInfo
([SymbolicPath Pkg ('Dir Source)]
-> [SymbolicPath Pkg ('Dir Source)])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> FieldName
-> ([SymbolicPath Pkg ('Dir Source)]
-> List
FSep
(SymbolicPathNT Pkg ('Dir Source))
(SymbolicPath Pkg ('Dir Source)))
-> ALens' BuildInfo [SymbolicPath Pkg ('Dir Source)]
-> g BuildInfo [SymbolicPath Pkg ('Dir Source)]
forall b a s.
(c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
forall (c :: * -> Constraint) (g :: * -> * -> *) b a s.
(FieldGrammar c g, c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
monoidalFieldAla FieldName
"hs-source-dirs" [SymbolicPath Pkg ('Dir Source)]
-> List
FSep
(SymbolicPathNT Pkg ('Dir Source))
(SymbolicPath Pkg ('Dir Source))
formatHsSourceDirs ALens' BuildInfo [SymbolicPath Pkg ('Dir Source)]
forall a.
HasBuildInfo a =>
Lens' a [SymbolicPath Pkg ('Dir Source)]
Lens' BuildInfo [SymbolicPath Pkg ('Dir Source)]
L.hsSourceDirs
g BuildInfo
([SymbolicPath Pkg ('Dir Source)]
-> [SymbolicPath Pkg ('Dir Source)])
-> g BuildInfo [SymbolicPath Pkg ('Dir Source)]
-> g BuildInfo [SymbolicPath Pkg ('Dir Source)]
forall a b. g BuildInfo (a -> b) -> g BuildInfo a -> g BuildInfo b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> FieldName
-> ([SymbolicPath Pkg ('Dir Source)]
-> List
FSep
(SymbolicPathNT Pkg ('Dir Source))
(SymbolicPath Pkg ('Dir Source)))
-> ALens' BuildInfo [SymbolicPath Pkg ('Dir Source)]
-> g BuildInfo [SymbolicPath Pkg ('Dir Source)]
forall b a s.
(c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
forall (c :: * -> Constraint) (g :: * -> * -> *) b a s.
(FieldGrammar c g, c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
monoidalFieldAla FieldName
"hs-source-dir" (FSep
-> (SymbolicPath Pkg ('Dir Source)
-> SymbolicPathNT Pkg ('Dir Source))
-> [SymbolicPath Pkg ('Dir Source)]
-> List
FSep
(SymbolicPathNT Pkg ('Dir Source))
(SymbolicPath Pkg ('Dir Source))
forall sep a b. sep -> (a -> b) -> [a] -> List sep b a
alaList' FSep
FSep SymbolicPath Pkg ('Dir Source) -> SymbolicPathNT Pkg ('Dir Source)
forall from (to :: FileOrDir).
SymbolicPath from to -> SymbolicPathNT from to
SymbolicPathNT) ALens' BuildInfo [SymbolicPath Pkg ('Dir Source)]
Lens' BuildInfo [SymbolicPath Pkg ('Dir Source)]
wrongLens
g BuildInfo [SymbolicPath Pkg ('Dir Source)]
-> (g BuildInfo [SymbolicPath Pkg ('Dir Source)]
-> g BuildInfo [SymbolicPath Pkg ('Dir Source)])
-> g BuildInfo [SymbolicPath Pkg ('Dir Source)]
forall a b. a -> (a -> b) -> b
^^^ CabalSpecVersion
-> String
-> g BuildInfo [SymbolicPath Pkg ('Dir Source)]
-> g BuildInfo [SymbolicPath Pkg ('Dir Source)]
forall s a. CabalSpecVersion -> String -> g s a -> g s a
forall (c :: * -> Constraint) (g :: * -> * -> *) s a.
FieldGrammar c g =>
CabalSpecVersion -> String -> g s a -> g s a
deprecatedSince CabalSpecVersion
CabalSpecV1_2 String
"Please use 'hs-source-dirs'"
g BuildInfo [SymbolicPath Pkg ('Dir Source)]
-> (g BuildInfo [SymbolicPath Pkg ('Dir Source)]
-> g BuildInfo [SymbolicPath Pkg ('Dir Source)])
-> g BuildInfo [SymbolicPath Pkg ('Dir Source)]
forall a b. a -> (a -> b) -> b
^^^ CabalSpecVersion
-> String
-> g BuildInfo [SymbolicPath Pkg ('Dir Source)]
-> g BuildInfo [SymbolicPath Pkg ('Dir Source)]
forall s a. CabalSpecVersion -> String -> g s a -> g s a
forall (c :: * -> Constraint) (g :: * -> * -> *) s a.
FieldGrammar c g =>
CabalSpecVersion -> String -> g s a -> g s a
removedIn CabalSpecVersion
CabalSpecV3_0 String
"Please use 'hs-source-dirs' field."
where
wrongLens :: Functor f => LensLike' f BuildInfo [SymbolicPath Pkg (Dir Source)]
wrongLens :: Lens' BuildInfo [SymbolicPath Pkg ('Dir Source)]
wrongLens [SymbolicPath Pkg ('Dir Source)]
-> f [SymbolicPath Pkg ('Dir Source)]
f BuildInfo
bi = (\[SymbolicPath Pkg ('Dir Source)]
fps -> ASetter
BuildInfo
BuildInfo
[SymbolicPath Pkg ('Dir Source)]
[SymbolicPath Pkg ('Dir Source)]
-> [SymbolicPath Pkg ('Dir Source)] -> BuildInfo -> BuildInfo
forall s t a b. ASetter s t a b -> b -> s -> t
set ASetter
BuildInfo
BuildInfo
[SymbolicPath Pkg ('Dir Source)]
[SymbolicPath Pkg ('Dir Source)]
forall a.
HasBuildInfo a =>
Lens' a [SymbolicPath Pkg ('Dir Source)]
Lens' BuildInfo [SymbolicPath Pkg ('Dir Source)]
L.hsSourceDirs [SymbolicPath Pkg ('Dir Source)]
fps BuildInfo
bi) ([SymbolicPath Pkg ('Dir Source)] -> BuildInfo)
-> f [SymbolicPath Pkg ('Dir Source)] -> f BuildInfo
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [SymbolicPath Pkg ('Dir Source)]
-> f [SymbolicPath Pkg ('Dir Source)]
f []
optionsFieldGrammar
:: (FieldGrammar c g, Applicative (g BuildInfo), c (List NoCommaFSep Token' String))
=> g BuildInfo (PerCompilerFlavor [String])
optionsFieldGrammar :: forall (c :: * -> Constraint) (g :: * -> * -> *).
(FieldGrammar c g, Applicative (g BuildInfo),
c (List NoCommaFSep Token' String)) =>
g BuildInfo (PerCompilerFlavor [String])
optionsFieldGrammar =
[String] -> [String] -> PerCompilerFlavor [String]
forall v. v -> v -> PerCompilerFlavor v
PerCompilerFlavor
([String] -> [String] -> PerCompilerFlavor [String])
-> g BuildInfo [String]
-> g BuildInfo ([String] -> PerCompilerFlavor [String])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> FieldName
-> ([String] -> List NoCommaFSep Token' String)
-> ALens' BuildInfo [String]
-> g BuildInfo [String]
forall b a s.
(c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
forall (c :: * -> Constraint) (g :: * -> * -> *) b a s.
(FieldGrammar c g, c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
monoidalFieldAla FieldName
"ghc-options" (NoCommaFSep
-> (String -> Token') -> [String] -> List NoCommaFSep Token' String
forall sep a b. sep -> (a -> b) -> [a] -> List sep b a
alaList' NoCommaFSep
NoCommaFSep String -> Token'
Token') (CompilerFlavor -> ALens' BuildInfo [String]
extract CompilerFlavor
GHC)
g BuildInfo ([String] -> PerCompilerFlavor [String])
-> g BuildInfo [String] -> g BuildInfo (PerCompilerFlavor [String])
forall a b. g BuildInfo (a -> b) -> g BuildInfo a -> g BuildInfo b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> FieldName
-> ([String] -> List NoCommaFSep Token' String)
-> ALens' BuildInfo [String]
-> g BuildInfo [String]
forall b a s.
(c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
forall (c :: * -> Constraint) (g :: * -> * -> *) b a s.
(FieldGrammar c g, c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
monoidalFieldAla FieldName
"ghcjs-options" (NoCommaFSep
-> (String -> Token') -> [String] -> List NoCommaFSep Token' String
forall sep a b. sep -> (a -> b) -> [a] -> List sep b a
alaList' NoCommaFSep
NoCommaFSep String -> Token'
Token') (CompilerFlavor -> ALens' BuildInfo [String]
extract CompilerFlavor
GHCJS)
g BuildInfo (PerCompilerFlavor [String])
-> g BuildInfo () -> g BuildInfo (PerCompilerFlavor [String])
forall a b. g BuildInfo a -> g BuildInfo b -> g BuildInfo a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* FieldName -> g BuildInfo ()
forall s. FieldName -> g s ()
forall (c :: * -> Constraint) (g :: * -> * -> *) s.
FieldGrammar c g =>
FieldName -> g s ()
knownField FieldName
"jhc-options"
g BuildInfo (PerCompilerFlavor [String])
-> g BuildInfo () -> g BuildInfo (PerCompilerFlavor [String])
forall a b. g BuildInfo a -> g BuildInfo b -> g BuildInfo a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* FieldName -> g BuildInfo ()
forall s. FieldName -> g s ()
forall (c :: * -> Constraint) (g :: * -> * -> *) s.
FieldGrammar c g =>
FieldName -> g s ()
knownField FieldName
"hugs-options"
g BuildInfo (PerCompilerFlavor [String])
-> g BuildInfo () -> g BuildInfo (PerCompilerFlavor [String])
forall a b. g BuildInfo a -> g BuildInfo b -> g BuildInfo a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* FieldName -> g BuildInfo ()
forall s. FieldName -> g s ()
forall (c :: * -> Constraint) (g :: * -> * -> *) s.
FieldGrammar c g =>
FieldName -> g s ()
knownField FieldName
"nhc98-options"
where
extract :: CompilerFlavor -> ALens' BuildInfo [String]
extract :: CompilerFlavor -> ALens' BuildInfo [String]
extract CompilerFlavor
flavor = LensLike
(Pretext [String] [String])
BuildInfo
BuildInfo
(PerCompilerFlavor [String])
(PerCompilerFlavor [String])
forall a. HasBuildInfo a => Lens' a (PerCompilerFlavor [String])
Lens' BuildInfo (PerCompilerFlavor [String])
L.options LensLike
(Pretext [String] [String])
BuildInfo
BuildInfo
(PerCompilerFlavor [String])
(PerCompilerFlavor [String])
-> (([String] -> Pretext [String] [String] [String])
-> PerCompilerFlavor [String]
-> Pretext [String] [String] (PerCompilerFlavor [String]))
-> ALens' BuildInfo [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CompilerFlavor
-> ([String] -> Pretext [String] [String] [String])
-> PerCompilerFlavor [String]
-> Pretext [String] [String] (PerCompilerFlavor [String])
forall (f :: * -> *) v.
(Functor f, Monoid v) =>
CompilerFlavor -> LensLike' f (PerCompilerFlavor v) v
lookupLens CompilerFlavor
flavor
profOptionsFieldGrammar
:: (FieldGrammar c g, Applicative (g BuildInfo), c (List NoCommaFSep Token' String))
=> g BuildInfo (PerCompilerFlavor [String])
profOptionsFieldGrammar :: forall (c :: * -> Constraint) (g :: * -> * -> *).
(FieldGrammar c g, Applicative (g BuildInfo),
c (List NoCommaFSep Token' String)) =>
g BuildInfo (PerCompilerFlavor [String])
profOptionsFieldGrammar =
[String] -> [String] -> PerCompilerFlavor [String]
forall v. v -> v -> PerCompilerFlavor v
PerCompilerFlavor
([String] -> [String] -> PerCompilerFlavor [String])
-> g BuildInfo [String]
-> g BuildInfo ([String] -> PerCompilerFlavor [String])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> FieldName
-> ([String] -> List NoCommaFSep Token' String)
-> ALens' BuildInfo [String]
-> g BuildInfo [String]
forall b a s.
(c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
forall (c :: * -> Constraint) (g :: * -> * -> *) b a s.
(FieldGrammar c g, c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
monoidalFieldAla FieldName
"ghc-prof-options" (NoCommaFSep
-> (String -> Token') -> [String] -> List NoCommaFSep Token' String
forall sep a b. sep -> (a -> b) -> [a] -> List sep b a
alaList' NoCommaFSep
NoCommaFSep String -> Token'
Token') (CompilerFlavor -> ALens' BuildInfo [String]
extract CompilerFlavor
GHC)
g BuildInfo ([String] -> PerCompilerFlavor [String])
-> g BuildInfo [String] -> g BuildInfo (PerCompilerFlavor [String])
forall a b. g BuildInfo (a -> b) -> g BuildInfo a -> g BuildInfo b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> FieldName
-> ([String] -> List NoCommaFSep Token' String)
-> ALens' BuildInfo [String]
-> g BuildInfo [String]
forall b a s.
(c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
forall (c :: * -> Constraint) (g :: * -> * -> *) b a s.
(FieldGrammar c g, c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
monoidalFieldAla FieldName
"ghcjs-prof-options" (NoCommaFSep
-> (String -> Token') -> [String] -> List NoCommaFSep Token' String
forall sep a b. sep -> (a -> b) -> [a] -> List sep b a
alaList' NoCommaFSep
NoCommaFSep String -> Token'
Token') (CompilerFlavor -> ALens' BuildInfo [String]
extract CompilerFlavor
GHCJS)
where
extract :: CompilerFlavor -> ALens' BuildInfo [String]
extract :: CompilerFlavor -> ALens' BuildInfo [String]
extract CompilerFlavor
flavor = LensLike
(Pretext [String] [String])
BuildInfo
BuildInfo
(PerCompilerFlavor [String])
(PerCompilerFlavor [String])
forall a. HasBuildInfo a => Lens' a (PerCompilerFlavor [String])
Lens' BuildInfo (PerCompilerFlavor [String])
L.profOptions LensLike
(Pretext [String] [String])
BuildInfo
BuildInfo
(PerCompilerFlavor [String])
(PerCompilerFlavor [String])
-> (([String] -> Pretext [String] [String] [String])
-> PerCompilerFlavor [String]
-> Pretext [String] [String] (PerCompilerFlavor [String]))
-> ALens' BuildInfo [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CompilerFlavor
-> ([String] -> Pretext [String] [String] [String])
-> PerCompilerFlavor [String]
-> Pretext [String] [String] (PerCompilerFlavor [String])
forall (f :: * -> *) v.
(Functor f, Monoid v) =>
CompilerFlavor -> LensLike' f (PerCompilerFlavor v) v
lookupLens CompilerFlavor
flavor
sharedOptionsFieldGrammar
:: (FieldGrammar c g, Applicative (g BuildInfo), c (List NoCommaFSep Token' String))
=> g BuildInfo (PerCompilerFlavor [String])
sharedOptionsFieldGrammar :: forall (c :: * -> Constraint) (g :: * -> * -> *).
(FieldGrammar c g, Applicative (g BuildInfo),
c (List NoCommaFSep Token' String)) =>
g BuildInfo (PerCompilerFlavor [String])
sharedOptionsFieldGrammar =
[String] -> [String] -> PerCompilerFlavor [String]
forall v. v -> v -> PerCompilerFlavor v
PerCompilerFlavor
([String] -> [String] -> PerCompilerFlavor [String])
-> g BuildInfo [String]
-> g BuildInfo ([String] -> PerCompilerFlavor [String])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> FieldName
-> ([String] -> List NoCommaFSep Token' String)
-> ALens' BuildInfo [String]
-> g BuildInfo [String]
forall b a s.
(c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
forall (c :: * -> Constraint) (g :: * -> * -> *) b a s.
(FieldGrammar c g, c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
monoidalFieldAla FieldName
"ghc-shared-options" (NoCommaFSep
-> (String -> Token') -> [String] -> List NoCommaFSep Token' String
forall sep a b. sep -> (a -> b) -> [a] -> List sep b a
alaList' NoCommaFSep
NoCommaFSep String -> Token'
Token') (CompilerFlavor -> ALens' BuildInfo [String]
extract CompilerFlavor
GHC)
g BuildInfo ([String] -> PerCompilerFlavor [String])
-> g BuildInfo [String] -> g BuildInfo (PerCompilerFlavor [String])
forall a b. g BuildInfo (a -> b) -> g BuildInfo a -> g BuildInfo b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> FieldName
-> ([String] -> List NoCommaFSep Token' String)
-> ALens' BuildInfo [String]
-> g BuildInfo [String]
forall b a s.
(c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
forall (c :: * -> Constraint) (g :: * -> * -> *) b a s.
(FieldGrammar c g, c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
monoidalFieldAla FieldName
"ghcjs-shared-options" (NoCommaFSep
-> (String -> Token') -> [String] -> List NoCommaFSep Token' String
forall sep a b. sep -> (a -> b) -> [a] -> List sep b a
alaList' NoCommaFSep
NoCommaFSep String -> Token'
Token') (CompilerFlavor -> ALens' BuildInfo [String]
extract CompilerFlavor
GHCJS)
where
extract :: CompilerFlavor -> ALens' BuildInfo [String]
extract :: CompilerFlavor -> ALens' BuildInfo [String]
extract CompilerFlavor
flavor = LensLike
(Pretext [String] [String])
BuildInfo
BuildInfo
(PerCompilerFlavor [String])
(PerCompilerFlavor [String])
forall a. HasBuildInfo a => Lens' a (PerCompilerFlavor [String])
Lens' BuildInfo (PerCompilerFlavor [String])
L.sharedOptions LensLike
(Pretext [String] [String])
BuildInfo
BuildInfo
(PerCompilerFlavor [String])
(PerCompilerFlavor [String])
-> (([String] -> Pretext [String] [String] [String])
-> PerCompilerFlavor [String]
-> Pretext [String] [String] (PerCompilerFlavor [String]))
-> ALens' BuildInfo [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CompilerFlavor
-> ([String] -> Pretext [String] [String] [String])
-> PerCompilerFlavor [String]
-> Pretext [String] [String] (PerCompilerFlavor [String])
forall (f :: * -> *) v.
(Functor f, Monoid v) =>
CompilerFlavor -> LensLike' f (PerCompilerFlavor v) v
lookupLens CompilerFlavor
flavor
profSharedOptionsFieldGrammar
:: (FieldGrammar c g, Applicative (g BuildInfo), c (List NoCommaFSep Token' String))
=> g BuildInfo (PerCompilerFlavor [String])
profSharedOptionsFieldGrammar :: forall (c :: * -> Constraint) (g :: * -> * -> *).
(FieldGrammar c g, Applicative (g BuildInfo),
c (List NoCommaFSep Token' String)) =>
g BuildInfo (PerCompilerFlavor [String])
profSharedOptionsFieldGrammar =
[String] -> [String] -> PerCompilerFlavor [String]
forall v. v -> v -> PerCompilerFlavor v
PerCompilerFlavor
([String] -> [String] -> PerCompilerFlavor [String])
-> g BuildInfo [String]
-> g BuildInfo ([String] -> PerCompilerFlavor [String])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> FieldName
-> ([String] -> List NoCommaFSep Token' String)
-> ALens' BuildInfo [String]
-> g BuildInfo [String]
forall b a s.
(c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
forall (c :: * -> Constraint) (g :: * -> * -> *) b a s.
(FieldGrammar c g, c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
monoidalFieldAla FieldName
"ghc-prof-shared-options" (NoCommaFSep
-> (String -> Token') -> [String] -> List NoCommaFSep Token' String
forall sep a b. sep -> (a -> b) -> [a] -> List sep b a
alaList' NoCommaFSep
NoCommaFSep String -> Token'
Token') (CompilerFlavor -> ALens' BuildInfo [String]
extract CompilerFlavor
GHC)
g BuildInfo [String]
-> (g BuildInfo [String] -> g BuildInfo [String])
-> g BuildInfo [String]
forall a b. a -> (a -> b) -> b
^^^ CabalSpecVersion
-> [String] -> g BuildInfo [String] -> g BuildInfo [String]
forall a s. CabalSpecVersion -> a -> g s a -> g s a
forall (c :: * -> Constraint) (g :: * -> * -> *) a s.
FieldGrammar c g =>
CabalSpecVersion -> a -> g s a -> g s a
availableSince CabalSpecVersion
CabalSpecV3_14 []
g BuildInfo ([String] -> PerCompilerFlavor [String])
-> g BuildInfo [String] -> g BuildInfo (PerCompilerFlavor [String])
forall a b. g BuildInfo (a -> b) -> g BuildInfo a -> g BuildInfo b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> FieldName
-> ([String] -> List NoCommaFSep Token' String)
-> ALens' BuildInfo [String]
-> g BuildInfo [String]
forall b a s.
(c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
forall (c :: * -> Constraint) (g :: * -> * -> *) b a s.
(FieldGrammar c g, c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
monoidalFieldAla FieldName
"ghcjs-prof-shared-options" (NoCommaFSep
-> (String -> Token') -> [String] -> List NoCommaFSep Token' String
forall sep a b. sep -> (a -> b) -> [a] -> List sep b a
alaList' NoCommaFSep
NoCommaFSep String -> Token'
Token') (CompilerFlavor -> ALens' BuildInfo [String]
extract CompilerFlavor
GHCJS)
g BuildInfo [String]
-> (g BuildInfo [String] -> g BuildInfo [String])
-> g BuildInfo [String]
forall a b. a -> (a -> b) -> b
^^^ CabalSpecVersion
-> [String] -> g BuildInfo [String] -> g BuildInfo [String]
forall a s. CabalSpecVersion -> a -> g s a -> g s a
forall (c :: * -> Constraint) (g :: * -> * -> *) a s.
FieldGrammar c g =>
CabalSpecVersion -> a -> g s a -> g s a
availableSince CabalSpecVersion
CabalSpecV3_14 []
where
extract :: CompilerFlavor -> ALens' BuildInfo [String]
extract :: CompilerFlavor -> ALens' BuildInfo [String]
extract CompilerFlavor
flavor = LensLike
(Pretext [String] [String])
BuildInfo
BuildInfo
(PerCompilerFlavor [String])
(PerCompilerFlavor [String])
forall a. HasBuildInfo a => Lens' a (PerCompilerFlavor [String])
Lens' BuildInfo (PerCompilerFlavor [String])
L.profSharedOptions LensLike
(Pretext [String] [String])
BuildInfo
BuildInfo
(PerCompilerFlavor [String])
(PerCompilerFlavor [String])
-> (([String] -> Pretext [String] [String] [String])
-> PerCompilerFlavor [String]
-> Pretext [String] [String] (PerCompilerFlavor [String]))
-> ALens' BuildInfo [String]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CompilerFlavor
-> ([String] -> Pretext [String] [String] [String])
-> PerCompilerFlavor [String]
-> Pretext [String] [String] (PerCompilerFlavor [String])
forall (f :: * -> *) v.
(Functor f, Monoid v) =>
CompilerFlavor -> LensLike' f (PerCompilerFlavor v) v
lookupLens CompilerFlavor
flavor
lookupLens :: (Functor f, Monoid v) => CompilerFlavor -> LensLike' f (PerCompilerFlavor v) v
lookupLens :: forall (f :: * -> *) v.
(Functor f, Monoid v) =>
CompilerFlavor -> LensLike' f (PerCompilerFlavor v) v
lookupLens CompilerFlavor
k v -> f v
f p :: PerCompilerFlavor v
p@(PerCompilerFlavor v
ghc v
ghcjs)
| CompilerFlavor
k CompilerFlavor -> CompilerFlavor -> Bool
forall a. Eq a => a -> a -> Bool
== CompilerFlavor
GHC = (\v
n -> v -> v -> PerCompilerFlavor v
forall v. v -> v -> PerCompilerFlavor v
PerCompilerFlavor v
n v
ghcjs) (v -> PerCompilerFlavor v) -> f v -> f (PerCompilerFlavor v)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> v -> f v
f v
ghc
| CompilerFlavor
k CompilerFlavor -> CompilerFlavor -> Bool
forall a. Eq a => a -> a -> Bool
== CompilerFlavor
GHCJS = (\v
n -> v -> v -> PerCompilerFlavor v
forall v. v -> v -> PerCompilerFlavor v
PerCompilerFlavor v
ghc v
n) (v -> PerCompilerFlavor v) -> f v -> f (PerCompilerFlavor v)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> v -> f v
f v
ghcjs
| Bool
otherwise = PerCompilerFlavor v
p PerCompilerFlavor v -> f v -> f (PerCompilerFlavor v)
forall a b. a -> f b -> f a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ v -> f v
f v
forall a. Monoid a => a
mempty
flagFieldGrammar
:: (FieldGrammar c g, Applicative (g PackageFlag))
=> FlagName
-> g PackageFlag PackageFlag
flagFieldGrammar :: forall (c :: * -> Constraint) (g :: * -> * -> *).
(FieldGrammar c g, Applicative (g PackageFlag)) =>
FlagName -> g PackageFlag PackageFlag
flagFieldGrammar FlagName
name =
FlagName -> String -> Bool -> Bool -> PackageFlag
MkPackageFlag FlagName
name
(String -> Bool -> Bool -> PackageFlag)
-> g PackageFlag String
-> g PackageFlag (Bool -> Bool -> PackageFlag)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> FieldName -> ALens' PackageFlag String -> g PackageFlag String
forall s. FieldName -> ALens' s String -> g s String
forall (c :: * -> Constraint) (g :: * -> * -> *) s.
FieldGrammar c g =>
FieldName -> ALens' s String -> g s String
freeTextFieldDef FieldName
"description" ALens' PackageFlag String
Lens' PackageFlag String
L.flagDescription
g PackageFlag (Bool -> Bool -> PackageFlag)
-> g PackageFlag Bool -> g PackageFlag (Bool -> PackageFlag)
forall a b.
g PackageFlag (a -> b) -> g PackageFlag a -> g PackageFlag b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> FieldName -> ALens' PackageFlag Bool -> Bool -> g PackageFlag Bool
forall s. FieldName -> ALens' s Bool -> Bool -> g s Bool
forall (c :: * -> Constraint) (g :: * -> * -> *) s.
FieldGrammar c g =>
FieldName -> ALens' s Bool -> Bool -> g s Bool
booleanFieldDef FieldName
"default" ALens' PackageFlag Bool
Lens' PackageFlag Bool
L.flagDefault Bool
True
g PackageFlag (Bool -> PackageFlag)
-> g PackageFlag Bool -> g PackageFlag PackageFlag
forall a b.
g PackageFlag (a -> b) -> g PackageFlag a -> g PackageFlag b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> FieldName -> ALens' PackageFlag Bool -> Bool -> g PackageFlag Bool
forall s. FieldName -> ALens' s Bool -> Bool -> g s Bool
forall (c :: * -> Constraint) (g :: * -> * -> *) s.
FieldGrammar c g =>
FieldName -> ALens' s Bool -> Bool -> g s Bool
booleanFieldDef FieldName
"manual" ALens' PackageFlag Bool
Lens' PackageFlag Bool
L.flagManual Bool
False
{-# SPECIALIZE flagFieldGrammar :: FlagName -> ParsecFieldGrammar' PackageFlag #-}
{-# SPECIALIZE flagFieldGrammar :: FlagName -> PrettyFieldGrammar' PackageFlag #-}
sourceRepoFieldGrammar
:: (FieldGrammar c g, Applicative (g SourceRepo), c (Identity RepoType), c Token, c FilePathNT)
=> RepoKind
-> g SourceRepo SourceRepo
sourceRepoFieldGrammar :: forall (c :: * -> Constraint) (g :: * -> * -> *).
(FieldGrammar c g, Applicative (g SourceRepo),
c (Identity RepoType), c Token, c FilePathNT) =>
RepoKind -> g SourceRepo SourceRepo
sourceRepoFieldGrammar RepoKind
kind =
RepoKind
-> Maybe RepoType
-> Maybe String
-> Maybe String
-> Maybe String
-> Maybe String
-> Maybe String
-> SourceRepo
SourceRepo RepoKind
kind
(Maybe RepoType
-> Maybe String
-> Maybe String
-> Maybe String
-> Maybe String
-> Maybe String
-> SourceRepo)
-> g SourceRepo (Maybe RepoType)
-> g SourceRepo
(Maybe String
-> Maybe String
-> Maybe String
-> Maybe String
-> Maybe String
-> SourceRepo)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> FieldName
-> ALens' SourceRepo (Maybe RepoType)
-> g SourceRepo (Maybe RepoType)
forall (c :: * -> Constraint) (g :: * -> * -> *) a s.
(FieldGrammar c g, c (Identity a)) =>
FieldName -> ALens' s (Maybe a) -> g s (Maybe a)
optionalField FieldName
"type" ALens' SourceRepo (Maybe RepoType)
Lens' SourceRepo (Maybe RepoType)
L.repoType
g SourceRepo
(Maybe String
-> Maybe String
-> Maybe String
-> Maybe String
-> Maybe String
-> SourceRepo)
-> g SourceRepo (Maybe String)
-> g SourceRepo
(Maybe String
-> Maybe String -> Maybe String -> Maybe String -> SourceRepo)
forall a b.
g SourceRepo (a -> b) -> g SourceRepo a -> g SourceRepo b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> FieldName
-> ALens' SourceRepo (Maybe String) -> g SourceRepo (Maybe String)
forall s.
FieldName -> ALens' s (Maybe String) -> g s (Maybe String)
forall (c :: * -> Constraint) (g :: * -> * -> *) s.
FieldGrammar c g =>
FieldName -> ALens' s (Maybe String) -> g s (Maybe String)
freeTextField FieldName
"location" ALens' SourceRepo (Maybe String)
Lens' SourceRepo (Maybe String)
L.repoLocation
g SourceRepo
(Maybe String
-> Maybe String -> Maybe String -> Maybe String -> SourceRepo)
-> g SourceRepo (Maybe String)
-> g SourceRepo
(Maybe String -> Maybe String -> Maybe String -> SourceRepo)
forall a b.
g SourceRepo (a -> b) -> g SourceRepo a -> g SourceRepo b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> FieldName
-> (String -> Token)
-> ALens' SourceRepo (Maybe String)
-> g SourceRepo (Maybe String)
forall b a s.
(c b, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s (Maybe a) -> g s (Maybe a)
forall (c :: * -> Constraint) (g :: * -> * -> *) b a s.
(FieldGrammar c g, c b, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s (Maybe a) -> g s (Maybe a)
optionalFieldAla FieldName
"module" String -> Token
Token ALens' SourceRepo (Maybe String)
Lens' SourceRepo (Maybe String)
L.repoModule
g SourceRepo
(Maybe String -> Maybe String -> Maybe String -> SourceRepo)
-> g SourceRepo (Maybe String)
-> g SourceRepo (Maybe String -> Maybe String -> SourceRepo)
forall a b.
g SourceRepo (a -> b) -> g SourceRepo a -> g SourceRepo b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> FieldName
-> (String -> Token)
-> ALens' SourceRepo (Maybe String)
-> g SourceRepo (Maybe String)
forall b a s.
(c b, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s (Maybe a) -> g s (Maybe a)
forall (c :: * -> Constraint) (g :: * -> * -> *) b a s.
(FieldGrammar c g, c b, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s (Maybe a) -> g s (Maybe a)
optionalFieldAla FieldName
"branch" String -> Token
Token ALens' SourceRepo (Maybe String)
Lens' SourceRepo (Maybe String)
L.repoBranch
g SourceRepo (Maybe String -> Maybe String -> SourceRepo)
-> g SourceRepo (Maybe String)
-> g SourceRepo (Maybe String -> SourceRepo)
forall a b.
g SourceRepo (a -> b) -> g SourceRepo a -> g SourceRepo b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> FieldName
-> (String -> Token)
-> ALens' SourceRepo (Maybe String)
-> g SourceRepo (Maybe String)
forall b a s.
(c b, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s (Maybe a) -> g s (Maybe a)
forall (c :: * -> Constraint) (g :: * -> * -> *) b a s.
(FieldGrammar c g, c b, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s (Maybe a) -> g s (Maybe a)
optionalFieldAla FieldName
"tag" String -> Token
Token ALens' SourceRepo (Maybe String)
Lens' SourceRepo (Maybe String)
L.repoTag
g SourceRepo (Maybe String -> SourceRepo)
-> g SourceRepo (Maybe String) -> g SourceRepo SourceRepo
forall a b.
g SourceRepo (a -> b) -> g SourceRepo a -> g SourceRepo b
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> FieldName
-> (String -> FilePathNT)
-> ALens' SourceRepo (Maybe String)
-> g SourceRepo (Maybe String)
forall b a s.
(c b, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s (Maybe a) -> g s (Maybe a)
forall (c :: * -> Constraint) (g :: * -> * -> *) b a s.
(FieldGrammar c g, c b, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s (Maybe a) -> g s (Maybe a)
optionalFieldAla FieldName
"subdir" String -> FilePathNT
FilePathNT ALens' SourceRepo (Maybe String)
Lens' SourceRepo (Maybe String)
L.repoSubdir
{-# SPECIALIZE sourceRepoFieldGrammar :: RepoKind -> ParsecFieldGrammar' SourceRepo #-}
{-# SPECIALIZE sourceRepoFieldGrammar :: RepoKind -> PrettyFieldGrammar' SourceRepo #-}
setupBInfoFieldGrammar
:: (FieldGrammar c g, Functor (g SetupBuildInfo), c (List CommaVCat (Identity Dependency) Dependency))
=> Bool
-> g SetupBuildInfo SetupBuildInfo
setupBInfoFieldGrammar :: forall (c :: * -> Constraint) (g :: * -> * -> *).
(FieldGrammar c g, Functor (g SetupBuildInfo),
c (List CommaVCat (Identity Dependency) Dependency)) =>
Bool -> g SetupBuildInfo SetupBuildInfo
setupBInfoFieldGrammar Bool
def =
([Dependency] -> Bool -> SetupBuildInfo)
-> Bool -> [Dependency] -> SetupBuildInfo
forall a b c. (a -> b -> c) -> b -> a -> c
flip [Dependency] -> Bool -> SetupBuildInfo
SetupBuildInfo Bool
def
([Dependency] -> SetupBuildInfo)
-> g SetupBuildInfo [Dependency] -> g SetupBuildInfo SetupBuildInfo
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> FieldName
-> ([Dependency]
-> List CommaVCat (Identity Dependency) Dependency)
-> ALens' SetupBuildInfo [Dependency]
-> g SetupBuildInfo [Dependency]
forall b a s.
(c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
forall (c :: * -> Constraint) (g :: * -> * -> *) b a s.
(FieldGrammar c g, c b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
monoidalFieldAla FieldName
"setup-depends" (CommaVCat
-> [Dependency] -> List CommaVCat (Identity Dependency) Dependency
forall sep a. sep -> [a] -> List sep (Identity a) a
alaList CommaVCat
CommaVCat) ALens' SetupBuildInfo [Dependency]
Lens' SetupBuildInfo [Dependency]
L.setupDepends
{-# SPECIALIZE setupBInfoFieldGrammar :: Bool -> ParsecFieldGrammar' SetupBuildInfo #-}
{-# SPECIALIZE setupBInfoFieldGrammar :: Bool -> PrettyFieldGrammar' SetupBuildInfo #-}
formatDependencyList :: [Dependency] -> List CommaVCat (Identity Dependency) Dependency
formatDependencyList :: [Dependency] -> List CommaVCat (Identity Dependency) Dependency
formatDependencyList = CommaVCat
-> [Dependency] -> List CommaVCat (Identity Dependency) Dependency
forall sep a. sep -> [a] -> List sep (Identity a) a
alaList CommaVCat
CommaVCat
formatMixinList :: [Mixin] -> List CommaVCat (Identity Mixin) Mixin
formatMixinList :: [Mixin] -> List CommaVCat (Identity Mixin) Mixin
formatMixinList = CommaVCat -> [Mixin] -> List CommaVCat (Identity Mixin) Mixin
forall sep a. sep -> [a] -> List sep (Identity a) a
alaList CommaVCat
CommaVCat
formatExtraSourceFiles :: [RelativePath Pkg File] -> List VCat (RelativePathNT Pkg File) (RelativePath Pkg File)
= VCat
-> (RelativePath Pkg 'File -> RelativePathNT Pkg 'File)
-> [RelativePath Pkg 'File]
-> List VCat (RelativePathNT Pkg 'File) (RelativePath Pkg 'File)
forall sep a b. sep -> (a -> b) -> [a] -> List sep b a
alaList' VCat
VCat RelativePath Pkg 'File -> RelativePathNT Pkg 'File
forall from (to :: FileOrDir).
RelativePath from to -> RelativePathNT from to
RelativePathNT
formatExposedModules :: [ModuleName] -> List VCat (MQuoted ModuleName) ModuleName
formatExposedModules :: [ModuleName] -> List VCat (MQuoted ModuleName) ModuleName
formatExposedModules = VCat
-> (ModuleName -> MQuoted ModuleName)
-> [ModuleName]
-> List VCat (MQuoted ModuleName) ModuleName
forall sep a b. sep -> (a -> b) -> [a] -> List sep b a
alaList' VCat
VCat ModuleName -> MQuoted ModuleName
forall a. a -> MQuoted a
MQuoted
formatHsSourceDirs :: [SymbolicPath Pkg (Dir Source)] -> List FSep (SymbolicPathNT Pkg (Dir Source)) (SymbolicPath Pkg (Dir Source))
formatHsSourceDirs :: [SymbolicPath Pkg ('Dir Source)]
-> List
FSep
(SymbolicPathNT Pkg ('Dir Source))
(SymbolicPath Pkg ('Dir Source))
formatHsSourceDirs = FSep
-> (SymbolicPath Pkg ('Dir Source)
-> SymbolicPathNT Pkg ('Dir Source))
-> [SymbolicPath Pkg ('Dir Source)]
-> List
FSep
(SymbolicPathNT Pkg ('Dir Source))
(SymbolicPath Pkg ('Dir Source))
forall sep a b. sep -> (a -> b) -> [a] -> List sep b a
alaList' FSep
FSep SymbolicPath Pkg ('Dir Source) -> SymbolicPathNT Pkg ('Dir Source)
forall from (to :: FileOrDir).
SymbolicPath from to -> SymbolicPathNT from to
SymbolicPathNT
formatOtherExtensions :: [Extension] -> List FSep (MQuoted Extension) Extension
formatOtherExtensions :: [Extension] -> List FSep (MQuoted Extension) Extension
formatOtherExtensions = FSep
-> (Extension -> MQuoted Extension)
-> [Extension]
-> List FSep (MQuoted Extension) Extension
forall sep a b. sep -> (a -> b) -> [a] -> List sep b a
alaList' FSep
FSep Extension -> MQuoted Extension
forall a. a -> MQuoted a
MQuoted
formatOtherModules :: [ModuleName] -> List VCat (MQuoted ModuleName) ModuleName
formatOtherModules :: [ModuleName] -> List VCat (MQuoted ModuleName) ModuleName
formatOtherModules = VCat
-> (ModuleName -> MQuoted ModuleName)
-> [ModuleName]
-> List VCat (MQuoted ModuleName) ModuleName
forall sep a b. sep -> (a -> b) -> [a] -> List sep b a
alaList' VCat
VCat ModuleName -> MQuoted ModuleName
forall a. a -> MQuoted a
MQuoted
newtype CompatDataDir = CompatDataDir {CompatDataDir -> SymbolicPath Pkg ('Dir DataDir)
getCompatDataDir :: SymbolicPath Pkg (Dir DataDir)}
instance Newtype (SymbolicPath Pkg (Dir DataDir)) CompatDataDir
instance Parsec CompatDataDir where
parsec :: forall (m :: * -> *). CabalParsing m => m CompatDataDir
parsec = do
token <- m String
forall (m :: * -> *). CabalParsing m => m String
parsecToken
when (null token) $
parsecWarning PWTEmptyFilePath "empty FilePath"
return (CompatDataDir $ makeSymbolicPath token)
instance Pretty CompatDataDir where
pretty :: CompatDataDir -> Doc
pretty = String -> Doc
showToken (String -> Doc)
-> (CompatDataDir -> String) -> CompatDataDir -> Doc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SymbolicPath Pkg ('Dir DataDir) -> String
forall (allowAbsolute :: AllowAbsolute) from (to :: FileOrDir).
SymbolicPathX allowAbsolute from to -> String
getSymbolicPath (SymbolicPath Pkg ('Dir DataDir) -> String)
-> (CompatDataDir -> SymbolicPath Pkg ('Dir DataDir))
-> CompatDataDir
-> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CompatDataDir -> SymbolicPath Pkg ('Dir DataDir)
getCompatDataDir
newtype CompatLicenseFile = CompatLicenseFile {CompatLicenseFile -> [RelativePath Pkg 'File]
getCompatLicenseFile :: [RelativePath Pkg File]}
instance Newtype [RelativePath Pkg File] CompatLicenseFile
instance Parsec CompatLicenseFile where
parsec :: forall (m :: * -> *). CabalParsing m => m CompatLicenseFile
parsec = m CompatLicenseFile
emptyToken m CompatLicenseFile -> m CompatLicenseFile -> m CompatLicenseFile
forall a. m a -> m a -> m a
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> [RelativePath Pkg 'File] -> CompatLicenseFile
CompatLicenseFile ([RelativePath Pkg 'File] -> CompatLicenseFile)
-> (List
FSep (Identity (RelativePath Pkg 'File)) (RelativePath Pkg 'File)
-> [RelativePath Pkg 'File])
-> List
FSep (Identity (RelativePath Pkg 'File)) (RelativePath Pkg 'File)
-> CompatLicenseFile
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([RelativePath Pkg 'File]
-> List
FSep (Identity (RelativePath Pkg 'File)) (RelativePath Pkg 'File))
-> List
FSep (Identity (RelativePath Pkg 'File)) (RelativePath Pkg 'File)
-> [RelativePath Pkg 'File]
forall o n. Newtype o n => (o -> n) -> n -> o
unpack' (FSep
-> [RelativePath Pkg 'File]
-> List
FSep (Identity (RelativePath Pkg 'File)) (RelativePath Pkg 'File)
forall sep a. sep -> [a] -> List sep (Identity a) a
alaList FSep
FSep) (List
FSep (Identity (RelativePath Pkg 'File)) (RelativePath Pkg 'File)
-> CompatLicenseFile)
-> m (List
FSep (Identity (RelativePath Pkg 'File)) (RelativePath Pkg 'File))
-> m CompatLicenseFile
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> m (List
FSep (Identity (RelativePath Pkg 'File)) (RelativePath Pkg 'File))
forall a (m :: * -> *). (Parsec a, CabalParsing m) => m a
forall (m :: * -> *).
CabalParsing m =>
m (List
FSep (Identity (RelativePath Pkg 'File)) (RelativePath Pkg 'File))
parsec
where
emptyToken :: m CompatLicenseFile
emptyToken = m CompatLicenseFile -> m CompatLicenseFile
forall a. m a -> m a
forall (m :: * -> *) a. Parsing m => m a -> m a
P.try (m CompatLicenseFile -> m CompatLicenseFile)
-> m CompatLicenseFile -> m CompatLicenseFile
forall a b. (a -> b) -> a -> b
$ do
token <- m String
forall (m :: * -> *). CabalParsing m => m String
parsecToken
if null token
then return (CompatLicenseFile [])
else P.unexpected "non-empty-token"
instance Pretty CompatLicenseFile where
pretty :: CompatLicenseFile -> Doc
pretty = List
FSep (Identity (RelativePath Pkg 'File)) (RelativePath Pkg 'File)
-> Doc
forall a. Pretty a => a -> Doc
pretty (List
FSep (Identity (RelativePath Pkg 'File)) (RelativePath Pkg 'File)
-> Doc)
-> (CompatLicenseFile
-> List
FSep (Identity (RelativePath Pkg 'File)) (RelativePath Pkg 'File))
-> CompatLicenseFile
-> Doc
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ([RelativePath Pkg 'File]
-> List
FSep (Identity (RelativePath Pkg 'File)) (RelativePath Pkg 'File))
-> [RelativePath Pkg 'File]
-> List
FSep (Identity (RelativePath Pkg 'File)) (RelativePath Pkg 'File)
forall o n. Newtype o n => (o -> n) -> o -> n
pack' (FSep
-> [RelativePath Pkg 'File]
-> List
FSep (Identity (RelativePath Pkg 'File)) (RelativePath Pkg 'File)
forall sep a. sep -> [a] -> List sep (Identity a) a
alaList FSep
FSep) ([RelativePath Pkg 'File]
-> List
FSep (Identity (RelativePath Pkg 'File)) (RelativePath Pkg 'File))
-> (CompatLicenseFile -> [RelativePath Pkg 'File])
-> CompatLicenseFile
-> List
FSep (Identity (RelativePath Pkg 'File)) (RelativePath Pkg 'File)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. CompatLicenseFile -> [RelativePath Pkg 'File]
getCompatLicenseFile
_syntaxFieldNames :: IO ()
_syntaxFieldNames :: IO ()
_syntaxFieldNames =
[IO ()] -> IO ()
forall (t :: * -> *) (m :: * -> *) a.
(Foldable t, Monad m) =>
t (m a) -> m ()
sequence_
[ FieldName -> IO ()
BS8.putStrLn (FieldName -> IO ()) -> FieldName -> IO ()
forall a b. (a -> b) -> a -> b
$ FieldName
" \\ " FieldName -> FieldName -> FieldName
forall a. Semigroup a => a -> a -> a
<> FieldName
n
| FieldName
n <-
[FieldName] -> [FieldName]
forall a. Eq a => [a] -> [a]
nub ([FieldName] -> [FieldName]) -> [FieldName] -> [FieldName]
forall a b. (a -> b) -> a -> b
$
[FieldName] -> [FieldName]
forall a. Ord a => [a] -> [a]
sort ([FieldName] -> [FieldName]) -> [FieldName] -> [FieldName]
forall a b. (a -> b) -> a -> b
$
[[FieldName]] -> [FieldName]
forall a. Monoid a => [a] -> a
mconcat
[ ParsecFieldGrammar PackageDescription PackageDescription
-> [FieldName]
forall s a. ParsecFieldGrammar s a -> [FieldName]
fieldGrammarKnownFieldList ParsecFieldGrammar PackageDescription PackageDescription
forall (c :: * -> Constraint) (g :: * -> * -> *).
(FieldGrammar c g, Applicative (g PackageDescription),
Applicative (g PackageIdentifier), c (Identity BuildType),
c (Identity PackageName), c (Identity Version),
forall from (to :: FileOrDir).
c (List FSep (RelativePathNT from to) (RelativePath from to)),
forall from (to :: FileOrDir).
c (List VCat (RelativePathNT from to) (RelativePath from to)),
c (List FSep TestedWith (CompilerFlavor, VersionRange)),
c CompatLicenseFile, c CompatDataDir) =>
g PackageDescription PackageDescription
packageDescriptionFieldGrammar
, ParsecFieldGrammar Library Library -> [FieldName]
forall s a. ParsecFieldGrammar s a -> [FieldName]
fieldGrammarKnownFieldList (ParsecFieldGrammar Library Library -> [FieldName])
-> ParsecFieldGrammar Library Library -> [FieldName]
forall a b. (a -> b) -> a -> b
$ LibraryName -> ParsecFieldGrammar Library Library
forall (c :: * -> Constraint) (g :: * -> * -> *).
(FieldGrammar c g, Applicative (g Library),
Applicative (g BuildInfo), c (Identity LibraryVisibility),
c (List CommaFSep (Identity ExeDependency) ExeDependency),
c (List
CommaFSep (Identity LegacyExeDependency) LegacyExeDependency),
c (List
CommaFSep (Identity PkgconfigDependency) PkgconfigDependency),
c (List CommaVCat (Identity Dependency) Dependency),
c (List CommaVCat (Identity Mixin) Mixin),
c (List CommaVCat (Identity ModuleReexport) ModuleReexport),
c (List FSep (MQuoted Extension) Extension),
c (List FSep (MQuoted Language) Language),
c (List FSep Token String), c (List NoCommaFSep Token' String),
c (List VCat (MQuoted ModuleName) ModuleName),
forall from (to :: FileOrDir).
c (List FSep (SymbolicPathNT from to) (SymbolicPath from to)),
forall from (to :: FileOrDir).
c (List FSep (RelativePathNT from to) (RelativePath from to)),
forall from (to :: FileOrDir).
c (List VCat (SymbolicPathNT from to) (SymbolicPath from to)),
c (List VCat Token String), c (MQuoted Language)) =>
LibraryName -> g Library Library
libraryFieldGrammar LibraryName
LMainLibName
, ParsecFieldGrammar Executable Executable -> [FieldName]
forall s a. ParsecFieldGrammar s a -> [FieldName]
fieldGrammarKnownFieldList (ParsecFieldGrammar Executable Executable -> [FieldName])
-> ParsecFieldGrammar Executable Executable -> [FieldName]
forall a b. (a -> b) -> a -> b
$ UnqualComponentName -> ParsecFieldGrammar Executable Executable
forall (c :: * -> Constraint) (g :: * -> * -> *).
(FieldGrammar c g, Applicative (g Executable),
Applicative (g BuildInfo), c (Identity ExecutableScope),
c (List CommaFSep (Identity ExeDependency) ExeDependency),
c (List
CommaFSep (Identity LegacyExeDependency) LegacyExeDependency),
c (List
CommaFSep (Identity PkgconfigDependency) PkgconfigDependency),
c (List CommaVCat (Identity Dependency) Dependency),
c (List CommaVCat (Identity Mixin) Mixin),
c (List FSep (MQuoted Extension) Extension),
c (List FSep (MQuoted Language) Language),
c (List FSep Token String),
forall from (to :: FileOrDir).
c (List FSep (SymbolicPathNT from to) (SymbolicPath from to)),
forall from (to :: FileOrDir).
c (List FSep (RelativePathNT from to) (RelativePath from to)),
forall from (to :: FileOrDir).
c (List FSep (SymbolicPathNT from to) (SymbolicPath from to)),
forall from (to :: FileOrDir).
c (List FSep (RelativePathNT from to) (RelativePath from to)),
forall from (to :: FileOrDir).
c (List VCat (SymbolicPathNT from to) (SymbolicPath from to)),
forall from (to :: FileOrDir). c (SymbolicPathNT from to),
forall from (to :: FileOrDir). c (RelativePathNT from to),
c (List NoCommaFSep Token' String),
c (List VCat (MQuoted ModuleName) ModuleName),
c (List VCat Token String), c (MQuoted Language)) =>
UnqualComponentName -> g Executable Executable
executableFieldGrammar UnqualComponentName
"exe"
, ParsecFieldGrammar ForeignLib ForeignLib -> [FieldName]
forall s a. ParsecFieldGrammar s a -> [FieldName]
fieldGrammarKnownFieldList (ParsecFieldGrammar ForeignLib ForeignLib -> [FieldName])
-> ParsecFieldGrammar ForeignLib ForeignLib -> [FieldName]
forall a b. (a -> b) -> a -> b
$ UnqualComponentName -> ParsecFieldGrammar ForeignLib ForeignLib
forall (c :: * -> Constraint) (g :: * -> * -> *).
(FieldGrammar c g, Applicative (g ForeignLib),
Applicative (g BuildInfo), c (Identity ForeignLibType),
c (Identity LibVersionInfo), c (Identity Version),
c (List CommaFSep (Identity ExeDependency) ExeDependency),
c (List
CommaFSep (Identity LegacyExeDependency) LegacyExeDependency),
c (List
CommaFSep (Identity PkgconfigDependency) PkgconfigDependency),
c (List CommaVCat (Identity Dependency) Dependency),
c (List CommaVCat (Identity Mixin) Mixin),
c (List FSep (Identity ForeignLibOption) ForeignLibOption),
c (List FSep (MQuoted Extension) Extension),
c (List FSep (MQuoted Language) Language),
c (List FSep Token String),
forall from (to :: FileOrDir).
c (List FSep (SymbolicPathNT from to) (SymbolicPath from to)),
forall from (to :: FileOrDir).
c (List FSep (RelativePathNT from to) (RelativePath from to)),
forall from (to :: FileOrDir).
c (List VCat (SymbolicPathNT from to) (SymbolicPath from to)),
c (List NoCommaFSep Token' String),
c (List VCat (MQuoted ModuleName) ModuleName),
c (List VCat Token String), c (MQuoted Language)) =>
UnqualComponentName -> g ForeignLib ForeignLib
foreignLibFieldGrammar UnqualComponentName
"flib"
, ParsecFieldGrammar TestSuiteStanza TestSuiteStanza -> [FieldName]
forall s a. ParsecFieldGrammar s a -> [FieldName]
fieldGrammarKnownFieldList ParsecFieldGrammar TestSuiteStanza TestSuiteStanza
forall (c :: * -> Constraint) (g :: * -> * -> *).
(FieldGrammar c g, Applicative (g TestSuiteStanza),
Applicative (g BuildInfo), c (Identity ModuleName),
c (Identity TestType),
c (List CommaFSep (Identity ExeDependency) ExeDependency),
c (List
CommaFSep (Identity LegacyExeDependency) LegacyExeDependency),
c (List
CommaFSep (Identity PkgconfigDependency) PkgconfigDependency),
c (List CommaFSep Token String),
c (List CommaVCat (Identity Dependency) Dependency),
c (List CommaVCat (Identity Mixin) Mixin),
c (List FSep (MQuoted Extension) Extension),
c (List FSep (MQuoted Language) Language),
c (List FSep Token String), c (List NoCommaFSep Token' String),
c (List VCat (MQuoted ModuleName) ModuleName),
forall from (to :: FileOrDir).
c (List FSep (SymbolicPathNT from to) (SymbolicPath from to)),
forall from (to :: FileOrDir).
c (List FSep (RelativePathNT from to) (RelativePath from to)),
forall from (to :: FileOrDir).
c (List VCat (SymbolicPathNT from to) (SymbolicPath from to)),
forall from (to :: FileOrDir). c (RelativePathNT from to),
c (List VCat Token String), c (MQuoted Language)) =>
g TestSuiteStanza TestSuiteStanza
testSuiteFieldGrammar
, ParsecFieldGrammar BenchmarkStanza BenchmarkStanza -> [FieldName]
forall s a. ParsecFieldGrammar s a -> [FieldName]
fieldGrammarKnownFieldList ParsecFieldGrammar BenchmarkStanza BenchmarkStanza
forall (c :: * -> Constraint) (g :: * -> * -> *).
(FieldGrammar c g, Applicative (g BenchmarkStanza),
Applicative (g BuildInfo), c (Identity BenchmarkType),
c (Identity ModuleName),
c (List CommaFSep (Identity ExeDependency) ExeDependency),
c (List
CommaFSep (Identity LegacyExeDependency) LegacyExeDependency),
c (List
CommaFSep (Identity PkgconfigDependency) PkgconfigDependency),
c (List CommaVCat (Identity Dependency) Dependency),
c (List CommaVCat (Identity Mixin) Mixin),
c (List FSep (MQuoted Extension) Extension),
c (List FSep (MQuoted Language) Language),
c (List FSep Token String), c (List NoCommaFSep Token' String),
c (List VCat (MQuoted ModuleName) ModuleName),
forall from (to :: FileOrDir).
c (List FSep (SymbolicPathNT from to) (SymbolicPath from to)),
forall from (to :: FileOrDir).
c (List FSep (RelativePathNT from to) (RelativePath from to)),
forall from (to :: FileOrDir).
c (List VCat (SymbolicPathNT from to) (SymbolicPath from to)),
forall from (to :: FileOrDir). c (RelativePathNT from to),
c (List VCat Token String), c (MQuoted Language)) =>
g BenchmarkStanza BenchmarkStanza
benchmarkFieldGrammar
, ParsecFieldGrammar PackageFlag PackageFlag -> [FieldName]
forall s a. ParsecFieldGrammar s a -> [FieldName]
fieldGrammarKnownFieldList (ParsecFieldGrammar PackageFlag PackageFlag -> [FieldName])
-> ParsecFieldGrammar PackageFlag PackageFlag -> [FieldName]
forall a b. (a -> b) -> a -> b
$ FlagName -> ParsecFieldGrammar PackageFlag PackageFlag
forall (c :: * -> Constraint) (g :: * -> * -> *).
(FieldGrammar c g, Applicative (g PackageFlag)) =>
FlagName -> g PackageFlag PackageFlag
flagFieldGrammar (String -> FlagName
forall a. HasCallStack => String -> a
error String
"flagname")
, ParsecFieldGrammar SourceRepo SourceRepo -> [FieldName]
forall s a. ParsecFieldGrammar s a -> [FieldName]
fieldGrammarKnownFieldList (ParsecFieldGrammar SourceRepo SourceRepo -> [FieldName])
-> ParsecFieldGrammar SourceRepo SourceRepo -> [FieldName]
forall a b. (a -> b) -> a -> b
$ RepoKind -> ParsecFieldGrammar SourceRepo SourceRepo
forall (c :: * -> Constraint) (g :: * -> * -> *).
(FieldGrammar c g, Applicative (g SourceRepo),
c (Identity RepoType), c Token, c FilePathNT) =>
RepoKind -> g SourceRepo SourceRepo
sourceRepoFieldGrammar (String -> RepoKind
forall a. HasCallStack => String -> a
error String
"repokind")
, ParsecFieldGrammar SetupBuildInfo SetupBuildInfo -> [FieldName]
forall s a. ParsecFieldGrammar s a -> [FieldName]
fieldGrammarKnownFieldList (ParsecFieldGrammar SetupBuildInfo SetupBuildInfo -> [FieldName])
-> ParsecFieldGrammar SetupBuildInfo SetupBuildInfo -> [FieldName]
forall a b. (a -> b) -> a -> b
$ Bool -> ParsecFieldGrammar SetupBuildInfo SetupBuildInfo
forall (c :: * -> Constraint) (g :: * -> * -> *).
(FieldGrammar c g, Functor (g SetupBuildInfo),
c (List CommaVCat (Identity Dependency) Dependency)) =>
Bool -> g SetupBuildInfo SetupBuildInfo
setupBInfoFieldGrammar Bool
True
]
]
_syntaxExtensions :: IO ()
_syntaxExtensions :: IO ()
_syntaxExtensions =
[IO ()] -> IO ()
forall (t :: * -> *) (m :: * -> *) a.
(Foldable t, Monad m) =>
t (m a) -> m ()
sequence_
[ String -> IO ()
putStrLn (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ String
" \\ " String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
e
| String
e <-
[String
"Safe", String
"Trustworthy", String
"Unsafe"]
[String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ [String]
es
[String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ (String -> String) -> [String] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map (String
"No" String -> String -> String
forall a. [a] -> [a] -> [a]
++) [String]
es
]
where
es :: [String]
es =
[String] -> [String]
forall a. Eq a => [a] -> [a]
nub ([String] -> [String]) -> [String] -> [String]
forall a b. (a -> b) -> a -> b
$
[String] -> [String]
forall a. Ord a => [a] -> [a]
sort
[ KnownExtension -> String
forall a. Pretty a => a -> String
prettyShow KnownExtension
e
| KnownExtension
e <- [KnownExtension
forall a. Bounded a => a
minBound .. KnownExtension
forall a. Bounded a => a
maxBound]
, KnownExtension
e KnownExtension -> [KnownExtension] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`notElem` [KnownExtension
Safe, KnownExtension
Unsafe, KnownExtension
Trustworthy]
]