codec-rpm-0.2.1: A library for manipulating RPM files

Copyright(c) 2016-2017 Red Hat Inc.
LicenseLGPL
Maintainerhttps://github.com/weldr
Stabilitystable
Portabilityportable
Safe HaskellSafe
LanguageHaskell2010

Codec.RPM.Tags

Contents

Description

 

Synopsis

Types

data Tag Source #

A very large data type that holds all the possibilities for the various tags that can be contained in an RPM Header. Each tag describes one piece of metadata. Most tags include some typed value, such as a String or Word32. Many tags contain lists of these values, for instance any tag involving files or changelog entries. Some tags contain no useful value at all.

Because there are so many possibilities for tags and each RPM likely contains dozens of tags, it is unwieldy to write functions that pattern match on tags and take some action. This module therefore provides a variety of find*Tag functions for searching the list of tags by name and returning a Maybe value. The name provided to each should be the constructor you are looking for in this data type.

To find the list of all files in the RPM, you would therefore do:

findStringTag "FileNames" tags

Constructors

DEPRECATED Tag 
INTERNAL Tag 
OBSOLETE Tag 
UNIMPLEMENTED Tag 
UNUSED Tag 
HeaderImage Null 
HeaderSignatures Null 
HeaderImmutable Null 
HeaderRegions Null 
HeaderI18NTable [String] 
SigBase Null 
SigSize Word32 
SigLEMD5_1 Null 
SigPGP ByteString 
SigLEMD5_2 Null 
SigMD5 ByteString 
SigGPG ByteString 
SigPGP5 Null 
SigBadSHA1_1 Null 
SigBadSHA1_2 Null 
PubKeys [String] 
DSAHeader ByteString 
RSAHeader ByteString 
SHA1Header String 
LongSigSize Word64 
LongArchiveSize Word64 
Name String 
Version String 
Release String 
Epoch Word32 
Summary ByteString 
Description ByteString 
BuildTime Word32 
BuildHost String 
InstallTime Word32 
Size Word32 
Distribution String 
Vendor String 
GIF ByteString 
XPM ByteString 
License String 
Packager String 
Group ByteString 
ChangeLog [String] 
Source [String] 
Patch [String] 
URL String 
OS String 
Arch String 
PreIn String 
PostIn String 
PreUn String 
PostUn String 
OldFileNames [String] 
FileSizes [Word32] 
FileStates [Char] 
FileModes [Word16] 
FileUIDs [Word32] 
FileGIDs [Word32] 
FileRDevs [Word16] 
FileMTimes [Word32] 
FileMD5s [String] 
FileLinkTos [String] 
FileFlags [Word32] 
Root Null 
FileUserName [String] 
FileGroupName [String] 
Exclude Null 
Exclusive Null 
Icon ByteString 
SourceRPM String 
FileVerifyFlags [Word32] 
ArchiveSize Word32 
ProvideName [String] 
RequireFlags [Word32] 
RequireName [String] 
RequireVersion [String] 
NoSource [Word32] 
NoPatch [Word32] 
ConflictFlags [Word32] 
ConflictName [String] 
ConflictVersion [String] 
DefaultPrefix String 
BuildRoot String 
InstallPrefix String 
ExcludeArch [String] 
ExcludeOS [String] 
ExclusiveArch [String] 
ExclusiveOS [String] 
AutoReqProv String 
RPMVersion String 
TriggerScripts [String] 
TriggerName [String] 
TriggerVersion [String] 
TriggerFlags [Word32] 
TriggerIndex [Word32] 
VerifyScript String 
ChangeLogTime [Word32] 
ChangeLogName [String] 
ChangeLogText [String] 
BrokenMD5 Null 
PreReq Null 
PreInProg [String] 
PostInProg [String] 
PreUnProg [String] 
PostUnProg [String] 
BuildArchs [String] 
ObsoleteName [String] 
VerifyScriptProg [String] 
TriggerScriptProg [String] 
DocDir Null 
Cookie String 
FileDevices [Word32] 
FileINodes [Word32] 
FileLangs [String] 
Prefixes [String] 
InstPrefixes [String] 
TriggerIn Null 
TriggerUn Null 
TriggerPostUn Null 
AutoReq Null 
AutoProv Null 
Capability Word32 
SourcePackage Word32 
OldOrigFileNames Null 
BuildPreReq Null 
BuildRequires Null 
BuildConflicts Null 
BuildMacros Null 
ProvideFlags [Word32] 
ProvideVersion [String] 
ObsoleteFlags [Word32] 
ObsoleteVersion [String] 
DirIndexes [Word32] 
BaseNames [String] 
DirNames [String] 
OrigDirIndexes [Word32] 
OrigBaseNames [String] 
OrigDirNames [String] 
OptFlags String 
DistURL String 
PayloadFormat String 
PayloadCompressor String 
PayloadFlags String 
InstallColor Word32 
InstallTID Word32 
RemoveTID Word32 
SHA1RHN Null 
RHNPlatform String 
Platform String 
PatchesName [String] 
PatchesFlags [Word32] 
PatchesVersion [String] 
CacheCTime Word32 
CachePkgPath String 
CachePkgSize Word32 
CachePkgMTime Word32 
FileColors [Word32] 
FileClass [Word32] 
ClassDict [String] 
FileDependsX [Word32] 
FileDependsN [Word32] 
DependsDict [(Word32, Word32)] 
SourcePkgID ByteString 
FileContexts [String] 
FSContexts [String] 
ReContexts [String] 
Policies [String] 
PreTrans String 
PostTrans String 
PreTransProg [String] 
PostTransProg [String] 
DistTag String 
OldSuggestsName [String] 
OldSuggestsVersion [String] 
OldSuggestsFlags [Word32] 
OldEnhancesName [String] 
OldEnhancesVersion [String] 
OldEnhancesFlags [Word32] 
Priority [Word32] 
CVSID String 
BLinkPkgID [String] 
BLinkHdrID [String] 
BLinkNEVRA [String] 
FLinkPkgID [String] 
FLinkHdrID [String] 
FLinkNEVRA [String] 
PackageOrigin String 
TriggerPreIn Null 
BuildSuggests Null 
BuildEnhances Null 
ScriptStates [Word32] 
ScriptMetrics [Word32] 
BuildCPUClock Word32 
FileDigestAlgos [Word32] 
Variants [String] 
XMajor Word32 
XMinor Word32 
RepoTag String 
Keywords [String] 
BuildPlatforms [String] 
PackageColor Word32 
PackagePrefColor Word32 
XattrsDict [String] 
FileXattrsx [Word32] 
DepAttrsDict [String] 
ConflictAttrsx [Word32] 
ObsoleteAttrsx [Word32] 
ProvideAttrsx [Word32] 
RequireAttrsx [Word32] 
BuildProvides Null 
BuildObsoletes Null 
DBInstance Word32 
NVRA String 
FileNames [String] 
FileProvide [String] 
FileRequire [String] 
FSNames [String] 
FSSizes [Word64] 
TriggerConds [String] 
TriggerType [String] 
OrigFileNames [String] 
LongFileSizes [Word64] 
LongSize Word64 
FileCaps [String] 
FileDigestAlgo Word32 
BugURL String 
EVR String 
NVR String 
NEVR String 
NEVRA String 
HeaderColor Word32 
Verbose Word32 
EpochNum Word32 
PreInFlags Word32 
PostInFlags Word32 
PreUnFlags Word32 
PostUnFlags Word32 
PreTransFlags Word32 
PostTransFlags Word32 
VerifyScriptFlags Word32 
TriggerScriptFlags [Word32] 
Collections [String] 
PolicyNames [String] 
PolicyTypes [String] 
PolicyTypesIndexes [Word32] 
PolicyFlags [Word32] 
PolicyVCS String 
OrderName [String] 
OrderVersion [String] 
OrderFlags [Word32] 
MSSFManifest [String] 
MSSFDomain [String] 
InstFileNames [String] 
RequireNEVRs [String] 
ProvideNEVRs [String] 
ObsoleteNEVRs [String] 
ConflictNEVRs [String] 
FileNLinks [Word32] 
RecommendName [String] 
RecommendVersion [String] 
RecommendFlags [Word32] 
SuggestName [String] 
SuggestVersion [String] 
SuggestFlags [Word32] 
SupplementName [String] 
SupplementVersion [String] 
SupplementFlags [Word32] 
EnhanceName [String] 
EnhanceVersion [String] 
EnhanceFlags [Word32] 
RecommendNEVRs [String] 
SuggestNEVRs [String] 
SupplementNEVRs [String] 
EnhanceNEVRs [String] 
Encoding String 
FileTriggerIn Null 
FileTriggerUn Null 
FileTriggerPostUn Null 
FileTriggerScripts [String] 
FileTriggerScriptProg [String] 
FileTriggerScriptFlags [Word32] 
FileTriggerName [String] 
FileTriggerIndex [Word32] 
FileTriggerVersion [String] 
FileTriggerFlags [Word32] 
TransFileTriggerIn Null 
TransFileTriggerUn Null 
TransFileTriggerPostUn Null 
TransFileTriggerScripts [String] 
TransFileTriggerScriptProg [String] 
TransFileTriggerScriptFlags [Word32] 
TransFileTriggerName [String] 
TransFileTriggerIndex [Word32] 
TransFileTriggerVersion [String] 
TransFileTriggerFlags [Word32] 
RemovePathPostFixes String 
FileTriggerPriorities [Word32] 
TransFileTriggerPriorities [Word32] 
FileTriggerConds [String] 
FileTriggerType [String] 
TransFileTriggerConds [String] 
TransFileTriggerType [String] 
FileSignatures [String] 
FileSignatureLength Word32 

