hackport-0.7.2.1: Hackage and Portage integration tool
Copyright(c) Duncan Coutts 2008
LicenseBSD-like
Maintainerduncan@community.haskell.org
Stabilityprovisional
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Distribution.Client.IndexUtils

Description

Extra utils related to the package indexes.

Synopsis

Documentation

getIndexFileAge :: Repo -> IO Double Source #

Return the age of the index file in days (as a Double).

getInstalledPackages :: Verbosity -> Compiler -> PackageDBStack -> 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 -> PackageDBStack -> ProgramDb -> Platform -> IO [FilePath] #

getSourcePackages :: Verbosity -> RepoContext -> IO SourcePackageDb Source #

Read a repository index from disk, from the local files specified by a list of Repos.

All the SourcePackages 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

Instances details
Eq TotalIndexState Source # 
Instance details

Defined in Distribution.Client.IndexUtils.IndexState

Show TotalIndexState Source # 
Instance details

Defined in Distribution.Client.IndexUtils.IndexState

Generic TotalIndexState Source # 
Instance details

Defined in Distribution.Client.IndexUtils.IndexState

Associated Types

type Rep TotalIndexState :: Type -> Type #

Binary TotalIndexState Source # 
Instance details

Defined in Distribution.Client.IndexUtils.IndexState

NFData TotalIndexState Source # 
Instance details

Defined in Distribution.Client.IndexUtils.IndexState

Methods

rnf :: TotalIndexState -> () #

Structured TotalIndexState Source # 
Instance details

Defined in Distribution.Client.IndexUtils.IndexState

Methods

structure :: Proxy TotalIndexState -> Structure

structureHash' :: Tagged TotalIndexState MD5

Parsec TotalIndexState Source #
>>> simpleParsec "HEAD" :: Maybe TotalIndexState
Just (TIS IndexStateHead (fromList []))
>>> simpleParsec "" :: Maybe TotalIndexState
Nothing
>>> simpleParsec "hackage.haskell.org HEAD" :: Maybe TotalIndexState
Just (TIS IndexStateHead (fromList []))
>>> simpleParsec "2020-02-04T12:34:56Z, hackage.haskell.org HEAD" :: Maybe TotalIndexState
Just (TIS (IndexStateTime (TS 1580819696)) (fromList [(RepoName "hackage.haskell.org",IndexStateHead)]))
>>> simpleParsec "hackage.haskell.org 2020-02-04T12:34:56Z" :: Maybe TotalIndexState
Just (TIS IndexStateHead (fromList [(RepoName "hackage.haskell.org",IndexStateTime (TS 1580819696))]))
Instance details

Defined in Distribution.Client.IndexUtils.IndexState

Methods

parsec :: CabalParsing m => m TotalIndexState

Pretty TotalIndexState Source # 
Instance details

Defined in Distribution.Client.IndexUtils.IndexState

Methods

pretty :: TotalIndexState -> Doc

prettyVersioned :: CabalSpecVersion -> TotalIndexState -> Doc

type Rep TotalIndexState Source # 
Instance details

Defined in Distribution.Client.IndexUtils.IndexState

