Cabal-3.0.1.0: A framework for packaging Haskell software

Safe HaskellNone
LanguageHaskell2010

Distribution.Types.PkgconfigVersionRange

Contents

Synopsis

Documentation

data PkgconfigVersionRange Source #

Since: 3.0

Instances
Eq PkgconfigVersionRange Source # 
Instance details

Defined in Distribution.Types.PkgconfigVersionRange

Data PkgconfigVersionRange Source # 
Instance details

Defined in Distribution.Types.PkgconfigVersionRange

Methods

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

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

toConstr :: PkgconfigVersionRange -> Constr #

dataTypeOf :: PkgconfigVersionRange -> DataType #

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

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

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

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

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

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

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

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

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

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

Read PkgconfigVersionRange Source # 
Instance details

Defined in Distribution.Types.PkgconfigVersionRange

Show PkgconfigVersionRange Source # 
Instance details

Defined in Distribution.Types.PkgconfigVersionRange

Generic PkgconfigVersionRange Source # 
Instance details

Defined in Distribution.Types.PkgconfigVersionRange

Associated Types

type Rep PkgconfigVersionRange :: Type -> Type #

Binary PkgconfigVersionRange Source # 
Instance details

Defined in Distribution.Types.PkgconfigVersionRange

NFData PkgconfigVersionRange Source # 
Instance details

Defined in Distribution.Types.PkgconfigVersionRange

Methods

rnf :: PkgconfigVersionRange -> () #

Pretty PkgconfigVersionRange Source # 
Instance details

Defined in Distribution.Types.PkgconfigVersionRange

Parsec PkgconfigVersionRange Source # 
Instance details

Defined in Distribution.Types.PkgconfigVersionRange

type Rep PkgconfigVersionRange Source # 
Instance details

Defined in Distribution.Types.PkgconfigVersionRange

type Rep PkgconfigVersionRange = D1 (MetaData "PkgconfigVersionRange" "Distribution.Types.PkgconfigVersionRange" "Cabal-3.0.1.0-7bhPNuc4emeBQNpr9F8jJ" False) (((C1 (MetaCons "PcAnyVersion" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "PcThisVersion" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PkgconfigVersion))) :+: (C1 (MetaCons "PcLaterVersion" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PkgconfigVersion)) :+: C1 (MetaCons "PcEarlierVersion" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PkgconfigVersion)))) :+: ((C1 (MetaCons "PcOrLaterVersion" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PkgconfigVersion)) :+: C1 (MetaCons "PcOrEarlierVersion" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PkgconfigVersion))) :+: (C1 (MetaCons "PcUnionVersionRanges" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PkgconfigVersionRange) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PkgconfigVersionRange)) :+: C1 (MetaCons "PcIntersectVersionRanges" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PkgconfigVersionRange) :*: S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 PkgconfigVersionRange)))))

isAnyPkgconfigVersion :: PkgconfigVersionRange -> Bool Source #

TODO: this is not precise, but used only to prettify output.

Internal