Cabal-2.2.0.1: A framework for packaging Haskell software

Safe HaskellNone
LanguageHaskell2010

Distribution.Types.GenericPackageDescription

Synopsis

Documentation

data GenericPackageDescription Source #

Instances
Eq GenericPackageDescription Source # 
Instance details

Defined in Distribution.Types.GenericPackageDescription

Data GenericPackageDescription Source # 
Instance details

Defined in Distribution.Types.GenericPackageDescription

Methods

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

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

toConstr :: GenericPackageDescription -> Constr Source #

dataTypeOf :: GenericPackageDescription -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Show GenericPackageDescription Source # 
Instance details

Defined in Distribution.Types.GenericPackageDescription

Generic GenericPackageDescription Source # 
Instance details

Defined in Distribution.Types.GenericPackageDescription

Associated Types

type Rep GenericPackageDescription :: * -> * Source #

NFData GenericPackageDescription Source # 
Instance details

Defined in Distribution.Types.GenericPackageDescription

Binary GenericPackageDescription Source # 
Instance details

Defined in Distribution.Types.GenericPackageDescription

Package GenericPackageDescription Source # 
Instance details

Defined in Distribution.Types.GenericPackageDescription

type Rep GenericPackageDescription Source # 
Instance details

Defined in Distribution.Types.GenericPackageDescription

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

Defined in Distribution.Types.GenericPackageDescription

Methods

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

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

Data Flag Source # 
Instance details

Defined in Distribution.Types.GenericPackageDescription

Methods

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 Source # 
Instance details

Defined in Distribution.Types.GenericPackageDescription

Generic Flag Source # 
Instance details

Defined in Distribution.Types.GenericPackageDescription

Associated Types

type Rep Flag :: * -> * Source #

Methods

from :: Flag -> Rep Flag x Source #

to :: Rep Flag x -> Flag Source #

NFData Flag Source # 
Instance details

Defined in Distribution.Types.GenericPackageDescription

Methods

rnf :: Flag -> () Source #

Binary Flag Source # 
Instance details

Defined in Distribution.Types.GenericPackageDescription

type Rep Flag Source # 
Instance details

Defined in Distribution.Types.GenericPackageDescription

emptyFlag :: FlagName -> Flag Source #

A Flag initialized with default parameters.

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: Cabal-2.0.0.2

Instances
Eq FlagName Source # 
Instance details

Defined in Distribution.Types.GenericPackageDescription

Data FlagName Source # 
Instance details

Defined in Distribution.Types.GenericPackageDescription

Methods

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

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

toConstr :: FlagName -> Constr Source #

dataTypeOf :: FlagName -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Ord FlagName Source # 
Instance details

Defined in Distribution.Types.GenericPackageDescription

Read FlagName Source # 
Instance details

Defined in Distribution.Types.GenericPackageDescription

Show FlagName Source # 
Instance details

Defined in Distribution.Types.GenericPackageDescription

IsString FlagName Source #

mkFlagName

Since: Cabal-2.0.0.2

Instance details

Defined in Distribution.Types.GenericPackageDescription

Generic FlagName Source # 
Instance details

Defined in Distribution.Types.GenericPackageDescription

Associated Types

type Rep FlagName :: * -> * Source #

NFData FlagName Source # 
Instance details

Defined in Distribution.Types.GenericPackageDescription

Methods

rnf :: FlagName -> () Source #

Binary FlagName Source # 
Instance details

Defined in Distribution.Types.GenericPackageDescription

Pretty FlagName Source # 
Instance details

Defined in Distribution.Types.GenericPackageDescription

Methods

pretty :: FlagName -> Doc Source #

Parsec FlagName Source # 
Instance details

Defined in Distribution.Types.GenericPackageDescription

Text FlagName Source # 
Instance details

Defined in Distribution.Types.GenericPackageDescription

type Rep FlagName Source # 
Instance details

Defined in Distribution.Types.GenericPackageDescription

type Rep FlagName = D1 (MetaData "FlagName" "Distribution.Types.GenericPackageDescription" "Cabal-2.2.0.1" True) (C1 (MetaCons "FlagName" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ShortText)))

mkFlagName :: String -> FlagName Source #

Construct a FlagName from a String

mkFlagName is the inverse to unFlagName

Note: No validations are performed to ensure that the resulting FlagName is valid

Since: Cabal-2.0.0.2

unFlagName :: FlagName -> String Source #

