Cabal-2.2.0.1: A framework for packaging Haskell software

Safe HaskellNone
LanguageHaskell2010

Distribution.Types.BuildInfo.Lens

Synopsis

Documentation

data BuildInfo Source #

Instances
Eq BuildInfo Source # 
Instance details

Defined in Distribution.Types.BuildInfo

Data BuildInfo Source # 
Instance details

Defined in Distribution.Types.BuildInfo

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BuildInfo -> c BuildInfo Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c BuildInfo Source #

toConstr :: BuildInfo -> Constr Source #

dataTypeOf :: BuildInfo -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c BuildInfo) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BuildInfo) Source #

gmapT :: (forall b. Data b => b -> b) -> BuildInfo -> BuildInfo Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BuildInfo -> r Source #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BuildInfo -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> BuildInfo -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> BuildInfo -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> BuildInfo -> m BuildInfo Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BuildInfo -> m BuildInfo Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BuildInfo -> m BuildInfo Source #

Read BuildInfo Source # 
Instance details

Defined in Distribution.Types.BuildInfo

Show BuildInfo Source # 
Instance details

Defined in Distribution.Types.BuildInfo

Generic BuildInfo Source # 
Instance details

Defined in Distribution.Types.BuildInfo

Associated Types

type Rep BuildInfo :: * -> * Source #

Semigroup BuildInfo Source # 
Instance details

Defined in Distribution.Types.BuildInfo

Monoid BuildInfo Source # 
Instance details

Defined in Distribution.Types.BuildInfo

NFData BuildInfo Source # 
Instance details

Defined in Distribution.Types.BuildInfo

Methods

rnf :: BuildInfo -> () Source #

Binary BuildInfo Source # 
Instance details

Defined in Distribution.Types.BuildInfo

HasBuildInfo BuildInfo Source # 
Instance details

Defined in Distribution.Types.BuildInfo.Lens

Methods

buildInfo :: Lens' BuildInfo BuildInfo Source #

buildable :: Lens' BuildInfo Bool Source #

buildTools :: Lens' BuildInfo [LegacyExeDependency] Source #

buildToolDepends :: Lens' BuildInfo [ExeDependency] Source #

cppOptions :: Lens' BuildInfo [String] Source #

asmOptions :: Lens' BuildInfo [String] Source #

cmmOptions :: Lens' BuildInfo [String] Source #

ccOptions :: Lens' BuildInfo [String] Source #

cxxOptions :: Lens' BuildInfo [String] Source #

ldOptions :: Lens' BuildInfo [String] Source #

pkgconfigDepends :: Lens' BuildInfo [PkgconfigDependency] Source #

frameworks :: Lens' BuildInfo [String] Source #

extraFrameworkDirs :: Lens' BuildInfo [String] Source #

asmSources :: Lens' BuildInfo [FilePath] Source #

cmmSources :: Lens' BuildInfo [FilePath] Source #

cSources :: Lens' BuildInfo [FilePath] Source #

cxxSources :: Lens' BuildInfo [FilePath] Source #

jsSources :: Lens' BuildInfo [FilePath] Source #

hsSourceDirs :: Lens' BuildInfo [FilePath] Source #

otherModules :: Lens' BuildInfo [ModuleName] Source #

virtualModules :: Lens' BuildInfo [ModuleName] Source #

autogenModules :: Lens' BuildInfo [ModuleName] Source #

defaultLanguage :: Lens' BuildInfo (Maybe Language) Source #

otherLanguages :: Lens' BuildInfo [Language] Source #

defaultExtensions :: Lens' BuildInfo [Extension] Source #

otherExtensions :: Lens' BuildInfo [Extension] Source #

oldExtensions :: Lens' BuildInfo [Extension] Source #

extraLibs :: Lens' BuildInfo [String] Source #

extraGHCiLibs :: Lens' BuildInfo [String] Source #

extraBundledLibs :: Lens' BuildInfo [String] Source #

extraLibFlavours :: Lens' BuildInfo [String] Source #

extraLibDirs :: Lens' BuildInfo [String] Source #

includeDirs :: Lens' BuildInfo [FilePath] Source #

includes :: Lens' BuildInfo [FilePath] Source #

installIncludes :: Lens' BuildInfo [FilePath] Source #

options :: Lens' BuildInfo [(CompilerFlavor, [String])] Source #

profOptions :: Lens' BuildInfo [(CompilerFlavor, [String])] Source #

sharedOptions :: Lens' BuildInfo [(CompilerFlavor, [String])] Source #

staticOptions :: Lens' BuildInfo [(CompilerFlavor, [String])] Source #

customFieldsBI :: Lens' BuildInfo [(String, String)] Source #

