Copyright | (c) Duncan Coutts 2008 |
---|---|
License | BSD-like |
Maintainer | duncan@community.haskell.org |
Stability | provisional |
Portability | portable |
Safe Haskell | None |
Language | Haskell2010 |
Distribution.Client.IndexUtils
Contents
Description
Extra utils related to the package indexes.
Synopsis
- getIndexFileAge :: Repo -> IO Double
- getInstalledPackages :: Verbosity -> Compiler -> PackageDBStackCWD -> ProgramDb -> IO InstalledPackageIndex
- indexBaseName :: Repo -> FilePath
- getInstalledPackagesMonitorFiles :: Verbosity -> Compiler -> Maybe (SymbolicPath CWD ('Dir from)) -> PackageDBStackS from -> ProgramDb -> Platform -> IO [FilePath]
- getSourcePackages :: Verbosity -> RepoContext -> IO SourcePackageDb
- getSourcePackagesMonitorFiles :: [Repo] -> [FilePath]
- data TotalIndexState
- getSourcePackagesAtIndexState :: Verbosity -> RepoContext -> Maybe TotalIndexState -> Maybe ActiveRepos -> IO (SourcePackageDb, TotalIndexState, ActiveRepos)
- data ActiveRepos
- filterSkippedActiveRepos :: ActiveRepos -> ActiveRepos
- data Index = RepoIndex RepoContext Repo
- data RepoIndexState
- data PackageEntry
- parsePackageIndex :: Verbosity -> ByteString -> [IO (Maybe PackageOrDep)]
- updateRepoIndexCache :: Verbosity -> Index -> IO ()
- updatePackageIndexCacheFile :: Verbosity -> Index -> IO ()
- writeIndexTimestamp :: Index -> RepoIndexState -> IO ()
- currentIndexTimestamp :: Verbosity -> Index -> IO Timestamp
- data BuildTreeRefType
- refTypeFromTypeCode :: TypeCode -> BuildTreeRefType
- typeCodeFromRefType :: BuildTreeRefType -> TypeCode
- preferredVersions :: FilePath
- isPreferredVersions :: FilePath -> Bool
- parsePreferredVersionsWarnings :: ByteString -> [Either PreferredVersionsParseError Dependency]
- data PreferredVersionsParseError = PreferredVersionsParseError {}
Documentation
getIndexFileAge :: Repo -> IO Double Source #
Return the age of the index file in days (as a Double).
getInstalledPackages :: Verbosity -> Compiler -> PackageDBStackCWD -> ProgramDb -> IO InstalledPackageIndex Source #
Reduced-verbosity version of getInstalledPackages
indexBaseName :: Repo -> FilePath Source #
Get filename base (i.e. without file extension) for index-related files
Secure cabal repositories use a new extended & incremental
01-index.tar
. In order to avoid issues resulting from clobbering
new/old-style index data, we save them locally to different names.
Example: Use indexBaseName repo . "tar.gz"
to compute the FilePath
of the
00-index.tar.gz
/01-index.tar.gz
file.
getInstalledPackagesMonitorFiles :: Verbosity -> Compiler -> Maybe (SymbolicPath CWD ('Dir from)) -> PackageDBStackS from -> ProgramDb -> Platform -> IO [FilePath] #
A set of files (or directories) that can be monitored to detect when there might have been a change in the installed packages.
getSourcePackages :: Verbosity -> RepoContext -> IO SourcePackageDb Source #
Read a repository index from disk, from the local files specified by
a list of Repo
s.
All the SourcePackage
s are marked as having come from the appropriate
Repo
.
This is a higher level wrapper used internally in cabal-install.
getSourcePackagesMonitorFiles :: [Repo] -> [FilePath] Source #
A set of files (or directories) that can be monitored to detect when there might have been a change in the source packages.
data TotalIndexState Source #
Index state of multiple repositories
Instances
getSourcePackagesAtIndexState :: Verbosity -> RepoContext -> Maybe TotalIndexState -> Maybe ActiveRepos -> IO (SourcePackageDb, TotalIndexState, ActiveRepos) Source #
Variant of getSourcePackages
which allows getting the source
packages at a particular IndexState
.
Current choices are either the latest (aka HEAD), or the index as it was at a particular time.
Returns also the total index where repositories' RepoIndexState's are not HEAD. This is used in v2-freeze.
data ActiveRepos Source #
Ordered list of active repositories.
Instances
Parsec ActiveRepos Source # | Note: empty string is not valid
| ||||
Defined in Distribution.Client.IndexUtils.ActiveRepos Methods parsec :: CabalParsing m => m ActiveRepos # | |||||
Pretty ActiveRepos Source # | |||||
Defined in Distribution.Client.IndexUtils.ActiveRepos | |||||
Structured ActiveRepos Source # | |||||
Defined in Distribution.Client.IndexUtils.ActiveRepos | |||||
Generic ActiveRepos Source # | |||||
Defined in Distribution.Client.IndexUtils.ActiveRepos Associated Types
| |||||
Show ActiveRepos Source # | |||||
Defined in Distribution.Client.IndexUtils.ActiveRepos Methods showsPrec :: Int -> ActiveRepos -> ShowS # show :: ActiveRepos -> String # showList :: [ActiveRepos] -> ShowS # | |||||
Binary ActiveRepos Source # | |||||
Defined in Distribution.Client.IndexUtils.ActiveRepos | |||||
NFData ActiveRepos Source # | |||||
Defined in Distribution.Client.IndexUtils.ActiveRepos Methods rnf :: ActiveRepos -> () # | |||||
Eq ActiveRepos Source # | |||||
Defined in Distribution.Client.IndexUtils.ActiveRepos | |||||
type Rep ActiveRepos Source # | |||||
Defined in Distribution.Client.IndexUtils.ActiveRepos type Rep ActiveRepos = D1 ('MetaData "ActiveRepos" "Distribution.Client.IndexUtils.ActiveRepos" "cabal-install-3.16.0.0-5Or0gjSnsvnBIy2HLcA6Z9" 'True) (C1 ('MetaCons "ActiveRepos" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ActiveRepoEntry]))) |
filterSkippedActiveRepos :: ActiveRepos -> ActiveRepos Source #
Note, this does nothing if ActiveRepoRest
is present.
Which index do we mean?
Constructors
RepoIndex RepoContext Repo | The main index for the specified repository |
data RepoIndexState Source #
Specification of the state of a specific repo package index
Constructors
IndexStateHead | Use all available entries |
IndexStateTime !Timestamp | Use all entries that existed at the specified time |
Instances
Parsec RepoIndexState Source # | |||||
Defined in Distribution.Client.IndexUtils.IndexState Methods parsec :: CabalParsing m => m RepoIndexState # | |||||
Pretty RepoIndexState Source # | |||||
Defined in Distribution.Client.IndexUtils.IndexState Methods pretty :: RepoIndexState -> Doc # prettyVersioned :: CabalSpecVersion -> RepoIndexState -> Doc # | |||||
Structured RepoIndexState Source # | |||||
Defined in Distribution.Client.IndexUtils.IndexState | |||||
Generic RepoIndexState Source # | |||||
Defined in Distribution.Client.IndexUtils.IndexState Associated Types
Methods from :: RepoIndexState -> Rep RepoIndexState x # to :: Rep RepoIndexState x -> RepoIndexState # | |||||
Show RepoIndexState Source # | |||||
Defined in Distribution.Client.IndexUtils.IndexState Methods showsPrec :: Int -> RepoIndexState -> ShowS # show :: RepoIndexState -> String # showList :: [RepoIndexState] -> ShowS # | |||||
Binary RepoIndexState Source # | |||||
Defined in Distribution.Client.IndexUtils.IndexState Methods put :: RepoIndexState -> Put # get :: Get RepoIndexState # putList :: [RepoIndexState] -> Put # | |||||
NFData RepoIndexState Source # | |||||
Defined in Distribution.Client.IndexUtils.IndexState Methods rnf :: RepoIndexState -> () # | |||||
Eq RepoIndexState Source # | |||||
Defined in Distribution.Client.IndexUtils.IndexState Methods (==) :: RepoIndexState -> RepoIndexState -> Bool # (/=) :: RepoIndexState -> RepoIndexState -> Bool # | |||||
type Rep RepoIndexState Source # | |||||
Defined in Distribution.Client.IndexUtils.IndexState type Rep RepoIndexState = D1 ('MetaData "RepoIndexState" "Distribution.Client.IndexUtils.IndexState" "cabal-install-3.16.0.0-5Or0gjSnsvnBIy2HLcA6Z9" 'False) (C1 ('MetaCons "IndexStateHead" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "IndexStateTime" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Timestamp))) |
data PackageEntry Source #
An index entry is either a normal package, or a local build tree reference.
Constructors
NormalPackage PackageId GenericPackageDescription ByteString BlockNo | |
BuildTreeRef BuildTreeRefType PackageId GenericPackageDescription FilePath BlockNo |
Instances
Package PackageEntry Source # | |
Defined in Distribution.Client.IndexUtils Methods |
parsePackageIndex :: Verbosity -> ByteString -> [IO (Maybe PackageOrDep)] Source #
Read 00-index.tar.gz
and extract .cabal
and preferred-versions
files
We read the index using read
, which gives us a lazily constructed
TarEntries
. We translate it to a list of entries using tarEntriesList
,
which preserves the lazy nature of TarEntries
, and finally concatMap
a
function over this to translate it to a list of IO actions returning
PackageOrDep
s. We can use lazySequence
to turn this into a list of
PackageOrDep
s, still maintaining the lazy nature of the original tar read.
updateRepoIndexCache :: Verbosity -> Index -> IO () Source #
It is not necessary to call this, as the cache will be updated when the index is read normally. However you can do the work earlier if you like.
writeIndexTimestamp :: Index -> RepoIndexState -> IO () Source #
Write the IndexState
to the filesystem
currentIndexTimestamp :: Verbosity -> Index -> IO Timestamp Source #
Read out the "current" index timestamp, i.e., what timestamp you would use to revert to this version.
Note: this is not the same as readIndexTimestamp
!
This resolves HEAD to the index's isiHeadTime
, i.e.
the index latest known timestamp.
Return NoTimestamp if the index has never been updated.
data BuildTreeRefType Source #
A build tree reference is either a link or a snapshot.
Constructors
SnapshotRef | |
LinkRef |
Instances
Structured BuildTreeRefType Source # | |||||
Defined in Distribution.Client.IndexUtils Methods structure :: Proxy BuildTreeRefType -> Structure # structureHash' :: Tagged BuildTreeRefType MD5 | |||||
Generic BuildTreeRefType Source # | |||||
Defined in Distribution.Client.IndexUtils Associated Types
Methods from :: BuildTreeRefType -> Rep BuildTreeRefType x # to :: Rep BuildTreeRefType x -> BuildTreeRefType # | |||||
Show BuildTreeRefType Source # | |||||
Defined in Distribution.Client.IndexUtils Methods showsPrec :: Int -> BuildTreeRefType -> ShowS # show :: BuildTreeRefType -> String # showList :: [BuildTreeRefType] -> ShowS # | |||||
Binary BuildTreeRefType Source # | |||||
Defined in Distribution.Client.IndexUtils Methods put :: BuildTreeRefType -> Put # get :: Get BuildTreeRefType # putList :: [BuildTreeRefType] -> Put # | |||||
Eq BuildTreeRefType Source # | |||||
Defined in Distribution.Client.IndexUtils Methods (==) :: BuildTreeRefType -> BuildTreeRefType -> Bool # (/=) :: BuildTreeRefType -> BuildTreeRefType -> Bool # | |||||
type Rep BuildTreeRefType Source # | |||||
Defined in Distribution.Client.IndexUtils |
preferred-versions utilities
preferredVersions :: FilePath Source #
Expected name of the 'preferred-versions' file.
Contains special constraints, such as a preferred version of a package or deprecations of certain package versions.
Expected format:
binary > 0.9.0.0 || < 0.9.0.0 text == 1.2.1.0
isPreferredVersions :: FilePath -> Bool Source #
Does the given filename match with the expected name of 'preferred-versions'?
parsePreferredVersionsWarnings :: ByteString -> [Either PreferredVersionsParseError Dependency] Source #
Parse `preferred-versions` file, collecting parse errors that can be shown in error messages.
data PreferredVersionsParseError Source #
Parser error of the `preferred-versions` file.
Constructors
PreferredVersionsParseError | |
Fields
|
Instances
Generic PreferredVersionsParseError Source # | |||||
Defined in Distribution.Client.IndexUtils Associated Types
Methods from :: PreferredVersionsParseError -> Rep PreferredVersionsParseError x # to :: Rep PreferredVersionsParseError x -> PreferredVersionsParseError # | |||||
Read PreferredVersionsParseError Source # | |||||
Show PreferredVersionsParseError Source # | |||||
Defined in Distribution.Client.IndexUtils Methods showsPrec :: Int -> PreferredVersionsParseError -> ShowS # show :: PreferredVersionsParseError -> String # showList :: [PreferredVersionsParseError] -> ShowS # | |||||
Eq PreferredVersionsParseError Source # | |||||
Defined in Distribution.Client.IndexUtils Methods (==) :: PreferredVersionsParseError -> PreferredVersionsParseError -> Bool # (/=) :: PreferredVersionsParseError -> PreferredVersionsParseError -> Bool # | |||||
Ord PreferredVersionsParseError Source # | |||||
Defined in Distribution.Client.IndexUtils Methods compare :: PreferredVersionsParseError -> PreferredVersionsParseError -> Ordering # (<) :: PreferredVersionsParseError -> PreferredVersionsParseError -> Bool # (<=) :: PreferredVersionsParseError -> PreferredVersionsParseError -> Bool # (>) :: PreferredVersionsParseError -> PreferredVersionsParseError -> Bool # (>=) :: PreferredVersionsParseError -> PreferredVersionsParseError -> Bool # max :: PreferredVersionsParseError -> PreferredVersionsParseError -> PreferredVersionsParseError # min :: PreferredVersionsParseError -> PreferredVersionsParseError -> PreferredVersionsParseError # | |||||
type Rep PreferredVersionsParseError Source # | |||||
Defined in Distribution.Client.IndexUtils type Rep PreferredVersionsParseError = D1 ('MetaData "PreferredVersionsParseError" "Distribution.Client.IndexUtils" "cabal-install-3.16.0.0-5Or0gjSnsvnBIy2HLcA6Z9" 'False) (C1 ('MetaCons "PreferredVersionsParseError" 'PrefixI 'True) (S1 ('MetaSel ('Just "preferredVersionsParsecError") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: S1 ('MetaSel ('Just "preferredVersionsOriginalDependency") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String))) |