module Distribution.Types.BuildInfo.Lens (
BuildInfo,
HasBuildInfo (..),
HasBuildInfos (..),
) where
import Prelude ()
import Distribution.Compat.Prelude
import Distribution.Compat.Lens
import Distribution.Compiler (PerCompilerFlavor)
import Distribution.ModuleName (ModuleName)
import Distribution.Types.BuildInfo (BuildInfo)
import Distribution.Types.Dependency (Dependency)
import Distribution.Types.ExeDependency (ExeDependency)
import Distribution.Types.LegacyExeDependency (LegacyExeDependency)
import Distribution.Types.Mixin (Mixin)
import Distribution.Types.PkgconfigDependency (PkgconfigDependency)
import Language.Haskell.Extension (Extension, Language)
import qualified Distribution.Types.BuildInfo as T
class HasBuildInfo a where
buildInfo :: Lens' a BuildInfo
buildable :: Lens' a Bool
buildable = buildInfo . buildable
buildTools :: Lens' a [LegacyExeDependency]
buildTools = buildInfo . buildTools
buildToolDepends :: Lens' a [ExeDependency]
buildToolDepends = buildInfo . buildToolDepends
cppOptions :: Lens' a [String]
cppOptions = buildInfo . cppOptions
asmOptions :: Lens' a [String]
asmOptions = buildInfo . asmOptions
cmmOptions :: Lens' a [String]
cmmOptions = buildInfo . cmmOptions
ccOptions :: Lens' a [String]
ccOptions = buildInfo . ccOptions
cxxOptions :: Lens' a [String]
cxxOptions = buildInfo . cxxOptions
ldOptions :: Lens' a [String]
ldOptions = buildInfo . ldOptions
pkgconfigDepends :: Lens' a [PkgconfigDependency]
pkgconfigDepends = buildInfo . pkgconfigDepends
frameworks :: Lens' a [String]
frameworks = buildInfo . frameworks
extraFrameworkDirs :: Lens' a [String]
extraFrameworkDirs = buildInfo . extraFrameworkDirs
asmSources :: Lens' a [FilePath]
asmSources = buildInfo . asmSources
cmmSources :: Lens' a [FilePath]
cmmSources = buildInfo . cmmSources
cSources :: Lens' a [FilePath]
cSources = buildInfo . cSources
cxxSources :: Lens' a [FilePath]
cxxSources = buildInfo . cxxSources
jsSources :: Lens' a [FilePath]
jsSources = buildInfo . jsSources
hsSourceDirs :: Lens' a [FilePath]
hsSourceDirs = buildInfo . hsSourceDirs
otherModules :: Lens' a [ModuleName]
otherModules = buildInfo . otherModules
virtualModules :: Lens' a [ModuleName]
virtualModules = buildInfo . virtualModules
autogenModules :: Lens' a [ModuleName]
autogenModules = buildInfo . autogenModules
defaultLanguage :: Lens' a (Maybe Language)
defaultLanguage = buildInfo . defaultLanguage
otherLanguages :: Lens' a [Language]
otherLanguages = buildInfo . otherLanguages
defaultExtensions :: Lens' a [Extension]
defaultExtensions = buildInfo . defaultExtensions
otherExtensions :: Lens' a [Extension]
otherExtensions = buildInfo . otherExtensions
oldExtensions :: Lens' a [Extension]
oldExtensions = buildInfo . oldExtensions
extraLibs :: Lens' a [String]
extraLibs = buildInfo . extraLibs
extraGHCiLibs :: Lens' a [String]
extraGHCiLibs = buildInfo . extraGHCiLibs
extraBundledLibs :: Lens' a [String]
extraBundledLibs = buildInfo . extraBundledLibs
extraLibFlavours :: Lens' a [String]
extraLibFlavours = buildInfo . extraLibFlavours
extraDynLibFlavours :: Lens' a [String]
extraDynLibFlavours = buildInfo . extraDynLibFlavours
extraLibDirs :: Lens' a [String]
extraLibDirs = buildInfo . extraLibDirs
includeDirs :: Lens' a [FilePath]
includeDirs = buildInfo . includeDirs
includes :: Lens' a [FilePath]
includes = buildInfo . includes
autogenIncludes :: Lens' a [FilePath]
autogenIncludes = buildInfo . autogenIncludes
installIncludes :: Lens' a [FilePath]
installIncludes = buildInfo . installIncludes
options :: Lens' a (PerCompilerFlavor [String])
options = buildInfo . options
profOptions :: Lens' a (PerCompilerFlavor [String])
profOptions = buildInfo . profOptions
sharedOptions :: Lens' a (PerCompilerFlavor [String])
sharedOptions = buildInfo . sharedOptions
staticOptions :: Lens' a (PerCompilerFlavor [String])
staticOptions = buildInfo . staticOptions
customFieldsBI :: Lens' a [(String,String)]
customFieldsBI = buildInfo . customFieldsBI
targetBuildDepends :: Lens' a [Dependency]
targetBuildDepends = buildInfo . targetBuildDepends
mixins :: Lens' a [Mixin]
mixins = buildInfo . mixins
instance HasBuildInfo BuildInfo where
buildInfo = id
buildable f s = fmap (\x -> s { T.buildable = x }) (f (T.buildable s))
buildTools f s = fmap (\x -> s { T.buildTools = x }) (f (T.buildTools s))
buildToolDepends f s = fmap (\x -> s { T.buildToolDepends = x }) (f (T.buildToolDepends s))
cppOptions f s = fmap (\x -> s { T.cppOptions = x }) (f (T.cppOptions s))
asmOptions f s = fmap (\x -> s { T.asmOptions = x }) (f (T.asmOptions s))
cmmOptions f s = fmap (\x -> s { T.cmmOptions = x }) (f (T.cmmOptions s))
ccOptions f s = fmap (\x -> s { T.ccOptions = x }) (f (T.ccOptions s))
cxxOptions f s = fmap (\x -> s { T.cxxOptions = x }) (f (T.cxxOptions s))
ldOptions f s = fmap (\x -> s { T.ldOptions = x }) (f (T.ldOptions s))
pkgconfigDepends f s = fmap (\x -> s { T.pkgconfigDepends = x }) (f (T.pkgconfigDepends s))
frameworks f s = fmap (\x -> s { T.frameworks = x }) (f (T.frameworks s))
extraFrameworkDirs f s = fmap (\x -> s { T.extraFrameworkDirs = x }) (f (T.extraFrameworkDirs s))
asmSources f s = fmap (\x -> s { T.asmSources = x }) (f (T.asmSources s))
cmmSources f s = fmap (\x -> s { T.cmmSources = x }) (f (T.cmmSources s))
cSources f s = fmap (\x -> s { T.cSources = x }) (f (T.cSources s))
cxxSources f s = fmap (\x -> s { T.cSources = x }) (f (T.cxxSources s))
jsSources f s = fmap (\x -> s { T.jsSources = x }) (f (T.jsSources s))
hsSourceDirs f s = fmap (\x -> s { T.hsSourceDirs = x }) (f (T.hsSourceDirs s))
otherModules f s = fmap (\x -> s { T.otherModules = x }) (f (T.otherModules s))
virtualModules f s = fmap (\x -> s { T.virtualModules = x }) (f (T.virtualModules s))
autogenModules f s = fmap (\x -> s { T.autogenModules = x }) (f (T.autogenModules s))
defaultLanguage f s = fmap (\x -> s { T.defaultLanguage = x }) (f (T.defaultLanguage s))
otherLanguages f s = fmap (\x -> s { T.otherLanguages = x }) (f (T.otherLanguages s))
defaultExtensions f s = fmap (\x -> s { T.defaultExtensions = x }) (f (T.defaultExtensions s))
otherExtensions f s = fmap (\x -> s { T.otherExtensions = x }) (f (T.otherExtensions s))
oldExtensions f s = fmap (\x -> s { T.oldExtensions = x }) (f (T.oldExtensions s))
extraLibs f s = fmap (\x -> s { T.extraLibs = x }) (f (T.extraLibs s))
extraGHCiLibs f s = fmap (\x -> s { T.extraGHCiLibs = x }) (f (T.extraGHCiLibs s))
extraBundledLibs f s = fmap (\x -> s { T.extraBundledLibs = x }) (f (T.extraBundledLibs s))
extraLibFlavours f s = fmap (\x -> s { T.extraLibFlavours = x }) (f (T.extraLibFlavours s))
extraDynLibFlavours f s = fmap (\x -> s { T.extraDynLibFlavours = x}) (f (T.extraDynLibFlavours s))
extraLibDirs f s = fmap (\x -> s { T.extraLibDirs = x }) (f (T.extraLibDirs s))
includeDirs f s = fmap (\x -> s { T.includeDirs = x }) (f (T.includeDirs s))
includes f s = fmap (\x -> s { T.includes = x }) (f (T.includes s))
autogenIncludes f s = fmap (\x -> s { T.autogenIncludes = x }) (f (T.autogenIncludes s))
installIncludes f s = fmap (\x -> s { T.installIncludes = x }) (f (T.installIncludes s))
options f s = fmap (\x -> s { T.options = x }) (f (T.options s))
profOptions f s = fmap (\x -> s { T.profOptions = x }) (f (T.profOptions s))
sharedOptions f s = fmap (\x -> s { T.sharedOptions = x }) (f (T.sharedOptions s))
staticOptions f s = fmap (\x -> s { T.staticOptions = x }) (f (T.staticOptions s))
customFieldsBI f s = fmap (\x -> s { T.customFieldsBI = x }) (f (T.customFieldsBI s))
targetBuildDepends f s = fmap (\x -> s { T.targetBuildDepends = x }) (f (T.targetBuildDepends s))
mixins f s = fmap (\x -> s { T.mixins = x }) (f (T.mixins s))
class HasBuildInfos a where
traverseBuildInfos :: Traversal' a BuildInfo