targetBuildDepends :: Lens' BuildInfo [Dependency] Source #

mixins :: Lens' BuildInfo [Mixin] Source #

type Rep BuildInfo Source # 
Instance details

Defined in Distribution.Types.BuildInfo

type Rep BuildInfo = D1 (MetaData "BuildInfo" "Distribution.Types.BuildInfo" "Cabal-2.2.0.1" False) (C1 (MetaCons "BuildInfo" PrefixI True) (((((S1 (MetaSel (Just "buildable") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool) :*: S1 (MetaSel (Just "buildTools") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [LegacyExeDependency])) :*: (S1 (MetaSel (Just "buildToolDepends") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [ExeDependency]) :*: (S1 (MetaSel (Just "cppOptions") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [String]) :*: S1 (MetaSel (Just "asmOptions") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [String])))) :*: ((S1 (MetaSel (Just "cmmOptions") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [String]) :*: S1 (MetaSel (Just "ccOptions") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [String])) :*: (S1 (MetaSel (Just "cxxOptions") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [String]) :*: (S1 (MetaSel (Just "ldOptions") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [String]) :*: S1 (MetaSel (Just "pkgconfigDepends") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [PkgconfigDependency]))))) :*: (((S1 (MetaSel (Just "frameworks") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [String]) :*: S1 (MetaSel (Just "extraFrameworkDirs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [String])) :*: (S1 (MetaSel (Just "asmSources") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [FilePath]) :*: (S1 (MetaSel (Just "cmmSources") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [FilePath]) :*: S1 (MetaSel (Just "cSources") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [FilePath])))) :*: ((S1 (MetaSel (Just "cxxSources") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [FilePath]) :*: S1 (MetaSel (Just "jsSources") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [FilePath])) :*: (S1 (MetaSel (Just "hsSourceDirs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [FilePath]) :*: (S1 (MetaSel (Just "otherModules") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [ModuleName]) :*: S1 (MetaSel (Just "virtualModules") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [ModuleName])))))) :*: ((((S1 (MetaSel (Just "autogenModules") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [ModuleName]) :*: S1 (MetaSel (Just "defaultLanguage") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Language))) :*: (S1 (MetaSel (Just "otherLanguages") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Language]) :*: (S1 (MetaSel (Just "defaultExtensions") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Extension]) :*: S1 (MetaSel (Just "otherExtensions") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Extension])))) :*: ((S1 (MetaSel (Just "oldExtensions") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Extension]) :*: S1 (MetaSel (Just "extraLibs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [String])) :*: (S1 (MetaSel (Just "extraGHCiLibs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [String]) :*: (S1 (MetaSel (Just "extraBundledLibs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [String]) :*: S1 (MetaSel (Just "extraLibFlavours") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [String]))))) :*: (((S1 (MetaSel (Just "extraLibDirs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [String]) :*: S1 (MetaSel (Just "includeDirs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [FilePath])) :*: (S1 (MetaSel (Just "includes") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [FilePath]) :*: (S1 (MetaSel (Just "installIncludes") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [FilePath]) :*: S1 (MetaSel (Just "options") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [(CompilerFlavor, [String])])))) :*: ((S1 (MetaSel (Just "profOptions") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [(CompilerFlavor, [String])]) :*: (S1 (MetaSel (Just "sharedOptions") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [(CompilerFlavor, [String])]) :*: S1 (MetaSel (Just "staticOptions") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [(CompilerFlavor, [String])]))) :*: (S1 (MetaSel (Just "customFieldsBI") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [(String, String)]) :*: (S1 (MetaSel (Just "targetBuildDepends") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Dependency]) :*: S1 (MetaSel (Just "mixins") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 [Mixin]))))))))

class HasBuildInfo a where Source #

Classy lenses for BuildInfo.

Minimal complete definition

buildInfo

Methods

buildInfo :: Lens' a BuildInfo Source #

buildable :: Lens' a Bool Source #

buildTools :: Lens' a [LegacyExeDependency] Source #

buildToolDepends :: Lens' a [ExeDependency] Source #

cppOptions :: Lens' a [String] Source #

asmOptions :: Lens' a [String] Source #

cmmOptions :: Lens' a [String] Source #

ccOptions :: Lens' a [String] Source #

cxxOptions :: Lens' a [String] Source #

ldOptions :: Lens' a [String] Source #

pkgconfigDepends :: Lens' a [PkgconfigDependency] Source #

frameworks :: Lens' a [String] Source #

extraFrameworkDirs :: Lens' a [String] Source #

asmSources :: Lens' a [FilePath] Source #

cmmSources :: Lens' a [FilePath] Source #

cSources :: Lens' a [FilePath] Source #

cxxSources :: Lens' a [FilePath] Source #

jsSources :: Lens' a [FilePath] Source #

hsSourceDirs :: Lens' a [FilePath] Source #

otherModules :: Lens' a [ModuleName] Source #

virtualModules :: Lens' a [ModuleName] Source #

autogenModules :: Lens' a [ModuleName] Source #

defaultLanguage :: Lens' a (Maybe Language) Source #

otherLanguages :: Lens' a [Language] Source #

defaultExtensions :: Lens' a [Extension] Source #

otherExtensions :: Lens' a [Extension] Source #

oldExtensions :: Lens' a [Extension] Source #

extraLibs :: Lens' a [String] Source #

extraGHCiLibs :: Lens' a [String] Source #

extraBundledLibs :: Lens' a [String] Source #

extraLibFlavours :: Lens' a [String] Source #

extraLibDirs :: Lens' a [String] Source #

includeDirs :: Lens' a [FilePath] Source #

includes :: Lens' a [FilePath] Source #

installIncludes :: Lens' a [FilePath] Source #

options :: Lens' a [(CompilerFlavor, [String])] Source #

profOptions :: Lens' a [(CompilerFlavor, [String])] Source #

sharedOptions :: Lens' a [(CompilerFlavor, [String])] Source #

staticOptions :: Lens' a [(CompilerFlavor, [String])] Source #

customFieldsBI :: Lens' a [(String, String)] Source #

targetBuildDepends :: Lens' a [Dependency] Source #

mixins :: Lens' a [Mixin] Source #

Instances
HasBuildInfo BuildInfo Source # 
Instance details

Defined in Distribution.Types.BuildInfo.Lens

Methods

buildInfo :: Lens' BuildInfo BuildInfo Source #

buildable :: Lens' BuildInfo Bool Source #

buildTools :: Lens' BuildInfo [LegacyExeDependency] Source #

buildToolDepends :: Lens' BuildInfo [ExeDependency] Source #

cppOptions :: Lens' BuildInfo [String] Source #

asmOptions :: Lens' BuildInfo [String] Source #

cmmOptions :: Lens' BuildInfo [String] Source #

ccOptions :: Lens' BuildInfo [String] Source #

cxxOptions :: Lens' BuildInfo [String] Source #

ldOptions :: Lens' BuildInfo [String] Source #

pkgconfigDepends :: Lens' BuildInfo [PkgconfigDependency] Source #

frameworks :: Lens' BuildInfo [String] Source #

extraFrameworkDirs :: Lens' BuildInfo [String] Source #

asmSources :: Lens' BuildInfo [FilePath] Source #

cmmSources :: Lens' BuildInfo [FilePath] Source #

cSources :: Lens' BuildInfo [FilePath] Source #

cxxSources :: Lens' BuildInfo [FilePath] Source #

jsSources :: Lens' BuildInfo [FilePath] Source #

hsSourceDirs :: Lens' BuildInfo [FilePath] Source #

otherModules :: Lens' BuildInfo [ModuleName] Source #

virtualModules :: Lens' BuildInfo [ModuleName] Source #

autogenModules :: Lens' BuildInfo [ModuleName] Source #

defaultLanguage :: Lens' BuildInfo (Maybe Language) Source #

otherLanguages :: Lens' BuildInfo [Language] Source #

defaultExtensions :: Lens' BuildInfo [Extension] Source #

otherExtensions :: Lens' BuildInfo [Extension] Source #

oldExtensions :: Lens' BuildInfo [Extension] Source #

extraLibs :: Lens' BuildInfo [String] Source #

extraGHCiLibs :: Lens' BuildInfo [String] Source #

extraBundledLibs :: Lens' BuildInfo [String] Source #

extraLibFlavours :: Lens' BuildInfo [String] Source #

extraLibDirs :: Lens' BuildInfo [String] Source #

includeDirs :: Lens' BuildInfo [FilePath] Source #

includes :: Lens' BuildInfo [FilePath] Source #

installIncludes :: Lens' BuildInfo [FilePath] Source #

options :: Lens' BuildInfo [(CompilerFlavor, [String])] Source #

profOptions :: Lens' BuildInfo [(CompilerFlavor, [String])] Source #

sharedOptions :: Lens' BuildInfo [(CompilerFlavor, [String])] Source #

staticOptions :: Lens' BuildInfo [(CompilerFlavor, [String])] Source #

customFieldsBI :: Lens' BuildInfo [(String, String)] Source #

targetBuildDepends :: Lens' BuildInfo [Dependency] Source #

mixins :: Lens' BuildInfo [Mixin] Source #

HasBuildInfo TestSuite Source # 
Instance details

Defined in Distribution.Types.TestSuite

Methods

buildInfo :: Lens' TestSuite BuildInfo Source #

buildable :: Lens' TestSuite Bool Source #

buildTools :: Lens' TestSuite [LegacyExeDependency] Source #

buildToolDepends :: Lens' TestSuite [ExeDependency] Source #

cppOptions :: Lens' TestSuite [String] Source #

asmOptions :: Lens' TestSuite [String] Source #

cmmOptions :: Lens' TestSuite [String] Source #

ccOptions :: Lens' TestSuite [String] Source #

cxxOptions :: Lens' TestSuite [String] Source #

ldOptions :: Lens' TestSuite [String] Source #

pkgconfigDepends :: Lens' TestSuite [PkgconfigDependency] Source #

frameworks :: Lens' TestSuite [String] Source #

extraFrameworkDirs :: Lens' TestSuite [String] Source #

asmSources :: Lens' TestSuite [FilePath] Source #

cmmSources :: Lens' TestSuite [FilePath] Source #

cSources :: Lens' TestSuite [FilePath] Source #

cxxSources :: Lens' TestSuite [FilePath] Source #

jsSources :: Lens' TestSuite [FilePath] Source #

hsSourceDirs :: Lens' TestSuite [FilePath] Source #

otherModules :: Lens' TestSuite [ModuleName] Source #

virtualModules :: Lens' TestSuite [ModuleName] Source #

autogenModules :: Lens' TestSuite [ModuleName] Source #

defaultLanguage :: Lens' TestSuite (Maybe Language) Source #

otherLanguages :: Lens' TestSuite [Language] Source #

defaultExtensions :: Lens' TestSuite [Extension] Source #

otherExtensions :: Lens' TestSuite [Extension] Source #

oldExtensions :: Lens' TestSuite [Extension] Source #

extraLibs :: Lens' TestSuite [String] Source #

extraGHCiLibs :: Lens' TestSuite [String] Source #

extraBundledLibs :: Lens' TestSuite [String] Source #

extraLibFlavours :: Lens' TestSuite [String] Source #

extraLibDirs :: Lens' TestSuite [String] Source #

includeDirs :: Lens' TestSuite [FilePath] Source #

includes :: Lens' TestSuite [FilePath] Source #

installIncludes :: Lens' TestSuite [FilePath] Source #

options :: Lens' TestSuite [(CompilerFlavor, [String])] Source #

profOptions :: Lens' TestSuite [(CompilerFlavor, [String])] Source #

sharedOptions :: Lens' TestSuite [(CompilerFlavor, [String])] Source #

staticOptions :: Lens' TestSuite [(CompilerFlavor, [String])] Source #

customFieldsBI :: Lens' TestSuite [(String, String)] Source #

targetBuildDepends :: Lens' TestSuite [Dependency] Source #

mixins :: Lens' TestSuite [Mixin] Source #

HasBuildInfo Library Source # 
Instance details

Defined in Distribution.Types.Library

Methods

buildInfo :: Lens' Library BuildInfo Source #

buildable :: Lens' Library Bool Source #

buildTools :: Lens' Library [LegacyExeDependency] Source #

buildToolDepends :: Lens' Library [ExeDependency] Source #

cppOptions :: Lens' Library [String] Source #

asmOptions :: Lens' Library [String] Source #

cmmOptions :: Lens' Library [String] Source #

ccOptions :: Lens' Library [String] Source #

cxxOptions :: Lens' Library [String] Source #

ldOptions :: Lens' Library [String] Source #

pkgconfigDepends :: Lens' Library [PkgconfigDependency] Source #

frameworks :: Lens' Library [String] Source #

extraFrameworkDirs :: Lens' Library [String] Source #

asmSources :: Lens' Library [FilePath] Source #

cmmSources :: Lens' Library [FilePath] Source #

cSources :: Lens' Library [FilePath] Source #

cxxSources :: Lens' Library [FilePath] Source #

jsSources :: Lens' Library [FilePath] Source #

hsSourceDirs :: Lens' Library [FilePath] Source #

otherModules :: Lens' Library [ModuleName] Source #

virtualModules :: Lens' Library [ModuleName] Source #

autogenModules :: Lens' Library [ModuleName] Source #

defaultLanguage :: Lens' Library (Maybe Language) Source #

otherLanguages :: Lens' Library [Language] Source #

defaultExtensions :: Lens' Library [Extension] Source #

otherExtensions :: Lens' Library [Extension] Source #

oldExtensions :: Lens' Library [Extension] Source #

extraLibs :: Lens' Library [String] Source #

extraGHCiLibs :: Lens' Library [String] Source #

extraBundledLibs :: Lens' Library [String] Source #

extraLibFlavours :: Lens' Library [String] Source #

extraLibDirs :: Lens' Library [String] Source #

includeDirs :: Lens' Library [FilePath] Source #

includes :: Lens' Library [FilePath] Source #

installIncludes :: Lens' Library [FilePath] Source #

options :: Lens' Library [(CompilerFlavor, [String])] Source #

profOptions :: Lens' Library [(CompilerFlavor, [String])] Source #

sharedOptions :: Lens' Library [(CompilerFlavor, [String])] Source #

staticOptions :: Lens' Library [(CompilerFlavor, [String])] Source #

customFieldsBI :: Lens' Library [(String, String)] Source #

targetBuildDepends :: Lens' Library [Dependency] Source #

mixins :: Lens' Library [Mixin] Source #

HasBuildInfo ForeignLib Source # 
Instance details

Defined in Distribution.Types.ForeignLib

Methods

buildInfo :: Lens' ForeignLib BuildInfo Source #

buildable :: Lens' ForeignLib Bool Source #

buildTools :: Lens' ForeignLib [LegacyExeDependency] Source #

buildToolDepends :: Lens' ForeignLib [ExeDependency] Source #

cppOptions :: Lens' ForeignLib [String] Source #

asmOptions :: Lens' ForeignLib [String] Source #

cmmOptions :: Lens' ForeignLib [String] Source #

ccOptions :: Lens' ForeignLib [String] Source #

cxxOptions :: Lens' ForeignLib [String] Source #

ldOptions :: Lens' ForeignLib [String] Source #

pkgconfigDepends :: Lens' ForeignLib [PkgconfigDependency] Source #

frameworks :: Lens' ForeignLib [String] Source #

extraFrameworkDirs :: Lens' ForeignLib [String] Source #

asmSources :: Lens' ForeignLib [FilePath] Source #

cmmSources :: Lens' ForeignLib [FilePath] Source #

cSources :: Lens' ForeignLib [FilePath] Source #

cxxSources :: Lens' ForeignLib [FilePath] Source #

jsSources :: Lens' ForeignLib [FilePath] Source #

hsSourceDirs :: Lens' ForeignLib [FilePath] Source #

otherModules :: Lens' ForeignLib [ModuleName] Source #

virtualModules :: Lens' ForeignLib [ModuleName] Source #

autogenModules :: Lens' ForeignLib [ModuleName] Source #

defaultLanguage :: Lens' ForeignLib (Maybe Language) Source #

otherLanguages :: Lens' ForeignLib [Language] Source #

defaultExtensions :: Lens' ForeignLib [Extension] Source #

otherExtensions :: Lens' ForeignLib [Extension] Source #

oldExtensions :: Lens' ForeignLib [Extension] Source #

extraLibs :: Lens' ForeignLib [String] Source #

extraGHCiLibs :: Lens' ForeignLib [String] Source #

extraBundledLibs :: Lens' ForeignLib [String] Source #

extraLibFlavours :: Lens' ForeignLib [String] Source #

extraLibDirs :: Lens' ForeignLib [String] Source #

includeDirs :: Lens' ForeignLib [FilePath] Source #

includes :: Lens' ForeignLib [FilePath] Source #

installIncludes :: Lens' ForeignLib [FilePath] Source #

options :: Lens' ForeignLib [(CompilerFlavor, [String])] Source #

profOptions :: Lens' ForeignLib [(CompilerFlavor, [String])] Source #

sharedOptions :: Lens' ForeignLib [(CompilerFlavor, [String])] Source #

staticOptions :: Lens' ForeignLib [(CompilerFlavor, [String])] Source #

customFieldsBI :: Lens' ForeignLib [(String, String)] Source #

targetBuildDepends :: Lens' ForeignLib [Dependency] Source #

mixins :: Lens' ForeignLib [Mixin] Source #

HasBuildInfo Executable Source # 
Instance details

Defined in Distribution.Types.Executable

Methods

buildInfo :: Lens' Executable BuildInfo Source #

buildable :: Lens' Executable Bool Source #

buildTools :: Lens' Executable [LegacyExeDependency] Source #

buildToolDepends :: Lens' Executable [ExeDependency] Source #

cppOptions :: Lens' Executable [String] Source #

asmOptions :: Lens' Executable [String] Source #

cmmOptions :: Lens' Executable [String] Source #

ccOptions :: Lens' Executable [String] Source #

cxxOptions :: Lens' Executable [String] Source #

ldOptions :: Lens' Executable [String] Source #

pkgconfigDepends :: Lens' Executable [PkgconfigDependency] Source #

frameworks :: Lens' Executable [String] Source #

extraFrameworkDirs :: Lens' Executable [String] Source #

asmSources :: Lens' Executable [FilePath] Source #

cmmSources :: Lens' Executable [FilePath] Source #

cSources :: Lens' Executable [FilePath] Source #

cxxSources :: Lens' Executable [FilePath] Source #

jsSources :: Lens' Executable [FilePath] Source #

hsSourceDirs :: Lens' Executable [FilePath] Source #

otherModules :: Lens' Executable [ModuleName] Source #

virtualModules :: Lens' Executable [ModuleName] Source #

autogenModules :: Lens' Executable [ModuleName] Source #

defaultLanguage :: Lens' Executable (Maybe Language) Source #

otherLanguages :: Lens' Executable [Language] Source #

defaultExtensions :: Lens' Executable [Extension] Source #

otherExtensions :: Lens' Executable [Extension] Source #

oldExtensions :: Lens' Executable [Extension] Source #

extraLibs :: Lens' Executable [String] Source #

extraGHCiLibs :: Lens' Executable [String] Source #

extraBundledLibs :: Lens' Executable [String] Source #

extraLibFlavours :: Lens' Executable [String] Source #

extraLibDirs :: Lens' Executable [String] Source #

includeDirs :: Lens' Executable [FilePath] Source #

includes :: Lens' Executable [FilePath] Source #

installIncludes :: Lens' Executable [FilePath] Source #

options :: Lens' Executable [(CompilerFlavor, [String])] Source #

profOptions :: Lens' Executable [(CompilerFlavor, [String])] Source #

sharedOptions :: Lens' Executable [(CompilerFlavor, [String])] Source #

staticOptions :: Lens' Executable [(CompilerFlavor, [String])] Source #

customFieldsBI :: Lens' Executable [(String, String)] Source #

targetBuildDepends :: Lens' Executable [Dependency] Source #

mixins :: Lens' Executable [Mixin] Source #

HasBuildInfo Benchmark Source # 
Instance details

Defined in Distribution.Types.Benchmark

Methods

buildInfo :: Lens' Benchmark BuildInfo Source #

buildable :: Lens' Benchmark Bool Source #

buildTools :: Lens' Benchmark [LegacyExeDependency] Source #

buildToolDepends :: Lens' Benchmark [ExeDependency] Source #

cppOptions :: Lens' Benchmark [String] Source #

asmOptions :: Lens' Benchmark [String] Source #

cmmOptions :: Lens' Benchmark [String] Source #

ccOptions :: Lens' Benchmark [String] Source #

cxxOptions :: Lens' Benchmark [String] Source #

ldOptions :: Lens' Benchmark [String] Source #

pkgconfigDepends :: Lens' Benchmark [PkgconfigDependency] Source #

frameworks :: Lens' Benchmark [String] Source #

extraFrameworkDirs :: Lens' Benchmark [String] Source #

asmSources :: Lens' Benchmark [FilePath] Source #

cmmSources :: Lens' Benchmark [FilePath] Source #

cSources :: Lens' Benchmark [FilePath] Source #

cxxSources :: Lens' Benchmark [FilePath] Source #

jsSources :: Lens' Benchmark [FilePath] Source #

hsSourceDirs :: Lens' Benchmark [FilePath] Source #

otherModules :: Lens' Benchmark [ModuleName] Source #

virtualModules :: Lens' Benchmark [ModuleName] Source #

autogenModules :: Lens' Benchmark [ModuleName] Source #

defaultLanguage :: Lens' Benchmark (Maybe Language) Source #

otherLanguages :: Lens' Benchmark [Language] Source #

defaultExtensions :: Lens' Benchmark [Extension] Source #

otherExtensions :: Lens' Benchmark [Extension] Source #

oldExtensions :: Lens' Benchmark [Extension] Source #

extraLibs :: Lens' Benchmark [String] Source #

extraGHCiLibs :: Lens' Benchmark [String] Source #

extraBundledLibs :: Lens' Benchmark [String] Source #

extraLibFlavours :: Lens' Benchmark [String] Source #

extraLibDirs :: Lens' Benchmark [String] Source #

includeDirs :: Lens' Benchmark [FilePath] Source #

includes :: Lens' Benchmark [FilePath] Source #

installIncludes :: Lens' Benchmark [FilePath] Source #

options :: Lens' Benchmark [(CompilerFlavor, [String])] Source #

profOptions :: Lens' Benchmark [(CompilerFlavor, [String])] Source #

sharedOptions :: Lens' Benchmark [(CompilerFlavor, [String])] Source #

staticOptions :: Lens' Benchmark [(CompilerFlavor, [String])] Source #

customFieldsBI :: Lens' Benchmark [(String, String)] Source #

targetBuildDepends :: Lens' Benchmark [Dependency] Source #

mixins :: Lens' Benchmark [Mixin] Source #

HasBuildInfo Component Source # 
Instance details

Defined in Distribution.Types.Component

Methods

buildInfo :: Lens' Component BuildInfo Source #

buildable :: Lens' Component Bool Source #

buildTools :: Lens' Component [LegacyExeDependency] Source #

buildToolDepends :: Lens' Component [ExeDependency] Source #

cppOptions :: Lens' Component [String] Source #

asmOptions :: Lens' Component [String] Source #

cmmOptions :: Lens' Component [String] Source #

ccOptions :: Lens' Component [String] Source #

cxxOptions :: Lens' Component [String] Source #

ldOptions :: Lens' Component [String] Source #

pkgconfigDepends :: Lens' Component [PkgconfigDependency] Source #

frameworks :: Lens' Component [String] Source #

extraFrameworkDirs :: Lens' Component [String] Source #

asmSources :: Lens' Component [FilePath] Source #

cmmSources :: Lens' Component [FilePath] Source #

cSources :: Lens' Component [FilePath] Source #

cxxSources :: Lens' Component [FilePath] Source #

jsSources :: Lens' Component [FilePath] Source #

hsSourceDirs :: Lens' Component [FilePath] Source #

otherModules :: Lens' Component [ModuleName] Source #

virtualModules :: Lens' Component [ModuleName] Source #

autogenModules :: Lens' Component [ModuleName] Source #

defaultLanguage :: Lens' Component (Maybe Language) Source #

otherLanguages :: Lens' Component [Language] Source #

defaultExtensions :: Lens' Component [Extension] Source #

otherExtensions :: Lens' Component [Extension] Source #

oldExtensions :: Lens' Component [Extension] Source #

extraLibs :: Lens' Component [String] Source #

extraGHCiLibs :: Lens' Component [String] Source #

extraBundledLibs :: Lens' Component [String] Source #

extraLibFlavours :: Lens' Component [String] Source #

extraLibDirs :: Lens' Component [String] Source #

includeDirs :: Lens' Component [FilePath] Source #

includes :: Lens' Component [FilePath] Source #

installIncludes :: Lens' Component [FilePath] Source #

options :: Lens' Component [(CompilerFlavor, [String])] Source #

profOptions :: Lens' Component [(CompilerFlavor, [String])] Source #

sharedOptions :: Lens' Component [(CompilerFlavor, [String])] Source #

staticOptions :: Lens' Component [(CompilerFlavor, [String])] Source #

customFieldsBI :: Lens' Component [(String, String)] Source #

targetBuildDepends :: Lens' Component [Dependency] Source #

mixins :: Lens' Component [Mixin] Source #

HasBuildInfo BenchmarkStanza Source # 
Instance details

Defined in Distribution.PackageDescription.FieldGrammar

Methods

buildInfo :: Lens' BenchmarkStanza BuildInfo Source #

buildable :: Lens' BenchmarkStanza Bool Source #

buildTools :: Lens' BenchmarkStanza [LegacyExeDependency] Source #

buildToolDepends :: Lens' BenchmarkStanza [ExeDependency] Source #

cppOptions :: Lens' BenchmarkStanza [String] Source #

asmOptions :: Lens' BenchmarkStanza [String] Source #

cmmOptions :: Lens' BenchmarkStanza [String] Source #

ccOptions :: Lens' BenchmarkStanza [String] Source #

cxxOptions :: Lens' BenchmarkStanza [String] Source #

ldOptions :: Lens' BenchmarkStanza [String] Source #

pkgconfigDepends :: Lens' BenchmarkStanza [PkgconfigDependency] Source #

frameworks :: Lens' BenchmarkStanza [String] Source #

extraFrameworkDirs :: Lens' BenchmarkStanza [String] Source #

asmSources :: Lens' BenchmarkStanza [FilePath] Source #

cmmSources :: Lens' BenchmarkStanza [FilePath] Source #

cSources :: Lens' BenchmarkStanza [FilePath] Source #

cxxSources :: Lens' BenchmarkStanza [FilePath] Source #

jsSources :: Lens' BenchmarkStanza [FilePath] Source #

hsSourceDirs :: Lens' BenchmarkStanza [FilePath] Source #

otherModules :: Lens' BenchmarkStanza [ModuleName] Source #

virtualModules :: Lens' BenchmarkStanza [ModuleName] Source #

autogenModules :: Lens' BenchmarkStanza [ModuleName] Source #

defaultLanguage :: Lens' BenchmarkStanza (Maybe Language) Source #

otherLanguages :: Lens' BenchmarkStanza [Language] Source #

defaultExtensions :: Lens' BenchmarkStanza [Extension] Source #

otherExtensions :: Lens' BenchmarkStanza [Extension] Source #

oldExtensions :: Lens' BenchmarkStanza [Extension] Source #

extraLibs :: Lens' BenchmarkStanza [String] Source #

extraGHCiLibs :: Lens' BenchmarkStanza [String] Source #

extraBundledLibs :: Lens' BenchmarkStanza [String] Source #

extraLibFlavours :: Lens' BenchmarkStanza [String] Source #

extraLibDirs :: Lens' BenchmarkStanza [String] Source #

includeDirs :: Lens' BenchmarkStanza [FilePath] Source #

includes :: Lens' BenchmarkStanza [FilePath] Source #

installIncludes :: Lens' BenchmarkStanza [FilePath] Source #

options :: Lens' BenchmarkStanza [(CompilerFlavor, [String])] Source #

profOptions :: Lens' BenchmarkStanza [(CompilerFlavor, [String])] Source #

sharedOptions :: Lens' BenchmarkStanza [(CompilerFlavor, [String])] Source #

staticOptions :: Lens' BenchmarkStanza [(CompilerFlavor, [String])] Source #

customFieldsBI :: Lens' BenchmarkStanza [(String, String)] Source #

targetBuildDepends :: Lens' BenchmarkStanza [Dependency] Source #

mixins :: Lens' BenchmarkStanza [Mixin] Source #

HasBuildInfo TestSuiteStanza Source # 
Instance details

Defined in Distribution.PackageDescription.FieldGrammar

Methods

buildInfo :: Lens' TestSuiteStanza BuildInfo Source #

buildable :: Lens' TestSuiteStanza Bool Source #

buildTools :: Lens' TestSuiteStanza [LegacyExeDependency] Source #

buildToolDepends :: Lens' TestSuiteStanza [ExeDependency] Source #

cppOptions :: Lens' TestSuiteStanza [String] Source #

asmOptions :: Lens' TestSuiteStanza [String] Source #

cmmOptions :: Lens' TestSuiteStanza [String] Source #

ccOptions :: Lens' TestSuiteStanza [String] Source #

cxxOptions :: Lens' TestSuiteStanza [String] Source #

ldOptions :: Lens' TestSuiteStanza [String] Source #

pkgconfigDepends :: Lens' TestSuiteStanza [PkgconfigDependency] Source #

frameworks :: Lens' TestSuiteStanza [String] Source #

extraFrameworkDirs :: Lens' TestSuiteStanza [String] Source #

asmSources :: Lens' TestSuiteStanza [FilePath] Source #

cmmSources :: Lens' TestSuiteStanza [FilePath] Source #

cSources :: Lens' TestSuiteStanza [FilePath] Source #

cxxSources :: Lens' TestSuiteStanza [FilePath] Source #

jsSources :: Lens' TestSuiteStanza [FilePath] Source #

hsSourceDirs :: Lens' TestSuiteStanza [FilePath] Source #

otherModules :: Lens' TestSuiteStanza [ModuleName] Source #

virtualModules :: Lens' TestSuiteStanza [ModuleName] Source #

autogenModules :: Lens' TestSuiteStanza [ModuleName] Source #

defaultLanguage :: Lens' TestSuiteStanza (Maybe Language) Source #

otherLanguages :: Lens' TestSuiteStanza [Language] Source #

defaultExtensions :: Lens' TestSuiteStanza [Extension] Source #

otherExtensions :: Lens' TestSuiteStanza [Extension] Source #

oldExtensions :: Lens' TestSuiteStanza [Extension] Source #

extraLibs :: Lens' TestSuiteStanza [String] Source #

extraGHCiLibs :: Lens' TestSuiteStanza [String] Source #

extraBundledLibs :: Lens' TestSuiteStanza [String] Source #

extraLibFlavours :: Lens' TestSuiteStanza [String] Source #

extraLibDirs :: Lens' TestSuiteStanza [String] Source #

includeDirs :: Lens' TestSuiteStanza [FilePath] Source #

includes :: Lens' TestSuiteStanza [FilePath] Source #

installIncludes :: Lens' TestSuiteStanza [FilePath] Source #

options :: Lens' TestSuiteStanza [(CompilerFlavor, [String])] Source #

profOptions :: Lens' TestSuiteStanza [(CompilerFlavor, [String])] Source #

sharedOptions :: Lens' TestSuiteStanza [(CompilerFlavor, [String])] Source #

staticOptions :: Lens' TestSuiteStanza [(CompilerFlavor, [String])] Source #

customFieldsBI :: Lens' TestSuiteStanza [(String, String)] Source #

targetBuildDepends :: Lens' TestSuiteStanza [Dependency] Source #

mixins :: Lens' TestSuiteStanza [Mixin] Source #