Cabal-3.0.2.0: A framework for packaging Haskell software

Safe HaskellNone
LanguageHaskell2010

Distribution.Types.PkgconfigVersion

Synopsis

Documentation

newtype PkgconfigVersion Source #

pkg-config versions.

In fact, this can be arbitrary ByteString, but Parsec instance is a little pickier.

Since: 3.0

Instances
Eq PkgconfigVersion Source # 
Instance details

Defined in Distribution.Types.PkgconfigVersion

Data PkgconfigVersion Source # 
Instance details

Defined in Distribution.Types.PkgconfigVersion

Methods

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

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

toConstr :: PkgconfigVersion -> Constr #

dataTypeOf :: PkgconfigVersion -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord PkgconfigVersion Source # 
Instance details

Defined in Distribution.Types.PkgconfigVersion

Read PkgconfigVersion Source # 
Instance details

Defined in Distribution.Types.PkgconfigVersion

Show PkgconfigVersion Source # 
Instance details

Defined in Distribution.Types.PkgconfigVersion

Generic PkgconfigVersion Source # 
Instance details

Defined in Distribution.Types.PkgconfigVersion

Associated Types

type Rep PkgconfigVersion :: Type -> Type #

Binary PkgconfigVersion Source # 
Instance details

Defined in Distribution.Types.PkgconfigVersion

NFData PkgconfigVersion Source # 
Instance details

Defined in Distribution.Types.PkgconfigVersion

Methods

rnf :: PkgconfigVersion -> () #

Pretty PkgconfigVersion Source # 
Instance details

Defined in Distribution.Types.PkgconfigVersion

Parsec PkgconfigVersion Source #
>>> simpleParsec "1.0.2n" :: Maybe PkgconfigVersion
Just (PkgconfigVersion "1.0.2n")
>>> simpleParsec "0.3.5+ds" :: Maybe PkgconfigVersion
Nothing
Instance details

Defined in Distribution.Types.PkgconfigVersion

type Rep PkgconfigVersion Source # 
Instance details

Defined in Distribution.Types.PkgconfigVersion

type Rep PkgconfigVersion = D1 (MetaData "PkgconfigVersion" "Distribution.Types.PkgconfigVersion" "Cabal-3.0.2.0-ISqdwnPR2WZBuDHNLZqElA" True) (C1 (MetaCons "PkgconfigVersion" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 ByteString)))

rpmvercmp :: ByteString -> ByteString -> Ordering Source #

Compare two version strings as pkg-config would compare them.

Since: 3.0