debian-4.0.2: Modules for working with the Debian package system

Safe HaskellNone
LanguageHaskell98

Debian.Version

Description

A module for parsing, comparing, and (eventually) modifying debian version numbers. http://www.debian.org/doc/debian-policy/ch-controlfields.html#s-f-Version

Synopsis

Documentation

data DebianVersion Source #

Instances
Eq DebianVersion Source # 
Instance details

Defined in Debian.Version.Common

Data DebianVersion Source # 
Instance details

Defined in Debian.Version.Internal

Methods

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

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

toConstr :: DebianVersion -> Constr #

dataTypeOf :: DebianVersion -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord DebianVersion Source # 
Instance details

Defined in Debian.Version.Common

Read DebianVersion Source # 
Instance details

Defined in Debian.Version.String

Show DebianVersion Source # 
Instance details

Defined in Debian.Version.Common

Pretty (PP DebianVersion) Source # 
Instance details

Defined in Debian.Version.Common

Methods

pretty :: PP DebianVersion -> Doc #

Exported abstract because the internal representation is likely to change

parseDebianVersion' :: ParseDebianVersion string => string -> DebianVersion Source #

Convert a string to a debian version number. May throw an exception if the string is unparsable -- but I am not sure if that can currently happen. Are there any invalid version strings? Perhaps ones with underscore, or something?

evr :: DebianVersion -> (Maybe Int, String, Maybe String) Source #

Split a DebianVersion into its three components: epoch, version, revision. It is not safe to use the parsed version number for this because you will lose information, such as leading zeros.