Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data GenericPackageDescription
- data Flag
- data FlagName
- data ConfVar
- condBenchmarks :: Lens' GenericPackageDescription [(UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)]
- condExecutables :: Lens' GenericPackageDescription [(UnqualComponentName, CondTree ConfVar [Dependency] Executable)]
- condForeignLibs :: Lens' GenericPackageDescription [(UnqualComponentName, CondTree ConfVar [Dependency] ForeignLib)]
- condLibrary :: Lens' GenericPackageDescription (Maybe (CondTree ConfVar [Dependency] Library))
- condSubLibraries :: Lens' GenericPackageDescription [(UnqualComponentName, CondTree ConfVar [Dependency] Library)]
- condTestSuites :: Lens' GenericPackageDescription [(UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)]
- genPackageFlags :: Lens' GenericPackageDescription [Flag]
- packageDescription :: Lens' GenericPackageDescription PackageDescription
- allCondTrees :: Applicative f => (forall a. CondTree ConfVar [Dependency] a -> f (CondTree ConfVar [Dependency] a)) -> GenericPackageDescription -> f GenericPackageDescription
- flagName :: Lens' Flag FlagName
- flagDescription :: Lens' Flag String
- flagDefault :: Lens' Flag Bool
- flagManual :: Lens' Flag Bool
- _OS :: Traversal' ConfVar OS
- _Arch :: Traversal' ConfVar Arch
- _Flag :: Traversal' ConfVar FlagName
- _Impl :: Traversal' ConfVar (CompilerFlavor, VersionRange)
Documentation
data GenericPackageDescription Source #
Instances
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 # | |
Data Flag # | |
Defined in Distribution.Types.GenericPackageDescription gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Flag -> c Flag Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Flag Source # toConstr :: Flag -> Constr Source # dataTypeOf :: Flag -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Flag) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Flag) Source # gmapT :: (forall b. Data b => b -> b) -> Flag -> Flag Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Flag -> r Source # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Flag -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Flag -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Flag -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Flag -> m Flag Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Flag -> m Flag Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Flag -> m Flag Source # | |
Show Flag # | |
Generic Flag # | |
Binary Flag # | |
NFData Flag # | |
Defined in Distribution.Types.GenericPackageDescription | |
type Rep Flag # | |
Defined in Distribution.Types.GenericPackageDescription type Rep Flag = D1 (MetaData "Flag" "Distribution.Types.GenericPackageDescription" "Cabal-2.4.0.1" False) (C1 (MetaCons "MkFlag" PrefixI True) ((S1 (MetaSel (Just "flagName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 FlagName) :*: S1 (MetaSel (Just "flagDescription") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)) :*: (S1 (MetaSel (Just "flagDefault") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool) :*: S1 (MetaSel (Just "flagManual") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)))) |
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: Cabal-2.0.0.2
Instances
A ConfVar
represents the variable type used.
Instances
condBenchmarks :: Lens' GenericPackageDescription [(UnqualComponentName, CondTree ConfVar [Dependency] Benchmark)] Source #
condExecutables :: Lens' GenericPackageDescription [(UnqualComponentName, CondTree ConfVar [Dependency] Executable)] Source #
condForeignLibs :: Lens' GenericPackageDescription [(UnqualComponentName, CondTree ConfVar [Dependency] ForeignLib)] Source #
condLibrary :: Lens' GenericPackageDescription (Maybe (CondTree ConfVar [Dependency] Library)) Source #
condSubLibraries :: Lens' GenericPackageDescription [(UnqualComponentName, CondTree ConfVar [Dependency] Library)] Source #
condTestSuites :: Lens' GenericPackageDescription [(UnqualComponentName, CondTree ConfVar [Dependency] TestSuite)] Source #
allCondTrees :: Applicative f => (forall a. CondTree ConfVar [Dependency] a -> f (CondTree ConfVar [Dependency] a)) -> GenericPackageDescription -> f GenericPackageDescription Source #