Cabal-2.2.0.0: A framework for packaging Haskell software

Safe HaskellNone
LanguageHaskell2010

Distribution.Types.GenericPackageDescription.Lens

Synopsis

Documentation

data GenericPackageDescription Source #

Instances

Eq GenericPackageDescription Source # 
Data GenericPackageDescription Source # 

Methods

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

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

toConstr :: GenericPackageDescription -> Constr #

dataTypeOf :: GenericPackageDescription -> DataType #

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

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

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

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

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

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

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

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

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

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

Show GenericPackageDescription Source # 
Generic GenericPackageDescription Source # 
Binary GenericPackageDescription Source # 
NFData GenericPackageDescription Source # 
Package GenericPackageDescription Source # 
type Rep GenericPackageDescription Source # 
type Rep GenericPackageDescription = D1 * (MetaData "GenericPackageDescription" "Distribution.Types.GenericPackageDescription" "Cabal-2.2.0.0-LjrPiS3OoG894mMpepVd4F" False) (C1 * (MetaCons "GenericPackageDescription" PrefixI True) ((:*:) * ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "packageDescription") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * PackageDescription)) (S1 * (MetaSel (Just Symbol "genPackageFlags") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [Flag]))) ((:*:) * (S1 * (MetaSel (Just Symbol "condLibrary") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe (CondTree ConfVar [Dependency] Library)))) (S1 * (MetaSel (Just Symbol "condSubLibraries") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [(UnqualComponentName, CondTree ConfVar [Dependency] Library)])))) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "condForeignLibs") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [(UnqualComponentName, CondTree ConfVar [Dependency] ForeignLib)])) (S1 * (MetaSel (Just Symbol "condExecutables") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [(UnqualComponentName, CondTree ConfVar [Dependency] Executable)]))) ((:*:) * (S1 * (MetaSel (Just Symbol "condTestSuites") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [(UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)])) (S1 * (MetaSel (Just Symbol "condBenchmarks") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [(UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)]))))))

data Flag Source #

A flag can represent a feature to be included, or a way of linking a target against its dependencies, or in fact whatever you can think of.

Instances

Eq Flag Source # 

Methods

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

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

Data Flag Source # 

Methods

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

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

toConstr :: Flag -> Constr #

dataTypeOf :: Flag -> DataType #

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

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

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

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

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

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

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

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

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

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

Show Flag Source # 

Methods

showsPrec :: Int -> Flag -> ShowS #

show :: Flag -> String #

showList :: [Flag] -> ShowS #

Generic Flag Source # 

Associated Types

type Rep Flag :: * -> * #

Methods

from :: Flag -> Rep Flag x #

to :: Rep Flag x -> Flag #

Binary Flag Source # 

Methods

put :: Flag -> Put #

get :: Get Flag #

putList :: [Flag] -> Put #

NFData Flag Source # 

Methods

rnf :: Flag -> () #

type Rep Flag Source # 
type Rep Flag = D1 * (MetaData "Flag" "Distribution.Types.GenericPackageDescription" "Cabal-2.2.0.0-LjrPiS3OoG894mMpepVd4F" False) (C1 * (MetaCons "MkFlag" PrefixI True) ((:*:) * ((:*:) * (S1 * (MetaSel (Just Symbol "flagName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * FlagName)) (S1 * (MetaSel (Just Symbol "flagDescription") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * String))) ((:*:) * (S1 * (MetaSel (Just Symbol "flagDefault") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool)) (S1 * (MetaSel (Just Symbol "flagManual") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Bool)))))

data FlagName Source #

A FlagName is the name of a user-defined configuration flag

Use mkFlagName and unFlagName to convert from/to a String.

This type is opaque since Cabal-2.0

Since: 2.0.0.2

Instances

Eq FlagName Source # 
Data FlagName Source # 

Methods

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

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

toConstr :: FlagName -> Constr #

dataTypeOf :: FlagName -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord FlagName Source # 
Read FlagName Source # 
Show FlagName Source # 
IsString FlagName Source #

mkFlagName

Since: 2.0.0.2

Generic FlagName Source # 

Associated Types

type Rep FlagName :: * -> * #

Methods

from :: FlagName -> Rep FlagName x #

to :: Rep FlagName x -> FlagName #

Binary FlagName Source # 

Methods

put :: FlagName -> Put #

get :: Get FlagName #

putList :: [FlagName] -> Put #

NFData FlagName Source # 

Methods

rnf :: FlagName -> () #

Pretty FlagName Source # 

Methods

pretty :: FlagName -> Doc Source #

Parsec FlagName Source # 
Text FlagName Source # 
type Rep FlagName Source # 
type Rep FlagName = D1 * (MetaData "FlagName" "Distribution.Types.GenericPackageDescription" "Cabal-2.2.0.0-LjrPiS3OoG894mMpepVd4F" True) (C1 * (MetaCons "FlagName" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * ShortText)))

data ConfVar Source #

A ConfVar represents the variable type used.

Instances

Eq ConfVar Source # 

Methods

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

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

Data ConfVar Source # 

Methods

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

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

toConstr :: ConfVar -> Constr #

dataTypeOf :: ConfVar -> DataType #

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

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

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

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

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

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

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

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

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

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

Show ConfVar Source # 
Generic ConfVar Source # 

Associated Types

type Rep ConfVar :: * -> * #

Methods

from :: ConfVar -> Rep ConfVar x #

to :: Rep ConfVar x -> ConfVar #

Binary ConfVar Source # 

Methods

put :: ConfVar -> Put #

get :: Get ConfVar #

putList :: [ConfVar] -> Put #

NFData ConfVar Source # 

Methods

rnf :: ConfVar -> () #

type Rep ConfVar Source #