Convert FlagName to String

Since: Cabal-2.0.0.2

data FlagAssignment Source #

A FlagAssignment is a total or partial mapping of FlagNames to Bool flag values. It represents the flags chosen by the user or discovered during configuration. For example --flags=foo --flags=-bar becomes [("foo", True), ("bar", False)]

Instances
Eq FlagAssignment Source # 
Instance details

Defined in Distribution.Types.GenericPackageDescription

Ord FlagAssignment Source # 
Instance details

Defined in Distribution.Types.GenericPackageDescription

Read FlagAssignment Source #

Since: Cabal-2.2.0

Instance details

Defined in Distribution.Types.GenericPackageDescription

Show FlagAssignment Source #

Since: Cabal-2.2.0

Instance details

Defined in Distribution.Types.GenericPackageDescription

Semigroup FlagAssignment Source # 
Instance details

Defined in Distribution.Types.GenericPackageDescription

Monoid FlagAssignment Source # 
Instance details

Defined in Distribution.Types.GenericPackageDescription

NFData FlagAssignment Source # 
Instance details

Defined in Distribution.Types.GenericPackageDescription

Methods

rnf :: FlagAssignment -> () Source #

Binary FlagAssignment Source # 
Instance details

Defined in Distribution.Types.GenericPackageDescription

mkFlagAssignment :: [(FlagName, Bool)] -> FlagAssignment Source #

Construct a FlagAssignment from a list of flag/value pairs.

If duplicate flags occur in the input list, the later entries in the list will take precedence.

Since: Cabal-2.2.0

unFlagAssignment :: FlagAssignment -> [(FlagName, Bool)] Source #

Deconstruct a FlagAssignment into a list of flag/value pairs.

 null (findDuplicateFlagAssignments fa) ==> (mkFlagAssignment . unFlagAssignment) fa == fa

Since: Cabal-2.2.0

lookupFlagAssignment :: FlagName -> FlagAssignment -> Maybe Bool Source #

Lookup the value for a flag

Returns Nothing if the flag isn't contained in the FlagAssignment.

Since: Cabal-2.2.0

insertFlagAssignment :: FlagName -> Bool -> FlagAssignment -> FlagAssignment Source #

Insert or update the boolean value of a flag.

If the flag is already present in the FlagAssigment, the value will be updated and the fact that multiple values have been provided for that flag will be recorded so that a warning can be generated later on.

Since: Cabal-2.2.0

diffFlagAssignment :: FlagAssignment -> FlagAssignment -> FlagAssignment Source #

Remove all flag-assignments from the first FlagAssignment that are contained in the second FlagAssignment

NB/TODO: This currently only removes flag assignments which also match the value assignment! We should review the code which uses this operation to figure out if this it's not enough to only compare the flagnames without the values.

Since: Cabal-2.2.0

findDuplicateFlagAssignments :: FlagAssignment -> [FlagName] Source #

Find the FlagNames that have been listed more than once.

Since: Cabal-2.2.0

nullFlagAssignment :: FlagAssignment -> Bool Source #

Test whether FlagAssignment is empty.

Since: Cabal-2.2.0

showFlagValue :: (FlagName, Bool) -> String Source #

String representation of a flag-value pair.

dispFlagAssignment :: FlagAssignment -> Doc Source #

Pretty-prints a flag assignment.

parseFlagAssignment :: ReadP r FlagAssignment Source #

Parses a flag assignment.

data ConfVar Source #

A ConfVar represents the variable type used.

Instances
Eq ConfVar Source # 
Instance details

Defined in Distribution.Types.GenericPackageDescription

Methods

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

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

Data ConfVar Source # 
Instance details

Defined in Distribution.Types.GenericPackageDescription

Methods

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

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

toConstr :: ConfVar -> Constr Source #

dataTypeOf :: ConfVar -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Show ConfVar Source # 
Instance details

Defined in Distribution.Types.GenericPackageDescription

Generic ConfVar Source # 
Instance details

Defined in Distribution.Types.GenericPackageDescription

Associated Types

type Rep ConfVar :: * -> * Source #

NFData ConfVar Source # 
Instance details

Defined in Distribution.Types.GenericPackageDescription

Methods

rnf :: ConfVar -> () Source #

Binary ConfVar Source # 
Instance details

Defined in Distribution.Types.GenericPackageDescription

type Rep ConfVar Source # 
Instance details

Defined in Distribution.Types.GenericPackageDescription