type Rep TotalIndexState = D1 ('MetaData "TotalIndexState" "Distribution.Client.IndexUtils.IndexState" "hackport-0.7.2.1-1OygFJYGTmY8Q1y3r3WxcM-hackport-external-libs-cabal-install" 'False) (C1 ('MetaCons "TIS" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 RepoIndexState) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map RepoName RepoIndexState))))

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

Instances details
Eq ActiveRepos Source # 
Instance details

Defined in Distribution.Client.IndexUtils.ActiveRepos

Show ActiveRepos Source # 
Instance details

Defined in Distribution.Client.IndexUtils.ActiveRepos

Generic ActiveRepos Source # 
Instance details

Defined in Distribution.Client.IndexUtils.ActiveRepos

Associated Types

type Rep ActiveRepos :: Type -> Type #

Binary ActiveRepos Source # 
Instance details

Defined in Distribution.Client.IndexUtils.ActiveRepos

NFData ActiveRepos Source # 
Instance details

Defined in Distribution.Client.IndexUtils.ActiveRepos

Methods

rnf :: ActiveRepos -> () #

Structured ActiveRepos Source # 
Instance details

Defined in Distribution.Client.IndexUtils.ActiveRepos

Methods

structure :: Proxy ActiveRepos -> Structure

structureHash' :: Tagged ActiveRepos MD5

Parsec ActiveRepos Source #

Note: empty string is not valid ActiveRepos.

>>> simpleParsec "" :: Maybe ActiveRepos
Nothing
>>> simpleParsec ":none" :: Maybe ActiveRepos
Just (ActiveRepos [])
>>> simpleParsec ":rest" :: Maybe ActiveRepos
Just (ActiveRepos [ActiveRepoRest CombineStrategyMerge])
>>> simpleParsec "hackage.haskell.org, :rest, head.hackage:override" :: Maybe ActiveRepos
Just (ActiveRepos [ActiveRepo (RepoName "hackage.haskell.org") CombineStrategyMerge,ActiveRepoRest CombineStrategyMerge,ActiveRepo (RepoName "head.hackage") CombineStrategyOverride])
Instance details

Defined in Distribution.Client.IndexUtils.ActiveRepos

Methods

parsec :: CabalParsing m => m ActiveRepos

Pretty ActiveRepos Source # 
Instance details

Defined in Distribution.Client.IndexUtils.ActiveRepos

Methods

pretty :: ActiveRepos -> Doc

prettyVersioned :: CabalSpecVersion -> ActiveRepos -> Doc

type Rep ActiveRepos Source # 
Instance details

Defined in Distribution.Client.IndexUtils.ActiveRepos

data Index Source #

Which index do we mean?

Constructors

RepoIndex RepoContext Repo

The main index for the specified repository

SandboxIndex FilePath

A sandbox-local repository Argument is the location of the index file

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

Instances details
Eq RepoIndexState Source # 
Instance details

Defined in Distribution.Client.IndexUtils.IndexState

Show RepoIndexState Source # 
Instance details

Defined in Distribution.Client.IndexUtils.IndexState

Generic RepoIndexState Source # 
Instance details

Defined in Distribution.Client.IndexUtils.IndexState

Associated Types

type Rep RepoIndexState :: Type -> Type #

Binary RepoIndexState Source # 
Instance details

Defined in Distribution.Client.IndexUtils.IndexState

NFData RepoIndexState Source # 
Instance details

Defined in Distribution.Client.IndexUtils.IndexState

Methods

rnf :: RepoIndexState -> () #

Structured RepoIndexState Source # 
Instance details

Defined in Distribution.Client.IndexUtils.IndexState

Methods

structure :: Proxy RepoIndexState -> Structure

structureHash' :: Tagged RepoIndexState MD5

Parsec RepoIndexState Source # 
Instance details

Defined in Distribution.Client.IndexUtils.IndexState

Methods

parsec :: CabalParsing m => m RepoIndexState

Pretty RepoIndexState Source # 
Instance details

Defined in Distribution.Client.IndexUtils.IndexState

Methods

pretty :: RepoIndexState -> Doc

prettyVersioned :: CabalSpecVersion -> RepoIndexState -> Doc

type Rep RepoIndexState Source # 
Instance details

Defined in Distribution.Client.IndexUtils.IndexState

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

Instances details
Package PackageEntry Source # 
Instance details

Defined in Distribution.Client.IndexUtils

Methods

packageId :: PackageEntry -> PackageIdentifier

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 PackageOrDeps. We can use lazySequence to turn this into a list of PackageOrDeps, 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 -> RepoContext -> Repo -> IO Timestamp Source #

Read out the "current" index timestamp, i.e., what timestamp you would use to revert to this version

data BuildTreeRefType Source #

A build tree reference is either a link or a snapshot.

Constructors

SnapshotRef 
LinkRef 

Instances

Instances details
Eq BuildTreeRefType Source # 
Instance details

Defined in Distribution.Client.IndexUtils

Show BuildTreeRefType Source # 
Instance details

Defined in Distribution.Client.IndexUtils

Generic BuildTreeRefType Source # 
Instance details

Defined in Distribution.Client.IndexUtils

Associated Types

type Rep BuildTreeRefType :: Type -> Type #

Binary BuildTreeRefType Source # 
Instance details

Defined in Distribution.Client.IndexUtils

Structured BuildTreeRefType Source # 
Instance details

Defined in Distribution.Client.IndexUtils

Methods

structure :: Proxy BuildTreeRefType -> Structure

structureHash' :: Tagged BuildTreeRefType MD5

type Rep BuildTreeRefType Source # 
Instance details

Defined in Distribution.Client.IndexUtils

type Rep BuildTreeRefType = D1 ('MetaData "BuildTreeRefType" "Distribution.Client.IndexUtils" "hackport-0.7.2.1-1OygFJYGTmY8Q1y3r3WxcM-hackport-external-libs-cabal-install" 'False) (C1 ('MetaCons "SnapshotRef" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "LinkRef" 'PrefixI 'False) (U1 :: Type -> Type))