{-# LANGUAGE OverloadedStrings #-}
-- | 'GenericPackageDescription' Field descriptions
module Distribution.PackageDescription.FieldGrammar (
    -- * Package description
    packageDescriptionFieldGrammar,
    -- * Library
    libraryFieldGrammar,
    -- * Foreign library
    foreignLibFieldGrammar,
    -- * Executable
    executableFieldGrammar,
    -- * Test suite
    TestSuiteStanza (..),
    testSuiteFieldGrammar,
    validateTestSuite,
    unvalidateTestSuite,
    -- ** Lenses
    testStanzaTestType,
    testStanzaMainIs,
    testStanzaTestModule,
    testStanzaBuildInfo,
    -- * Benchmark
    BenchmarkStanza (..),
    benchmarkFieldGrammar,
    validateBenchmark,
    unvalidateBenchmark,
    -- ** Lenses
    benchmarkStanzaBenchmarkType,
    benchmarkStanzaMainIs,
    benchmarkStanzaBenchmarkModule,
    benchmarkStanzaBuildInfo,
    -- * Flag
    flagFieldGrammar,
    -- * Source repository
    sourceRepoFieldGrammar,
    -- * Setup build info
    setupBInfoFieldGrammar,
    -- * Component build info
    buildInfoFieldGrammar,
    ) where

import Distribution.Compat.Lens
import Distribution.Compat.Prelude
import Prelude ()

import Distribution.CabalSpecVersion
import Distribution.Compiler                  (CompilerFlavor (..), PerCompilerFlavor (..))
import Distribution.FieldGrammar
import Distribution.ModuleName                (ModuleName)
import Distribution.Package
import Distribution.PackageDescription
import Distribution.Parsec
import Distribution.Parsec.Newtypes
import Distribution.Fields
import Distribution.Pretty                    (prettyShow)
import Distribution.Types.ExecutableScope
import Distribution.Types.ForeignLib
import Distribution.Types.ForeignLibType
import Distribution.Types.LibraryVisibility
import Distribution.Types.UnqualComponentName
import Distribution.Version                   (anyVersion)

import qualified Distribution.SPDX as SPDX

import qualified Distribution.Types.Lens as L

-------------------------------------------------------------------------------
-- PackageDescription
-------------------------------------------------------------------------------

packageDescriptionFieldGrammar
    :: (FieldGrammar g, Applicative (g PackageDescription), Applicative (g PackageIdentifier))
    => g PackageDescription PackageDescription
packageDescriptionFieldGrammar :: g PackageDescription PackageDescription
packageDescriptionFieldGrammar = Either Version VersionRange
-> PackageIdentifier
-> Either License License
-> [String]
-> ShortText
-> ShortText
-> ShortText
-> ShortText
-> [(CompilerFlavor, VersionRange)]
-> ShortText
-> ShortText
-> ShortText
-> [SourceRepo]
-> ShortText
-> ShortText
-> ShortText
-> [(String, String)]
-> Maybe BuildType
-> Maybe SetupBuildInfo
-> Maybe Library
-> [Library]
-> [Executable]
-> [ForeignLib]
-> [TestSuite]
-> [Benchmark]
-> [String]
-> String
-> [String]
-> [String]
-> [String]
-> PackageDescription
PackageDescription
    (Either Version VersionRange
 -> PackageIdentifier
 -> Either License License
 -> [String]
 -> ShortText
 -> ShortText
 -> ShortText
 -> ShortText
 -> [(CompilerFlavor, VersionRange)]
 -> ShortText
 -> ShortText
 -> ShortText
 -> [SourceRepo]
 -> ShortText
 -> ShortText
 -> ShortText
 -> [(String, String)]
 -> Maybe BuildType
 -> Maybe SetupBuildInfo
 -> Maybe Library
 -> [Library]
 -> [Executable]
 -> [ForeignLib]
 -> [TestSuite]
 -> [Benchmark]
 -> [String]
 -> String
 -> [String]
 -> [String]
 -> [String]
 -> PackageDescription)
-> g PackageDescription (Either Version VersionRange)
-> g PackageDescription
     (PackageIdentifier
      -> Either License License
      -> [String]
      -> ShortText
      -> ShortText
      -> ShortText
      -> ShortText
      -> [(CompilerFlavor, VersionRange)]
      -> ShortText
      -> ShortText
      -> ShortText
      -> [SourceRepo]
      -> ShortText
      -> ShortText
      -> ShortText
      -> [(String, String)]
      -> Maybe BuildType
      -> Maybe SetupBuildInfo
      -> Maybe Library
      -> [Library]
      -> [Executable]
      -> [ForeignLib]
      -> [TestSuite]
      -> [Benchmark]
      -> [String]
      -> String
      -> [String]
      -> [String]
      -> [String]
      -> PackageDescription)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type forall (f :: * -> *). Applicative f => Functor f
Evidence bound by a type signature of the constraint type Applicative (g PackageDescription)
<$> FieldName
-> (Either Version VersionRange -> SpecVersion)
-> ALens' PackageDescription (Either Version VersionRange)
-> Either Version VersionRange
-> g PackageDescription (Either Version VersionRange)
forall (g :: * -> * -> *) b a s.
(FieldGrammar g, Parsec b, Pretty b, Newtype a b, Eq a) =>
FieldName -> (a -> b) -> ALens' s a -> a -> g s a
External instance of the constraint type forall a b. (Eq a, Eq b) => Eq (Either a b)
External instance of the constraint type Eq Version
External instance of the constraint type Eq VersionRange
External instance of the constraint type Newtype (Either Version VersionRange) SpecVersion
External instance of the constraint type Pretty SpecVersion
External instance of the constraint type Parsec SpecVersion
Evidence bound by a type signature of the constraint type FieldGrammar g
optionalFieldDefAla FieldName
"cabal-version" Either Version VersionRange -> SpecVersion
SpecVersion                ALens' PackageDescription (Either Version VersionRange)
Lens' PackageDescription (Either Version VersionRange)
External instance of the constraint type forall a b. Functor (Pretext a b)
L.specVersionRaw (VersionRange -> Either Version VersionRange
forall a b. b -> Either a b
Right VersionRange
anyVersion)
    g PackageDescription
  (PackageIdentifier
   -> Either License License
   -> [String]
   -> ShortText
   -> ShortText
   -> ShortText
   -> ShortText
   -> [(CompilerFlavor, VersionRange)]
   -> ShortText
   -> ShortText
   -> ShortText
   -> [SourceRepo]
   -> ShortText
   -> ShortText
   -> ShortText
   -> [(String, String)]
   -> Maybe BuildType
   -> Maybe SetupBuildInfo
   -> Maybe Library
   -> [Library]
   -> [Executable]
   -> [ForeignLib]
   -> [TestSuite]
   -> [Benchmark]
   -> [String]
   -> String
   -> [String]
   -> [String]
   -> [String]
   -> PackageDescription)
-> g PackageDescription PackageIdentifier
-> g PackageDescription
     (Either License License
      -> [String]
      -> ShortText
      -> ShortText
      -> ShortText
      -> ShortText
      -> [(CompilerFlavor, VersionRange)]
      -> ShortText
      -> ShortText
      -> ShortText
      -> [SourceRepo]
      -> ShortText
      -> ShortText
      -> ShortText
      -> [(String, String)]
      -> Maybe BuildType
      -> Maybe SetupBuildInfo
      -> Maybe Library
      -> [Library]
      -> [Executable]
      -> [ForeignLib]
      -> [TestSuite]
      -> [Benchmark]
      -> [String]
      -> String
      -> [String]
      -> [String]
      -> [String]
      -> PackageDescription)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Applicative (g PackageDescription)
<*> ALens' PackageDescription PackageIdentifier
-> g PackageIdentifier PackageIdentifier
-> g PackageDescription PackageIdentifier
forall (g :: * -> * -> *) a b c.
FieldGrammar g =>
ALens' a b -> g b c -> g a c
Evidence bound by a type signature of the constraint type FieldGrammar g
blurFieldGrammar ALens' PackageDescription PackageIdentifier
Lens' PackageDescription PackageIdentifier
External instance of the constraint type forall a b. Functor (Pretext a b)
L.package g PackageIdentifier PackageIdentifier
packageIdentifierGrammar
    g PackageDescription
  (Either License License
   -> [String]
   -> ShortText
   -> ShortText
   -> ShortText
   -> ShortText
   -> [(CompilerFlavor, VersionRange)]
   -> ShortText
   -> ShortText
   -> ShortText
   -> [SourceRepo]
   -> ShortText
   -> ShortText
   -> ShortText
   -> [(String, String)]
   -> Maybe BuildType
   -> Maybe SetupBuildInfo
   -> Maybe Library
   -> [Library]
   -> [Executable]
   -> [ForeignLib]
   -> [TestSuite]
   -> [Benchmark]
   -> [String]
   -> String
   -> [String]
   -> [String]
   -> [String]
   -> PackageDescription)
-> g PackageDescription (Either License License)
-> g PackageDescription
     ([String]
      -> ShortText
      -> ShortText
      -> ShortText
      -> ShortText
      -> [(CompilerFlavor, VersionRange)]
      -> ShortText
      -> ShortText
      -> ShortText
      -> [SourceRepo]
      -> ShortText
      -> ShortText
      -> ShortText
      -> [(String, String)]
      -> Maybe BuildType
      -> Maybe SetupBuildInfo
      -> Maybe Library
      -> [Library]
      -> [Executable]
      -> [ForeignLib]
      -> [TestSuite]
      -> [Benchmark]
      -> [String]
      -> String
      -> [String]
      -> [String]
      -> [String]
      -> PackageDescription)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Applicative (g PackageDescription)
<*> FieldName
-> (Either License License -> SpecLicense)
-> ALens' PackageDescription (Either License License)
-> Either License License
-> g PackageDescription (Either License License)
forall (g :: * -> * -> *) b a s.
(FieldGrammar g, Parsec b, Pretty b, Newtype a b, Eq a) =>
FieldName -> (a -> b) -> ALens' s a -> a -> g s a
External instance of the constraint type forall a b. (Eq a, Eq b) => Eq (Either a b)
External instance of the constraint type Eq License
External instance of the constraint type Eq License
External instance of the constraint type Newtype (Either License License) SpecLicense
External instance of the constraint type Pretty SpecLicense
External instance of the constraint type Parsec SpecLicense
Evidence bound by a type signature of the constraint type FieldGrammar g
optionalFieldDefAla FieldName
"license"       Either License License -> SpecLicense
SpecLicense                ALens' PackageDescription (Either License License)
Lens' PackageDescription (Either License License)
External instance of the constraint type forall a b. Functor (Pretext a b)
L.licenseRaw (License -> Either License License
forall a b. a -> Either a b
Left License
SPDX.NONE)
    g PackageDescription
  ([String]
   -> ShortText
   -> ShortText
   -> ShortText
   -> ShortText
   -> [(CompilerFlavor, VersionRange)]
   -> ShortText
   -> ShortText
   -> ShortText
   -> [SourceRepo]
   -> ShortText
   -> ShortText
   -> ShortText
   -> [(String, String)]
   -> Maybe BuildType
   -> Maybe SetupBuildInfo
   -> Maybe Library
   -> [Library]
   -> [Executable]
   -> [ForeignLib]
   -> [TestSuite]
   -> [Benchmark]
   -> [String]
   -> String
   -> [String]
   -> [String]
   -> [String]
   -> PackageDescription)
-> g PackageDescription [String]
-> 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]
      -> [String]
      -> String
      -> [String]
      -> [String]
      -> [String]
      -> PackageDescription)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Applicative (g PackageDescription)
<*> g PackageDescription [String]
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]
   -> [String]
   -> String
   -> [String]
   -> [String]
   -> [String]
   -> 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]
      -> [String]
      -> String
      -> [String]
      -> [String]
      -> [String]
      -> PackageDescription)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Applicative (g PackageDescription)
<*> FieldName
-> ALens' PackageDescription ShortText
-> g PackageDescription ShortText
forall (g :: * -> * -> *) s.
FieldGrammar g =>
FieldName -> ALens' s ShortText -> g s ShortText
Evidence bound by a type signature of the constraint type FieldGrammar g
freeTextFieldDefST  FieldName
"copyright"                                ALens' PackageDescription ShortText
Lens' PackageDescription ShortText
External instance of the constraint type forall a b. Functor (Pretext a b)
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]
   -> [String]
   -> String
   -> [String]
   -> [String]
   -> [String]
   -> 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]
      -> [String]
      -> String
      -> [String]
      -> [String]
      -> [String]
      -> PackageDescription)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Applicative (g PackageDescription)
<*> FieldName
-> ALens' PackageDescription ShortText
-> g PackageDescription ShortText
forall (g :: * -> * -> *) s.
FieldGrammar g =>
FieldName -> ALens' s ShortText -> g s ShortText
Evidence bound by a type signature of the constraint type FieldGrammar g
freeTextFieldDefST  FieldName
"maintainer"                               ALens' PackageDescription ShortText
Lens' PackageDescription ShortText
External instance of the constraint type forall a b. Functor (Pretext a b)
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]
   -> [String]
   -> String
   -> [String]
   -> [String]
   -> [String]
   -> 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]
      -> [String]
      -> String
      -> [String]
      -> [String]
      -> [String]
      -> PackageDescription)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Applicative (g PackageDescription)
<*> FieldName
-> ALens' PackageDescription ShortText
-> g PackageDescription ShortText
forall (g :: * -> * -> *) s.
FieldGrammar g =>
FieldName -> ALens' s ShortText -> g s ShortText
Evidence bound by a type signature of the constraint type FieldGrammar g
freeTextFieldDefST  FieldName
"author"                                   ALens' PackageDescription ShortText
Lens' PackageDescription ShortText
External instance of the constraint type forall a b. Functor (Pretext a b)
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]
   -> [String]
   -> String
   -> [String]
   -> [String]
   -> [String]
   -> 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]
      -> [String]
      -> String
      -> [String]
      -> [String]
      -> [String]
      -> PackageDescription)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Applicative (g PackageDescription)
<*> FieldName
-> ALens' PackageDescription ShortText
-> g PackageDescription ShortText
forall (g :: * -> * -> *) s.
FieldGrammar g =>
FieldName -> ALens' s ShortText -> g s ShortText
Evidence bound by a type signature of the constraint type FieldGrammar g
freeTextFieldDefST  FieldName
"stability"                                ALens' PackageDescription ShortText
Lens' PackageDescription ShortText
External instance of the constraint type forall a b. Functor (Pretext a b)
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]
   -> [String]
   -> String
   -> [String]
   -> [String]
   -> [String]
   -> 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]
      -> [String]
      -> String
      -> [String]
      -> [String]
      -> [String]
      -> PackageDescription)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Applicative (g PackageDescription)
<*> FieldName
-> ([(CompilerFlavor, VersionRange)]
    -> List FSep TestedWith (CompilerFlavor, VersionRange))
-> ALens' PackageDescription [(CompilerFlavor, VersionRange)]
-> g PackageDescription [(CompilerFlavor, VersionRange)]
forall (g :: * -> * -> *) b a s.
(FieldGrammar g, Parsec b, Pretty b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
External instance of the constraint type forall a sep wrapper. Newtype [a] (List sep wrapper a)
External instance of the constraint type forall a. Monoid [a]
External instance of the constraint type forall a b sep.
(Newtype a b, Sep sep, Pretty b) =>
Pretty (List sep b a)
External instance of the constraint type Newtype (CompilerFlavor, VersionRange) TestedWith
External instance of the constraint type Sep FSep
External instance of the constraint type Pretty TestedWith
External instance of the constraint type forall a b sep.
(Newtype a b, Sep sep, Parsec b) =>
Parsec (List sep b a)
External instance of the constraint type Newtype (CompilerFlavor, VersionRange) TestedWith
External instance of the constraint type Sep FSep
External instance of the constraint type Parsec TestedWith
Evidence bound by a type signature of the constraint type FieldGrammar g
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)]
External instance of the constraint type forall a b. Functor (Pretext a b)
L.testedWith
    g PackageDescription
  (ShortText
   -> ShortText
   -> ShortText
   -> [SourceRepo]
   -> ShortText
   -> ShortText
   -> ShortText
   -> [(String, String)]
   -> Maybe BuildType
   -> Maybe SetupBuildInfo
   -> Maybe Library
   -> [Library]
   -> [Executable]
   -> [ForeignLib]
   -> [TestSuite]
   -> [Benchmark]
   -> [String]
   -> String
   -> [String]
   -> [String]
   -> [String]
   -> PackageDescription)
-> g PackageDescription ShortText
-> g PackageDescription
     (ShortText
      -> ShortText
      -> [SourceRepo]
      -> ShortText
      -> ShortText
      -> ShortText
      -> [(String, String)]
      -> Maybe BuildType
      -> Maybe SetupBuildInfo
      -> Maybe Library
      -> [Library]
      -> [Executable]
      -> [ForeignLib]
      -> [TestSuite]
      -> [Benchmark]
      -> [String]
      -> String
      -> [String]
      -> [String]
      -> [String]
      -> PackageDescription)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Applicative (g PackageDescription)
<*> FieldName
-> ALens' PackageDescription ShortText
-> g PackageDescription ShortText
forall (g :: * -> * -> *) s.
FieldGrammar g =>
FieldName -> ALens' s ShortText -> g s ShortText
Evidence bound by a type signature of the constraint type FieldGrammar g
freeTextFieldDefST  FieldName
"homepage"                                 ALens' PackageDescription ShortText
Lens' PackageDescription ShortText
External instance of the constraint type forall a b. Functor (Pretext a b)
L.homepage
    g PackageDescription
  (ShortText
   -> ShortText
   -> [SourceRepo]
   -> ShortText
   -> ShortText
   -> ShortText
   -> [(String, String)]
   -> Maybe BuildType
   -> Maybe SetupBuildInfo
   -> Maybe Library
   -> [Library]
   -> [Executable]
   -> [ForeignLib]
   -> [TestSuite]
   -> [Benchmark]
   -> [String]
   -> String
   -> [String]
   -> [String]
   -> [String]
   -> PackageDescription)
-> g PackageDescription ShortText
-> g PackageDescription
     (ShortText
      -> [SourceRepo]
      -> ShortText
      -> ShortText
      -> ShortText
      -> [(String, String)]
      -> Maybe BuildType
      -> Maybe SetupBuildInfo
      -> Maybe Library
      -> [Library]
      -> [Executable]
      -> [ForeignLib]
      -> [TestSuite]
      -> [Benchmark]
      -> [String]
      -> String
      -> [String]
      -> [String]
      -> [String]
      -> PackageDescription)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Applicative (g PackageDescription)
<*> FieldName
-> ALens' PackageDescription ShortText
-> g PackageDescription ShortText
forall (g :: * -> * -> *) s.
FieldGrammar g =>
FieldName -> ALens' s ShortText -> g s ShortText
Evidence bound by a type signature of the constraint type FieldGrammar g
freeTextFieldDefST  FieldName
"package-url"                              ALens' PackageDescription ShortText
Lens' PackageDescription ShortText
External instance of the constraint type forall a b. Functor (Pretext a b)
L.pkgUrl
    g PackageDescription
  (ShortText
   -> [SourceRepo]
   -> ShortText
   -> ShortText
   -> ShortText
   -> [(String, String)]
   -> Maybe BuildType
   -> Maybe SetupBuildInfo
   -> Maybe Library
   -> [Library]
   -> [Executable]
   -> [ForeignLib]
   -> [TestSuite]
   -> [Benchmark]
   -> [String]
   -> String
   -> [String]
   -> [String]
   -> [String]
   -> PackageDescription)
-> g PackageDescription ShortText
-> g PackageDescription
     ([SourceRepo]
      -> ShortText
      -> ShortText
      -> ShortText
      -> [(String, String)]
      -> Maybe BuildType
      -> Maybe SetupBuildInfo
      -> Maybe Library
      -> [Library]
      -> [Executable]
      -> [ForeignLib]
      -> [TestSuite]
      -> [Benchmark]
      -> [String]
      -> String
      -> [String]
      -> [String]
      -> [String]
      -> PackageDescription)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Applicative (g PackageDescription)
<*> FieldName
-> ALens' PackageDescription ShortText
-> g PackageDescription ShortText
forall (g :: * -> * -> *) s.
FieldGrammar g =>
FieldName -> ALens' s ShortText -> g s ShortText
Evidence bound by a type signature of the constraint type FieldGrammar g
freeTextFieldDefST   FieldName
"bug-reports"                              ALens' PackageDescription ShortText
Lens' PackageDescription ShortText
External instance of the constraint type forall a b. Functor (Pretext a b)
L.bugReports
    g PackageDescription
  ([SourceRepo]
   -> ShortText
   -> ShortText
   -> ShortText
   -> [(String, String)]
   -> Maybe BuildType
   -> Maybe SetupBuildInfo
   -> Maybe Library
   -> [Library]
   -> [Executable]
   -> [ForeignLib]
   -> [TestSuite]
   -> [Benchmark]
   -> [String]
   -> String
   -> [String]
   -> [String]
   -> [String]
   -> PackageDescription)
-> g PackageDescription [SourceRepo]
-> g PackageDescription
     (ShortText
      -> ShortText
      -> ShortText
      -> [(String, String)]
      -> Maybe BuildType
      -> Maybe SetupBuildInfo
      -> Maybe Library
      -> [Library]
      -> [Executable]
      -> [ForeignLib]
      -> [TestSuite]
      -> [Benchmark]
      -> [String]
      -> String
      -> [String]
      -> [String]
      -> [String]
      -> PackageDescription)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Applicative (g PackageDescription)
<*> [SourceRepo] -> g PackageDescription [SourceRepo]
forall (f :: * -> *) a. Applicative f => a -> f a
Evidence bound by a type signature of the constraint type Applicative (g PackageDescription)
pure [] -- source-repos are stanza
    g PackageDescription
  (ShortText
   -> ShortText
   -> ShortText
   -> [(String, String)]
   -> Maybe BuildType
   -> Maybe SetupBuildInfo
   -> Maybe Library
   -> [Library]
   -> [Executable]
   -> [ForeignLib]
   -> [TestSuite]
   -> [Benchmark]
   -> [String]
   -> String
   -> [String]
   -> [String]
   -> [String]
   -> PackageDescription)
-> g PackageDescription ShortText
-> g PackageDescription
     (ShortText
      -> ShortText
      -> [(String, String)]
      -> Maybe BuildType
      -> Maybe SetupBuildInfo
      -> Maybe Library
      -> [Library]
      -> [Executable]
      -> [ForeignLib]
      -> [TestSuite]
      -> [Benchmark]
      -> [String]
      -> String
      -> [String]
      -> [String]
      -> [String]
      -> PackageDescription)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Applicative (g PackageDescription)
<*> FieldName
-> ALens' PackageDescription ShortText
-> g PackageDescription ShortText
forall (g :: * -> * -> *) s.
FieldGrammar g =>
FieldName -> ALens' s ShortText -> g s ShortText
Evidence bound by a type signature of the constraint type FieldGrammar g
freeTextFieldDefST  FieldName
"synopsis"                                 ALens' PackageDescription ShortText
Lens' PackageDescription ShortText
External instance of the constraint type forall a b. Functor (Pretext a b)
L.synopsis
    g PackageDescription
  (ShortText
   -> ShortText
   -> [(String, String)]
   -> Maybe BuildType
   -> Maybe SetupBuildInfo
   -> Maybe Library
   -> [Library]
   -> [Executable]
   -> [ForeignLib]
   -> [TestSuite]
   -> [Benchmark]
   -> [String]
   -> String
   -> [String]
   -> [String]
   -> [String]
   -> PackageDescription)
-> g PackageDescription ShortText
-> g PackageDescription
     (ShortText
      -> [(String, String)]
      -> Maybe BuildType
      -> Maybe SetupBuildInfo
      -> Maybe Library
      -> [Library]
      -> [Executable]
      -> [ForeignLib]
      -> [TestSuite]
      -> [Benchmark]
      -> [String]
      -> String
      -> [String]
      -> [String]
      -> [String]
      -> PackageDescription)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Applicative (g PackageDescription)
<*> FieldName
-> ALens' PackageDescription ShortText
-> g PackageDescription ShortText
forall (g :: * -> * -> *) s.
FieldGrammar g =>
FieldName -> ALens' s ShortText -> g s ShortText
Evidence bound by a type signature of the constraint type FieldGrammar g
freeTextFieldDefST  FieldName
"description"                              ALens' PackageDescription ShortText
Lens' PackageDescription ShortText
External instance of the constraint type forall a b. Functor (Pretext a b)
L.description
    g PackageDescription
  (ShortText
   -> [(String, String)]
   -> Maybe BuildType
   -> Maybe SetupBuildInfo
   -> Maybe Library
   -> [Library]
   -> [Executable]
   -> [ForeignLib]
   -> [TestSuite]
   -> [Benchmark]
   -> [String]
   -> String
   -> [String]
   -> [String]
   -> [String]
   -> PackageDescription)
-> g PackageDescription ShortText
-> g PackageDescription
     ([(String, String)]
      -> Maybe BuildType
      -> Maybe SetupBuildInfo
      -> Maybe Library
      -> [Library]
      -> [Executable]
      -> [ForeignLib]
      -> [TestSuite]
      -> [Benchmark]
      -> [String]
      -> String
      -> [String]
      -> [String]
      -> [String]
      -> PackageDescription)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Applicative (g PackageDescription)
<*> FieldName
-> ALens' PackageDescription ShortText
-> g PackageDescription ShortText
forall (g :: * -> * -> *) s.
FieldGrammar g =>
FieldName -> ALens' s ShortText -> g s ShortText
Evidence bound by a type signature of the constraint type FieldGrammar g
freeTextFieldDefST  FieldName
"category"                                 ALens' PackageDescription ShortText
Lens' PackageDescription ShortText
External instance of the constraint type forall a b. Functor (Pretext a b)
L.category
    g PackageDescription
  ([(String, String)]
   -> Maybe BuildType
   -> Maybe SetupBuildInfo
   -> Maybe Library
   -> [Library]
   -> [Executable]
   -> [ForeignLib]
   -> [TestSuite]
   -> [Benchmark]
   -> [String]
   -> String
   -> [String]
   -> [String]
   -> [String]
   -> PackageDescription)