Instances

Eq Tag Source # 

Methods

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

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

Data Tag Source # 

Methods

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

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

toConstr :: Tag -> Constr #

dataTypeOf :: Tag -> DataType #

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

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

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

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

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

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

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

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

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

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

Show Tag Source # 

Methods

showsPrec :: Int -> Tag -> ShowS #

show :: Tag -> String #

showList :: [Tag] -> ShowS #

Pretty Tag Source # 

data Null Source #

Some Tags do not contain any value, likely because support for that tag has been removed. RPM never removes a tag from its list of known values, however, so we must still recognize them. These tags have a special value of Null, which contains no value.

Constructors

Null 

Instances

Eq Null Source # 

Methods

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

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

Data Null Source # 

Methods

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

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

toConstr :: Null -> Constr #

dataTypeOf :: Null -> DataType #

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

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

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

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

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

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

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

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

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

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

Show Null Source # 

Methods

showsPrec :: Int -> Null -> ShowS #

show :: Null -> String #

showList :: [Null] -> ShowS #

Tag finding functions

findTag :: String -> [Tag] -> Maybe Tag Source #

Given the name of a Tag and a list of Tags (say, from the Header of some RPM), find the match and return it as a Maybe. This is the most generic of the various finding functions - it will return any match regardless of its type. You are expected to know what type you are looking for.

