Cabal-syntax-3.11.0.0: A library for working with .cabal files
Safe HaskellNone
LanguageHaskell2010

Distribution.Types.Library

Synopsis

Documentation

data Library Source #

Constructors

Library 

Fields

Instances

Instances details
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 #

hsc2hsOptions :: 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 [SymbolicPath PackageDir SourceDir] 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 #

extraLibsStatic :: Lens' Library [String] Source #

extraGHCiLibs :: Lens' Library [String] Source #

extraBundledLibs :: Lens' Library [String] Source #

extraLibFlavours :: Lens' Library [String] Source #

extraDynLibFlavours :: Lens' Library [String] Source #

extraLibDirs :: Lens' Library [String] Source #

extraLibDirsStatic :: Lens' Library [String] Source #

includeDirs :: Lens' Library [FilePath] Source #

includes :: Lens' Library [FilePath] Source #

autogenIncludes :: Lens' Library [FilePath] Source #

installIncludes :: Lens' Library [FilePath] Source #

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

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

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

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

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

targetBuildDepends :: Lens' Library [Dependency] Source #

mixins :: Lens' Library [Mixin] Source #

Structured Library Source # 
Instance details

Defined in Distribution.Types.Library

Binary Library Source # 
Instance details

Defined in Distribution.Types.Library

NFData Library Source # 
Instance details

Defined in Distribution.Types.Library

Methods

rnf :: Library -> () Source #

Monoid Library Source #

This instance is not good.

We need it for addBuildableCondition. More correct method would be some kind of "create empty clone".

More concretely, addBuildableCondition will make `libVisibility = False` libraries when `buildable: false`. This may cause problems.

Instance details

Defined in Distribution.Types.Library

Semigroup Library Source # 
Instance details

Defined in Distribution.Types.Library

Data Library Source # 
Instance details

Defined in Distribution.Types.Library

Methods

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

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

toConstr :: Library -> Constr #

dataTypeOf :: Library -> DataType #

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

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

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

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

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

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

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

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

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

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

Generic Library Source # 
Instance details

Defined in Distribution.Types.Library

Methods

from :: Library -> Rep Library x #

to :: Rep Library x -> Library #

Read Library Source # 
Instance details

Defined in Distribution.Types.Library

Show Library Source # 
Instance details

Defined in Distribution.Types.Library

Eq Library Source # 
Instance details

Defined in Distribution.Types.Library

Methods

(==) :: Library -> Library -> Bool #

(/=) :: Library -> Library -> Bool #

Ord Library Source # 
Instance details

Defined in Distribution.Types.Library

type Rep Library Source # 
Instance details

Defined in Distribution.Types.Library

explicitLibModules :: Library -> [ModuleName] Source #

Get all the module names from the library (exposed and internal modules) which are explicitly listed in the package description which would need to be compiled. (This does not include reexports, which do not need to be compiled.) This may not include all modules for which GHC generated interface files (i.e., implicit modules.)

libModulesAutogen :: Library -> [ModuleName] Source #

Get all the auto generated module names from the library, exposed or not. This are a subset of libModules.