-> g PackageDescription [(String, String)]
-> g PackageDescription
     (Maybe BuildType
      -> Maybe SetupBuildInfo
      -> Maybe Library
      -> [Library]
      -> [Executable]
      -> [ForeignLib]
      -> [TestSuite]
      -> [Benchmark]
      -> [String]
      -> String
      -> [String]
      -> [String]
      -> [String]
      -> PackageDescription)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Applicative (g PackageDescription)
<*> FieldName
-> ALens' PackageDescription [(String, String)]
-> g PackageDescription [(String, String)]
forall (g :: * -> * -> *) s.
FieldGrammar g =>
FieldName -> ALens' s [(String, String)] -> g s [(String, String)]
Evidence bound by a type signature of the constraint type FieldGrammar g
prefixedFields      FieldName
"x-"                                       ALens' PackageDescription [(String, String)]
Lens' PackageDescription [(String, String)]
External instance of the constraint type forall a b. Functor (Pretext a b)
L.customFieldsPD
    g PackageDescription
  (Maybe BuildType
   -> Maybe SetupBuildInfo
   -> Maybe Library
   -> [Library]
   -> [Executable]
   -> [ForeignLib]
   -> [TestSuite]
   -> [Benchmark]
   -> [String]
   -> String
   -> [String]
   -> [String]
   -> [String]
   -> PackageDescription)
-> g PackageDescription (Maybe BuildType)
-> g PackageDescription
     (Maybe SetupBuildInfo
      -> Maybe Library
      -> [Library]
      -> [Executable]
      -> [ForeignLib]
      -> [TestSuite]
      -> [Benchmark]
      -> [String]
      -> String
      -> [String]
      -> [String]
      -> [String]
      -> PackageDescription)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Applicative (g PackageDescription)
<*> FieldName
-> ALens' PackageDescription (Maybe BuildType)
-> g PackageDescription (Maybe BuildType)
forall (g :: * -> * -> *) a s.
(FieldGrammar g, Parsec a, Pretty a) =>
FieldName -> ALens' s (Maybe a) -> g s (Maybe a)
External instance of the constraint type Pretty BuildType
External instance of the constraint type Parsec BuildType
Evidence bound by a type signature of the constraint type FieldGrammar g
optionalField       FieldName
"build-type"                               ALens' PackageDescription (Maybe BuildType)
Lens' PackageDescription (Maybe BuildType)
External instance of the constraint type forall a b. Functor (Pretext a b)
L.buildTypeRaw
    g PackageDescription
  (Maybe SetupBuildInfo
   -> Maybe Library
   -> [Library]
   -> [Executable]
   -> [ForeignLib]
   -> [TestSuite]
   -> [Benchmark]
   -> [String]
   -> String
   -> [String]
   -> [String]
   -> [String]
   -> PackageDescription)
-> g PackageDescription (Maybe SetupBuildInfo)
-> g PackageDescription
     (Maybe Library
      -> [Library]
      -> [Executable]
      -> [ForeignLib]
      -> [TestSuite]
      -> [Benchmark]
      -> [String]
      -> String
      -> [String]
      -> [String]
      -> [String]
      -> PackageDescription)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Applicative (g PackageDescription)
<*> Maybe SetupBuildInfo -> g PackageDescription (Maybe SetupBuildInfo)
forall (f :: * -> *) a. Applicative f => a -> f a
Evidence bound by a type signature of the constraint type Applicative (g PackageDescription)
pure Maybe SetupBuildInfo
forall a. Maybe a
Nothing -- custom-setup
    -- components
    g PackageDescription
  (Maybe Library
   -> [Library]
   -> [Executable]
   -> [ForeignLib]
   -> [TestSuite]
   -> [Benchmark]
   -> [String]
   -> String
   -> [String]
   -> [String]
   -> [String]
   -> PackageDescription)
-> g PackageDescription (Maybe Library)
-> g PackageDescription
     ([Library]
      -> [Executable]
      -> [ForeignLib]
      -> [TestSuite]
      -> [Benchmark]
      -> [String]
      -> String
      -> [String]
      -> [String]
      -> [String]
      -> PackageDescription)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Applicative (g PackageDescription)
<*> Maybe Library -> g PackageDescription (Maybe Library)
forall (f :: * -> *) a. Applicative f => a -> f a
Evidence bound by a type signature of the constraint type Applicative (g PackageDescription)
pure Maybe Library
forall a. Maybe a
Nothing  -- lib
    g PackageDescription
  ([Library]
   -> [Executable]
   -> [ForeignLib]
   -> [TestSuite]
   -> [Benchmark]
   -> [String]
   -> String
   -> [String]
   -> [String]
   -> [String]
   -> PackageDescription)
-> g PackageDescription [Library]
-> g PackageDescription
     ([Executable]
      -> [ForeignLib]
      -> [TestSuite]
      -> [Benchmark]
      -> [String]
      -> String
      -> [String]
      -> [String]
      -> [String]
      -> PackageDescription)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Applicative (g PackageDescription)
<*> [Library] -> g PackageDescription [Library]
forall (f :: * -> *) a. Applicative f => a -> f a
Evidence bound by a type signature of the constraint type Applicative (g PackageDescription)
pure []       -- sub libs
    g PackageDescription
  ([Executable]
   -> [ForeignLib]
   -> [TestSuite]
   -> [Benchmark]
   -> [String]
   -> String
   -> [String]
   -> [String]
   -> [String]
   -> PackageDescription)
-> g PackageDescription [Executable]
-> g PackageDescription
     ([ForeignLib]
      -> [TestSuite]
      -> [Benchmark]
      -> [String]
      -> String
      -> [String]
      -> [String]
      -> [String]
      -> PackageDescription)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Applicative (g PackageDescription)
<*> [Executable] -> g PackageDescription [Executable]
forall (f :: * -> *) a. Applicative f => a -> f a
Evidence bound by a type signature of the constraint type Applicative (g PackageDescription)
pure []       -- executables
    g PackageDescription
  ([ForeignLib]
   -> [TestSuite]
   -> [Benchmark]
   -> [String]
   -> String
   -> [String]
   -> [String]
   -> [String]
   -> PackageDescription)
-> g PackageDescription [ForeignLib]
-> g PackageDescription
     ([TestSuite]
      -> [Benchmark]
      -> [String]
      -> String
      -> [String]
      -> [String]
      -> [String]
      -> PackageDescription)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Applicative (g PackageDescription)
<*> [ForeignLib] -> g PackageDescription [ForeignLib]
forall (f :: * -> *) a. Applicative f => a -> f a
Evidence bound by a type signature of the constraint type Applicative (g PackageDescription)
pure []       -- foreign libs
    g PackageDescription
  ([TestSuite]
   -> [Benchmark]
   -> [String]
   -> String
   -> [String]
   -> [String]
   -> [String]
   -> PackageDescription)
-> g PackageDescription [TestSuite]
-> g PackageDescription
     ([Benchmark]
      -> [String]
      -> String
      -> [String]
      -> [String]
      -> [String]
      -> PackageDescription)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Applicative (g PackageDescription)
<*> [TestSuite] -> g PackageDescription [TestSuite]
forall (f :: * -> *) a. Applicative f => a -> f a
Evidence bound by a type signature of the constraint type Applicative (g PackageDescription)
pure []       -- test suites
    g PackageDescription
  ([Benchmark]
   -> [String]
   -> String
   -> [String]
   -> [String]
   -> [String]
   -> PackageDescription)
-> g PackageDescription [Benchmark]
-> g PackageDescription
     ([String]
      -> String
      -> [String]
      -> [String]
      -> [String]
      -> PackageDescription)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Applicative (g PackageDescription)
<*> [Benchmark] -> g PackageDescription [Benchmark]
forall (f :: * -> *) a. Applicative f => a -> f a
Evidence bound by a type signature of the constraint type Applicative (g PackageDescription)
pure []       -- benchmarks
    --  * Files
    g PackageDescription
  ([String]
   -> String
   -> [String]
   -> [String]
   -> [String]
   -> PackageDescription)
-> g PackageDescription [String]
-> g PackageDescription
     (String -> [String] -> [String] -> [String] -> PackageDescription)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Applicative (g PackageDescription)
