debian-3.23: Modules for working with the Debian package systemSource codeContentsIndex
Debian.Repo.Types
Contents
Repository
Release
Each line of the sources.list represents a slice of a repository
Package, Source and Binary Debs
Cached OS Image
Synopsis
data EnvRoot = EnvRoot {
rootPath :: FilePath
}
data EnvPath = EnvPath {
envRoot :: EnvRoot
envPath :: FilePath
}
outsidePath :: EnvPath -> FilePath
appendPath :: FilePath -> EnvPath -> EnvPath
rootEnvPath :: FilePath -> EnvPath
class (Eq a, Ord a) => PackageVersion a where
pkgName :: a -> PkgName
pkgVersion :: a -> DebianVersion
data PkgVersion = PkgVersion {
getName :: PkgName
getVersion :: DebianVersion
}
class (Ord t, Eq t) => Repo t where
repoURI :: t -> URI
repositoryCompatibilityLevel :: t -> IO (Maybe Int)
repoReleaseInfo :: t -> [ReleaseInfo]
checkCompatibility :: t -> IO ()
libraryCompatibilityLevel :: Int
compatibilityFile :: FilePath
data Repository
= LocalRepo LocalRepository
| VerifiedRepo URIString [ReleaseInfo]
| UnverifiedRepo URIString
data LocalRepository = LocalRepository {
repoRoot :: EnvPath
repoLayout :: Maybe Layout
repoReleaseInfoLocal :: [ReleaseInfo]
}
data Layout
= Flat
| Pool
data ReleaseName = ReleaseName {
relName :: String
}
parseReleaseName :: String -> ReleaseName
data ReleaseInfo = ReleaseInfo {
releaseInfoName :: ReleaseName
releaseInfoAliases :: [ReleaseName]
releaseInfoArchitectures :: [Arch]
releaseInfoComponents :: [Section]
}
data Arch
= Source
| Binary String
archName :: Arch -> String
newtype Section = Section String
data SubSection = SubSection {
section :: Section
subSectionName :: String
}
sectionNameOfSubSection :: SubSection -> String
sectionName :: SubSection -> String
sectionName' :: Section -> String
parseSection
parseSection'
data Release = Release {
releaseRepo :: Repository
releaseInfo :: ReleaseInfo
}
releaseName' :: ReleaseName -> String
releaseName :: Release -> ReleaseName
releaseComponents :: Release -> [Section]
releaseArchitectures :: Release -> [Arch]
data SourceType
= Deb
| DebSrc
data DebSource = DebSource {
sourceType :: SourceType
sourceUri :: URI
sourceDist :: Either String (ReleaseName, [Section])
}
data SliceName = SliceName {
sliceName :: String
}
data Slice = Slice {
sliceRepo :: Repository
sliceSource :: DebSource
}
data SliceList = SliceList {
slices :: [Slice]
}
data NamedSliceList = NamedSliceList {
sliceList :: SliceList
sliceListName :: SliceName
}
data PackageIndex = PackageIndex {
packageIndexRelease :: Release
packageIndexComponent :: Section
packageIndexArch :: Arch
}
type PackageIndexLocal = PackageIndex
data PackageID = PackageID {
packageIndex :: PackageIndex
packageName :: String
packageVersion :: DebianVersion
}
data BinaryPackage = BinaryPackage {
packageID :: PackageID
packageInfo :: Paragraph
pDepends :: Relations
pPreDepends :: Relations
pConflicts :: Relations
pReplaces :: Relations
pProvides :: Relations
}
data SourcePackage = SourcePackage {
sourcePackageID :: PackageID
sourceParagraph :: Paragraph
sourceDirectory :: String
sourcePackageFiles :: [SourceFileSpec]
}
data SourceFileSpec = SourceFileSpec {
sourceFileMD5sum :: String
sourceFileSize :: FileOffset
sourceFileName :: FilePath
}
type PackageIDLocal = PackageID
type BinaryPackageLocal = BinaryPackage
type SourcePackageLocal = SourcePackage
class (Ord t, Eq t, Show t) => AptCache t where
globalCacheDir :: t -> FilePath
rootDir :: t -> EnvRoot
aptBaseSliceList :: t -> SliceList
aptArch :: t -> Arch
aptSourcePackages :: t -> [SourcePackage]
aptBinaryPackages :: t -> [BinaryPackage]
aptReleaseName :: t -> ReleaseName
class AptCache t => AptBuildCache t where
aptSliceList :: t -> SliceList
data AptImage = AptImage {
aptGlobalCacheDir :: FilePath
aptImageRoot :: EnvRoot
aptImageArch :: Arch
aptImageSliceList :: SliceList
aptImageReleaseName :: ReleaseName
aptImageSourcePackages :: [SourcePackage]
aptImageBinaryPackages :: [BinaryPackage]
}
Documentation
data EnvRoot Source
The root directory of an OS image.
Constructors
EnvRoot
rootPath :: FilePath
show/hide Instances
data EnvPath Source
A directory inside of an OS image.
Constructors
EnvPath
envRoot :: EnvRoot
envPath :: FilePath
show/hide Instances
outsidePath :: EnvPath -> FilePathSource
appendPath :: FilePath -> EnvPath -> EnvPathSource
rootEnvPath :: FilePath -> EnvPathSource
Repository
class (Eq a, Ord a) => PackageVersion a whereSource
Methods
pkgName :: a -> PkgNameSource
pkgVersion :: a -> DebianVersionSource
show/hide Instances
data PkgVersion Source
This is an old type which is still used to interface with the Debian.Relation module.
Constructors
PkgVersion
getName :: PkgName
getVersion :: DebianVersion
show/hide Instances
class (Ord t, Eq t) => Repo t whereSource
Methods
repoURI :: t -> URISource
repositoryCompatibilityLevel :: t -> IO (Maybe Int)Source
repoReleaseInfo :: t -> [ReleaseInfo]Source
This method returns a list of all the release in the repository. This can be used to identify all of the files in the repository that are not garbage.
checkCompatibility :: t -> IO ()Source
show/hide Instances
libraryCompatibilityLevel :: IntSource
The compatibility level of this library and any applications which use it. It is an error if we try to use a repository whose compatibility level is higher than this, a newer version of the library must be used. This value was increased from 1 to 2 due to a new version number tagging policy.
compatibilityFile :: FilePathSource
The name of the file which holds the repository's compatibility level.
data Repository Source
The Repository type reprents any instance of the Repo class, so it might be local or remote. data Repository = forall a. (Repo a) => Repository a
Constructors
LocalRepo LocalRepository
VerifiedRepo URIString [ReleaseInfo]
UnverifiedRepo URIString
show/hide Instances
data LocalRepository Source
Constructors
LocalRepository
repoRoot :: EnvPath
repoLayout :: Maybe Layout
repoReleaseInfoLocal :: [ReleaseInfo]
show/hide Instances
data Layout Source
The possible file arrangements for a repository. An empty repository does not yet have either of these attributes.
Constructors
Flat
Pool
show/hide Instances
Release
data ReleaseName Source
A distribution (aka release) name. This type is expected to refer to a subdirectory of the dists directory which is at the top level of a repository.
Constructors
ReleaseName
relName :: String
show/hide Instances
parseReleaseName :: String -> ReleaseNameSource
data ReleaseInfo Source
Constructors
ReleaseInfo
releaseInfoName :: ReleaseName
releaseInfoAliases :: [ReleaseName]
releaseInfoArchitectures :: [Arch]
releaseInfoComponents :: [Section]
show/hide Instances
data Arch Source
The types of architecture that a package can have, either Source or some type of binary architecture.
Constructors
Source
Binary String
show/hide Instances
archName :: Arch -> StringSource
newtype Section Source
A section of a repository such as main, contrib, non-free, restricted. The indexes for a section are located below the distribution directory.
Constructors
Section String
show/hide Instances
data SubSection Source
A package's subsection is only evident in its control information, packages from different subsections all reside in the same index.
Constructors
SubSection
section :: Section
subSectionName :: String
show/hide Instances
sectionNameOfSubSection :: SubSection -> StringSource
sectionName :: SubSection -> StringSource
sectionName' :: Section -> StringSource
parseSection
parseSection'
data Release Source
Parse the value that appears in the Section field of a .changes file. (Does this need to be unesacped?)
Constructors
Release
releaseRepo :: Repository
releaseInfo :: ReleaseInfo
show/hide Instances
releaseName' :: ReleaseName -> StringSource
releaseName :: Release -> ReleaseNameSource
releaseComponents :: Release -> [Section]Source
releaseArchitectures :: Release -> [Arch]Source
Each line of the sources.list represents a slice of a repository
data SourceType Source
Constructors
Deb
DebSrc
show/hide Instances
data DebSource Source
Constructors
DebSource
sourceType :: SourceType
sourceUri :: URI
sourceDist :: Either String (ReleaseName, [Section])
show/hide Instances
data SliceName Source
This is a name given to a combination of parts of one or more releases that can be specified by a sources.list file.
Constructors
SliceName
sliceName :: String
show/hide Instances
data Slice Source
Constructors
Slice
sliceRepo :: Repository
sliceSource :: DebSource
show/hide Instances
data SliceList Source
Constructors
SliceList
slices :: [Slice]
show/hide Instances
data NamedSliceList Source
Constructors
NamedSliceList
sliceList :: SliceList
sliceListName :: SliceName
show/hide Instances
Package, Source and Binary Debs
data PackageIndex Source
The PackageIndex type represents a file containing control information about debian packages, either source or binary. Though the control information for a binary package does not specify an architecture, the architecture here is that of the environment where the package information is cached.
Constructors
PackageIndex
packageIndexRelease :: Release
packageIndexComponent :: Section
packageIndexArch :: Arch
show/hide Instances
type PackageIndexLocal = PackageIndexSource
data PackageID Source
The PackageID type fully identifies a package by name, version, and a PackageIndex which identifies the package's release, component and architecture.
Constructors
PackageID
packageIndex :: PackageIndex
packageName :: String
packageVersion :: DebianVersion
show/hide Instances
data BinaryPackage Source
The BinaryPackage type adds to the PackageID type the control information obtained from the package index.
Constructors
BinaryPackage
packageID :: PackageID
packageInfo :: Paragraph
pDepends :: Relations
pPreDepends :: Relations
pConflicts :: Relations
pReplaces :: Relations
pProvides :: Relations
show/hide Instances
data SourcePackage Source
Constructors
SourcePackage
sourcePackageID :: PackageID
sourceParagraph :: Paragraph
sourceDirectory :: String
sourcePackageFiles :: [SourceFileSpec]
data SourceFileSpec Source
Constructors
SourceFileSpec
sourceFileMD5sum :: String
sourceFileSize :: FileOffset
sourceFileName :: FilePath
type PackageIDLocal = PackageIDSource
type BinaryPackageLocal = BinaryPackageSource
type SourcePackageLocal = SourcePackageSource
Cached OS Image
class (Ord t, Eq t, Show t) => AptCache t whereSource
Methods
globalCacheDir :: t -> FilePathSource
rootDir :: t -> EnvRootSource
The directory you might chroot to.
aptBaseSliceList :: t -> SliceListSource
The sources.list without the local repository
aptArch :: t -> ArchSource
The build architecture
aptSourcePackages :: t -> [SourcePackage]Source
Return the all source packages in this AptCache.
aptBinaryPackages :: t -> [BinaryPackage]Source
Return the all binary packages for the architecture of this AptCache.
aptReleaseName :: t -> ReleaseNameSource
Name of release
show/hide Instances
class AptCache t => AptBuildCache t whereSource
Methods
aptSliceList :: t -> SliceListSource
The sources.list
show/hide Instances
data AptImage Source
Constructors
AptImage
aptGlobalCacheDir :: FilePath
aptImageRoot :: EnvRoot
aptImageArch :: Arch
aptImageSliceList :: SliceList
aptImageReleaseName :: ReleaseName
aptImageSourcePackages :: [SourcePackage]
aptImageBinaryPackages :: [BinaryPackage]
show/hide Instances
Produced by Haddock version 2.4.2