debian-4.0.4: Modules for working with the Debian package system
Safe HaskellNone
LanguageHaskell2010

Debian.Relation.Common

Synopsis

Documentation

data Relation Source #

Instances

Instances details
Eq Relation Source # 
Instance details

Defined in Debian.Relation.Common

Ord Relation Source # 
Instance details

Defined in Debian.Relation.Common

Read Relation Source # 
Instance details

Defined in Debian.Relation.Common

Show Relation Source # 
Instance details

Defined in Debian.Relation.Common

Pretty (PP Relation) Source # 
Instance details

Defined in Debian.Relation.Common

Pretty (PP OrRelation) Source # 
Instance details

Defined in Debian.Relation.Common

Pretty (PP Relations) Source #

Wrap PP around type synonyms that might overlap with the `Pretty [a]` instance.

Instance details

Defined in Debian.Relation.Common

newtype SrcPkgName Source #

Constructors

SrcPkgName 

Fields

Instances

Instances details
Eq SrcPkgName Source # 
Instance details

Defined in Debian.Relation.Common

Data SrcPkgName Source # 
Instance details

Defined in Debian.Relation.Common

Methods

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

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

toConstr :: SrcPkgName -> Constr #

dataTypeOf :: SrcPkgName -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord SrcPkgName Source # 
Instance details

Defined in Debian.Relation.Common

Read SrcPkgName Source # 
Instance details

Defined in Debian.Relation.Common

Show SrcPkgName Source # 
Instance details

Defined in Debian.Relation.Common

PkgName SrcPkgName Source # 
Instance details

Defined in Debian.Relation.Common

Pretty (PP SrcPkgName) Source # 
Instance details

Defined in Debian.Relation.Common

newtype BinPkgName Source #

Constructors

BinPkgName 

Fields

Instances

Instances details
Eq BinPkgName Source # 
Instance details

Defined in Debian.Relation.Common

Data BinPkgName Source # 
Instance details

Defined in Debian.Relation.Common

Methods

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

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

toConstr :: BinPkgName -> Constr #

dataTypeOf :: BinPkgName -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord BinPkgName Source # 
Instance details

Defined in Debian.Relation.Common

Read BinPkgName Source # 
Instance details

Defined in Debian.Relation.Common

Show BinPkgName Source # 
Instance details

Defined in Debian.Relation.Common

PkgName BinPkgName Source # 
Instance details

Defined in Debian.Relation.Common

Pretty (PP BinPkgName) Source # 
Instance details

Defined in Debian.Relation.Common

class Pretty (PP a) => PkgName a where Source #

Instances

Instances details
PkgName BinPkgName Source # 
Instance details

Defined in Debian.Relation.Common

PkgName SrcPkgName Source # 
Instance details

Defined in Debian.Relation.Common

class ParseRelations a where Source #

Methods

parseRelations :: a -> Either ParseError Relations Source #

parseRelations parse a debian relation (i.e. the value of a Depends field). Return a parsec error or a value of type Relations

prettyRelations :: [[Relation]] -> Doc Source #

This needs to be indented for use in a control file: intercalate "n " . lines . show

data VersionReq Source #

Instances

Instances details
Eq VersionReq Source # 
Instance details

Defined in Debian.Relation.Common

Ord VersionReq Source #

The sort order is based on version number first, then on the kind of relation, sorting in the order

Instance details

Defined in Debian.Relation.Common

Read VersionReq Source # 
Instance details

Defined in Debian.Relation.Common

Show VersionReq Source # 
Instance details

Defined in Debian.Relation.Common

Pretty (PP VersionReq) Source # 
Instance details

Defined in Debian.Relation.Common

checkVersionReq :: Maybe VersionReq -> Maybe DebianVersion -> Bool Source #

Check if a version number satisfies a version requirement.