<*> FieldName
-> ([String] -> List VCat FilePathNT String)
-> ALens' PackageDescription [String]
-> g PackageDescription [String]
forall (g :: * -> * -> *) b a s.
(FieldGrammar g, Parsec b, Pretty b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
External instance of the constraint type forall a sep wrapper. Newtype [a] (List sep wrapper a)
External instance of the constraint type forall a. Monoid [a]
External instance of the constraint type forall a b sep.
(Newtype a b, Sep sep, Pretty b) =>
Pretty (List sep b a)
External instance of the constraint type Newtype String FilePathNT
External instance of the constraint type Sep VCat
External instance of the constraint type Pretty FilePathNT
External instance of the constraint type forall a b sep.
(Newtype a b, Sep sep, Parsec b) =>
Parsec (List sep b a)
External instance of the constraint type Newtype String FilePathNT
External instance of the constraint type Sep VCat
External instance of the constraint type Parsec FilePathNT
Evidence bound by a type signature of the constraint type FieldGrammar g
monoidalFieldAla    FieldName
"data-files"         (VCat
-> (String -> FilePathNT)
-> [String]
-> List VCat FilePathNT String
forall sep a b. sep -> (a -> b) -> [a] -> List sep b a
alaList' VCat
VCat String -> FilePathNT
FilePathNT) ALens' PackageDescription [String]
Lens' PackageDescription [String]
External instance of the constraint type forall a b. Functor (Pretext a b)
L.dataFiles
    g PackageDescription
  (String -> [String] -> [String] -> [String] -> PackageDescription)
-> g PackageDescription String
-> g PackageDescription
     ([String] -> [String] -> [String] -> PackageDescription)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Applicative (g PackageDescription)
<*> FieldName
-> (String -> FilePathNT)
-> ALens' PackageDescription String
-> String
-> g PackageDescription String
forall (g :: * -> * -> *) b a s.
(FieldGrammar g, Parsec b, Pretty b, Newtype a b, Eq a) =>
FieldName -> (a -> b) -> ALens' s a -> a -> g s a
External instance of the constraint type forall a. Eq a => Eq [a]
External instance of the constraint type Eq Char
External instance of the constraint type Newtype String FilePathNT
External instance of the constraint type Pretty FilePathNT
External instance of the constraint type Parsec FilePathNT
Evidence bound by a type signature of the constraint type FieldGrammar g
optionalFieldDefAla FieldName
"data-dir"           String -> FilePathNT
FilePathNT                 ALens' PackageDescription String
Lens' PackageDescription String
External instance of the constraint type forall a b. Functor (Pretext a b)
L.dataDir String
""
    g PackageDescription
  ([String] -> [String] -> [String] -> PackageDescription)
-> g PackageDescription [String]
-> g PackageDescription
     ([String] -> [String] -> PackageDescription)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Applicative (g PackageDescription)
<*> FieldName
-> ([String] -> List VCat FilePathNT String)
-> ALens' PackageDescription [String]
-> g PackageDescription [String]
forall (g :: * -> * -> *) b a s.
(FieldGrammar g, Parsec b, Pretty b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
External instance of the constraint type forall a sep wrapper. Newtype [a] (List sep wrapper a)
External instance of the constraint type forall a. Monoid [a]
External instance of the constraint type forall a b sep.
(Newtype a b, Sep sep, Pretty b) =>
Pretty (List sep b a)
External instance of the constraint type Newtype String FilePathNT
External instance of the constraint type Sep VCat
External instance of the constraint type Pretty FilePathNT
External instance of the constraint type forall a b sep.
(Newtype a b, Sep sep, Parsec b) =>
Parsec (List sep b a)
External instance of the constraint type Newtype String FilePathNT
External instance of the constraint type Sep VCat
External instance of the constraint type Parsec FilePathNT
Evidence bound by a type signature of the constraint type FieldGrammar g
monoidalFieldAla    FieldName
"extra-source-files" (VCat
-> (String -> FilePathNT)
-> [String]
-> List VCat FilePathNT String
forall sep a b. sep -> (a -> b) -> [a] -> List sep b a
alaList' VCat
VCat String -> FilePathNT
FilePathNT) ALens' PackageDescription [String]
Lens' PackageDescription [String]
External instance of the constraint type forall a b. Functor (Pretext a b)
L.extraSrcFiles
    g PackageDescription ([String] -> [String] -> PackageDescription)
-> g PackageDescription [String]
-> g PackageDescription ([String] -> PackageDescription)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Applicative (g PackageDescription)
<*> FieldName
-> ([String] -> List VCat FilePathNT String)
-> ALens' PackageDescription [String]
-> g PackageDescription [String]
forall (g :: * -> * -> *) b a s.
(FieldGrammar g, Parsec b, Pretty b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
External instance of the constraint type forall a sep wrapper. Newtype [a] (List sep wrapper a)
External instance of the constraint type forall a. Monoid [a]
External instance of the constraint type forall a b sep.
(Newtype a b, Sep sep, Pretty b) =>
Pretty (List sep b a)
External instance of the constraint type Newtype String FilePathNT
External instance of the constraint type Sep VCat
External instance of the constraint type Pretty FilePathNT
External instance of the constraint type forall a b sep.
(Newtype a b, Sep sep, Parsec b) =>
Parsec (List sep b a)
External instance of the constraint type Newtype String FilePathNT
External instance of the constraint type Sep VCat
External instance of the constraint type Parsec FilePathNT
Evidence bound by a type signature of the constraint type FieldGrammar g
monoidalFieldAla    FieldName
"extra-tmp-files"    (VCat
-> (String -> FilePathNT)
-> [String]
-> List VCat FilePathNT String
forall sep a b. sep -> (a -> b) -> [a] -> List sep b a
alaList' VCat
VCat String -> FilePathNT
FilePathNT) ALens' PackageDescription [String]
Lens' PackageDescription [String]
External instance of the constraint type forall a b. Functor (Pretext a b)
L.extraTmpFiles
    g PackageDescription ([String] -> PackageDescription)
-> g PackageDescription [String]
-> g PackageDescription PackageDescription
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Applicative (g PackageDescription)
<*> FieldName
-> ([String] -> List VCat FilePathNT String)
-> ALens' PackageDescription [String]
-> g PackageDescription [String]
forall (g :: * -> * -> *) b a s.
(FieldGrammar g, Parsec b, Pretty b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
External instance of the constraint type forall a sep wrapper. Newtype [a] (List sep wrapper a)
External instance of the constraint type forall a. Monoid [a]
External instance of the constraint type forall a b sep.
(Newtype a b, Sep sep, Pretty b) =>
Pretty (List sep b a)
External instance of the constraint type Newtype String FilePathNT
External instance of the constraint type Sep VCat
External instance of the constraint type Pretty FilePathNT
External instance of the constraint type forall a b sep.
(Newtype a b, Sep sep, Parsec b) =>
Parsec (List sep b a)
External instance of the constraint type Newtype String FilePathNT
External instance of the constraint type Sep VCat
External instance of the constraint type Parsec FilePathNT
Evidence bound by a type signature of the constraint type FieldGrammar g
monoidalFieldAla    FieldName
"extra-doc-files"    (VCat
-> (String -> FilePathNT)
-> [String]
-> List VCat FilePathNT String
forall sep a b. sep -> (a -> b) -> [a] -> List sep b a
alaList' VCat
VCat String -> FilePathNT
FilePathNT) ALens' PackageDescription [String]
Lens' PackageDescription [String]
External instance of the constraint type forall a b. Functor (Pretext a b)
L.extraDocFiles
  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
External instance of the constraint type forall (f :: * -> *). Applicative f => Functor f
Evidence bound by a type signature of the constraint type Applicative (g PackageIdentifier)
<$> FieldName
-> ALens' PackageIdentifier PackageName
-> g PackageIdentifier PackageName
forall (g :: * -> * -> *) a s.
(FieldGrammar g, Parsec a, Pretty a) =>
FieldName -> ALens' s a -> g s a
External instance of the constraint type Pretty PackageName
External instance of the constraint type Parsec PackageName
Evidence bound by a type signature of the constraint type FieldGrammar g
uniqueField FieldName
"name"    ALens' PackageIdentifier PackageName
Lens' PackageIdentifier PackageName
External instance of the constraint type forall a b. Functor (Pretext a b)
L.pkgName
        g PackageIdentifier (Version -> PackageIdentifier)
-> g PackageIdentifier Version
-> g PackageIdentifier PackageIdentifier
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Applicative (g PackageIdentifier)
<*> FieldName
-> ALens' PackageIdentifier Version -> g PackageIdentifier Version
forall (g :: * -> * -> *) a s.
(FieldGrammar g, Parsec a, Pretty a) =>
FieldName -> ALens' s a -> g s a
External instance of the constraint type Pretty Version
External instance of the constraint type Parsec Version
Evidence bound by a type signature of the constraint type FieldGrammar g
uniqueField FieldName
"version" ALens' PackageIdentifier Version
Lens' PackageIdentifier Version
External instance of the constraint type forall a b. Functor (Pretext a b)
L.pkgVersion

    licenseFilesGrammar :: g PackageDescription [String]
licenseFilesGrammar = [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
(++)
        -- TODO: neither field is deprecated
        -- should we pretty print license-file if there's single license file
        -- and license-files when more
        ([String] -> [String] -> [String])
-> g PackageDescription [String]
-> g PackageDescription ([String] -> [String])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type forall (f :: * -> *). Applicative f => Functor f
Evidence bound by a type signature of the constraint type Applicative (g PackageDescription)
<$> FieldName
-> ([String] -> List FSep FilePathNT String)
-> ALens' PackageDescription [String]
-> g PackageDescription [String]
forall (g :: * -> * -> *) b a s.
(FieldGrammar g, Parsec b, Pretty b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
External instance of the constraint type forall a sep wrapper. Newtype [a] (List sep wrapper a)
External instance of the constraint type forall a. Monoid [a]
External instance of the constraint type forall a b sep.
(Newtype a b, Sep sep, Pretty b) =>
Pretty (List sep b a)
External instance of the constraint type Newtype String FilePathNT
External instance of the constraint type Sep FSep
External instance of the constraint type Pretty FilePathNT
External instance of the constraint type forall a b sep.
(Newtype a b, Sep sep, Parsec b) =>
Parsec (List sep b a)
External instance of the constraint type Newtype String FilePathNT
External instance of the constraint type Sep FSep
External instance of the constraint type Parsec FilePathNT
Evidence bound by a type signature of the constraint type FieldGrammar g
monoidalFieldAla    FieldName
"license-file"  (FSep
-> (String -> FilePathNT)
-> [String]
-> List FSep FilePathNT String
forall sep a b. sep -> (a -> b) -> [a] -> List sep b a
alaList' FSep
FSep String -> FilePathNT
FilePathNT)  ALens' PackageDescription [String]
Lens' PackageDescription [String]
External instance of the constraint type forall a b. Functor (Pretext a b)
L.licenseFiles
        g PackageDescription ([String] -> [String])
-> g PackageDescription [String] -> g PackageDescription [String]
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Applicative (g PackageDescription)
<*> FieldName
-> ([String] -> List FSep FilePathNT String)
-> ALens' PackageDescription [String]
-> g PackageDescription [String]
forall (g :: * -> * -> *) b a s.
(FieldGrammar g, Parsec b, Pretty b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
External instance of the constraint type forall a sep wrapper. Newtype [a] (List sep wrapper a)
External instance of the constraint type forall a. Monoid [a]
External instance of the constraint type forall a b sep.
(Newtype a b, Sep sep, Pretty b) =>
Pretty (List sep b a)
External instance of the constraint type Newtype String FilePathNT
External instance of the constraint type Sep FSep
External instance of the constraint type Pretty FilePathNT
External instance of the constraint type forall a b sep.
(Newtype a b, Sep sep, Parsec b) =>
Parsec (List sep b a)
External instance of the constraint type Newtype String FilePathNT
External instance of the constraint type Sep FSep
External instance of the constraint type Parsec FilePathNT
Evidence bound by a type signature of the constraint type FieldGrammar g
monoidalFieldAla    FieldName
"license-files"  (FSep
-> (String -> FilePathNT)
-> [String]
-> List FSep FilePathNT String
forall sep a b. sep -> (a -> b) -> [a] -> List sep b a
alaList' FSep
FSep String -> FilePathNT
FilePathNT) ALens' PackageDescription [String]
Lens' PackageDescription [String]
External instance of the constraint type forall a b. Functor (Pretext a b)
L.licenseFiles
            g PackageDescription [String]
-> (g PackageDescription [String] -> g PackageDescription [String])
-> g PackageDescription [String]
forall a b. a -> (a -> b) -> b
^^^ g PackageDescription [String] -> g PackageDescription [String]
forall (g :: * -> * -> *) s a. FieldGrammar g => g s a -> g s a
Evidence bound by a type signature of the constraint type FieldGrammar g
hiddenField

-------------------------------------------------------------------------------
-- Library
-------------------------------------------------------------------------------

libraryFieldGrammar
    :: (FieldGrammar g, Applicative (g Library), Applicative (g BuildInfo))
    => LibraryName
    -> g Library Library
libraryFieldGrammar :: 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
External instance of the constraint type forall (f :: * -> *). Applicative f => Functor f
Evidence bound by a type signature of the constraint type Applicative (g Library)
<$> FieldName
-> ([ModuleName] -> List VCat (MQuoted ModuleName) ModuleName)
-> ALens' Library [ModuleName]
-> g Library [ModuleName]
forall (g :: * -> * -> *) b a s.
(FieldGrammar g, Parsec b, Pretty b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
External instance of the constraint type forall a sep wrapper. Newtype [a] (List sep wrapper a)
External instance of the constraint type forall a. Monoid [a]
External instance of the constraint type forall a b sep.
(Newtype a b, Sep sep, Pretty b) =>
Pretty (List sep b a)
External instance of the constraint type forall a. Newtype a (MQuoted a)
External instance of the constraint type Sep VCat
External instance of the constraint type forall a. Pretty a => Pretty (MQuoted a)
External instance of the constraint type Pretty ModuleName
External instance of the constraint type forall a b sep.
(Newtype a b, Sep sep, Parsec b) =>
Parsec (List sep b a)
External instance of the constraint type forall a. Newtype a (MQuoted a)
External instance of the constraint type Sep VCat
External instance of the constraint type forall a. Parsec a => Parsec (MQuoted a)
External instance of the constraint type Parsec ModuleName
Evidence bound by a type signature of the constraint type FieldGrammar g
monoidalFieldAla  FieldName
"exposed-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' Library [ModuleName]
Lens' Library [ModuleName]
External instance of the constraint type forall a b. Functor (Pretext a b)
L.exposedModules
    g Library
  ([ModuleReexport]
   -> [ModuleName]
   -> Bool
   -> LibraryVisibility
   -> BuildInfo
   -> Library)
-> g Library [ModuleReexport]
-> g Library
     ([ModuleName] -> Bool -> LibraryVisibility -> BuildInfo -> Library)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Applicative (g Library)
<*> FieldName
-> ([ModuleReexport]
    -> List CommaVCat (Identity ModuleReexport) ModuleReexport)
-> ALens' Library [ModuleReexport]
-> g Library [ModuleReexport]
forall (g :: * -> * -> *) b a s.
(FieldGrammar g, Parsec b, Pretty b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
External instance of the constraint type forall a sep wrapper. Newtype [a] (List sep wrapper a)
External instance of the constraint type forall a. Monoid [a]
External instance of the constraint type forall a b sep.
(Newtype a b, Sep sep, Pretty b) =>
Pretty (List sep b a)
External instance of the constraint type forall a. Newtype a (Identity a)
External instance of the constraint type Sep CommaVCat
External instance of the constraint type forall a. Pretty a => Pretty (Identity a)
External instance of the constraint type Pretty ModuleReexport
External instance of the constraint type forall a b sep.
(Newtype a b, Sep sep, Parsec b) =>
Parsec (List sep b a)
External instance of the constraint type forall a. Newtype a (Identity a)
External instance of the constraint type Sep CommaVCat
External instance of the constraint type forall a. Parsec a => Parsec (Identity a)
External instance of the constraint type Parsec ModuleReexport
Evidence bound by a type signature of the constraint type FieldGrammar g
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]
External instance of the constraint type forall a b. Functor (Pretext a b)
L.reexportedModules
    g Library
  ([ModuleName] -> Bool -> LibraryVisibility -> BuildInfo -> Library)
-> g Library [ModuleName]
-> g Library (Bool -> LibraryVisibility -> BuildInfo -> Library)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Applicative (g Library)
<*> FieldName
-> ([ModuleName] -> List VCat (MQuoted ModuleName) ModuleName)
-> ALens' Library [ModuleName]
-> g Library [ModuleName]
forall (g :: * -> * -> *) b a s.
(FieldGrammar g, Parsec b, Pretty b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
External instance of the constraint type forall a sep wrapper. Newtype [a] (List sep wrapper a)
External instance of the constraint type forall a. Monoid [a]
External instance of the constraint type forall a b sep.
(Newtype a b, Sep sep, Pretty b) =>
Pretty (List sep b a)
External instance of the constraint type forall a. Newtype a (MQuoted a)
External instance of the constraint type Sep VCat
External instance of the constraint type forall a. Pretty a => Pretty (MQuoted a)
External instance of the constraint type Pretty ModuleName
External instance of the constraint type forall a b sep.
(Newtype a b, Sep sep, Parsec b) =>
Parsec (List sep b a)
External instance of the constraint type forall a. Newtype a (MQuoted a)
External instance of the constraint type Sep VCat
External instance of the constraint type forall a. Parsec a => Parsec (MQuoted a)
External instance of the constraint type Parsec ModuleName
Evidence bound by a type signature of the constraint type FieldGrammar g
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]
External instance of the constraint type forall a b. Functor (Pretext a b)
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 (g :: * -> * -> *) a s.
FieldGrammar g =>
CabalSpecVersion -> a -> g s a -> g s a
Evidence bound by a type signature of the constraint type FieldGrammar g
availableSince CabalSpecVersion
CabalSpecV2_0 []
    g Library (Bool -> LibraryVisibility -> BuildInfo -> Library)
-> g Library Bool
-> g Library (LibraryVisibility -> BuildInfo -> Library)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Applicative (g Library)
<*> FieldName -> ALens' Library Bool -> Bool -> g Library Bool
forall (g :: * -> * -> *) s.
FieldGrammar g =>
FieldName -> ALens' s Bool -> Bool -> g s Bool
Evidence bound by a type signature of the constraint type FieldGrammar g
booleanFieldDef   FieldName
"exposed"                                    ALens' Library Bool
Lens' Library Bool
External instance of the constraint type forall a b. Functor (Pretext a b)
L.libExposed Bool
True
    g Library (LibraryVisibility -> BuildInfo -> Library)
-> g Library LibraryVisibility -> g Library (BuildInfo -> Library)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Applicative (g Library)
<*> g Library LibraryVisibility
visibilityField
    g Library (BuildInfo -> Library)
-> g Library BuildInfo -> g Library Library
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Applicative (g Library)
<*> ALens' Library BuildInfo
-> g BuildInfo BuildInfo -> g Library BuildInfo
forall (g :: * -> * -> *) a b c.
FieldGrammar g =>
ALens' a b -> g b c -> g a c
Evidence bound by a type signature of the constraint type FieldGrammar g
blurFieldGrammar ALens' Library BuildInfo
Lens' Library BuildInfo
External instance of the constraint type forall a b. Functor (Pretext a b)
L.libBuildInfo g BuildInfo BuildInfo
forall (g :: * -> * -> *).
(FieldGrammar g, Applicative (g BuildInfo)) =>
g BuildInfo BuildInfo
Evidence bound by a type signature of the constraint type Applicative (g BuildInfo)
Evidence bound by a type signature of the constraint type FieldGrammar g
buildInfoFieldGrammar
  where
    visibilityField :: g Library LibraryVisibility
visibilityField = case LibraryName
n of
        -- nameless/"main" libraries are public
        LibraryName
LMainLibName -> LibraryVisibility -> g Library LibraryVisibility
forall (f :: * -> *) a. Applicative f => a -> f a
Evidence bound by a type signature of the constraint type Applicative (g Library)
pure LibraryVisibility
LibraryVisibilityPublic
        -- named libraries have the field
        LSubLibName UnqualComponentName
_ ->
            FieldName
-> ALens' Library LibraryVisibility
-> LibraryVisibility
-> g Library LibraryVisibility
forall (g :: * -> * -> *) s a.
(FieldGrammar g, Functor (g s), Parsec a, Pretty a, Eq a) =>
FieldName -> ALens' s a -> a -> g s a
External instance of the constraint type Eq LibraryVisibility
External instance of the constraint type Pretty LibraryVisibility
External instance of the constraint type Parsec LibraryVisibility
External instance of the constraint type forall (f :: * -> *). Applicative f => Functor f
Evidence bound by a type signature of the constraint type Applicative (g Library)
Evidence bound by a type signature of the constraint type FieldGrammar g
optionalFieldDef FieldName
"visibility" ALens' Library LibraryVisibility
Lens' Library LibraryVisibility
External instance of the constraint type forall a b. Functor (Pretext a b)
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 (g :: * -> * -> *) a s.
FieldGrammar g =>
CabalSpecVersion -> a -> g s a -> g s a
Evidence bound by a type signature of the constraint type FieldGrammar g
availableSince CabalSpecVersion
CabalSpecV3_0 LibraryVisibility
LibraryVisibilityPrivate

{-# SPECIALIZE libraryFieldGrammar :: LibraryName -> ParsecFieldGrammar' Library #-}
{-# SPECIALIZE libraryFieldGrammar :: LibraryName -> PrettyFieldGrammar' Library #-}

-------------------------------------------------------------------------------
-- Foreign library
-------------------------------------------------------------------------------

foreignLibFieldGrammar
    :: (FieldGrammar g, Applicative (g ForeignLib), Applicative (g BuildInfo))
    => UnqualComponentName -> g ForeignLib ForeignLib
foreignLibFieldGrammar :: UnqualComponentName -> g ForeignLib ForeignLib
foreignLibFieldGrammar UnqualComponentName
n = UnqualComponentName
-> ForeignLibType
-> [ForeignLibOption]
-> BuildInfo
-> Maybe LibVersionInfo
-> Maybe Version
-> [String]
-> ForeignLib
ForeignLib UnqualComponentName
n
    (ForeignLibType
 -> [ForeignLibOption]
 -> BuildInfo
 -> Maybe LibVersionInfo
 -> Maybe Version
 -> [String]
 -> ForeignLib)
-> g ForeignLib ForeignLibType
-> g ForeignLib
     ([ForeignLibOption]
      -> BuildInfo
      -> Maybe LibVersionInfo
      -> Maybe Version
      -> [String]
      -> ForeignLib)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type forall (f :: * -> *). Applicative f => Functor f
Evidence bound by a type signature of the constraint type Applicative (g ForeignLib)
<$> FieldName
-> ALens' ForeignLib ForeignLibType
-> ForeignLibType
-> g ForeignLib ForeignLibType
forall (g :: * -> * -> *) s a.
(FieldGrammar g, Functor (g s), Parsec a, Pretty a, Eq a) =>
FieldName -> ALens' s a -> a -> g s a
External instance of the constraint type Eq ForeignLibType
External instance of the constraint type Pretty ForeignLibType
External instance of the constraint type Parsec ForeignLibType
External instance of the constraint type forall (f :: * -> *). Applicative f => Functor f
Evidence bound by a type signature of the constraint type Applicative (g ForeignLib)
Evidence bound by a type signature of the constraint type FieldGrammar g
optionalFieldDef FieldName
"type"                                         ALens' ForeignLib ForeignLibType
Lens' ForeignLib ForeignLibType
External instance of the constraint type forall a b. Functor (Pretext a b)
L.foreignLibType ForeignLibType
ForeignLibTypeUnknown
    g ForeignLib
  ([ForeignLibOption]
   -> BuildInfo
   -> Maybe LibVersionInfo
   -> Maybe Version
   -> [String]
   -> ForeignLib)
-> g ForeignLib [ForeignLibOption]
-> g ForeignLib
     (BuildInfo
      -> Maybe LibVersionInfo -> Maybe Version -> [String] -> ForeignLib)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Applicative (g ForeignLib)
<*> FieldName
-> ([ForeignLibOption]
    -> List FSep (Identity ForeignLibOption) ForeignLibOption)
-> ALens' ForeignLib [ForeignLibOption]
-> g ForeignLib [ForeignLibOption]
forall (g :: * -> * -> *) b a s.
(FieldGrammar g, Parsec b, Pretty b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
External instance of the constraint type forall a sep wrapper. Newtype [a] (List sep wrapper a)
External instance of the constraint type forall a. Monoid [a]
External instance of the constraint type forall a b sep.
(Newtype a b, Sep sep, Pretty b) =>
Pretty (List sep b a)
External instance of the constraint type forall a. Newtype a (Identity a)
External instance of the constraint type Sep FSep
External instance of the constraint type forall a. Pretty a => Pretty (Identity a)
External instance of the constraint type Pretty ForeignLibOption
External instance of the constraint type forall a b sep.
(Newtype a b, Sep sep, Parsec b) =>
Parsec (List sep b a)
External instance of the constraint type forall a. Newtype a (Identity a)
External instance of the constraint type Sep FSep
External instance of the constraint type forall a. Parsec a => Parsec (Identity a)
External instance of the constraint type Parsec ForeignLibOption
Evidence bound by a type signature of the constraint type FieldGrammar g
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]
External instance of the constraint type forall a b. Functor (Pretext a b)
L.foreignLibOptions
    g ForeignLib
  (BuildInfo
   -> Maybe LibVersionInfo -> Maybe Version -> [String] -> ForeignLib)
-> g ForeignLib BuildInfo
-> g ForeignLib
     (Maybe LibVersionInfo -> Maybe Version -> [String] -> ForeignLib)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Applicative (g ForeignLib)
<*> ALens' ForeignLib BuildInfo
-> g BuildInfo BuildInfo -> g ForeignLib BuildInfo
forall (g :: * -> * -> *) a b c.
FieldGrammar g =>
ALens' a b -> g b c -> g a c
Evidence bound by a type signature of the constraint type FieldGrammar g
blurFieldGrammar ALens' ForeignLib BuildInfo
Lens' ForeignLib BuildInfo
External instance of the constraint type forall a b. Functor (Pretext a b)
L.foreignLibBuildInfo g BuildInfo BuildInfo
forall (g :: * -> * -> *).
(FieldGrammar g, Applicative (g BuildInfo)) =>
g BuildInfo BuildInfo
Evidence bound by a type signature of the constraint type Applicative (g BuildInfo)
Evidence bound by a type signature of the constraint type FieldGrammar g
buildInfoFieldGrammar
    g ForeignLib
  (Maybe LibVersionInfo -> Maybe Version -> [String] -> ForeignLib)
-> g ForeignLib (Maybe LibVersionInfo)
-> g ForeignLib (Maybe Version -> [String] -> ForeignLib)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Applicative (g ForeignLib)
<*> FieldName
-> ALens' ForeignLib (Maybe LibVersionInfo)
-> g ForeignLib (Maybe LibVersionInfo)
forall (g :: * -> * -> *) a s.
(FieldGrammar g, Parsec a, Pretty a) =>
FieldName -> ALens' s (Maybe a) -> g s (Maybe a)
External instance of the constraint type Pretty LibVersionInfo
External instance of the constraint type Parsec LibVersionInfo
Evidence bound by a type signature of the constraint type FieldGrammar g
optionalField    FieldName
"lib-version-info"                             ALens' ForeignLib (Maybe LibVersionInfo)
Lens' ForeignLib (Maybe LibVersionInfo)
External instance of the constraint type forall a b. Functor (Pretext a b)
L.foreignLibVersionInfo
    g ForeignLib (Maybe Version -> [String] -> ForeignLib)
-> g ForeignLib (Maybe Version)
-> g ForeignLib ([String] -> ForeignLib)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Applicative (g ForeignLib)
<*> FieldName
-> ALens' ForeignLib (Maybe Version)
-> g ForeignLib (Maybe Version)
forall (g :: * -> * -> *) a s.
(FieldGrammar g, Parsec a, Pretty a) =>
FieldName -> ALens' s (Maybe a) -> g s (Maybe a)
External instance of the constraint type Pretty Version
External instance of the constraint type Parsec Version
Evidence bound by a type signature of the constraint type FieldGrammar g
optionalField    FieldName
"lib-version-linux"                            ALens' ForeignLib (Maybe Version)
Lens' ForeignLib (Maybe Version)
External instance of the constraint type forall a b. Functor (Pretext a b)
L.foreignLibVersionLinux
    g ForeignLib ([String] -> ForeignLib)
-> g ForeignLib [String] -> g ForeignLib ForeignLib
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Applicative (g ForeignLib)
<*> FieldName
-> ([String] -> List FSep FilePathNT String)
-> ALens' ForeignLib [String]
-> g ForeignLib [String]
forall (g :: * -> * -> *) b a s.
(FieldGrammar g, Parsec b, Pretty b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
External instance of the constraint type forall a sep wrapper. Newtype [a] (List sep wrapper a)
External instance of the constraint type forall a. Monoid [a]
External instance of the constraint type forall a b sep.
(Newtype a b, Sep sep, Pretty b) =>
Pretty (List sep b a)
External instance of the constraint type Newtype String FilePathNT
External instance of the constraint type Sep FSep
External instance of the constraint type Pretty FilePathNT
External instance of the constraint type forall a b sep.
(Newtype a b, Sep sep, Parsec b) =>
Parsec (List sep b a)
External instance of the constraint type Newtype String FilePathNT
External instance of the constraint type Sep FSep
External instance of the constraint type Parsec FilePathNT
Evidence bound by a type signature of the constraint type FieldGrammar g
monoidalFieldAla FieldName
"mod-def-file"      (FSep
-> (String -> FilePathNT)
-> [String]
-> List FSep FilePathNT String
forall sep a b. sep -> (a -> b) -> [a] -> List sep b a
alaList' FSep
FSep String -> FilePathNT
FilePathNT) ALens' ForeignLib [String]
Lens' ForeignLib [String]
External instance of the constraint type forall a b. Functor (Pretext a b)
L.foreignLibModDefFile
{-# SPECIALIZE foreignLibFieldGrammar :: UnqualComponentName -> ParsecFieldGrammar' ForeignLib #-}
{-# SPECIALIZE foreignLibFieldGrammar :: UnqualComponentName -> PrettyFieldGrammar' ForeignLib #-}

-------------------------------------------------------------------------------
-- Executable
-------------------------------------------------------------------------------

executableFieldGrammar
    :: (FieldGrammar g, Applicative (g Executable), Applicative (g BuildInfo))
    => UnqualComponentName -> g Executable Executable
executableFieldGrammar :: UnqualComponentName -> g Executable Executable
executableFieldGrammar UnqualComponentName
n = UnqualComponentName
-> String -> ExecutableScope -> BuildInfo -> Executable
Executable UnqualComponentName
n
    -- main-is is optional as conditional blocks don't have it
    (String -> ExecutableScope -> BuildInfo -> Executable)
-> g Executable String
-> g Executable (ExecutableScope -> BuildInfo -> Executable)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type forall (f :: * -> *). Applicative f => Functor f
Evidence bound by a type signature of the constraint type Applicative (g Executable)
<$> FieldName
-> (String -> FilePathNT)
-> ALens' Executable String
-> String
-> g Executable String
forall (g :: * -> * -> *) b a s.
(FieldGrammar g, Parsec b, Pretty b, Newtype a b, Eq a) =>
FieldName -> (a -> b) -> ALens' s a -> a -> g s a
External instance of the constraint type forall a. Eq a => Eq [a]
External instance of the constraint type Eq Char
External instance of the constraint type Newtype String FilePathNT
External instance of the constraint type Pretty FilePathNT
External instance of the constraint type Parsec FilePathNT
Evidence bound by a type signature of the constraint type FieldGrammar g
optionalFieldDefAla FieldName
"main-is" String -> FilePathNT
FilePathNT ALens' Executable String
Lens' Executable String
External instance of the constraint type forall a b. Functor (Pretext a b)
L.modulePath String
""
    g Executable (ExecutableScope -> BuildInfo -> Executable)
-> g Executable ExecutableScope
-> g Executable (BuildInfo -> Executable)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Applicative (g Executable)
<*> FieldName
-> ALens' Executable ExecutableScope
-> ExecutableScope
-> g Executable ExecutableScope
forall (g :: * -> * -> *) s a.
(FieldGrammar g, Functor (g s), Parsec a, Pretty a, Eq a) =>
FieldName -> ALens' s a -> a -> g s a
External instance of the constraint type Eq ExecutableScope
External instance of the constraint type Pretty ExecutableScope
External instance of the constraint type Parsec ExecutableScope
External instance of the constraint type forall (f :: * -> *). Applicative f => Functor f
Evidence bound by a type signature of the constraint type Applicative (g Executable)
Evidence bound by a type signature of the constraint type FieldGrammar g
optionalFieldDef    FieldName
"scope"              ALens' Executable ExecutableScope
Lens' Executable ExecutableScope
External instance of the constraint type forall a b. Functor (Pretext a b)
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 (g :: * -> * -> *) a s.
FieldGrammar g =>
CabalSpecVersion -> a -> g s a -> g s a
Evidence bound by a type signature of the constraint type FieldGrammar g
availableSince CabalSpecVersion
CabalSpecV2_0 ExecutableScope
ExecutablePublic
    g Executable (BuildInfo -> Executable)
-> g Executable BuildInfo -> g Executable Executable
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Applicative (g Executable)
<*> ALens' Executable BuildInfo
-> g BuildInfo BuildInfo -> g Executable BuildInfo
forall (g :: * -> * -> *) a b c.
FieldGrammar g =>
ALens' a b -> g b c -> g a c
Evidence bound by a type signature of the constraint type FieldGrammar g
blurFieldGrammar ALens' Executable BuildInfo
forall a. HasBuildInfo a => Lens' a BuildInfo
External instance of the constraint type forall a b. Functor (Pretext a b)
External instance of the constraint type HasBuildInfo Executable
L.buildInfo g BuildInfo BuildInfo
forall (g :: * -> * -> *).
(FieldGrammar g, Applicative (g BuildInfo)) =>
g BuildInfo BuildInfo
Evidence bound by a type signature of the constraint type Applicative (g BuildInfo)
Evidence bound by a type signature of the constraint type FieldGrammar g
buildInfoFieldGrammar
{-# SPECIALIZE executableFieldGrammar :: UnqualComponentName -> ParsecFieldGrammar' Executable #-}
{-# SPECIALIZE executableFieldGrammar :: UnqualComponentName -> PrettyFieldGrammar' Executable #-}

-------------------------------------------------------------------------------
-- TestSuite
-------------------------------------------------------------------------------

-- | An intermediate type just used for parsing the test-suite stanza.
-- After validation it is converted into the proper 'TestSuite' type.
data TestSuiteStanza = TestSuiteStanza
    { TestSuiteStanza -> Maybe TestType
_testStanzaTestType   :: Maybe TestType
    , TestSuiteStanza -> Maybe String
_testStanzaMainIs     :: Maybe FilePath
    , TestSuiteStanza -> Maybe ModuleName
_testStanzaTestModule :: Maybe ModuleName
    , TestSuiteStanza -> BuildInfo
_testStanzaBuildInfo  :: BuildInfo
    }

instance L.HasBuildInfo TestSuiteStanza where
    buildInfo :: LensLike f TestSuiteStanza TestSuiteStanza BuildInfo BuildInfo
buildInfo = LensLike f TestSuiteStanza TestSuiteStanza BuildInfo BuildInfo
Lens' TestSuiteStanza BuildInfo
Evidence bound by a type signature of the constraint type Functor f
testStanzaBuildInfo

testStanzaTestType :: Lens' TestSuiteStanza (Maybe TestType)
testStanzaTestType :: LensLike
  f TestSuiteStanza TestSuiteStanza (Maybe TestType) (Maybe TestType)
testStanzaTestType Maybe TestType -> f (Maybe TestType)
f TestSuiteStanza
s = (Maybe TestType -> TestSuiteStanza)
-> f (Maybe TestType) -> f TestSuiteStanza
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Functor f
fmap (\Maybe TestType
x -> TestSuiteStanza
s { _testStanzaTestType :: Maybe TestType
_testStanzaTestType = Maybe TestType
x }) (Maybe TestType -> f (Maybe TestType)
f (TestSuiteStanza -> Maybe TestType
_testStanzaTestType TestSuiteStanza
s))
{-# INLINE testStanzaTestType #-}

testStanzaMainIs :: Lens' TestSuiteStanza (Maybe FilePath)
testStanzaMainIs :: LensLike
  f TestSuiteStanza TestSuiteStanza (Maybe String) (Maybe String)
testStanzaMainIs Maybe String -> f (Maybe String)
f TestSuiteStanza
s = (Maybe String -> TestSuiteStanza)
-> f (Maybe String) -> f TestSuiteStanza
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Functor f
fmap (\Maybe String
x -> TestSuiteStanza
s { _testStanzaMainIs :: Maybe String
_testStanzaMainIs = Maybe String
x }) (Maybe String -> f (Maybe String)
f (TestSuiteStanza -> Maybe String
_testStanzaMainIs TestSuiteStanza
s))
{-# INLINE testStanzaMainIs #-}

testStanzaTestModule :: Lens' TestSuiteStanza (Maybe ModuleName)
testStanzaTestModule :: LensLike
  f
  TestSuiteStanza
  TestSuiteStanza
  (Maybe ModuleName)
  (Maybe ModuleName)
testStanzaTestModule Maybe ModuleName -> f (Maybe ModuleName)
f TestSuiteStanza
s = (Maybe ModuleName -> TestSuiteStanza)
-> f (Maybe ModuleName) -> f TestSuiteStanza
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Functor f
fmap (\Maybe ModuleName
x -> TestSuiteStanza
s { _testStanzaTestModule :: Maybe ModuleName
_testStanzaTestModule = Maybe ModuleName
x }) (Maybe ModuleName -> f (Maybe ModuleName)
f (TestSuiteStanza -> Maybe ModuleName
_testStanzaTestModule TestSuiteStanza
s))
{-# INLINE testStanzaTestModule #-}

testStanzaBuildInfo :: Lens' TestSuiteStanza BuildInfo
testStanzaBuildInfo :: LensLike f TestSuiteStanza TestSuiteStanza BuildInfo BuildInfo
testStanzaBuildInfo BuildInfo -> f BuildInfo
f TestSuiteStanza
s = (BuildInfo -> TestSuiteStanza) -> f BuildInfo -> f TestSuiteStanza
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Functor f
fmap (\BuildInfo
x -> TestSuiteStanza
s { _testStanzaBuildInfo :: BuildInfo
_testStanzaBuildInfo = BuildInfo
x }) (BuildInfo -> f BuildInfo
f (TestSuiteStanza -> BuildInfo
_testStanzaBuildInfo TestSuiteStanza
s))
{-# INLINE testStanzaBuildInfo #-}

testSuiteFieldGrammar
    :: (FieldGrammar g, Applicative (g TestSuiteStanza), Applicative (g BuildInfo))
    => g TestSuiteStanza TestSuiteStanza
testSuiteFieldGrammar :: g TestSuiteStanza TestSuiteStanza
testSuiteFieldGrammar = Maybe TestType
-> Maybe String -> Maybe ModuleName -> BuildInfo -> TestSuiteStanza
TestSuiteStanza
    (Maybe TestType
 -> Maybe String
 -> Maybe ModuleName
 -> BuildInfo
 -> TestSuiteStanza)
-> g TestSuiteStanza (Maybe TestType)
-> g TestSuiteStanza
     (Maybe String -> Maybe ModuleName -> BuildInfo -> TestSuiteStanza)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type forall (f :: * -> *). Applicative f => Functor f
Evidence bound by a type signature of the constraint type Applicative (g TestSuiteStanza)
<$> FieldName
-> ALens' TestSuiteStanza (Maybe TestType)
-> g TestSuiteStanza (Maybe TestType)
forall (g :: * -> * -> *) a s.
(FieldGrammar g, Parsec a, Pretty a) =>
FieldName -> ALens' s (Maybe a) -> g s (Maybe a)
External instance of the constraint type Pretty TestType
External instance of the constraint type Parsec TestType
Evidence bound by a type signature of the constraint type FieldGrammar g
optionalField    FieldName
"type"                   ALens' TestSuiteStanza (Maybe TestType)
Lens' TestSuiteStanza (Maybe TestType)
External instance of the constraint type forall a b. Functor (Pretext a b)
testStanzaTestType
    g TestSuiteStanza
  (Maybe String -> Maybe ModuleName -> BuildInfo -> TestSuiteStanza)
-> g TestSuiteStanza (Maybe String)
-> g TestSuiteStanza
     (Maybe ModuleName -> BuildInfo -> TestSuiteStanza)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Applicative (g TestSuiteStanza)
<*> FieldName
-> (String -> FilePathNT)
-> ALens' TestSuiteStanza (Maybe String)
-> g TestSuiteStanza (Maybe String)
forall (g :: * -> * -> *) b a s.
(FieldGrammar g, Parsec b, Pretty b, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s (Maybe a) -> g s (Maybe a)
External instance of the constraint type Newtype String FilePathNT
External instance of the constraint type Pretty FilePathNT
External instance of the constraint type Parsec FilePathNT
Evidence bound by a type signature of the constraint type FieldGrammar g
optionalFieldAla FieldName
"main-is"     String -> FilePathNT
FilePathNT ALens' TestSuiteStanza (Maybe String)
Lens' TestSuiteStanza (Maybe String)
External instance of the constraint type forall a b. Functor (Pretext a b)
testStanzaMainIs
    g TestSuiteStanza
  (Maybe ModuleName -> BuildInfo -> TestSuiteStanza)
-> g TestSuiteStanza (Maybe ModuleName)
-> g TestSuiteStanza (BuildInfo -> TestSuiteStanza)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Applicative (g TestSuiteStanza)
<*> FieldName
-> ALens' TestSuiteStanza (Maybe ModuleName)
-> g TestSuiteStanza (Maybe ModuleName)
forall (g :: * -> * -> *) a s.
(FieldGrammar g, Parsec a, Pretty a) =>
FieldName -> ALens' s (Maybe a) -> g s (Maybe a)
External instance of the constraint type Pretty ModuleName
External instance of the constraint type Parsec ModuleName
Evidence bound by a type signature of the constraint type FieldGrammar g
optionalField    FieldName
"test-module"            ALens' TestSuiteStanza (Maybe ModuleName)
Lens' TestSuiteStanza (Maybe ModuleName)
External instance of the constraint type forall a b. Functor (Pretext a b)
testStanzaTestModule
    g TestSuiteStanza (BuildInfo -> TestSuiteStanza)
-> g TestSuiteStanza BuildInfo -> g TestSuiteStanza TestSuiteStanza
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Applicative (g TestSuiteStanza)
<*> ALens' TestSuiteStanza BuildInfo
-> g BuildInfo BuildInfo -> g TestSuiteStanza BuildInfo
forall (g :: * -> * -> *) a b c.
FieldGrammar g =>
ALens' a b -> g b c -> g a c
Evidence bound by a type signature of the constraint type FieldGrammar g
blurFieldGrammar ALens' TestSuiteStanza BuildInfo
Lens' TestSuiteStanza BuildInfo
External instance of the constraint type forall a b. Functor (Pretext a b)
testStanzaBuildInfo g BuildInfo BuildInfo
forall (g :: * -> * -> *).
(FieldGrammar g, Applicative (g BuildInfo)) =>
g BuildInfo BuildInfo
Evidence bound by a type signature of the constraint type Applicative (g BuildInfo)
Evidence bound by a type signature of the constraint type FieldGrammar g
buildInfoFieldGrammar

validateTestSuite :: Position -> TestSuiteStanza -> ParseResult TestSuite
validateTestSuite :: Position -> TestSuiteStanza -> ParseResult TestSuite
validateTestSuite Position
pos TestSuiteStanza
stanza = case TestSuiteStanza -> Maybe TestType
_testStanzaTestType TestSuiteStanza
stanza of
    Maybe TestType
Nothing -> TestSuite -> ParseResult TestSuite
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad ParseResult
return (TestSuite -> ParseResult TestSuite)
-> TestSuite -> ParseResult TestSuite
forall a b. (a -> b) -> a -> b
$
        TestSuite
emptyTestSuite { testBuildInfo :: BuildInfo
testBuildInfo = TestSuiteStanza -> BuildInfo
_testStanzaBuildInfo TestSuiteStanza
stanza }

    Just tt :: TestType
tt@(TestTypeUnknown String
_ Version
_) ->
        TestSuite -> ParseResult TestSuite
forall (f :: * -> *) a. Applicative f => a -> f a
External instance of the constraint type Applicative ParseResult
pure TestSuite
emptyTestSuite
            { testInterface :: TestSuiteInterface
testInterface = TestType -> TestSuiteInterface
TestSuiteUnsupported TestType
tt
            , testBuildInfo :: BuildInfo
testBuildInfo = TestSuiteStanza -> BuildInfo
_testStanzaBuildInfo TestSuiteStanza
stanza
            }

    Just TestType
tt | TestType
tt TestType -> [TestType] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
External instance of the constraint type Eq TestType
External instance of the constraint type Foldable []
`notElem` [TestType]
knownTestTypes ->
        TestSuite -> ParseResult TestSuite
forall (f :: * -> *) a. Applicative f => a -> f a
External instance of the constraint type Applicative ParseResult
pure TestSuite
emptyTestSuite
            { testInterface :: TestSuiteInterface
testInterface = TestType -> TestSuiteInterface
TestSuiteUnsupported TestType
tt
            , testBuildInfo :: BuildInfo
testBuildInfo = TestSuiteStanza -> BuildInfo
_testStanzaBuildInfo TestSuiteStanza
stanza
            }

    Just tt :: TestType
tt@(TestTypeExe Version
ver) -> case TestSuiteStanza -> Maybe String
_testStanzaMainIs TestSuiteStanza
stanza of
        Maybe String
Nothing   -> do
            Position -> String -> ParseResult ()
parseFailure Position
pos (String -> TestType -> String
forall {a}. Pretty a => String -> a -> String
External instance of the constraint type Pretty TestType
missingField String
"main-is" TestType
tt)
            TestSuite -> ParseResult TestSuite
forall (f :: * -> *) a. Applicative f => a -> f a
External instance of the constraint type Applicative ParseResult
pure TestSuite
emptyTestSuite
        Just String
file -> do
            Bool -> ParseResult () -> ParseResult ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
External instance of the constraint type Applicative ParseResult
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
External instance of the constraint type Pretty TestType
extraField String
"test-module" TestType
tt)
            TestSuite -> ParseResult TestSuite
forall (f :: * -> *) a. Applicative f => a -> f a
External instance of the constraint type Applicative ParseResult
pure TestSuite
emptyTestSuite
                { testInterface :: TestSuiteInterface
testInterface = Version -> String -> TestSuiteInterface
TestSuiteExeV10 Version
ver String
file
                , testBuildInfo :: BuildInfo
testBuildInfo = TestSuiteStanza -> BuildInfo
_testStanzaBuildInfo TestSuiteStanza
stanza
                }

    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
External instance of the constraint type Pretty TestType
missingField String
"test-module" TestType
tt)
             TestSuite -> ParseResult TestSuite
forall (f :: * -> *) a. Applicative f => a -> f a
External instance of the constraint type Applicative ParseResult
pure TestSuite
emptyTestSuite
         Just ModuleName
module_ -> do
            Bool -> ParseResult () -> ParseResult ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
External instance of the constraint type Applicative ParseResult
when (Maybe String -> Bool
forall a. Maybe a -> Bool
isJust (TestSuiteStanza -> Maybe String
_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
External instance of the constraint type Pretty TestType
extraField String
"main-is" TestType
tt)
            TestSuite -> ParseResult TestSuite
forall (f :: * -> *) a. Applicative f => a -> f a
External instance of the constraint type Applicative ParseResult
pure TestSuite
emptyTestSuite
                { testInterface :: TestSuiteInterface
testInterface = Version -> ModuleName -> TestSuiteInterface
TestSuiteLibV09 Version
ver ModuleName
module_
                , testBuildInfo :: BuildInfo
testBuildInfo = TestSuiteStanza -> BuildInfo
_testStanzaBuildInfo TestSuiteStanza
stanza
                }

  where
    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
Evidence bound by a type signature of the constraint type Pretty a
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
Evidence bound by a type signature of the constraint type Pretty a
prettyShow a
tt String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"' test suite type."

unvalidateTestSuite :: TestSuite -> TestSuiteStanza
unvalidateTestSuite :: TestSuite -> TestSuiteStanza
unvalidateTestSuite TestSuite
t = TestSuiteStanza :: Maybe TestType
-> Maybe String -> Maybe ModuleName -> BuildInfo -> TestSuiteStanza
TestSuiteStanza
    { _testStanzaTestType :: Maybe TestType
_testStanzaTestType   = Maybe TestType
ty
    , _testStanzaMainIs :: Maybe String
_testStanzaMainIs     = Maybe String
ma
    , _testStanzaTestModule :: Maybe ModuleName
_testStanzaTestModule = Maybe ModuleName
mo
    , _testStanzaBuildInfo :: BuildInfo
_testStanzaBuildInfo  = TestSuite -> BuildInfo
testBuildInfo TestSuite
t
    }
  where
    (Maybe TestType
ty, Maybe String
ma, Maybe ModuleName
mo) = case TestSuite -> TestSuiteInterface
testInterface TestSuite
t of
        TestSuiteExeV10 Version
ver String
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, String -> Maybe String
forall a. a -> Maybe a
Just String
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 String
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 String
forall a. Maybe a
Nothing, Maybe ModuleName
forall a. Maybe a
Nothing)

-------------------------------------------------------------------------------
-- Benchmark
-------------------------------------------------------------------------------

-- | An intermediate type just used for parsing the benchmark stanza.
-- After validation it is converted into the proper 'Benchmark' type.
data BenchmarkStanza = BenchmarkStanza
    { BenchmarkStanza -> Maybe BenchmarkType
_benchmarkStanzaBenchmarkType   :: Maybe BenchmarkType
    , BenchmarkStanza -> Maybe String
_benchmarkStanzaMainIs          :: Maybe FilePath
    , BenchmarkStanza -> Maybe ModuleName
_benchmarkStanzaBenchmarkModule :: Maybe ModuleName
    , BenchmarkStanza -> BuildInfo
_benchmarkStanzaBuildInfo       :: BuildInfo
    }

instance L.HasBuildInfo BenchmarkStanza where
    buildInfo :: LensLike f BenchmarkStanza BenchmarkStanza BuildInfo BuildInfo
buildInfo = LensLike f BenchmarkStanza BenchmarkStanza BuildInfo BuildInfo
Lens' BenchmarkStanza BuildInfo
Evidence bound by a type signature of the constraint type Functor f
benchmarkStanzaBuildInfo

benchmarkStanzaBenchmarkType :: Lens' BenchmarkStanza (Maybe BenchmarkType)
benchmarkStanzaBenchmarkType :: LensLike
  f
  BenchmarkStanza
  BenchmarkStanza
  (Maybe BenchmarkType)
  (Maybe BenchmarkType)
benchmarkStanzaBenchmarkType Maybe BenchmarkType -> f (Maybe BenchmarkType)
f BenchmarkStanza
s = (Maybe BenchmarkType -> BenchmarkStanza)
-> f (Maybe BenchmarkType) -> f BenchmarkStanza
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Functor f
fmap (\Maybe BenchmarkType
x -> BenchmarkStanza
s { _benchmarkStanzaBenchmarkType :: Maybe BenchmarkType
_benchmarkStanzaBenchmarkType = Maybe BenchmarkType
x }) (Maybe BenchmarkType -> f (Maybe BenchmarkType)
f (BenchmarkStanza -> Maybe BenchmarkType
_benchmarkStanzaBenchmarkType BenchmarkStanza
s))
{-# INLINE benchmarkStanzaBenchmarkType #-}

benchmarkStanzaMainIs :: Lens' BenchmarkStanza (Maybe FilePath)
benchmarkStanzaMainIs :: LensLike
  f BenchmarkStanza BenchmarkStanza (Maybe String) (Maybe String)
benchmarkStanzaMainIs Maybe String -> f (Maybe String)
f BenchmarkStanza
s = (Maybe String -> BenchmarkStanza)
-> f (Maybe String) -> f BenchmarkStanza
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Functor f
fmap (\Maybe String
x -> BenchmarkStanza
s { _benchmarkStanzaMainIs :: Maybe String
_benchmarkStanzaMainIs = Maybe String
x }) (Maybe String -> f (Maybe String)
f (BenchmarkStanza -> Maybe String
_benchmarkStanzaMainIs BenchmarkStanza
s))
{-# INLINE benchmarkStanzaMainIs #-}

benchmarkStanzaBenchmarkModule :: Lens' BenchmarkStanza (Maybe ModuleName)
benchmarkStanzaBenchmarkModule :: LensLike
  f
  BenchmarkStanza
  BenchmarkStanza
  (Maybe ModuleName)
  (Maybe ModuleName)
benchmarkStanzaBenchmarkModule Maybe ModuleName -> f (Maybe ModuleName)
f BenchmarkStanza
s = (Maybe ModuleName -> BenchmarkStanza)
-> f (Maybe ModuleName) -> f BenchmarkStanza
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Functor f
fmap (\Maybe ModuleName
x -> BenchmarkStanza
s { _benchmarkStanzaBenchmarkModule :: Maybe ModuleName
_benchmarkStanzaBenchmarkModule = Maybe ModuleName
x }) (Maybe ModuleName -> f (Maybe ModuleName)
f (BenchmarkStanza -> Maybe ModuleName
_benchmarkStanzaBenchmarkModule BenchmarkStanza
s))
{-# INLINE benchmarkStanzaBenchmarkModule #-}

benchmarkStanzaBuildInfo :: Lens' BenchmarkStanza BuildInfo
benchmarkStanzaBuildInfo :: LensLike f BenchmarkStanza BenchmarkStanza BuildInfo BuildInfo
benchmarkStanzaBuildInfo BuildInfo -> f BuildInfo
f BenchmarkStanza
s = (BuildInfo -> BenchmarkStanza) -> f BuildInfo -> f BenchmarkStanza
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Functor f
fmap (\BuildInfo
x -> BenchmarkStanza
s { _benchmarkStanzaBuildInfo :: BuildInfo
_benchmarkStanzaBuildInfo = BuildInfo
x }) (BuildInfo -> f BuildInfo
f (BenchmarkStanza -> BuildInfo
_benchmarkStanzaBuildInfo BenchmarkStanza
s))
{-# INLINE benchmarkStanzaBuildInfo #-}

benchmarkFieldGrammar
    :: (FieldGrammar g, Applicative (g BenchmarkStanza), Applicative (g BuildInfo))
    => g BenchmarkStanza BenchmarkStanza
benchmarkFieldGrammar :: g BenchmarkStanza BenchmarkStanza
benchmarkFieldGrammar = Maybe BenchmarkType
-> Maybe String -> Maybe ModuleName -> BuildInfo -> BenchmarkStanza
BenchmarkStanza
    (Maybe BenchmarkType
 -> Maybe String
 -> Maybe ModuleName
 -> BuildInfo
 -> BenchmarkStanza)
-> g BenchmarkStanza (Maybe BenchmarkType)
-> g BenchmarkStanza
     (Maybe String -> Maybe ModuleName -> BuildInfo -> BenchmarkStanza)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type forall (f :: * -> *). Applicative f => Functor f
Evidence bound by a type signature of the constraint type Applicative (g BenchmarkStanza)
<$> FieldName
-> ALens' BenchmarkStanza (Maybe BenchmarkType)
-> g BenchmarkStanza (Maybe BenchmarkType)
forall (g :: * -> * -> *) a s.
(FieldGrammar g, Parsec a, Pretty a) =>
FieldName -> ALens' s (Maybe a) -> g s (Maybe a)
External instance of the constraint type Pretty BenchmarkType
External instance of the constraint type Parsec BenchmarkType
Evidence bound by a type signature of the constraint type FieldGrammar g
optionalField    FieldName
"type"                        ALens' BenchmarkStanza (Maybe BenchmarkType)
Lens' BenchmarkStanza (Maybe BenchmarkType)
External instance of the constraint type forall a b. Functor (Pretext a b)
benchmarkStanzaBenchmarkType
    g BenchmarkStanza
  (Maybe String -> Maybe ModuleName -> BuildInfo -> BenchmarkStanza)
-> g BenchmarkStanza (Maybe String)
-> g BenchmarkStanza
     (Maybe ModuleName -> BuildInfo -> BenchmarkStanza)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Applicative (g BenchmarkStanza)
<*> FieldName
-> (String -> FilePathNT)
-> ALens' BenchmarkStanza (Maybe String)
-> g BenchmarkStanza (Maybe String)
forall (g :: * -> * -> *) b a s.
(FieldGrammar g, Parsec b, Pretty b, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s (Maybe a) -> g s (Maybe a)
External instance of the constraint type Newtype String FilePathNT
External instance of the constraint type Pretty FilePathNT
External instance of the constraint type Parsec FilePathNT
Evidence bound by a type signature of the constraint type FieldGrammar g
optionalFieldAla FieldName
"main-is"          String -> FilePathNT
FilePathNT ALens' BenchmarkStanza (Maybe String)
Lens' BenchmarkStanza (Maybe String)
External instance of the constraint type forall a b. Functor (Pretext a b)
benchmarkStanzaMainIs
    g BenchmarkStanza
  (Maybe ModuleName -> BuildInfo -> BenchmarkStanza)
-> g BenchmarkStanza (Maybe ModuleName)
-> g BenchmarkStanza (BuildInfo -> BenchmarkStanza)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Applicative (g BenchmarkStanza)
<*> FieldName
-> ALens' BenchmarkStanza (Maybe ModuleName)
-> g BenchmarkStanza (Maybe ModuleName)
forall (g :: * -> * -> *) a s.
(FieldGrammar g, Parsec a, Pretty a) =>
FieldName -> ALens' s (Maybe a) -> g s (Maybe a)
External instance of the constraint type Pretty ModuleName
External instance of the constraint type Parsec ModuleName
Evidence bound by a type signature of the constraint type FieldGrammar g
optionalField    FieldName
"benchmark-module"            ALens' BenchmarkStanza (Maybe ModuleName)
Lens' BenchmarkStanza (Maybe ModuleName)
External instance of the constraint type forall a b. Functor (Pretext a b)
benchmarkStanzaBenchmarkModule
    g BenchmarkStanza (BuildInfo -> BenchmarkStanza)
-> g BenchmarkStanza BuildInfo -> g BenchmarkStanza BenchmarkStanza
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Applicative (g BenchmarkStanza)
<*> ALens' BenchmarkStanza BuildInfo
-> g BuildInfo BuildInfo -> g BenchmarkStanza BuildInfo
forall (g :: * -> * -> *) a b c.
FieldGrammar g =>
ALens' a b -> g b c -> g a c
Evidence bound by a type signature of the constraint type FieldGrammar g
blurFieldGrammar ALens' BenchmarkStanza BuildInfo
Lens' BenchmarkStanza BuildInfo
External instance of the constraint type forall a b. Functor (Pretext a b)
benchmarkStanzaBuildInfo g BuildInfo BuildInfo
forall (g :: * -> * -> *).
(FieldGrammar g, Applicative (g BuildInfo)) =>
g BuildInfo BuildInfo
Evidence bound by a type signature of the constraint type Applicative (g BuildInfo)
Evidence bound by a type signature of the constraint type FieldGrammar g
buildInfoFieldGrammar

validateBenchmark :: Position -> BenchmarkStanza -> ParseResult Benchmark
validateBenchmark :: Position -> BenchmarkStanza -> ParseResult Benchmark
validateBenchmark Position
pos BenchmarkStanza
stanza = case BenchmarkStanza -> Maybe BenchmarkType
_benchmarkStanzaBenchmarkType BenchmarkStanza
stanza of
    Maybe BenchmarkType
Nothing -> Benchmark -> ParseResult Benchmark
forall (f :: * -> *) a. Applicative f => a -> f a
External instance of the constraint type Applicative ParseResult
pure Benchmark
emptyBenchmark
        { benchmarkBuildInfo :: BuildInfo
benchmarkBuildInfo = BenchmarkStanza -> BuildInfo
_benchmarkStanzaBuildInfo BenchmarkStanza
stanza }

    Just tt :: BenchmarkType
tt@(BenchmarkTypeUnknown String
_ Version
_) -> Benchmark -> ParseResult Benchmark
forall (f :: * -> *) a. Applicative f => a -> f a
External instance of the constraint type Applicative ParseResult
pure Benchmark
emptyBenchmark
        { benchmarkInterface :: BenchmarkInterface
benchmarkInterface = BenchmarkType -> BenchmarkInterface
BenchmarkUnsupported BenchmarkType
tt
        , benchmarkBuildInfo :: BuildInfo
benchmarkBuildInfo = BenchmarkStanza -> BuildInfo
_benchmarkStanzaBuildInfo BenchmarkStanza
stanza
        }

    Just BenchmarkType
tt | BenchmarkType
tt BenchmarkType -> [BenchmarkType] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
External instance of the constraint type Eq BenchmarkType
External instance of the constraint type Foldable []
`notElem` [BenchmarkType]
knownBenchmarkTypes -> Benchmark -> ParseResult Benchmark
forall (f :: * -> *) a. Applicative f => a -> f a
External instance of the constraint type Applicative ParseResult
pure Benchmark
emptyBenchmark
        { benchmarkInterface :: BenchmarkInterface
benchmarkInterface = BenchmarkType -> BenchmarkInterface
BenchmarkUnsupported BenchmarkType
tt
        , benchmarkBuildInfo :: BuildInfo
benchmarkBuildInfo = BenchmarkStanza -> BuildInfo
_benchmarkStanzaBuildInfo BenchmarkStanza
stanza
        }

    Just tt :: BenchmarkType
tt@(BenchmarkTypeExe Version
ver) -> case BenchmarkStanza -> Maybe String
_benchmarkStanzaMainIs BenchmarkStanza
stanza of
        Maybe String
Nothing   -> do
            Position -> String -> ParseResult ()
parseFailure Position
pos (String -> BenchmarkType -> String
forall {a}. Pretty a => String -> a -> String
External instance of the constraint type Pretty BenchmarkType
missingField String
"main-is" BenchmarkType
tt)
            Benchmark -> ParseResult Benchmark
forall (f :: * -> *) a. Applicative f => a -> f a
External instance of the constraint type Applicative ParseResult
pure Benchmark
emptyBenchmark
        Just String
file -> do
            Bool -> ParseResult () -> ParseResult ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
External instance of the constraint type Applicative ParseResult
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
External instance of the constraint type Pretty BenchmarkType
extraField String
"benchmark-module" BenchmarkType
tt)
            Benchmark -> ParseResult Benchmark
forall (f :: * -> *) a. Applicative f => a -> f a
External instance of the constraint type Applicative ParseResult
pure Benchmark
emptyBenchmark
                { benchmarkInterface :: BenchmarkInterface
benchmarkInterface = Version -> String -> BenchmarkInterface
BenchmarkExeV10 Version
ver String
file
                , benchmarkBuildInfo :: BuildInfo
benchmarkBuildInfo = BenchmarkStanza -> BuildInfo
_benchmarkStanzaBuildInfo BenchmarkStanza
stanza
                }

  where
    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
Evidence bound by a type signature of the constraint type Pretty a
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
Evidence bound by a type signature of the constraint type Pretty a
prettyShow a
tt String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"' benchmark type."

unvalidateBenchmark :: Benchmark -> BenchmarkStanza
unvalidateBenchmark :: Benchmark -> BenchmarkStanza
unvalidateBenchmark Benchmark
b = BenchmarkStanza :: Maybe BenchmarkType
-> Maybe String -> Maybe ModuleName -> BuildInfo -> BenchmarkStanza
BenchmarkStanza
    { _benchmarkStanzaBenchmarkType :: Maybe BenchmarkType
_benchmarkStanzaBenchmarkType   = Maybe BenchmarkType
ty
    , _benchmarkStanzaMainIs :: Maybe String
_benchmarkStanzaMainIs          = Maybe String
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 String
ma, Maybe a
mo) = case Benchmark -> BenchmarkInterface
benchmarkInterface Benchmark
b of
        BenchmarkExeV10 Version
ver 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 String
forall a. Maybe a
Nothing,  Maybe a
forall a. Maybe a
Nothing)
        BenchmarkExeV10 Version
ver String
ma' -> (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, String -> Maybe String
forall a. a -> Maybe a
Just String
ma', Maybe a
forall a. Maybe a
Nothing)
        BenchmarkInterface
_                       -> (Maybe BenchmarkType
forall a. Maybe a
Nothing, Maybe String
forall a. Maybe a
Nothing,  Maybe a
forall a. Maybe a
Nothing)

-------------------------------------------------------------------------------
-- Build info
-------------------------------------------------------------------------------

buildInfoFieldGrammar
    :: (FieldGrammar g, Applicative (g BuildInfo))
    => g BuildInfo BuildInfo
buildInfoFieldGrammar :: g BuildInfo BuildInfo
buildInfoFieldGrammar = Bool
-> [LegacyExeDependency]
-> [ExeDependency]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [PkgconfigDependency]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [ModuleName]
-> [ModuleName]
-> [ModuleName]
-> Maybe Language
-> [Language]
-> [Extension]
-> [Extension]
-> [Extension]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> PerCompilerFlavor [String]
-> [(String, String)]
-> [Dependency]
-> [Mixin]
-> BuildInfo
BuildInfo
    (Bool
 -> [LegacyExeDependency]
 -> [ExeDependency]
 -> [String]
 -> [String]
 -> [String]
 -> [String]
 -> [String]
 -> [String]
 -> [PkgconfigDependency]
 -> [String]
 -> [String]
 -> [String]
 -> [String]
 -> [String]
 -> [String]
 -> [String]
 -> [String]
 -> [ModuleName]
 -> [ModuleName]
 -> [ModuleName]
 -> Maybe Language
 -> [Language]
 -> [Extension]
 -> [Extension]
 -> [Extension]
 -> [String]
 -> [String]
 -> [String]
 -> [String]
 -> [String]
 -> [String]
 -> [String]
 -> [String]
 -> [String]
 -> [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]
      -> [PkgconfigDependency]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [ModuleName]
      -> [ModuleName]
      -> [ModuleName]
      -> Maybe Language
      -> [Language]
      -> [Extension]
      -> [Extension]
      -> [Extension]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [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
External instance of the constraint type forall (f :: * -> *). Applicative f => Functor f
Evidence bound by a type signature of the constraint type Applicative (g BuildInfo)
<$> FieldName -> ALens' BuildInfo Bool -> Bool -> g BuildInfo Bool
forall (g :: * -> * -> *) s.
FieldGrammar g =>
FieldName -> ALens' s Bool -> Bool -> g s Bool
Evidence bound by a type signature of the constraint type FieldGrammar g
booleanFieldDef  FieldName
"buildable"                                          ALens' BuildInfo Bool
forall a. HasBuildInfo a => Lens' a Bool
External instance of the constraint type forall a b. Functor (Pretext a b)
External instance of the constraint type HasBuildInfo BuildInfo
L.buildable Bool
True
    g BuildInfo
  ([LegacyExeDependency]
   -> [ExeDependency]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [PkgconfigDependency]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [ModuleName]
   -> [ModuleName]
   -> [ModuleName]
   -> Maybe Language
   -> [Language]
   -> [Extension]
   -> [Extension]
   -> [Extension]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [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]
      -> [PkgconfigDependency]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [ModuleName]
      -> [ModuleName]
      -> [ModuleName]
      -> Maybe Language
      -> [Language]
      -> [Extension]
      -> [Extension]
      -> [Extension]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> PerCompilerFlavor [String]
      -> PerCompilerFlavor [String]
      -> PerCompilerFlavor [String]
      -> PerCompilerFlavor [String]
      -> [(String, String)]
      -> [Dependency]
      -> [Mixin]
      -> BuildInfo)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Applicative (g BuildInfo)
<*> FieldName
-> ([LegacyExeDependency]
    -> List
         CommaFSep (Identity LegacyExeDependency) LegacyExeDependency)
-> ALens' BuildInfo [LegacyExeDependency]
-> g BuildInfo [LegacyExeDependency]
forall (g :: * -> * -> *) b a s.
(FieldGrammar g, Parsec b, Pretty b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
External instance of the constraint type forall a sep wrapper. Newtype [a] (List sep wrapper a)
External instance of the constraint type forall a. Monoid [a]
External instance of the constraint type forall a b sep.
(Newtype a b, Sep sep, Pretty b) =>
Pretty (List sep b a)
External instance of the constraint type forall a. Newtype a (Identity a)
External instance of the constraint type Sep CommaFSep
External instance of the constraint type forall a. Pretty a => Pretty (Identity a)
External instance of the constraint type Pretty LegacyExeDependency
External instance of the constraint type forall a b sep.
(Newtype a b, Sep sep, Parsec b) =>
Parsec (List sep b a)
External instance of the constraint type forall a. Newtype a (Identity a)
External instance of the constraint type Sep CommaFSep
External instance of the constraint type forall a. Parsec a => Parsec (Identity a)
External instance of the constraint type Parsec LegacyExeDependency
Evidence bound by a type signature of the constraint type FieldGrammar g
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]
External instance of the constraint type forall a b. Functor (Pretext a b)
External instance of the constraint type HasBuildInfo BuildInfo
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 (g :: * -> * -> *) s a.
FieldGrammar g =>
CabalSpecVersion -> String -> g s a -> g s a
Evidence bound by a type signature of the constraint type FieldGrammar g
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 (g :: * -> * -> *) s a.
FieldGrammar g =>
CabalSpecVersion -> String -> g s a -> g s a
Evidence bound by a type signature of the constraint type FieldGrammar g
removedIn CabalSpecVersion
CabalSpecV3_0
            String
"Please use 'build-tool-depends' field."
    g BuildInfo
  ([ExeDependency]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [PkgconfigDependency]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [ModuleName]
   -> [ModuleName]
   -> [ModuleName]
   -> Maybe Language
   -> [Language]
   -> [Extension]
   -> [Extension]
   -> [Extension]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [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]
      -> [PkgconfigDependency]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [ModuleName]
      -> [ModuleName]
      -> [ModuleName]
      -> Maybe Language
      -> [Language]
      -> [Extension]
      -> [Extension]
      -> [Extension]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> PerCompilerFlavor [String]
      -> PerCompilerFlavor [String]
      -> PerCompilerFlavor [String]
      -> PerCompilerFlavor [String]
      -> [(String, String)]
      -> [Dependency]
      -> [Mixin]
      -> BuildInfo)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Applicative (g BuildInfo)
<*> FieldName
-> ([ExeDependency]
    -> List CommaFSep (Identity ExeDependency) ExeDependency)
-> ALens' BuildInfo [ExeDependency]
-> g BuildInfo [ExeDependency]
forall (g :: * -> * -> *) b a s.
(FieldGrammar g, Parsec b, Pretty b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
External instance of the constraint type forall a sep wrapper. Newtype [a] (List sep wrapper a)
External instance of the constraint type forall a. Monoid [a]
External instance of the constraint type forall a b sep.
(Newtype a b, Sep sep, Pretty b) =>
Pretty (List sep b a)
External instance of the constraint type forall a. Newtype a (Identity a)
External instance of the constraint type Sep CommaFSep
External instance of the constraint type forall a. Pretty a => Pretty (Identity a)
External instance of the constraint type Pretty ExeDependency
External instance of the constraint type forall a b sep.
(Newtype a b, Sep sep, Parsec b) =>
Parsec (List sep b a)
External instance of the constraint type forall a. Newtype a (Identity a)
External instance of the constraint type Sep CommaFSep
External instance of the constraint type forall a. Parsec a => Parsec (Identity a)
External instance of the constraint type Parsec ExeDependency
Evidence bound by a type signature of the constraint type FieldGrammar g
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]
External instance of the constraint type forall a b. Functor (Pretext a b)
External instance of the constraint type HasBuildInfo BuildInfo
L.buildToolDepends
        -- {- ^^^ availableSince [2,0] [] -}
        -- here, we explicitly want to recognise build-tool-depends for all Cabal files
        -- as otherwise cabal new-build cannot really work.
        --
        -- I.e. we don't want trigger unknown field warning
    g BuildInfo
  ([String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [PkgconfigDependency]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [ModuleName]
   -> [ModuleName]
   -> [ModuleName]
   -> Maybe Language
   -> [Language]
   -> [Extension]
   -> [Extension]
   -> [Extension]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [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]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [ModuleName]
      -> [ModuleName]
      -> [ModuleName]
      -> Maybe Language
      -> [Language]
      -> [Extension]
      -> [Extension]
      -> [Extension]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> PerCompilerFlavor [String]
      -> PerCompilerFlavor [String]
      -> PerCompilerFlavor [String]
      -> PerCompilerFlavor [String]
      -> [(String, String)]
      -> [Dependency]
      -> [Mixin]
      -> BuildInfo)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Applicative (g BuildInfo)
<*> FieldName
-> ([String] -> List NoCommaFSep Token' String)
-> ALens' BuildInfo [String]
-> g BuildInfo [String]
forall (g :: * -> * -> *) b a s.
(FieldGrammar g, Parsec b, Pretty b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
External instance of the constraint type forall a sep wrapper. Newtype [a] (List sep wrapper a)
External instance of the constraint type forall a. Monoid [a]
External instance of the constraint type forall a b sep.
(Newtype a b, Sep sep, Pretty b) =>
Pretty (List sep b a)
External instance of the constraint type Newtype String Token'
External instance of the constraint type Sep NoCommaFSep
External instance of the constraint type Pretty Token'
External instance of the constraint type forall a b sep.
(Newtype a b, Sep sep, Parsec b) =>
Parsec (List sep b a)
External instance of the constraint type Newtype String Token'
External instance of the constraint type Sep NoCommaFSep
External instance of the constraint type Parsec Token'
Evidence bound by a type signature of the constraint type FieldGrammar g
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]
External instance of the constraint type forall a b. Functor (Pretext a b)
External instance of the constraint type HasBuildInfo BuildInfo
L.cppOptions
    g BuildInfo
  ([String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [PkgconfigDependency]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [ModuleName]
   -> [ModuleName]
   -> [ModuleName]
   -> Maybe Language
   -> [Language]
   -> [Extension]
   -> [Extension]
   -> [Extension]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> PerCompilerFlavor [String]
   -> PerCompilerFlavor [String]
   -> PerCompilerFlavor [String]
   -> PerCompilerFlavor [String]
   -> [(String, String)]
   -> [Dependency]
   -> [Mixin]
   -> BuildInfo)
-> g BuildInfo [String]
-> g BuildInfo
     ([String]
      -> [String]
      -> [String]
      -> [String]
      -> [PkgconfigDependency]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [ModuleName]
      -> [ModuleName]
      -> [ModuleName]
      -> Maybe Language
      -> [Language]
      -> [Extension]
      -> [Extension]
      -> [Extension]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> PerCompilerFlavor [String]
      -> PerCompilerFlavor [String]
      -> PerCompilerFlavor [String]
      -> PerCompilerFlavor [String]
      -> [(String, String)]
      -> [Dependency]
      -> [Mixin]
      -> BuildInfo)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Applicative (g BuildInfo)
<*> FieldName
-> ([String] -> List NoCommaFSep Token' String)
-> ALens' BuildInfo [String]
-> g BuildInfo [String]
forall (g :: * -> * -> *) b a s.
(FieldGrammar g, Parsec b, Pretty b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
External instance of the constraint type forall a sep wrapper. Newtype [a] (List sep wrapper a)
External instance of the constraint type forall a. Monoid [a]
External instance of the constraint type forall a b sep.
(Newtype a b, Sep sep, Pretty b) =>
Pretty (List sep b a)
External instance of the constraint type Newtype String Token'
External instance of the constraint type Sep NoCommaFSep
External instance of the constraint type Pretty Token'
External instance of the constraint type forall a b sep.
(Newtype a b, Sep sep, Parsec b) =>
Parsec (List sep b a)
External instance of the constraint type Newtype String Token'
External instance of the constraint type Sep NoCommaFSep
External instance of the constraint type Parsec Token'
Evidence bound by a type signature of the constraint type FieldGrammar g
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]
External instance of the constraint type forall a b. Functor (Pretext a b)
External instance of the constraint type HasBuildInfo BuildInfo
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 (g :: * -> * -> *) a s.
FieldGrammar g =>
CabalSpecVersion -> a -> g s a -> g s a
Evidence bound by a type signature of the constraint type FieldGrammar g
availableSince CabalSpecVersion
CabalSpecV3_0 []
    g BuildInfo
  ([String]
   -> [String]
   -> [String]
   -> [String]
   -> [PkgconfigDependency]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [ModuleName]
   -> [ModuleName]
   -> [ModuleName]
   -> Maybe Language
   -> [Language]
   -> [Extension]
   -> [Extension]
   -> [Extension]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> PerCompilerFlavor [String]
   -> PerCompilerFlavor [String]
   -> PerCompilerFlavor [String]
   -> PerCompilerFlavor [String]
   -> [(String, String)]
   -> [Dependency]
   -> [Mixin]
   -> BuildInfo)
-> g BuildInfo [String]
-> g BuildInfo
     ([String]
      -> [String]
      -> [String]
      -> [PkgconfigDependency]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [ModuleName]
      -> [ModuleName]
      -> [ModuleName]
      -> Maybe Language
      -> [Language]
      -> [Extension]
      -> [Extension]
      -> [Extension]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> PerCompilerFlavor [String]
      -> PerCompilerFlavor [String]
      -> PerCompilerFlavor [String]
      -> PerCompilerFlavor [String]
      -> [(String, String)]
      -> [Dependency]
      -> [Mixin]
      -> BuildInfo)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Applicative (g BuildInfo)
<*> FieldName
-> ([String] -> List NoCommaFSep Token' String)
-> ALens' BuildInfo [String]
-> g BuildInfo [String]
forall (g :: * -> * -> *) b a s.
(FieldGrammar g, Parsec b, Pretty b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
External instance of the constraint type forall a sep wrapper. Newtype [a] (List sep wrapper a)
External instance of the constraint type forall a. Monoid [a]
External instance of the constraint type forall a b sep.
(Newtype a b, Sep sep, Pretty b) =>
Pretty (List sep b a)
External instance of the constraint type Newtype String Token'
External instance of the constraint type Sep NoCommaFSep
External instance of the constraint type Pretty Token'
External instance of the constraint type forall a b sep.
(Newtype a b, Sep sep, Parsec b) =>
Parsec (List sep b a)
External instance of the constraint type Newtype String Token'
External instance of the constraint type Sep NoCommaFSep
External instance of the constraint type Parsec Token'
Evidence bound by a type signature of the constraint type FieldGrammar g
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]
External instance of the constraint type forall a b. Functor (Pretext a b)
External instance of the constraint type HasBuildInfo BuildInfo
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 (g :: * -> * -> *) a s.
FieldGrammar g =>
CabalSpecVersion -> a -> g s a -> g s a
Evidence bound by a type signature of the constraint type FieldGrammar g
availableSince CabalSpecVersion
CabalSpecV3_0 []
    g BuildInfo
  ([String]
   -> [String]
   -> [String]
   -> [PkgconfigDependency]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [ModuleName]
   -> [ModuleName]
   -> [ModuleName]
   -> Maybe Language
   -> [Language]
   -> [Extension]
   -> [Extension]
   -> [Extension]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> PerCompilerFlavor [String]
   -> PerCompilerFlavor [String]
   -> PerCompilerFlavor [String]
   -> PerCompilerFlavor [String]
   -> [(String, String)]
   -> [Dependency]
   -> [Mixin]
   -> BuildInfo)
-> g BuildInfo [String]
-> g BuildInfo
     ([String]
      -> [String]
      -> [PkgconfigDependency]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [ModuleName]
      -> [ModuleName]
      -> [ModuleName]
      -> Maybe Language
      -> [Language]
      -> [Extension]
      -> [Extension]
      -> [Extension]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> PerCompilerFlavor [String]
      -> PerCompilerFlavor [String]
      -> PerCompilerFlavor [String]
      -> PerCompilerFlavor [String]
      -> [(String, String)]
      -> [Dependency]
      -> [Mixin]
      -> BuildInfo)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Applicative (g BuildInfo)
<*> FieldName
-> ([String] -> List NoCommaFSep Token' String)
-> ALens' BuildInfo [String]
-> g BuildInfo [String]
forall (g :: * -> * -> *) b a s.
(FieldGrammar g, Parsec b, Pretty b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
External instance of the constraint type forall a sep wrapper. Newtype [a] (List sep wrapper a)
External instance of the constraint type forall a. Monoid [a]
External instance of the constraint type forall a b sep.
(Newtype a b, Sep sep, Pretty b) =>
Pretty (List sep b a)
External instance of the constraint type Newtype String Token'
External instance of the constraint type Sep NoCommaFSep
External instance of the constraint type Pretty Token'
External instance of the constraint type forall a b sep.
(Newtype a b, Sep sep, Parsec b) =>
Parsec (List sep b a)
External instance of the constraint type Newtype String Token'
External instance of the constraint type Sep NoCommaFSep
External instance of the constraint type Parsec Token'
Evidence bound by a type signature of the constraint type FieldGrammar g
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]
External instance of the constraint type forall a b. Functor (Pretext a b)
External instance of the constraint type HasBuildInfo BuildInfo
L.ccOptions
    g BuildInfo
  ([String]
   -> [String]
   -> [PkgconfigDependency]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [ModuleName]
   -> [ModuleName]
   -> [ModuleName]
   -> Maybe Language
   -> [Language]
   -> [Extension]
   -> [Extension]
   -> [Extension]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> PerCompilerFlavor [String]
   -> PerCompilerFlavor [String]
   -> PerCompilerFlavor [String]
   -> PerCompilerFlavor [String]
   -> [(String, String)]
   -> [Dependency]
   -> [Mixin]
   -> BuildInfo)
-> g BuildInfo [String]
-> g BuildInfo
     ([String]
      -> [PkgconfigDependency]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [ModuleName]
      -> [ModuleName]
      -> [ModuleName]
      -> Maybe Language
      -> [Language]
      -> [Extension]
      -> [Extension]
      -> [Extension]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> PerCompilerFlavor [String]
      -> PerCompilerFlavor [String]
      -> PerCompilerFlavor [String]
      -> PerCompilerFlavor [String]
      -> [(String, String)]
      -> [Dependency]
      -> [Mixin]
      -> BuildInfo)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Applicative (g BuildInfo)
<*> FieldName
-> ([String] -> List NoCommaFSep Token' String)
-> ALens' BuildInfo [String]
-> g BuildInfo [String]
forall (g :: * -> * -> *) b a s.
(FieldGrammar g, Parsec b, Pretty b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
External instance of the constraint type forall a sep wrapper. Newtype [a] (List sep wrapper a)
External instance of the constraint type forall a. Monoid [a]
External instance of the constraint type forall a b sep.
(Newtype a b, Sep sep, Pretty b) =>
Pretty (List sep b a)
External instance of the constraint type Newtype String Token'
External instance of the constraint type Sep NoCommaFSep
External instance of the constraint type Pretty Token'
External instance of the constraint type forall a b sep.
(Newtype a b, Sep sep, Parsec b) =>
Parsec (List sep b a)
External instance of the constraint type Newtype String Token'
External instance of the constraint type Sep NoCommaFSep
External instance of the constraint type Parsec Token'
Evidence bound by a type signature of the constraint type FieldGrammar g
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]
External instance of the constraint type forall a b. Functor (Pretext a b)
External instance of the constraint type HasBuildInfo BuildInfo
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 (g :: * -> * -> *) a s.
FieldGrammar g =>
CabalSpecVersion -> a -> g s a -> g s a
Evidence bound by a type signature of the constraint type FieldGrammar g
availableSince CabalSpecVersion
CabalSpecV2_2 []
    g BuildInfo
  ([String]
   -> [PkgconfigDependency]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [ModuleName]
   -> [ModuleName]
   -> [ModuleName]
   -> Maybe Language
   -> [Language]
   -> [Extension]
   -> [Extension]
   -> [Extension]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> PerCompilerFlavor [String]
   -> PerCompilerFlavor [String]
   -> PerCompilerFlavor [String]
   -> PerCompilerFlavor [String]
   -> [(String, String)]
   -> [Dependency]
   -> [Mixin]
   -> BuildInfo)
-> g BuildInfo [String]
-> g BuildInfo
     ([PkgconfigDependency]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [ModuleName]
      -> [ModuleName]
      -> [ModuleName]
      -> Maybe Language
      -> [Language]
      -> [Extension]
      -> [Extension]
      -> [Extension]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> PerCompilerFlavor [String]
      -> PerCompilerFlavor [String]
      -> PerCompilerFlavor [String]
      -> PerCompilerFlavor [String]
      -> [(String, String)]
      -> [Dependency]
      -> [Mixin]
      -> BuildInfo)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Applicative (g BuildInfo)
<*> FieldName
-> ([String] -> List NoCommaFSep Token' String)
-> ALens' BuildInfo [String]
-> g BuildInfo [String]
forall (g :: * -> * -> *) b a s.
(FieldGrammar g, Parsec b, Pretty b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
External instance of the constraint type forall a sep wrapper. Newtype [a] (List sep wrapper a)
External instance of the constraint type forall a. Monoid [a]
External instance of the constraint type forall a b sep.
(Newtype a b, Sep sep, Pretty b) =>
Pretty (List sep b a)
External instance of the constraint type Newtype String Token'
External instance of the constraint type Sep NoCommaFSep
External instance of the constraint type Pretty Token'
External instance of the constraint type forall a b sep.
(Newtype a b, Sep sep, Parsec b) =>
Parsec (List sep b a)
External instance of the constraint type Newtype String Token'
External instance of the constraint type Sep NoCommaFSep
External instance of the constraint type Parsec Token'
Evidence bound by a type signature of the constraint type FieldGrammar g
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]
External instance of the constraint type forall a b. Functor (Pretext a b)
External instance of the constraint type HasBuildInfo BuildInfo
L.ldOptions
    g BuildInfo
  ([PkgconfigDependency]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [ModuleName]
   -> [ModuleName]
   -> [ModuleName]
   -> Maybe Language
   -> [Language]
   -> [Extension]
   -> [Extension]
   -> [Extension]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> PerCompilerFlavor [String]
   -> PerCompilerFlavor [String]
   -> PerCompilerFlavor [String]
   -> PerCompilerFlavor [String]
   -> [(String, String)]
   -> [Dependency]
   -> [Mixin]
   -> BuildInfo)
-> g BuildInfo [PkgconfigDependency]
-> g BuildInfo
     ([String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [ModuleName]
      -> [ModuleName]
      -> [ModuleName]
      -> Maybe Language
      -> [Language]
      -> [Extension]
      -> [Extension]
      -> [Extension]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> PerCompilerFlavor [String]
      -> PerCompilerFlavor [String]
      -> PerCompilerFlavor [String]
      -> PerCompilerFlavor [String]
      -> [(String, String)]
      -> [Dependency]
      -> [Mixin]
      -> BuildInfo)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Applicative (g BuildInfo)
<*> FieldName
-> ([PkgconfigDependency]
    -> List
         CommaFSep (Identity PkgconfigDependency) PkgconfigDependency)
-> ALens' BuildInfo [PkgconfigDependency]
-> g BuildInfo [PkgconfigDependency]
forall (g :: * -> * -> *) b a s.
(FieldGrammar g, Parsec b, Pretty b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
External instance of the constraint type forall a sep wrapper. Newtype [a] (List sep wrapper a)
External instance of the constraint type forall a. Monoid [a]
External instance of the constraint type forall a b sep.
(Newtype a b, Sep sep, Pretty b) =>
Pretty (List sep b a)
External instance of the constraint type forall a. Newtype a (Identity a)
External instance of the constraint type Sep CommaFSep
External instance of the constraint type forall a. Pretty a => Pretty (Identity a)
External instance of the constraint type Pretty PkgconfigDependency
External instance of the constraint type forall a b sep.
(Newtype a b, Sep sep, Parsec b) =>
Parsec (List sep b a)
External instance of the constraint type forall a. Newtype a (Identity a)
External instance of the constraint type Sep CommaFSep
External instance of the constraint type forall a. Parsec a => Parsec (Identity a)
External instance of the constraint type Parsec PkgconfigDependency
Evidence bound by a type signature of the constraint type FieldGrammar g
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]
External instance of the constraint type forall a b. Functor (Pretext a b)
External instance of the constraint type HasBuildInfo BuildInfo
L.pkgconfigDepends
    g BuildInfo
  ([String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [ModuleName]
   -> [ModuleName]
   -> [ModuleName]
   -> Maybe Language
   -> [Language]
   -> [Extension]
   -> [Extension]
   -> [Extension]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [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]
      -> [String]
      -> [ModuleName]
      -> [ModuleName]
      -> [ModuleName]
      -> Maybe Language
      -> [Language]
      -> [Extension]
      -> [Extension]
      -> [Extension]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> PerCompilerFlavor [String]
      -> PerCompilerFlavor [String]
      -> PerCompilerFlavor [String]
      -> PerCompilerFlavor [String]
      -> [(String, String)]
      -> [Dependency]
      -> [Mixin]
      -> BuildInfo)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Applicative (g BuildInfo)
<*> FieldName
-> ([String] -> List FSep Token String)
-> ALens' BuildInfo [String]
-> g BuildInfo [String]
forall (g :: * -> * -> *) b a s.
(FieldGrammar g, Parsec b, Pretty b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
External instance of the constraint type forall a sep wrapper. Newtype [a] (List sep wrapper a)
External instance of the constraint type forall a. Monoid [a]
External instance of the constraint type forall a b sep.
(Newtype a b, Sep sep, Pretty b) =>
Pretty (List sep b a)
External instance of the constraint type Newtype String Token
External instance of the constraint type Sep FSep
External instance of the constraint type Pretty Token
External instance of the constraint type forall a b sep.
(Newtype a b, Sep sep, Parsec b) =>
Parsec (List sep b a)
External instance of the constraint type Newtype String Token
External instance of the constraint type Sep FSep
External instance of the constraint type Parsec Token
Evidence bound by a type signature of the constraint type FieldGrammar g
monoidalFieldAla FieldName
"frameworks"           (FSep -> (String -> Token) -> [String] -> List FSep Token String
forall sep a b. sep -> (a -> b) -> [a] -> List sep b a
alaList' FSep
FSep String -> Token
Token)         ALens' BuildInfo [String]
forall a. HasBuildInfo a => Lens' a [String]
External instance of the constraint type forall a b. Functor (Pretext a b)
External instance of the constraint type HasBuildInfo BuildInfo
L.frameworks
    g BuildInfo
  ([String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [ModuleName]
   -> [ModuleName]
   -> [ModuleName]
   -> Maybe Language
   -> [Language]
   -> [Extension]
   -> [Extension]
   -> [Extension]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [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]
      -> [ModuleName]
      -> [ModuleName]
      -> [ModuleName]
      -> Maybe Language
      -> [Language]
      -> [Extension]
      -> [Extension]
      -> [Extension]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> PerCompilerFlavor [String]
      -> PerCompilerFlavor [String]
      -> PerCompilerFlavor [String]
      -> PerCompilerFlavor [String]
      -> [(String, String)]
      -> [Dependency]
      -> [Mixin]
      -> BuildInfo)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Applicative (g BuildInfo)
<*> FieldName
-> ([String] -> List FSep FilePathNT String)
-> ALens' BuildInfo [String]
-> g BuildInfo [String]
forall (g :: * -> * -> *) b a s.
(FieldGrammar g, Parsec b, Pretty b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
External instance of the constraint type forall a sep wrapper. Newtype [a] (List sep wrapper a)
External instance of the constraint type forall a. Monoid [a]
External instance of the constraint type forall a b sep.
(Newtype a b, Sep sep, Pretty b) =>
Pretty (List sep b a)
External instance of the constraint type Newtype String FilePathNT
External instance of the constraint type Sep FSep
External instance of the constraint type Pretty FilePathNT
External instance of the constraint type forall a b sep.
(Newtype a b, Sep sep, Parsec b) =>
Parsec (List sep b a)
External instance of the constraint type Newtype String FilePathNT
External instance of the constraint type Sep FSep
External instance of the constraint type Parsec FilePathNT
Evidence bound by a type signature of the constraint type FieldGrammar g
monoidalFieldAla FieldName
"extra-framework-dirs" (FSep
-> (String -> FilePathNT)
-> [String]
-> List FSep FilePathNT String
forall sep a b. sep -> (a -> b) -> [a] -> List sep b a
alaList' FSep
FSep String -> FilePathNT
FilePathNT)    ALens' BuildInfo [String]
forall a. HasBuildInfo a => Lens' a [String]
External instance of the constraint type forall a b. Functor (Pretext a b)
External instance of the constraint type HasBuildInfo BuildInfo
L.extraFrameworkDirs
    g BuildInfo
  ([String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [ModuleName]
   -> [ModuleName]
   -> [ModuleName]
   -> Maybe Language
   -> [Language]
   -> [Extension]
   -> [Extension]
   -> [Extension]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> PerCompilerFlavor [String]
   -> PerCompilerFlavor [String]
   -> PerCompilerFlavor [String]
   -> PerCompilerFlavor [String]
   -> [(String, String)]
   -> [Dependency]
   -> [Mixin]
   -> BuildInfo)
-> g BuildInfo [String]
-> g BuildInfo
     ([String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [ModuleName]
      -> [ModuleName]
      -> [ModuleName]
      -> Maybe Language
      -> [Language]
      -> [Extension]
      -> [Extension]
      -> [Extension]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> PerCompilerFlavor [String]
      -> PerCompilerFlavor [String]
      -> PerCompilerFlavor [String]
      -> PerCompilerFlavor [String]
      -> [(String, String)]
      -> [Dependency]
      -> [Mixin]
      -> BuildInfo)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Applicative (g BuildInfo)
<*> FieldName
-> ([String] -> List VCat FilePathNT String)
-> ALens' BuildInfo [String]
-> g BuildInfo [String]
forall (g :: * -> * -> *) b a s.
(FieldGrammar g, Parsec b, Pretty b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
External instance of the constraint type forall a sep wrapper. Newtype [a] (List sep wrapper a)
External instance of the constraint type forall a. Monoid [a]
External instance of the constraint type forall a b sep.
(Newtype a b, Sep sep, Pretty b) =>
Pretty (List sep b a)
External instance of the constraint type Newtype String FilePathNT
External instance of the constraint type Sep VCat
External instance of the constraint type Pretty FilePathNT
External instance of the constraint type forall a b sep.
(Newtype a b, Sep sep, Parsec b) =>
Parsec (List sep b a)
External instance of the constraint type Newtype String FilePathNT
External instance of the constraint type Sep VCat
External instance of the constraint type Parsec FilePathNT
Evidence bound by a type signature of the constraint type FieldGrammar g
monoidalFieldAla FieldName
"asm-sources"          (VCat
-> (String -> FilePathNT)
-> [String]
-> List VCat FilePathNT String
forall sep a b. sep -> (a -> b) -> [a] -> List sep b a
alaList' VCat
VCat String -> FilePathNT
FilePathNT)    ALens' BuildInfo [String]
forall a. HasBuildInfo a => Lens' a [String]
External instance of the constraint type forall a b. Functor (Pretext a b)
External instance of the constraint type HasBuildInfo BuildInfo
L.asmSources
        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 (g :: * -> * -> *) a s.
FieldGrammar g =>
CabalSpecVersion -> a -> g s a -> g s a
Evidence bound by a type signature of the constraint type FieldGrammar g
availableSince CabalSpecVersion
CabalSpecV3_0 []
    g BuildInfo
  ([String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [ModuleName]
   -> [ModuleName]
   -> [ModuleName]
   -> Maybe Language
   -> [Language]
   -> [Extension]
   -> [Extension]
   -> [Extension]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> PerCompilerFlavor [String]
   -> PerCompilerFlavor [String]
   -> PerCompilerFlavor [String]
   -> PerCompilerFlavor [String]
   -> [(String, String)]
   -> [Dependency]
   -> [Mixin]
   -> BuildInfo)
-> g BuildInfo [String]
-> g BuildInfo
     ([String]
      -> [String]
      -> [String]
      -> [String]
      -> [ModuleName]
      -> [ModuleName]
      -> [ModuleName]
      -> Maybe Language
      -> [Language]
      -> [Extension]
      -> [Extension]
      -> [Extension]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> PerCompilerFlavor [String]
      -> PerCompilerFlavor [String]
      -> PerCompilerFlavor [String]
      -> PerCompilerFlavor [String]
      -> [(String, String)]
      -> [Dependency]
      -> [Mixin]
      -> BuildInfo)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Applicative (g BuildInfo)
<*> FieldName
-> ([String] -> List VCat FilePathNT String)
-> ALens' BuildInfo [String]
-> g BuildInfo [String]
forall (g :: * -> * -> *) b a s.
(FieldGrammar g, Parsec b, Pretty b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
External instance of the constraint type forall a sep wrapper. Newtype [a] (List sep wrapper a)
External instance of the constraint type forall a. Monoid [a]
External instance of the constraint type forall a b sep.
(Newtype a b, Sep sep, Pretty b) =>
Pretty (List sep b a)
External instance of the constraint type Newtype String FilePathNT
External instance of the constraint type Sep VCat
External instance of the constraint type Pretty FilePathNT
External instance of the constraint type forall a b sep.
(Newtype a b, Sep sep, Parsec b) =>
Parsec (List sep b a)
External instance of the constraint type Newtype String FilePathNT
External instance of the constraint type Sep VCat
External instance of the constraint type Parsec FilePathNT
Evidence bound by a type signature of the constraint type FieldGrammar g
monoidalFieldAla FieldName
"cmm-sources"          (VCat
-> (String -> FilePathNT)
-> [String]
-> List VCat FilePathNT String
forall sep a b. sep -> (a -> b) -> [a] -> List sep b a
alaList' VCat
VCat String -> FilePathNT
FilePathNT)    ALens' BuildInfo [String]
forall a. HasBuildInfo a => Lens' a [String]
External instance of the constraint type forall a b. Functor (Pretext a b)
External instance of the constraint type HasBuildInfo BuildInfo
L.cmmSources
        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 (g :: * -> * -> *) a s.
FieldGrammar g =>
CabalSpecVersion -> a -> g s a -> g s a
Evidence bound by a type signature of the constraint type FieldGrammar g
availableSince CabalSpecVersion
CabalSpecV3_0 []
    g BuildInfo
  ([String]
   -> [String]
   -> [String]
   -> [String]
   -> [ModuleName]
   -> [ModuleName]
   -> [ModuleName]
   -> Maybe Language
   -> [Language]
   -> [Extension]
   -> [Extension]
   -> [Extension]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> PerCompilerFlavor [String]
   -> PerCompilerFlavor [String]
   -> PerCompilerFlavor [String]
   -> PerCompilerFlavor [String]
   -> [(String, String)]
   -> [Dependency]
   -> [Mixin]
   -> BuildInfo)
-> g BuildInfo [String]
-> g BuildInfo
     ([String]
      -> [String]
      -> [String]
      -> [ModuleName]
      -> [ModuleName]
      -> [ModuleName]
      -> Maybe Language
      -> [Language]
      -> [Extension]
      -> [Extension]
      -> [Extension]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> PerCompilerFlavor [String]
      -> PerCompilerFlavor [String]
      -> PerCompilerFlavor [String]
      -> PerCompilerFlavor [String]
      -> [(String, String)]
      -> [Dependency]
      -> [Mixin]
      -> BuildInfo)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Applicative (g BuildInfo)
<*> FieldName
-> ([String] -> List VCat FilePathNT String)
-> ALens' BuildInfo [String]
-> g BuildInfo [String]
forall (g :: * -> * -> *) b a s.
(FieldGrammar g, Parsec b, Pretty b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
External instance of the constraint type forall a sep wrapper. Newtype [a] (List sep wrapper a)
External instance of the constraint type forall a. Monoid [a]
External instance of the constraint type forall a b sep.
(Newtype a b, Sep sep, Pretty b) =>
Pretty (List sep b a)
External instance of the constraint type Newtype String FilePathNT
External instance of the constraint type Sep VCat
External instance of the constraint type Pretty FilePathNT
External instance of the constraint type forall a b sep.
(Newtype a b, Sep sep, Parsec b) =>
Parsec (List sep b a)
External instance of the constraint type Newtype String FilePathNT
External instance of the constraint type Sep VCat
External instance of the constraint type Parsec FilePathNT
Evidence bound by a type signature of the constraint type FieldGrammar g
monoidalFieldAla FieldName
"c-sources"            (VCat
-> (String -> FilePathNT)
-> [String]
-> List VCat FilePathNT String
forall sep a b. sep -> (a -> b) -> [a] -> List sep b a
alaList' VCat
VCat String -> FilePathNT
FilePathNT)    ALens' BuildInfo [String]
forall a. HasBuildInfo a => Lens' a [String]
External instance of the constraint type forall a b. Functor (Pretext a b)
External instance of the constraint type HasBuildInfo BuildInfo
L.cSources
    g BuildInfo
  ([String]
   -> [String]
   -> [String]
   -> [ModuleName]
   -> [ModuleName]
   -> [ModuleName]
   -> Maybe Language
   -> [Language]
   -> [Extension]
   -> [Extension]
   -> [Extension]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> PerCompilerFlavor [String]
   -> PerCompilerFlavor [String]
   -> PerCompilerFlavor [String]
   -> PerCompilerFlavor [String]
   -> [(String, String)]
   -> [Dependency]
   -> [Mixin]
   -> BuildInfo)
-> g BuildInfo [String]
-> g BuildInfo
     ([String]
      -> [String]
      -> [ModuleName]
      -> [ModuleName]
      -> [ModuleName]
      -> Maybe Language
      -> [Language]
      -> [Extension]
      -> [Extension]
      -> [Extension]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> PerCompilerFlavor [String]
      -> PerCompilerFlavor [String]
      -> PerCompilerFlavor [String]
      -> PerCompilerFlavor [String]
      -> [(String, String)]
      -> [Dependency]
      -> [Mixin]
      -> BuildInfo)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Applicative (g BuildInfo)
<*> FieldName
-> ([String] -> List VCat FilePathNT String)
-> ALens' BuildInfo [String]
-> g BuildInfo [String]
forall (g :: * -> * -> *) b a s.
(FieldGrammar g, Parsec b, Pretty b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
External instance of the constraint type forall a sep wrapper. Newtype [a] (List sep wrapper a)
External instance of the constraint type forall a. Monoid [a]
External instance of the constraint type forall a b sep.
(Newtype a b, Sep sep, Pretty b) =>
Pretty (List sep b a)
External instance of the constraint type Newtype String FilePathNT
External instance of the constraint type Sep VCat
External instance of the constraint type Pretty FilePathNT
External instance of the constraint type forall a b sep.
(Newtype a b, Sep sep, Parsec b) =>
Parsec (List sep b a)
External instance of the constraint type Newtype String FilePathNT
External instance of the constraint type Sep VCat
External instance of the constraint type Parsec FilePathNT
Evidence bound by a type signature of the constraint type FieldGrammar g
monoidalFieldAla FieldName
"cxx-sources"          (VCat
-> (String -> FilePathNT)
-> [String]
-> List VCat FilePathNT String
forall sep a b. sep -> (a -> b) -> [a] -> List sep b a
alaList' VCat
VCat String -> FilePathNT
FilePathNT)    ALens' BuildInfo [String]
forall a. HasBuildInfo a => Lens' a [String]
External instance of the constraint type forall a b. Functor (Pretext a b)
External instance of the constraint type HasBuildInfo BuildInfo
L.cxxSources
        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 (g :: * -> * -> *) a s.
FieldGrammar g =>
CabalSpecVersion -> a -> g s a -> g s a
Evidence bound by a type signature of the constraint type FieldGrammar g
availableSince CabalSpecVersion
CabalSpecV2_2 []
    g BuildInfo
  ([String]
   -> [String]
   -> [ModuleName]
   -> [ModuleName]
   -> [ModuleName]
   -> Maybe Language
   -> [Language]
   -> [Extension]
   -> [Extension]
   -> [Extension]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> PerCompilerFlavor [String]
   -> PerCompilerFlavor [String]
   -> PerCompilerFlavor [String]
   -> PerCompilerFlavor [String]
   -> [(String, String)]
   -> [Dependency]
   -> [Mixin]
   -> BuildInfo)
-> g BuildInfo [String]
-> g BuildInfo
     ([String]
      -> [ModuleName]
      -> [ModuleName]
      -> [ModuleName]
      -> Maybe Language
      -> [Language]
      -> [Extension]
      -> [Extension]
      -> [Extension]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> PerCompilerFlavor [String]
      -> PerCompilerFlavor [String]
      -> PerCompilerFlavor [String]
      -> PerCompilerFlavor [String]
      -> [(String, String)]
      -> [Dependency]
      -> [Mixin]
      -> BuildInfo)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Applicative (g BuildInfo)
<*> FieldName
-> ([String] -> List VCat FilePathNT String)
-> ALens' BuildInfo [String]
-> g BuildInfo [String]
forall (g :: * -> * -> *) b a s.
(FieldGrammar g, Parsec b, Pretty b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
External instance of the constraint type forall a sep wrapper. Newtype [a] (List sep wrapper a)
External instance of the constraint type forall a. Monoid [a]
External instance of the constraint type forall a b sep.
(Newtype a b, Sep sep, Pretty b) =>
Pretty (List sep b a)
External instance of the constraint type Newtype String FilePathNT
External instance of the constraint type Sep VCat
External instance of the constraint type Pretty FilePathNT
External instance of the constraint type forall a b sep.
(Newtype a b, Sep sep, Parsec b) =>
Parsec (List sep b a)
External instance of the constraint type Newtype String FilePathNT
External instance of the constraint type Sep VCat
External instance of the constraint type Parsec FilePathNT
Evidence bound by a type signature of the constraint type FieldGrammar g
monoidalFieldAla FieldName
"js-sources"           (VCat
-> (String -> FilePathNT)
-> [String]
-> List VCat FilePathNT String
forall sep a b. sep -> (a -> b) -> [a] -> List sep b a
alaList' VCat
VCat String -> FilePathNT
FilePathNT)    ALens' BuildInfo [String]
forall a. HasBuildInfo a => Lens' a [String]
External instance of the constraint type forall a b. Functor (Pretext a b)
External instance of the constraint type HasBuildInfo BuildInfo
L.jsSources
    g BuildInfo
  ([String]
   -> [ModuleName]
   -> [ModuleName]
   -> [ModuleName]
   -> Maybe Language
   -> [Language]
   -> [Extension]
   -> [Extension]
   -> [Extension]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> PerCompilerFlavor [String]
   -> PerCompilerFlavor [String]
   -> PerCompilerFlavor [String]
   -> PerCompilerFlavor [String]
   -> [(String, String)]
   -> [Dependency]
   -> [Mixin]
   -> BuildInfo)
-> g BuildInfo [String]
-> g BuildInfo
     ([ModuleName]
      -> [ModuleName]
      -> [ModuleName]
      -> Maybe Language
      -> [Language]
      -> [Extension]
      -> [Extension]
      -> [Extension]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> PerCompilerFlavor [String]
      -> PerCompilerFlavor [String]
      -> PerCompilerFlavor [String]
      -> PerCompilerFlavor [String]
      -> [(String, String)]
      -> [Dependency]
      -> [Mixin]
      -> BuildInfo)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Applicative (g BuildInfo)
<*> g BuildInfo [String]
forall (g :: * -> * -> *).
(FieldGrammar g, Applicative (g BuildInfo)) =>
g BuildInfo [String]
Evidence bound by a type signature of the constraint type Applicative (g BuildInfo)
Evidence bound by a type signature of the constraint type FieldGrammar g
hsSourceDirsGrammar
    g BuildInfo
  ([ModuleName]
   -> [ModuleName]
   -> [ModuleName]
   -> Maybe Language
   -> [Language]
   -> [Extension]
   -> [Extension]
   -> [Extension]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [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]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> PerCompilerFlavor [String]
      -> PerCompilerFlavor [String]
      -> PerCompilerFlavor [String]
      -> PerCompilerFlavor [String]
      -> [(String, String)]
      -> [Dependency]
      -> [Mixin]
      -> BuildInfo)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Applicative (g BuildInfo)
<*> FieldName
-> ([ModuleName] -> List VCat (MQuoted ModuleName) ModuleName)
-> ALens' BuildInfo [ModuleName]
-> g BuildInfo [ModuleName]
forall (g :: * -> * -> *) b a s.
(FieldGrammar g, Parsec b, Pretty b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
External instance of the constraint type forall a sep wrapper. Newtype [a] (List sep wrapper a)
External instance of the constraint type forall a. Monoid [a]
External instance of the constraint type forall a b sep.
(Newtype a b, Sep sep, Pretty b) =>
Pretty (List sep b a)
External instance of the constraint type forall a. Newtype a (MQuoted a)
External instance of the constraint type Sep VCat
External instance of the constraint type forall a. Pretty a => Pretty (MQuoted a)
External instance of the constraint type Pretty ModuleName
External instance of the constraint type forall a b sep.
(Newtype a b, Sep sep, Parsec b) =>
Parsec (List sep b a)
External instance of the constraint type forall a. Newtype a (MQuoted a)
External instance of the constraint type Sep VCat
External instance of the constraint type forall a. Parsec a => Parsec (MQuoted a)
External instance of the constraint type Parsec ModuleName
Evidence bound by a type signature of the constraint type FieldGrammar g
monoidalFieldAla FieldName
"other-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]
External instance of the constraint type forall a b. Functor (Pretext a b)
External instance of the constraint type HasBuildInfo BuildInfo
L.otherModules
    g BuildInfo
  ([ModuleName]
   -> [ModuleName]
   -> Maybe Language
   -> [Language]
   -> [Extension]
   -> [Extension]
   -> [Extension]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [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]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> PerCompilerFlavor [String]
      -> PerCompilerFlavor [String]
      -> PerCompilerFlavor [String]
      -> PerCompilerFlavor [String]
      -> [(String, String)]
      -> [Dependency]
      -> [Mixin]
      -> BuildInfo)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Applicative (g BuildInfo)
<*> FieldName
-> ([ModuleName] -> List VCat (MQuoted ModuleName) ModuleName)
-> ALens' BuildInfo [ModuleName]
-> g BuildInfo [ModuleName]
forall (g :: * -> * -> *) b a s.
(FieldGrammar g, Parsec b, Pretty b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
External instance of the constraint type forall a sep wrapper. Newtype [a] (List sep wrapper a)
External instance of the constraint type forall a. Monoid [a]
External instance of the constraint type forall a b sep.
(Newtype a b, Sep sep, Pretty b) =>
Pretty (List sep b a)
External instance of the constraint type forall a. Newtype a (MQuoted a)
External instance of the constraint type Sep VCat
External instance of the constraint type forall a. Pretty a => Pretty (MQuoted a)
External instance of the constraint type Pretty ModuleName
External instance of the constraint type forall a b sep.
(Newtype a b, Sep sep, Parsec b) =>
Parsec (List sep b a)
External instance of the constraint type forall a. Newtype a (MQuoted a)
External instance of the constraint type Sep VCat
External instance of the constraint type forall a. Parsec a => Parsec (MQuoted a)
External instance of the constraint type Parsec ModuleName
Evidence bound by a type signature of the constraint type FieldGrammar g
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]
External instance of the constraint type forall a b. Functor (Pretext a b)
External instance of the constraint type HasBuildInfo BuildInfo
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 (g :: * -> * -> *) a s.
FieldGrammar g =>
CabalSpecVersion -> a -> g s a -> g s a
Evidence bound by a type signature of the constraint type FieldGrammar g
availableSince CabalSpecVersion
CabalSpecV2_2 []
    g BuildInfo
  ([ModuleName]
   -> Maybe Language
   -> [Language]
   -> [Extension]
   -> [Extension]
   -> [Extension]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [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]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> PerCompilerFlavor [String]
      -> PerCompilerFlavor [String]
      -> PerCompilerFlavor [String]
      -> PerCompilerFlavor [String]
      -> [(String, String)]
      -> [Dependency]
      -> [Mixin]
      -> BuildInfo)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Applicative (g BuildInfo)
<*> FieldName
-> ([ModuleName] -> List VCat (MQuoted ModuleName) ModuleName)
-> ALens' BuildInfo [ModuleName]
-> g BuildInfo [ModuleName]
forall (g :: * -> * -> *) b a s.
(FieldGrammar g, Parsec b, Pretty b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
External instance of the constraint type forall a sep wrapper. Newtype [a] (List sep wrapper a)
External instance of the constraint type forall a. Monoid [a]
External instance of the constraint type forall a b sep.
(Newtype a b, Sep sep, Pretty b) =>
Pretty (List sep b a)
External instance of the constraint type forall a. Newtype a (MQuoted a)
External instance of the constraint type Sep VCat
External instance of the constraint type forall a. Pretty a => Pretty (MQuoted a)
External instance of the constraint type Pretty ModuleName
External instance of the constraint type forall a b sep.
(Newtype a b, Sep sep, Parsec b) =>
Parsec (List sep b a)
External instance of the constraint type forall a. Newtype a (MQuoted a)
External instance of the constraint type Sep VCat
External instance of the constraint type forall a. Parsec a => Parsec (MQuoted a)
External instance of the constraint type Parsec ModuleName
Evidence bound by a type signature of the constraint type FieldGrammar g
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]
External instance of the constraint type forall a b. Functor (Pretext a b)
External instance of the constraint type HasBuildInfo BuildInfo
L.autogenModules
    g BuildInfo
  (Maybe Language
   -> [Language]
   -> [Extension]
   -> [Extension]
   -> [Extension]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [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]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> PerCompilerFlavor [String]
      -> PerCompilerFlavor [String]
      -> PerCompilerFlavor [String]
      -> PerCompilerFlavor [String]
      -> [(String, String)]
      -> [Dependency]
      -> [Mixin]
      -> BuildInfo)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Applicative (g BuildInfo)
<*> FieldName
-> (Language -> MQuoted Language)
-> ALens' BuildInfo (Maybe Language)
-> g BuildInfo (Maybe Language)
forall (g :: * -> * -> *) b a s.
(FieldGrammar g, Parsec b, Pretty b, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s (Maybe a) -> g s (Maybe a)
External instance of the constraint type forall a. Newtype a (MQuoted a)
External instance of the constraint type forall a. Pretty a => Pretty (MQuoted a)
External instance of the constraint type Pretty Language
External instance of the constraint type forall a. Parsec a => Parsec (MQuoted a)
External instance of the constraint type Parsec Language
Evidence bound by a type signature of the constraint type FieldGrammar g
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)
External instance of the constraint type forall a b. Functor (Pretext a b)
External instance of the constraint type HasBuildInfo BuildInfo
L.defaultLanguage
    g BuildInfo
  ([Language]
   -> [Extension]
   -> [Extension]
   -> [Extension]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [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]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> PerCompilerFlavor [String]
      -> PerCompilerFlavor [String]
      -> PerCompilerFlavor [String]
      -> PerCompilerFlavor [String]
      -> [(String, String)]
      -> [Dependency]
      -> [Mixin]
      -> BuildInfo)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Applicative (g BuildInfo)
<*> FieldName
-> ([Language] -> List FSep (MQuoted Language) Language)
-> ALens' BuildInfo [Language]
-> g BuildInfo [Language]
forall (g :: * -> * -> *) b a s.
(FieldGrammar g, Parsec b, Pretty b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
External instance of the constraint type forall a sep wrapper. Newtype [a] (List sep wrapper a)
External instance of the constraint type forall a. Monoid [a]
External instance of the constraint type forall a b sep.
(Newtype a b, Sep sep, Pretty b) =>
Pretty (List sep b a)
External instance of the constraint type forall a. Newtype a (MQuoted a)
External instance of the constraint type Sep FSep
External instance of the constraint type forall a. Pretty a => Pretty (MQuoted a)
External instance of the constraint type Pretty Language
External instance of the constraint type forall a b sep.
(Newtype a b, Sep sep, Parsec b) =>
Parsec (List sep b a)
External instance of the constraint type forall a. Newtype a (MQuoted a)
External instance of the constraint type Sep FSep
External instance of the constraint type forall a. Parsec a => Parsec (MQuoted a)
External instance of the constraint type Parsec Language
Evidence bound by a type signature of the constraint type FieldGrammar g
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]
External instance of the constraint type forall a b. Functor (Pretext a b)
External instance of the constraint type HasBuildInfo BuildInfo
L.otherLanguages
    g BuildInfo
  ([Extension]
   -> [Extension]
   -> [Extension]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [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]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> PerCompilerFlavor [String]
      -> PerCompilerFlavor [String]
      -> PerCompilerFlavor [String]
      -> PerCompilerFlavor [String]
      -> [(String, String)]
      -> [Dependency]
      -> [Mixin]
      -> BuildInfo)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Applicative (g BuildInfo)
<*> FieldName
-> ([Extension] -> List FSep (MQuoted Extension) Extension)
-> ALens' BuildInfo [Extension]
-> g BuildInfo [Extension]
forall (g :: * -> * -> *) b a s.
(FieldGrammar g, Parsec b, Pretty b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
External instance of the constraint type forall a sep wrapper. Newtype [a] (List sep wrapper a)
External instance of the constraint type forall a. Monoid [a]
External instance of the constraint type forall a b sep.
(Newtype a b, Sep sep, Pretty b) =>
Pretty (List sep b a)
External instance of the constraint type forall a. Newtype a (MQuoted a)
External instance of the constraint type Sep FSep
External instance of the constraint type forall a. Pretty a => Pretty (MQuoted a)
External instance of the constraint type Pretty Extension
External instance of the constraint type forall a b sep.
(Newtype a b, Sep sep, Parsec b) =>
Parsec (List sep b a)
External instance of the constraint type forall a. Newtype a (MQuoted a)
External instance of the constraint type Sep FSep
External instance of the constraint type forall a. Parsec a => Parsec (MQuoted a)
External instance of the constraint type Parsec Extension
Evidence bound by a type signature of the constraint type FieldGrammar g
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]
External instance of the constraint type forall a b. Functor (Pretext a b)
External instance of the constraint type HasBuildInfo BuildInfo
L.defaultExtensions
    g BuildInfo
  ([Extension]
   -> [Extension]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [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]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> PerCompilerFlavor [String]
      -> PerCompilerFlavor [String]
      -> PerCompilerFlavor [String]
      -> PerCompilerFlavor [String]
      -> [(String, String)]
      -> [Dependency]
      -> [Mixin]
      -> BuildInfo)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Applicative (g BuildInfo)
<*> FieldName
-> ([Extension] -> List FSep (MQuoted Extension) Extension)
-> ALens' BuildInfo [Extension]
-> g BuildInfo [Extension]
forall (g :: * -> * -> *) b a s.
(FieldGrammar g, Parsec b, Pretty b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
External instance of the constraint type forall a sep wrapper. Newtype [a] (List sep wrapper a)
External instance of the constraint type forall a. Monoid [a]
External instance of the constraint type forall a b sep.
(Newtype a b, Sep sep, Pretty b) =>
Pretty (List sep b a)
External instance of the constraint type forall a. Newtype a (MQuoted a)
External instance of the constraint type Sep FSep
External instance of the constraint type forall a. Pretty a => Pretty (MQuoted a)
External instance of the constraint type Pretty Extension
External instance of the constraint type forall a b sep.
(Newtype a b, Sep sep, Parsec b) =>
Parsec (List sep b a)
External instance of the constraint type forall a. Newtype a (MQuoted a)
External instance of the constraint type Sep FSep
External instance of the constraint type forall a. Parsec a => Parsec (MQuoted a)
External instance of the constraint type Parsec Extension
Evidence bound by a type signature of the constraint type FieldGrammar g
monoidalFieldAla FieldName
"other-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]
External instance of the constraint type forall a b. Functor (Pretext a b)
External instance of the constraint type HasBuildInfo BuildInfo
L.otherExtensions
    g BuildInfo
  ([Extension]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [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]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> PerCompilerFlavor [String]
      -> PerCompilerFlavor [String]
      -> PerCompilerFlavor [String]
      -> PerCompilerFlavor [String]
      -> [(String, String)]
      -> [Dependency]
      -> [Mixin]
      -> BuildInfo)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Applicative (g BuildInfo)
<*> FieldName
-> ([Extension] -> List FSep (MQuoted Extension) Extension)
-> ALens' BuildInfo [Extension]
-> g BuildInfo [Extension]
forall (g :: * -> * -> *) b a s.
(FieldGrammar g, Parsec b, Pretty b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
External instance of the constraint type forall a sep wrapper. Newtype [a] (List sep wrapper a)
External instance of the constraint type forall a. Monoid [a]
External instance of the constraint type forall a b sep.
(Newtype a b, Sep sep, Pretty b) =>
Pretty (List sep b a)
External instance of the constraint type forall a. Newtype a (MQuoted a)
External instance of the constraint type Sep FSep
External instance of the constraint type forall a. Pretty a => Pretty (MQuoted a)
External instance of the constraint type Pretty Extension
External instance of the constraint type forall a b sep.
(Newtype a b, Sep sep, Parsec b) =>
Parsec (List sep b a)
External instance of the constraint type forall a. Newtype a (MQuoted a)
External instance of the constraint type Sep FSep
External instance of the constraint type forall a. Parsec a => Parsec (MQuoted a)
External instance of the constraint type Parsec Extension
Evidence bound by a type signature of the constraint type FieldGrammar g
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]
External instance of the constraint type forall a b. Functor (Pretext a b)
External instance of the constraint type HasBuildInfo BuildInfo
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 (g :: * -> * -> *) s a.
FieldGrammar g =>
CabalSpecVersion -> String -> g s a -> g s a
Evidence bound by a type signature of the constraint type FieldGrammar g
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 (g :: * -> * -> *) s a.
FieldGrammar g =>
CabalSpecVersion -> String -> g s a -> g s a
Evidence bound by a type signature of the constraint type FieldGrammar g
removedIn CabalSpecVersion
CabalSpecV3_0
            String
"Please use 'default-extensions' or 'other-extensions' fields."
    g BuildInfo
  ([String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [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]
      -> [String]
      -> [String]
      -> [String]
      -> PerCompilerFlavor [String]
      -> PerCompilerFlavor [String]
      -> PerCompilerFlavor [String]
      -> PerCompilerFlavor [String]
      -> [(String, String)]
      -> [Dependency]
      -> [Mixin]
      -> BuildInfo)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Applicative (g BuildInfo)
<*> FieldName
-> ([String] -> List VCat Token String)
-> ALens' BuildInfo [String]
-> g BuildInfo [String]
forall (g :: * -> * -> *) b a s.
(FieldGrammar g, Parsec b, Pretty b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
External instance of the constraint type forall a sep wrapper. Newtype [a] (List sep wrapper a)
External instance of the constraint type forall a. Monoid [a]
External instance of the constraint type forall a b sep.
(Newtype a b, Sep sep, Pretty b) =>
Pretty (List sep b a)
External instance of the constraint type Newtype String Token
External instance of the constraint type Sep VCat
External instance of the constraint type Pretty Token
External instance of the constraint type forall a b sep.
(Newtype a b, Sep sep, Parsec b) =>
Parsec (List sep b a)
External instance of the constraint type Newtype String Token
External instance of the constraint type Sep VCat
External instance of the constraint type Parsec Token
Evidence bound by a type signature of the constraint type FieldGrammar g
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]
External instance of the constraint type forall a b. Functor (Pretext a b)
External instance of the constraint type HasBuildInfo BuildInfo
L.extraLibs
    g BuildInfo
  ([String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [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]
      -> [String]
      -> [String]
      -> PerCompilerFlavor [String]
      -> PerCompilerFlavor [String]
      -> PerCompilerFlavor [String]
      -> PerCompilerFlavor [String]
      -> [(String, String)]
      -> [Dependency]
      -> [Mixin]
      -> BuildInfo)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Applicative (g BuildInfo)
<*> FieldName
-> ([String] -> List VCat Token String)
-> ALens' BuildInfo [String]
-> g BuildInfo [String]
forall (g :: * -> * -> *) b a s.
(FieldGrammar g, Parsec b, Pretty b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
External instance of the constraint type forall a sep wrapper. Newtype [a] (List sep wrapper a)
External instance of the constraint type forall a. Monoid [a]
External instance of the constraint type forall a b sep.
(Newtype a b, Sep sep, Pretty b) =>
Pretty (List sep b a)
External instance of the constraint type Newtype String Token
External instance of the constraint type Sep VCat
External instance of the constraint type Pretty Token
External instance of the constraint type forall a b sep.
(Newtype a b, Sep sep, Parsec b) =>
Parsec (List sep b a)
External instance of the constraint type Newtype String Token
External instance of the constraint type Sep VCat
External instance of the constraint type Parsec Token
Evidence bound by a type signature of the constraint type FieldGrammar g
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]
External instance of the constraint type forall a b. Functor (Pretext a b)
External instance of the constraint type HasBuildInfo BuildInfo
L.extraGHCiLibs
    g BuildInfo
  ([String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [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]
      -> [String]
      -> PerCompilerFlavor [String]
      -> PerCompilerFlavor [String]
      -> PerCompilerFlavor [String]
      -> PerCompilerFlavor [String]
      -> [(String, String)]
      -> [Dependency]
      -> [Mixin]
      -> BuildInfo)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Applicative (g BuildInfo)
<*> FieldName
-> ([String] -> List VCat Token String)
-> ALens' BuildInfo [String]
-> g BuildInfo [String]
forall (g :: * -> * -> *) b a s.
(FieldGrammar g, Parsec b, Pretty b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
External instance of the constraint type forall a sep wrapper. Newtype [a] (List sep wrapper a)
External instance of the constraint type forall a. Monoid [a]
External instance of the constraint type forall a b sep.
(Newtype a b, Sep sep, Pretty b) =>
Pretty (List sep b a)
External instance of the constraint type Newtype String Token
External instance of the constraint type Sep VCat
External instance of the constraint type Pretty Token
External instance of the constraint type forall a b sep.
(Newtype a b, Sep sep, Parsec b) =>
Parsec (List sep b a)
External instance of the constraint type Newtype String Token
External instance of the constraint type Sep VCat
External instance of the constraint type Parsec Token
Evidence bound by a type signature of the constraint type FieldGrammar g
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]
External instance of the constraint type forall a b. Functor (Pretext a b)
External instance of the constraint type HasBuildInfo BuildInfo
L.extraBundledLibs
    g BuildInfo
  ([String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [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]
      -> PerCompilerFlavor [String]
      -> PerCompilerFlavor [String]
      -> PerCompilerFlavor [String]
      -> PerCompilerFlavor [String]
      -> [(String, String)]
      -> [Dependency]
      -> [Mixin]
      -> BuildInfo)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Applicative (g BuildInfo)
<*> FieldName
-> ([String] -> List VCat Token String)
-> ALens' BuildInfo [String]
-> g BuildInfo [String]
forall (g :: * -> * -> *) b a s.
(FieldGrammar g, Parsec b, Pretty b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
External instance of the constraint type forall a sep wrapper. Newtype [a] (List sep wrapper a)
External instance of the constraint type forall a. Monoid [a]
External instance of the constraint type forall a b sep.
(Newtype a b, Sep sep, Pretty b) =>
Pretty (List sep b a)
External instance of the constraint type Newtype String Token
External instance of the constraint type Sep VCat
External instance of the constraint type Pretty Token
External instance of the constraint type forall a b sep.
(Newtype a b, Sep sep, Parsec b) =>
Parsec (List sep b a)
External instance of the constraint type Newtype String Token
External instance of the constraint type Sep VCat
External instance of the constraint type Parsec Token
Evidence bound by a type signature of the constraint type FieldGrammar g
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]
External instance of the constraint type forall a b. Functor (Pretext a b)
External instance of the constraint type HasBuildInfo BuildInfo
L.extraLibFlavours
    g BuildInfo
  ([String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> PerCompilerFlavor [String]
   -> PerCompilerFlavor [String]
   -> PerCompilerFlavor [String]
   -> PerCompilerFlavor [String]
   -> [(String, String)]
   -> [Dependency]
   -> [Mixin]
   -> BuildInfo)
-> g BuildInfo [String]
-> g BuildInfo
     ([String]
      -> [String]
      -> [String]
      -> [String]
      -> [String]
      -> PerCompilerFlavor [String]
      -> PerCompilerFlavor [String]
      -> PerCompilerFlavor [String]
      -> PerCompilerFlavor [String]
      -> [(String, String)]
      -> [Dependency]
      -> [Mixin]
      -> BuildInfo)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Applicative (g BuildInfo)
<*> FieldName
-> ([String] -> List VCat Token String)
-> ALens' BuildInfo [String]
-> g BuildInfo [String]
forall (g :: * -> * -> *) b a s.
(FieldGrammar g, Parsec b, Pretty b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
External instance of the constraint type forall a sep wrapper. Newtype [a] (List sep wrapper a)
External instance of the constraint type forall a. Monoid [a]
External instance of the constraint type forall a b sep.
(Newtype a b, Sep sep, Pretty b) =>
Pretty (List sep b a)
External instance of the constraint type Newtype String Token
External instance of the constraint type Sep VCat
External instance of the constraint type Pretty Token
External instance of the constraint type forall a b sep.
(Newtype a b, Sep sep, Parsec b) =>
Parsec (List sep b a)
External instance of the constraint type Newtype String Token
External instance of the constraint type Sep VCat
External instance of the constraint type Parsec Token
Evidence bound by a type signature of the constraint type FieldGrammar g
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]
External instance of the constraint type forall a b. Functor (Pretext a b)
External instance of the constraint type HasBuildInfo BuildInfo
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 (g :: * -> * -> *) a s.
FieldGrammar g =>
CabalSpecVersion -> a -> g s a -> g s a
Evidence bound by a type signature of the constraint type FieldGrammar g
availableSince CabalSpecVersion
CabalSpecV3_0 []
    g BuildInfo
  ([String]
   -> [String]
   -> [String]
   -> [String]
   -> [String]
   -> PerCompilerFlavor [String]
   -> PerCompilerFlavor [String]
   -> PerCompilerFlavor [String]
   -> PerCompilerFlavor [String]
   -> [(String, String)]
   -> [Dependency]
   -> [Mixin]
   -> BuildInfo)
-> g BuildInfo [String]
-> g BuildInfo
     ([String]
      -> [String]
      -> [String]
      -> [String]
      -> PerCompilerFlavor [String]
      -> PerCompilerFlavor [String]
      -> PerCompilerFlavor [String]
      -> PerCompilerFlavor [String]
      -> [(String, String)]
      -> [Dependency]
      -> [Mixin]
      -> BuildInfo)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Applicative (g BuildInfo)
<*> FieldName
-> ([String] -> List FSep FilePathNT String)
-> ALens' BuildInfo [String]
-> g BuildInfo [String]
forall (g :: * -> * -> *) b a s.
(FieldGrammar g, Parsec b, Pretty b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
External instance of the constraint type forall a sep wrapper. Newtype [a] (List sep wrapper a)
External instance of the constraint type forall a. Monoid [a]
External instance of the constraint type forall a b sep.
(Newtype a b, Sep sep, Pretty b) =>
Pretty (List sep b a)
External instance of the constraint type Newtype String FilePathNT
External instance of the constraint type Sep FSep
External instance of the constraint type Pretty FilePathNT
External instance of the constraint type forall a b sep.
(Newtype a b, Sep sep, Parsec b) =>
Parsec (List sep b a)
External instance of the constraint type Newtype String FilePathNT
External instance of the constraint type Sep FSep
External instance of the constraint type Parsec FilePathNT
Evidence bound by a type signature of the constraint type FieldGrammar g
monoidalFieldAla FieldName
"extra-lib-dirs"       (FSep
-> (String -> FilePathNT)
-> [String]
-> List FSep FilePathNT String
forall sep a b. sep -> (a -> b) -> [a] -> List sep b a
alaList' FSep
FSep String -> FilePathNT
FilePathNT)    ALens' BuildInfo [String]
forall a. HasBuildInfo a => Lens' a [String]
External instance of the constraint type forall a b. Functor (Pretext a b)
External instance of the constraint type HasBuildInfo BuildInfo
L.extraLibDirs
    g BuildInfo
  ([String]
   -> [String]
   -> [String]
   -> [String]
   -> PerCompilerFlavor [String]
   -> PerCompilerFlavor [String]
   -> PerCompilerFlavor [String]
   -> PerCompilerFlavor [String]
   -> [(String, String)]
   -> [Dependency]
   -> [Mixin]
   -> BuildInfo)
-> g BuildInfo [String]
-> g BuildInfo
     ([String]
      -> [String]
      -> [String]
      -> PerCompilerFlavor [String]
      -> PerCompilerFlavor [String]
      -> PerCompilerFlavor [String]
      -> PerCompilerFlavor [String]
      -> [(String, String)]
      -> [Dependency]
      -> [Mixin]
      -> BuildInfo)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Applicative (g BuildInfo)
<*> FieldName
-> ([String] -> List FSep FilePathNT String)
-> ALens' BuildInfo [String]
-> g BuildInfo [String]
forall (g :: * -> * -> *) b a s.
(FieldGrammar g, Parsec b, Pretty b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
External instance of the constraint type forall a sep wrapper. Newtype [a] (List sep wrapper a)
External instance of the constraint type forall a. Monoid [a]
External instance of the constraint type forall a b sep.
(Newtype a b, Sep sep, Pretty b) =>
Pretty (List sep b a)
External instance of the constraint type Newtype String FilePathNT
External instance of the constraint type Sep FSep
External instance of the constraint type Pretty FilePathNT
External instance of the constraint type forall a b sep.
(Newtype a b, Sep sep, Parsec b) =>
Parsec (List sep b a)
External instance of the constraint type Newtype String FilePathNT
External instance of the constraint type Sep FSep
External instance of the constraint type Parsec FilePathNT
Evidence bound by a type signature of the constraint type FieldGrammar g
monoidalFieldAla FieldName
"include-dirs"         (FSep
-> (String -> FilePathNT)
-> [String]
-> List FSep FilePathNT String
forall sep a b. sep -> (a -> b) -> [a] -> List sep b a
alaList' FSep
FSep String -> FilePathNT
FilePathNT)    ALens' BuildInfo [String]
forall a. HasBuildInfo a => Lens' a [String]
External instance of the constraint type forall a b. Functor (Pretext a b)
External instance of the constraint type HasBuildInfo BuildInfo
L.includeDirs
    g BuildInfo
  ([String]
   -> [String]
   -> [String]
   -> PerCompilerFlavor [String]
   -> PerCompilerFlavor [String]
   -> PerCompilerFlavor [String]
   -> PerCompilerFlavor [String]
   -> [(String, String)]
   -> [Dependency]
   -> [Mixin]
   -> BuildInfo)
-> g BuildInfo [String]
-> g BuildInfo
     ([String]
      -> [String]
      -> PerCompilerFlavor [String]
      -> PerCompilerFlavor [String]
      -> PerCompilerFlavor [String]
      -> PerCompilerFlavor [String]
      -> [(String, String)]
      -> [Dependency]
      -> [Mixin]
      -> BuildInfo)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Applicative (g BuildInfo)
<*> FieldName
-> ([String] -> List FSep FilePathNT String)
-> ALens' BuildInfo [String]
-> g BuildInfo [String]
forall (g :: * -> * -> *) b a s.
(FieldGrammar g, Parsec b, Pretty b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
External instance of the constraint type forall a sep wrapper. Newtype [a] (List sep wrapper a)
External instance of the constraint type forall a. Monoid [a]
External instance of the constraint type forall a b sep.
(Newtype a b, Sep sep, Pretty b) =>
Pretty (List sep b a)
External instance of the constraint type Newtype String FilePathNT
External instance of the constraint type Sep FSep
External instance of the constraint type Pretty FilePathNT
External instance of the constraint type forall a b sep.
(Newtype a b, Sep sep, Parsec b) =>
Parsec (List sep b a)
External instance of the constraint type Newtype String FilePathNT
External instance of the constraint type Sep FSep
External instance of the constraint type Parsec FilePathNT
Evidence bound by a type signature of the constraint type FieldGrammar g
monoidalFieldAla FieldName
"includes"             (FSep
-> (String -> FilePathNT)
-> [String]
-> List FSep FilePathNT String
forall sep a b. sep -> (a -> b) -> [a] -> List sep b a
alaList' FSep
FSep String -> FilePathNT
FilePathNT)    ALens' BuildInfo [String]
forall a. HasBuildInfo a => Lens' a [String]
External instance of the constraint type forall a b. Functor (Pretext a b)
External instance of the constraint type HasBuildInfo BuildInfo
L.includes
    g BuildInfo
  ([String]
   -> [String]
   -> PerCompilerFlavor [String]
   -> PerCompilerFlavor [String]
   -> PerCompilerFlavor [String]
   -> PerCompilerFlavor [String]
   -> [(String, String)]
   -> [Dependency]
   -> [Mixin]
   -> BuildInfo)
-> g BuildInfo [String]
-> g BuildInfo
     ([String]
      -> PerCompilerFlavor [String]
      -> PerCompilerFlavor [String]
      -> PerCompilerFlavor [String]
      -> PerCompilerFlavor [String]
      -> [(String, String)]
      -> [Dependency]
      -> [Mixin]
      -> BuildInfo)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Applicative (g BuildInfo)
<*> FieldName
-> ([String] -> List FSep FilePathNT String)
-> ALens' BuildInfo [String]
-> g BuildInfo [String]
forall (g :: * -> * -> *) b a s.
(FieldGrammar g, Parsec b, Pretty b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
External instance of the constraint type forall a sep wrapper. Newtype [a] (List sep wrapper a)
External instance of the constraint type forall a. Monoid [a]
External instance of the constraint type forall a b sep.
(Newtype a b, Sep sep, Pretty b) =>
Pretty (List sep b a)
External instance of the constraint type Newtype String FilePathNT
External instance of the constraint type Sep FSep
External instance of the constraint type Pretty FilePathNT
External instance of the constraint type forall a b sep.
(Newtype a b, Sep sep, Parsec b) =>
Parsec (List sep b a)
External instance of the constraint type Newtype String FilePathNT
External instance of the constraint type Sep FSep
External instance of the constraint type Parsec FilePathNT
Evidence bound by a type signature of the constraint type FieldGrammar g
monoidalFieldAla FieldName
"autogen-includes"     (FSep
-> (String -> FilePathNT)
-> [String]
-> List FSep FilePathNT String
forall sep a b. sep -> (a -> b) -> [a] -> List sep b a
alaList' FSep
FSep String -> FilePathNT
FilePathNT)    ALens' BuildInfo [String]
forall a. HasBuildInfo a => Lens' a [String]
External instance of the constraint type forall a b. Functor (Pretext a b)
External instance of the constraint type HasBuildInfo BuildInfo
L.autogenIncludes
        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 (g :: * -> * -> *) a s.
FieldGrammar g =>
CabalSpecVersion -> a -> g s a -> g s a
Evidence bound by a type signature of the constraint type FieldGrammar g
availableSince CabalSpecVersion
CabalSpecV3_0 []
    g BuildInfo
  ([String]
   -> PerCompilerFlavor [String]
   -> PerCompilerFlavor [String]
   -> PerCompilerFlavor [String]
   -> PerCompilerFlavor [String]
   -> [(String, String)]
   -> [Dependency]
   -> [Mixin]
   -> BuildInfo)
-> g BuildInfo [String]
-> g BuildInfo
     (PerCompilerFlavor [String]
      -> PerCompilerFlavor [String]
      -> PerCompilerFlavor [String]
      -> PerCompilerFlavor [String]
      -> [(String, String)]
      -> [Dependency]
      -> [Mixin]
      -> BuildInfo)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Applicative (g BuildInfo)
<*> FieldName
-> ([String] -> List FSep FilePathNT String)
-> ALens' BuildInfo [String]
-> g BuildInfo [String]
forall (g :: * -> * -> *) b a s.
(FieldGrammar g, Parsec b, Pretty b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
External instance of the constraint type forall a sep wrapper. Newtype [a] (List sep wrapper a)
External instance of the constraint type forall a. Monoid [a]
External instance of the constraint type forall a b sep.
(Newtype a b, Sep sep, Pretty b) =>
Pretty (List sep b a)
External instance of the constraint type Newtype String FilePathNT
External instance of the constraint type Sep FSep
External instance of the constraint type Pretty FilePathNT
External instance of the constraint type forall a b sep.
(Newtype a b, Sep sep, Parsec b) =>
Parsec (List sep b a)
External instance of the constraint type Newtype String FilePathNT
External instance of the constraint type Sep FSep
External instance of the constraint type Parsec FilePathNT
Evidence bound by a type signature of the constraint type FieldGrammar g
monoidalFieldAla FieldName
"install-includes"     (FSep
-> (String -> FilePathNT)
-> [String]
-> List FSep FilePathNT String
forall sep a b. sep -> (a -> b) -> [a] -> List sep b a
alaList' FSep
FSep String -> FilePathNT
FilePathNT)    ALens' BuildInfo [String]
forall a. HasBuildInfo a => Lens' a [String]
External instance of the constraint type forall a b. Functor (Pretext a b)
External instance of the constraint type HasBuildInfo BuildInfo
L.installIncludes
    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 (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Applicative (g BuildInfo)
<*> g BuildInfo (PerCompilerFlavor [String])
forall (g :: * -> * -> *).
(FieldGrammar g, Applicative (g BuildInfo)) =>
g BuildInfo (PerCompilerFlavor [String])
Evidence bound by a type signature of the constraint type Applicative (g BuildInfo)
Evidence bound by a type signature of the constraint type FieldGrammar g
optionsFieldGrammar
    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 (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Applicative (g BuildInfo)
<*> g BuildInfo (PerCompilerFlavor [String])
forall (g :: * -> * -> *).
(FieldGrammar g, Applicative (g BuildInfo)) =>
g BuildInfo (PerCompilerFlavor [String])
Evidence bound by a type signature of the constraint type Applicative (g BuildInfo)
Evidence bound by a type signature of the constraint type FieldGrammar g
profOptionsFieldGrammar
    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 (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Applicative (g BuildInfo)
<*> g BuildInfo (PerCompilerFlavor [String])
forall (g :: * -> * -> *).
(FieldGrammar g, Applicative (g BuildInfo)) =>
g BuildInfo (PerCompilerFlavor [String])
Evidence bound by a type signature of the constraint type Applicative (g BuildInfo)
Evidence bound by a type signature of the constraint type FieldGrammar g
sharedOptionsFieldGrammar
    g BuildInfo
  (PerCompilerFlavor [String]
   -> [(String, String)] -> [Dependency] -> [Mixin] -> BuildInfo)
-> g BuildInfo (PerCompilerFlavor [String])
-> g BuildInfo
     ([(String, String)] -> [Dependency] -> [Mixin] -> BuildInfo)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Applicative (g BuildInfo)
<*> PerCompilerFlavor [String]
-> g BuildInfo (PerCompilerFlavor [String])
forall (f :: * -> *) a. Applicative f => a -> f a
Evidence bound by a type signature of the constraint type Applicative (g BuildInfo)
pure PerCompilerFlavor [String]
forall a. Monoid a => a
External instance of the constraint type forall a. (Semigroup a, Monoid a) => Monoid (PerCompilerFlavor a)
External instance of the constraint type forall a. Semigroup [a]
External instance of the constraint type forall a. Monoid [a]
mempty -- static-options ???
    g BuildInfo
  ([(String, String)] -> [Dependency] -> [Mixin] -> BuildInfo)
-> g BuildInfo [(String, String)]
-> g BuildInfo ([Dependency] -> [Mixin] -> BuildInfo)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Applicative (g BuildInfo)
<*> FieldName
-> ALens' BuildInfo [(String, String)]
-> g BuildInfo [(String, String)]
forall (g :: * -> * -> *) s.
FieldGrammar g =>
FieldName -> ALens' s [(String, String)] -> g s [(String, String)]
Evidence bound by a type signature of the constraint type FieldGrammar g
prefixedFields   FieldName
"x-"                                                 ALens' BuildInfo [(String, String)]
forall a. HasBuildInfo a => Lens' a [(String, String)]
External instance of the constraint type forall a b. Functor (Pretext a b)
External instance of the constraint type HasBuildInfo BuildInfo
L.customFieldsBI
    g BuildInfo ([Dependency] -> [Mixin] -> BuildInfo)
-> g BuildInfo [Dependency] -> g BuildInfo ([Mixin] -> BuildInfo)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Applicative (g BuildInfo)
<*> FieldName
-> ([Dependency]
    -> List CommaVCat (Identity Dependency) Dependency)
-> ALens' BuildInfo [Dependency]
-> g BuildInfo [Dependency]
forall (g :: * -> * -> *) b a s.
(FieldGrammar g, Parsec b, Pretty b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
External instance of the constraint type forall a sep wrapper. Newtype [a] (List sep wrapper a)
External instance of the constraint type forall a. Monoid [a]
External instance of the constraint type forall a b sep.
(Newtype a b, Sep sep, Pretty b) =>
Pretty (List sep b a)
External instance of the constraint type forall a. Newtype a (Identity a)
External instance of the constraint type Sep CommaVCat
External instance of the constraint type forall a. Pretty a => Pretty (Identity a)
External instance of the constraint type Pretty Dependency
External instance of the constraint type forall a b sep.
(Newtype a b, Sep sep, Parsec b) =>
Parsec (List sep b a)
External instance of the constraint type forall a. Newtype a (Identity a)
External instance of the constraint type Sep CommaVCat
External instance of the constraint type forall a. Parsec a => Parsec (Identity a)
External instance of the constraint type Parsec Dependency
Evidence bound by a type signature of the constraint type FieldGrammar g
monoidalFieldAla FieldName
"build-depends"        (CommaVCat
-> [Dependency] -> List CommaVCat (Identity Dependency) Dependency
forall sep a. sep -> [a] -> List sep (Identity a) a
alaList  CommaVCat
CommaVCat)          ALens' BuildInfo [Dependency]
forall a. HasBuildInfo a => Lens' a [Dependency]
External instance of the constraint type forall a b. Functor (Pretext a b)
External instance of the constraint type HasBuildInfo BuildInfo
L.targetBuildDepends
    g BuildInfo ([Mixin] -> BuildInfo)
-> g BuildInfo [Mixin] -> g BuildInfo BuildInfo
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Applicative (g BuildInfo)
<*> FieldName
-> ([Mixin] -> List CommaVCat (Identity Mixin) Mixin)
-> ALens' BuildInfo [Mixin]
-> g BuildInfo [Mixin]
forall (g :: * -> * -> *) b a s.
(FieldGrammar g, Parsec b, Pretty b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
External instance of the constraint type forall a sep wrapper. Newtype [a] (List sep wrapper a)
External instance of the constraint type forall a. Monoid [a]
External instance of the constraint type forall a b sep.
(Newtype a b, Sep sep, Pretty b) =>
Pretty (List sep b a)
External instance of the constraint type forall a. Newtype a (Identity a)
External instance of the constraint type Sep CommaVCat
External instance of the constraint type forall a. Pretty a => Pretty (Identity a)
External instance of the constraint type Pretty Mixin
External instance of the constraint type forall a b sep.
(Newtype a b, Sep sep, Parsec b) =>
Parsec (List sep b a)
External instance of the constraint type forall a. Newtype a (Identity a)
External instance of the constraint type Sep CommaVCat
External instance of the constraint type forall a. Parsec a => Parsec (Identity a)
External instance of the constraint type Parsec Mixin
Evidence bound by a type signature of the constraint type FieldGrammar g
monoidalFieldAla FieldName
"mixins"               (CommaVCat -> [Mixin] -> List CommaVCat (Identity Mixin) Mixin
forall sep a. sep -> [a] -> List sep (Identity a) a
alaList  CommaVCat
CommaVCat)          ALens' BuildInfo [Mixin]
forall a. HasBuildInfo a => Lens' a [Mixin]
External instance of the constraint type forall a b. Functor (Pretext a b)
External instance of the constraint type HasBuildInfo BuildInfo
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 (g :: * -> * -> *) a s.
FieldGrammar g =>
CabalSpecVersion -> a -> g s a -> g s a
Evidence bound by a type signature of the constraint type FieldGrammar g
availableSince CabalSpecVersion
CabalSpecV2_0 []
{-# SPECIALIZE buildInfoFieldGrammar :: ParsecFieldGrammar' BuildInfo #-}
{-# SPECIALIZE buildInfoFieldGrammar :: PrettyFieldGrammar' BuildInfo #-}

hsSourceDirsGrammar
    :: (FieldGrammar g, Applicative (g BuildInfo))
    => g BuildInfo [FilePath]
hsSourceDirsGrammar :: g BuildInfo [String]
hsSourceDirsGrammar = [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
(++)
    ([String] -> [String] -> [String])
-> g BuildInfo [String] -> g BuildInfo ([String] -> [String])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type forall (f :: * -> *). Applicative f => Functor f
Evidence bound by a type signature of the constraint type Applicative (g BuildInfo)
<$> FieldName
-> ([String] -> List FSep FilePathNT String)
-> ALens' BuildInfo [String]
-> g BuildInfo [String]
forall (g :: * -> * -> *) b a s.
(FieldGrammar g, Parsec b, Pretty b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
External instance of the constraint type forall a sep wrapper. Newtype [a] (List sep wrapper a)
External instance of the constraint type forall a. Monoid [a]
External instance of the constraint type forall a b sep.
(Newtype a b, Sep sep, Pretty b) =>
Pretty (List sep b a)
External instance of the constraint type Newtype String FilePathNT
External instance of the constraint type Sep FSep
External instance of the constraint type Pretty FilePathNT
External instance of the constraint type forall a b sep.
(Newtype a b, Sep sep, Parsec b) =>
Parsec (List sep b a)
External instance of the constraint type Newtype String FilePathNT
External instance of the constraint type Sep FSep
External instance of the constraint type Parsec FilePathNT
Evidence bound by a type signature of the constraint type FieldGrammar g
monoidalFieldAla FieldName
"hs-source-dirs" (FSep
-> (String -> FilePathNT)
-> [String]
-> List FSep FilePathNT String
forall sep a b. sep -> (a -> b) -> [a] -> List sep b a
alaList' FSep
FSep String -> FilePathNT
FilePathNT) ALens' BuildInfo [String]
forall a. HasBuildInfo a => Lens' a [String]
External instance of the constraint type forall a b. Functor (Pretext a b)
External instance of the constraint type HasBuildInfo BuildInfo
L.hsSourceDirs
    g BuildInfo ([String] -> [String])
-> g BuildInfo [String] -> g BuildInfo [String]
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Applicative (g BuildInfo)
<*> FieldName
-> ([String] -> List FSep FilePathNT String)
-> ALens' BuildInfo [String]
-> g BuildInfo [String]
forall (g :: * -> * -> *) b a s.
(FieldGrammar g, Parsec b, Pretty b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
External instance of the constraint type forall a sep wrapper. Newtype [a] (List sep wrapper a)
External instance of the constraint type forall a. Monoid [a]
External instance of the constraint type forall a b sep.
(Newtype a b, Sep sep, Pretty b) =>
Pretty (List sep b a)
External instance of the constraint type Newtype String FilePathNT
External instance of the constraint type Sep FSep
External instance of the constraint type Pretty FilePathNT
External instance of the constraint type forall a b sep.
(Newtype a b, Sep sep, Parsec b) =>
Parsec (List sep b a)
External instance of the constraint type Newtype String FilePathNT
External instance of the constraint type Sep FSep
External instance of the constraint type Parsec FilePathNT
Evidence bound by a type signature of the constraint type FieldGrammar g
monoidalFieldAla FieldName
"hs-source-dir"  (FSep
-> (String -> FilePathNT)
-> [String]
-> List FSep FilePathNT String
forall sep a b. sep -> (a -> b) -> [a] -> List sep b a
alaList' FSep
FSep String -> FilePathNT
FilePathNT) ALens' BuildInfo [String]
forall (f :: * -> *). Functor f => LensLike' f BuildInfo [String]
External instance of the constraint type forall a b. Functor (Pretext a b)
wrongLens
        --- https://github.com/haskell/cabal/commit/49e3cdae3bdf21b017ccd42e66670ca402e22b44
        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 (g :: * -> * -> *) s a.
FieldGrammar g =>
CabalSpecVersion -> String -> g s a -> g s a
Evidence bound by a type signature of the constraint type FieldGrammar g
deprecatedSince CabalSpecVersion
CabalSpecV1_2 String
"Please use 'hs-source-dirs'"
        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 (g :: * -> * -> *) s a.
FieldGrammar g =>
CabalSpecVersion -> String -> g s a -> g s a
Evidence bound by a type signature of the constraint type FieldGrammar g
removedIn CabalSpecVersion
CabalSpecV3_0 String
"Please use 'hs-source-dirs' field."
  where
    -- TODO: make pretty printer aware of CabalSpecVersion
    wrongLens :: Functor f => LensLike' f BuildInfo [FilePath]
    wrongLens :: LensLike' f BuildInfo [String]
wrongLens [String] -> f [String]
f BuildInfo
bi = (\[String]
fps -> ASetter BuildInfo BuildInfo [String] [String]
-> [String] -> BuildInfo -> BuildInfo
forall s t a b. ASetter s t a b -> b -> s -> t
set ASetter BuildInfo BuildInfo [String] [String]
forall a. HasBuildInfo a => Lens' a [String]
External instance of the constraint type Functor Identity
External instance of the constraint type HasBuildInfo BuildInfo
L.hsSourceDirs [String]
fps BuildInfo
bi) ([String] -> BuildInfo) -> f [String] -> f BuildInfo
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Functor f
<$> [String] -> f [String]
f []

optionsFieldGrammar
    :: (FieldGrammar g, Applicative (g BuildInfo))
    => g BuildInfo (PerCompilerFlavor [String])
optionsFieldGrammar :: 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
External instance of the constraint type forall (f :: * -> *). Applicative f => Functor f
Evidence bound by a type signature of the constraint type Applicative (g BuildInfo)
<$> FieldName
-> ([String] -> List NoCommaFSep Token' String)
-> ALens' BuildInfo [String]
-> g BuildInfo [String]
forall (g :: * -> * -> *) b a s.
(FieldGrammar g, Parsec b, Pretty b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
External instance of the constraint type forall a sep wrapper. Newtype [a] (List sep wrapper a)
External instance of the constraint type forall a. Monoid [a]
External instance of the constraint type forall a b sep.
(Newtype a b, Sep sep, Pretty b) =>
Pretty (List sep b a)
External instance of the constraint type Newtype String Token'
External instance of the constraint type Sep NoCommaFSep
External instance of the constraint type Pretty Token'
External instance of the constraint type forall a b sep.
(Newtype a b, Sep sep, Parsec b) =>
Parsec (List sep b a)
External instance of the constraint type Newtype String Token'
External instance of the constraint type Sep NoCommaFSep
External instance of the constraint type Parsec Token'
Evidence bound by a type signature of the constraint type FieldGrammar g
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 (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Applicative (g BuildInfo)
<*> FieldName
-> ([String] -> List NoCommaFSep Token' String)
-> ALens' BuildInfo [String]
-> g BuildInfo [String]
forall (g :: * -> * -> *) b a s.
(FieldGrammar g, Parsec b, Pretty b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
External instance of the constraint type forall a sep wrapper. Newtype [a] (List sep wrapper a)
External instance of the constraint type forall a. Monoid [a]
External instance of the constraint type forall a b sep.
(Newtype a b, Sep sep, Pretty b) =>
Pretty (List sep b a)
External instance of the constraint type Newtype String Token'
External instance of the constraint type Sep NoCommaFSep
External instance of the constraint type Pretty Token'
External instance of the constraint type forall a b sep.
(Newtype a b, Sep sep, Parsec b) =>
Parsec (List sep b a)
External instance of the constraint type Newtype String Token'
External instance of the constraint type Sep NoCommaFSep
External instance of the constraint type Parsec Token'
Evidence bound by a type signature of the constraint type FieldGrammar g
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)
    -- NOTE: Hugs, NHC and JHC are not supported anymore, but these
    -- fields are kept around so that we can still parse legacy .cabal
    -- files that have them.
    g BuildInfo (PerCompilerFlavor [String])
-> g BuildInfo () -> g BuildInfo (PerCompilerFlavor [String])
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
Evidence bound by a type signature of the constraint type Applicative (g BuildInfo)
<*  FieldName -> g BuildInfo ()
forall (g :: * -> * -> *) s. FieldGrammar g => FieldName -> g s ()
Evidence bound by a type signature of the constraint type FieldGrammar g
knownField FieldName
"jhc-options"
    g BuildInfo (PerCompilerFlavor [String])
-> g BuildInfo () -> g BuildInfo (PerCompilerFlavor [String])
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
Evidence bound by a type signature of the constraint type Applicative (g BuildInfo)
<*  FieldName -> g BuildInfo ()
forall (g :: * -> * -> *) s. FieldGrammar g => FieldName -> g s ()
Evidence bound by a type signature of the constraint type FieldGrammar g
knownField FieldName
"hugs-options"
    g BuildInfo (PerCompilerFlavor [String])
-> g BuildInfo () -> g BuildInfo (PerCompilerFlavor [String])
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
Evidence bound by a type signature of the constraint type Applicative (g BuildInfo)
<*  FieldName -> g BuildInfo ()
forall (g :: * -> * -> *) s. FieldGrammar g => FieldName -> g s ()
Evidence bound by a type signature of the constraint type FieldGrammar g
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])
External instance of the constraint type forall a b. Functor (Pretext a b)
External instance of the constraint type HasBuildInfo BuildInfo
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
External instance of the constraint type forall a. Monoid [a]
External instance of the constraint type forall a b. Functor (Pretext a b)
lookupLens CompilerFlavor
flavor

profOptionsFieldGrammar
    :: (FieldGrammar g, Applicative (g BuildInfo))
    => g BuildInfo (PerCompilerFlavor [String])
profOptionsFieldGrammar :: 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
External instance of the constraint type forall (f :: * -> *). Applicative f => Functor f
Evidence bound by a type signature of the constraint type Applicative (g BuildInfo)
<$> FieldName
-> ([String] -> List NoCommaFSep Token' String)
-> ALens' BuildInfo [String]
-> g BuildInfo [String]
forall (g :: * -> * -> *) b a s.
(FieldGrammar g, Parsec b, Pretty b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
External instance of the constraint type forall a sep wrapper. Newtype [a] (List sep wrapper a)
External instance of the constraint type forall a. Monoid [a]
External instance of the constraint type forall a b sep.
(Newtype a b, Sep sep, Pretty b) =>
Pretty (List sep b a)
External instance of the constraint type Newtype String Token'
External instance of the constraint type Sep NoCommaFSep
External instance of the constraint type Pretty Token'
External instance of the constraint type forall a b sep.
(Newtype a b, Sep sep, Parsec b) =>
Parsec (List sep b a)
External instance of the constraint type Newtype String Token'
External instance of the constraint type Sep NoCommaFSep
External instance of the constraint type Parsec Token'
Evidence bound by a type signature of the constraint type FieldGrammar g
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 (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Applicative (g BuildInfo)
<*> FieldName
-> ([String] -> List NoCommaFSep Token' String)
-> ALens' BuildInfo [String]
-> g BuildInfo [String]
forall (g :: * -> * -> *) b a s.
(FieldGrammar g, Parsec b, Pretty b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
External instance of the constraint type forall a sep wrapper. Newtype [a] (List sep wrapper a)
External instance of the constraint type forall a. Monoid [a]
External instance of the constraint type forall a b sep.
(Newtype a b, Sep sep, Pretty b) =>
Pretty (List sep b a)
External instance of the constraint type Newtype String Token'
External instance of the constraint type Sep NoCommaFSep
External instance of the constraint type Pretty Token'
External instance of the constraint type forall a b sep.
(Newtype a b, Sep sep, Parsec b) =>
Parsec (List sep b a)
External instance of the constraint type Newtype String Token'
External instance of the constraint type Sep NoCommaFSep
External instance of the constraint type Parsec Token'
Evidence bound by a type signature of the constraint type FieldGrammar g
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])
External instance of the constraint type forall a b. Functor (Pretext a b)
External instance of the constraint type HasBuildInfo BuildInfo
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
External instance of the constraint type forall a. Monoid [a]
External instance of the constraint type forall a b. Functor (Pretext a b)
lookupLens CompilerFlavor
flavor

sharedOptionsFieldGrammar
    :: (FieldGrammar g, Applicative (g BuildInfo))
    => g BuildInfo (PerCompilerFlavor [String])
sharedOptionsFieldGrammar :: 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
External instance of the constraint type forall (f :: * -> *). Applicative f => Functor f
Evidence bound by a type signature of the constraint type Applicative (g BuildInfo)
<$> FieldName
-> ([String] -> List NoCommaFSep Token' String)
-> ALens' BuildInfo [String]
-> g BuildInfo [String]
forall (g :: * -> * -> *) b a s.
(FieldGrammar g, Parsec b, Pretty b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
External instance of the constraint type forall a sep wrapper. Newtype [a] (List sep wrapper a)
External instance of the constraint type forall a. Monoid [a]
External instance of the constraint type forall a b sep.
(Newtype a b, Sep sep, Pretty b) =>
Pretty (List sep b a)
External instance of the constraint type Newtype String Token'
External instance of the constraint type Sep NoCommaFSep
External instance of the constraint type Pretty Token'
External instance of the constraint type forall a b sep.
(Newtype a b, Sep sep, Parsec b) =>
Parsec (List sep b a)
External instance of the constraint type Newtype String Token'
External instance of the constraint type Sep NoCommaFSep
External instance of the constraint type Parsec Token'
Evidence bound by a type signature of the constraint type FieldGrammar g
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 (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Applicative (g BuildInfo)
<*> FieldName
-> ([String] -> List NoCommaFSep Token' String)
-> ALens' BuildInfo [String]
-> g BuildInfo [String]
forall (g :: * -> * -> *) b a s.
(FieldGrammar g, Parsec b, Pretty b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
External instance of the constraint type forall a sep wrapper. Newtype [a] (List sep wrapper a)
External instance of the constraint type forall a. Monoid [a]
External instance of the constraint type forall a b sep.
(Newtype a b, Sep sep, Pretty b) =>
Pretty (List sep b a)
External instance of the constraint type Newtype String Token'
External instance of the constraint type Sep NoCommaFSep
External instance of the constraint type Pretty Token'
External instance of the constraint type forall a b sep.
(Newtype a b, Sep sep, Parsec b) =>
Parsec (List sep b a)
External instance of the constraint type Newtype String Token'
External instance of the constraint type Sep NoCommaFSep
External instance of the constraint type Parsec Token'
Evidence bound by a type signature of the constraint type FieldGrammar g
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])
External instance of the constraint type forall a b. Functor (Pretext a b)
External instance of the constraint type HasBuildInfo BuildInfo
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
External instance of the constraint type forall a. Monoid [a]
External instance of the constraint type forall a b. Functor (Pretext a b)
lookupLens CompilerFlavor
flavor

lookupLens :: (Functor f, Monoid v) => CompilerFlavor -> LensLike' f (PerCompilerFlavor v) v
lookupLens :: 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
External instance of the constraint type Eq CompilerFlavor
== 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
Evidence bound by a type signature of the constraint type Functor f
<$> v -> f v
f v
ghc
    | CompilerFlavor
k CompilerFlavor -> CompilerFlavor -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type Eq CompilerFlavor
== 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
Evidence bound by a type signature of the constraint type Functor f
<$> v -> f v
f v
ghcjs
    | Bool
otherwise  = PerCompilerFlavor v
p PerCompilerFlavor v -> f v -> f (PerCompilerFlavor v)
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
Evidence bound by a type signature of the constraint type Functor f
<$ v -> f v
f v
forall a. Monoid a => a
Evidence bound by a type signature of the constraint type Monoid v
mempty

-------------------------------------------------------------------------------
-- Flag
-------------------------------------------------------------------------------

flagFieldGrammar
    :: (FieldGrammar g, Applicative (g Flag))
    =>  FlagName -> g Flag Flag
flagFieldGrammar :: FlagName -> g Flag Flag
flagFieldGrammar FlagName
name = FlagName -> String -> Bool -> Bool -> Flag
MkFlag FlagName
name
    (String -> Bool -> Bool -> Flag)
-> g Flag String -> g Flag (Bool -> Bool -> Flag)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type forall (f :: * -> *). Applicative f => Functor f
Evidence bound by a type signature of the constraint type Applicative (g Flag)
<$> FieldName -> ALens' Flag String -> g Flag String
forall (g :: * -> * -> *) s.
FieldGrammar g =>
FieldName -> ALens' s String -> g s String
Evidence bound by a type signature of the constraint type FieldGrammar g
freeTextFieldDef    FieldName
"description"          ALens' Flag String
Lens' Flag String
External instance of the constraint type forall a b. Functor (Pretext a b)
L.flagDescription
    g Flag (Bool -> Bool -> Flag)
-> g Flag Bool -> g Flag (Bool -> Flag)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Applicative (g Flag)
<*> FieldName -> ALens' Flag Bool -> Bool -> g Flag Bool
forall (g :: * -> * -> *) s.
FieldGrammar g =>
FieldName -> ALens' s Bool -> Bool -> g s Bool
Evidence bound by a type signature of the constraint type FieldGrammar g
booleanFieldDef     FieldName
"default"              ALens' Flag Bool
Lens' Flag Bool
External instance of the constraint type forall a b. Functor (Pretext a b)
L.flagDefault     Bool
True
    g Flag (Bool -> Flag) -> g Flag Bool -> g Flag Flag
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Applicative (g Flag)
<*> FieldName -> ALens' Flag Bool -> Bool -> g Flag Bool
forall (g :: * -> * -> *) s.
FieldGrammar g =>
FieldName -> ALens' s Bool -> Bool -> g s Bool
Evidence bound by a type signature of the constraint type FieldGrammar g
booleanFieldDef     FieldName
"manual"               ALens' Flag Bool
Lens' Flag Bool
External instance of the constraint type forall a b. Functor (Pretext a b)
L.flagManual      Bool
False
{-# SPECIALIZE flagFieldGrammar :: FlagName -> ParsecFieldGrammar' Flag #-}
{-# SPECIALIZE flagFieldGrammar :: FlagName -> PrettyFieldGrammar' Flag #-}

-------------------------------------------------------------------------------
-- SourceRepo
-------------------------------------------------------------------------------

sourceRepoFieldGrammar
    :: (FieldGrammar g, Applicative (g SourceRepo))
    => RepoKind -> g SourceRepo SourceRepo
sourceRepoFieldGrammar :: 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
External instance of the constraint type forall (f :: * -> *). Applicative f => Functor f
Evidence bound by a type signature of the constraint type Applicative (g SourceRepo)
<$> FieldName
-> ALens' SourceRepo (Maybe RepoType)
-> g SourceRepo (Maybe RepoType)
forall (g :: * -> * -> *) a s.
(FieldGrammar g, Parsec a, Pretty a) =>
FieldName -> ALens' s (Maybe a) -> g s (Maybe a)
External instance of the constraint type Pretty RepoType
External instance of the constraint type Parsec RepoType
Evidence bound by a type signature of the constraint type FieldGrammar g
optionalField    FieldName
"type"                ALens' SourceRepo (Maybe RepoType)
Lens' SourceRepo (Maybe RepoType)
External instance of the constraint type forall a b. Functor (Pretext a b)
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 (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Applicative (g SourceRepo)
<*> FieldName
-> ALens' SourceRepo (Maybe String) -> g SourceRepo (Maybe String)
forall (g :: * -> * -> *) s.
FieldGrammar g =>
FieldName -> ALens' s (Maybe String) -> g s (Maybe String)
Evidence bound by a type signature of the constraint type FieldGrammar g
freeTextField    FieldName
"location"            ALens' SourceRepo (Maybe String)
Lens' SourceRepo (Maybe String)
External instance of the constraint type forall a b. Functor (Pretext a b)
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 (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Applicative (g SourceRepo)
<*> FieldName
-> (String -> Token)
-> ALens' SourceRepo (Maybe String)
-> g SourceRepo (Maybe String)
forall (g :: * -> * -> *) b a s.
(FieldGrammar g, Parsec b, Pretty b, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s (Maybe a) -> g s (Maybe a)
External instance of the constraint type Newtype String Token
External instance of the constraint type Pretty Token
External instance of the constraint type Parsec Token
Evidence bound by a type signature of the constraint type FieldGrammar g
optionalFieldAla FieldName
"module"   String -> Token
Token      ALens' SourceRepo (Maybe String)
Lens' SourceRepo (Maybe String)
External instance of the constraint type forall a b. Functor (Pretext a b)
L.repoModule
    g SourceRepo
  (Maybe String -> Maybe String -> Maybe String -> SourceRepo)
-> g SourceRepo (Maybe String)
-> g SourceRepo (Maybe String -> Maybe String -> SourceRepo)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Applicative (g SourceRepo)
<*> FieldName
-> (String -> Token)
-> ALens' SourceRepo (Maybe String)
-> g SourceRepo (Maybe String)
forall (g :: * -> * -> *) b a s.
(FieldGrammar g, Parsec b, Pretty b, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s (Maybe a) -> g s (Maybe a)
External instance of the constraint type Newtype String Token
External instance of the constraint type Pretty Token
External instance of the constraint type Parsec Token
Evidence bound by a type signature of the constraint type FieldGrammar g
optionalFieldAla FieldName
"branch"   String -> Token
Token      ALens' SourceRepo (Maybe String)
Lens' SourceRepo (Maybe String)
External instance of the constraint type forall a b. Functor (Pretext a b)
L.repoBranch
    g SourceRepo (Maybe String -> Maybe String -> SourceRepo)
-> g SourceRepo (Maybe String)
-> g SourceRepo (Maybe String -> SourceRepo)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Applicative (g SourceRepo)
<*> FieldName
-> (String -> Token)
-> ALens' SourceRepo (Maybe String)
-> g SourceRepo (Maybe String)
forall (g :: * -> * -> *) b a s.
(FieldGrammar g, Parsec b, Pretty b, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s (Maybe a) -> g s (Maybe a)
External instance of the constraint type Newtype String Token
External instance of the constraint type Pretty Token
External instance of the constraint type Parsec Token
Evidence bound by a type signature of the constraint type FieldGrammar g
optionalFieldAla FieldName
"tag"      String -> Token
Token      ALens' SourceRepo (Maybe String)
Lens' SourceRepo (Maybe String)
External instance of the constraint type forall a b. Functor (Pretext a b)
L.repoTag
    g SourceRepo (Maybe String -> SourceRepo)
-> g SourceRepo (Maybe String) -> g SourceRepo SourceRepo
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Applicative (g SourceRepo)
<*> FieldName
-> (String -> FilePathNT)
-> ALens' SourceRepo (Maybe String)
-> g SourceRepo (Maybe String)
forall (g :: * -> * -> *) b a s.
(FieldGrammar g, Parsec b, Pretty b, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s (Maybe a) -> g s (Maybe a)
External instance of the constraint type Newtype String FilePathNT
External instance of the constraint type Pretty FilePathNT
External instance of the constraint type Parsec FilePathNT
Evidence bound by a type signature of the constraint type FieldGrammar g
optionalFieldAla FieldName
"subdir"   String -> FilePathNT
FilePathNT ALens' SourceRepo (Maybe String)
Lens' SourceRepo (Maybe String)
External instance of the constraint type forall a b. Functor (Pretext a b)
L.repoSubdir
{-# SPECIALIZE sourceRepoFieldGrammar :: RepoKind -> ParsecFieldGrammar' SourceRepo #-}
{-# SPECIALIZE sourceRepoFieldGrammar :: RepoKind ->PrettyFieldGrammar' SourceRepo #-}

-------------------------------------------------------------------------------
-- SetupBuildInfo
-------------------------------------------------------------------------------

setupBInfoFieldGrammar
    :: (FieldGrammar g, Functor (g SetupBuildInfo))
    => Bool -> g SetupBuildInfo SetupBuildInfo
setupBInfoFieldGrammar :: 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
Evidence bound by a type signature of the constraint type Functor (g SetupBuildInfo)
<$> FieldName
-> ([Dependency]
    -> List CommaVCat (Identity Dependency) Dependency)
-> ALens' SetupBuildInfo [Dependency]
-> g SetupBuildInfo [Dependency]
forall (g :: * -> * -> *) b a s.
(FieldGrammar g, Parsec b, Pretty b, Monoid a, Newtype a b) =>
FieldName -> (a -> b) -> ALens' s a -> g s a
External instance of the constraint type forall a sep wrapper. Newtype [a] (List sep wrapper a)
External instance of the constraint type forall a. Monoid [a]
External instance of the constraint type forall a b sep.
(Newtype a b, Sep sep, Pretty b) =>
Pretty (List sep b a)
External instance of the constraint type forall a. Newtype a (Identity a)
External instance of the constraint type Sep CommaVCat
External instance of the constraint type forall a. Pretty a => Pretty (Identity a)
External instance of the constraint type Pretty Dependency
External instance of the constraint type forall a b sep.
(Newtype a b, Sep sep, Parsec b) =>
Parsec (List sep b a)
External instance of the constraint type forall a. Newtype a (Identity a)
External instance of the constraint type Sep CommaVCat
External instance of the constraint type forall a. Parsec a => Parsec (Identity a)
External instance of the constraint type Parsec Dependency
Evidence bound by a type signature of the constraint type FieldGrammar g
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]
External instance of the constraint type forall a b. Functor (Pretext a b)
L.setupDepends
{-# SPECIALIZE setupBInfoFieldGrammar :: Bool -> ParsecFieldGrammar' SetupBuildInfo #-}
{-# SPECIALIZE setupBInfoFieldGrammar :: Bool ->PrettyFieldGrammar' SetupBuildInfo #-}