findByteStringTag :: String -> [Tag] -> Maybe ByteString Source #

Given the name of a Tag and a list of Tags, find the match, convert it into a ByteString, and return it as a Maybe. If the value of the Tag cannot be converted into a ByteString (say, because it is of the wrong type), Nothing will be returned. Thus, this should only be used on tags whose value is known - see the definition of Tag for the possibilities.

findStringTag :: String -> [Tag] -> Maybe String Source #

Given the name of a Tag and a list of Tags, find the match, convert it into a String, and return it as a Maybe. If the value of the Tag cannot be converted into a String (say, because it is of the wrong type), Nothing will be returned. Thus, this should only be used on tags whose value is known - see the definition of Tag for the possibilities.

findStringListTag :: String -> [Tag] -> [String] Source #

Given the name of a Tag and a list of Tags, find all matches, convert them into Strings, and return a list. If no results are found or the value of a single Tag cannot be converted into a String (say, because it is of the wrong type), an empty list will be returned. Thus, this should only be used on tags whose value is known - see the definition of Tag for the possibilities.

findWord16Tag :: String -> [Tag] -> Maybe Word16 Source #

Given the name of a Tag and a list of Tags, find the match, convert it into a Word16, and return it as a Maybe. If the value of the Tag cannot be converted into a Word16 (say, because it is of the wrong type), Nothing will be returned. Thus, this should only be used on tags whose value is known - see the definition of Tag for the possibilities.

findWord16ListTag :: String -> [Tag] -> [Word16] Source #

Given the name of a Tag and a list of Tags, find all matches, convert them into Word16s, and return a list. If no results are found or the value of a single Tag cannot be converted into a Word16 (say, because it is of the wrong type), an empty list will be returned. Thus, this should only be used on tags whose value is known - see the definition of Tag for the possibilities.

findWord32Tag :: String -> [Tag] -> Maybe Word32 Source #

Given the name of a Tag and a list of Tags, find the match, convert it into a Word16, and return it as a Maybe. If the value of the Tag cannot be converted into a Word16 (say, because it is of the wrong type), Nothing will be returned. Thus, this should only be used on tags whose value is known - see the definition of Tag for the possibilities.

findWord32ListTag :: String -> [Tag] -> [Word32] Source #

Given the name of a Tag and a list of Tags, find all matches, convert them into Word32s, and return a list. If no results are found or the value of a single Tag cannot be converted into a Word32 (say, because it is of the wrong type), an empty list will be returned. Thus, this should only be used on tags whose value is known - see the definition of Tag for the possibilities.

Tag making functions

mkTag Source #

Arguments

:: ByteString

The headerStore containing the value of the potential Tag.

-> Int

The number of the Tag, as read out of the store. Valid numbers may be found in lib/rpmtag.h in the RPM source, though most users will not need to know this since it will be read from the store.

-> Word32

What is the type of this tag's value? Valid numbers may be found in the rpmTagType_e enum in lib/rpmtag.h in the RPM source, though most users will not need to know this since it will be read from the store. Here, it is used as a simple form of type checking.

-> Word32

How far into the headerStore is this Tags value stored?

-> Word32

How many values are stored for this Tag?

-> Maybe Tag 

Attempt to create a Tag based on various parameters.

Tag inspection functions

tagValue :: Typeable a => Tag -> Maybe a Source #

Given a Tag, return its value. This is a helper function to be used with findTag, essentially as a type-safe way to cast the value into a known type. It is used internally in all the type-specific find*Tag functions but can also be used on its own. A function to find the Epoch tag could be written as follows:

epoch = findTag "Epoch" tags >>= \t -> tagValue t :: Maybe Word32