hackage-security-0.6.2.3: Hackage security library
Safe HaskellSafe-Inferred
LanguageHaskell2010

Hackage.Security.Client.Repository

Description

Abstract definition of a Repository

Most clients should only need to import this module if they wish to define their own Repository implementations.

Synopsis

Files

data RemoteFile :: * -> * -> * where Source #

Abstract definition of files we might have to download

RemoteFile is parametrized by the type of the formats that we can accept from the remote repository, as well as with information on whether this file is metadata actual binary content.

NOTE: Haddock lacks GADT support so constructors have only regular comments.

Instances

Instances details
Show (RemoteFile fs typ) Source # 
Instance details

Defined in Hackage.Security.Client.Repository

Methods

showsPrec :: Int -> RemoteFile fs typ -> ShowS #

show :: RemoteFile fs typ -> String #

showList :: [RemoteFile fs typ] -> ShowS #

Pretty (RemoteFile fs typ) Source # 
Instance details

Defined in Hackage.Security.Client.Repository

Methods

pretty :: RemoteFile fs typ -> String Source #

data CachedFile Source #

Files that we might request from the local cache

Constructors

CachedTimestamp

Timestamp metadata (timestamp.json)

CachedRoot

Root metadata (root.json)

CachedSnapshot

Snapshot metadata (snapshot.json)

CachedMirrors

Mirrors list (mirrors.json)

data IndexFile :: * -> * where Source #

Files that we might request from the index

The type index tells us the type of the decoded file, if any. For files for which the library does not support decoding this will be (). NOTE: Clients should NOT rely on this type index being (), or they might break if we add support for parsing additional file formats in the future.

TODO: If we wanted to support legacy Hackage, we should also have a case for the global preferred-versions file. But supporting legacy Hackage will probably require more work anyway..

Instances

Instances details
SomePretty IndexFile Source # 
Instance details

Defined in Hackage.Security.TUF.Layout.Index

SomeShow IndexFile Source # 
Instance details

Defined in Hackage.Security.TUF.Layout.Index

Show (IndexFile dec) Source # 
Instance details

Defined in Hackage.Security.TUF.Layout.Index

Methods

showsPrec :: Int -> IndexFile dec -> ShowS #

show :: IndexFile dec -> String #

showList :: [IndexFile dec] -> ShowS #

Pretty (IndexFile dec) Source # 
Instance details

Defined in Hackage.Security.TUF.Layout.Index

Methods

pretty :: IndexFile dec -> String Source #

remoteFileDefaultFormat :: RemoteFile fs typ -> Some (HasFormat fs) Source #

Default format for each file type

For most file types we don't have a choice; for the index the repository is only required to offer the GZip-compressed format so that is the default.

Repository proper

data Repository down Source #

Repository

This is an abstract representation of a repository. It simply provides a way to download metafiles and target files, without specifying how this is done. For instance, for a local repository this could just be doing a file read, whereas for remote repositories this could be using any kind of HTTP client.

Constructors

DownloadedFile down => Repository 

Fields

  • repGetRemote :: forall fs typ. Throws SomeRemoteError => AttemptNr -> RemoteFile fs typ -> Verify (Some (HasFormat fs), down typ)

    Get a file from the server

    Responsibilies of repGetRemote:

    • Download the file from the repository and make it available at a temporary location
    • Use the provided file length to protect against endless data attacks. (Repositories such as local repositories that are not susceptible to endless data attacks can safely ignore this argument.)
    • Move the file from its temporary location to its permanent location if verification succeeds.

    NOTE: Calls to repGetRemote should _always_ be in the scope of repWithMirror.

  • repGetCached :: CachedFile -> IO (Maybe (Path Absolute))

    Get a cached file (if available)

  • repGetCachedRoot :: IO (Path Absolute)

    Get the cached root

    This is a separate method only because clients must ALWAYS have root information available.

  • repClearCache :: IO ()

    Clear all cached data

    In particular, this should remove the snapshot and the timestamp. It would also be okay, but not required, to delete the index.

  • repWithIndex :: forall a. (Handle -> IO a) -> IO a

    Open the tarball for reading

    This function has this shape so that:

    • We can read multiple files from the tarball without having to open and close the handle each time
    • We can close the handle immediately when done.
  • repGetIndexIdx :: IO TarIndex

    Read the index index

  • repLockCache :: IO () -> IO ()

    Lock the cache (during updates)

  • repWithMirror :: forall a. Maybe [Mirror] -> IO a -> IO a

    Mirror selection

    The purpose of repWithMirror is to scope mirror selection. The idea is that if we have

    repWithMirror mirrorList $
      someCallback

    then the repository may pick a mirror before calling someCallback, catch exceptions thrown by someCallback, and potentially try the callback again with a different mirror.

    The list of mirrors may be Nothing if we haven't yet downloaded the list of mirrors from the repository, or when our cached list of mirrors is invalid. Of course, if we did download it, then the list of mirrors may still be empty. In this case the repository must fall back to its primary download mechanism.

    Mirrors as currently defined (in terms of a "base URL") are inherently a HTTP (or related) concept, so in repository implementations such as the local-repo repWithMirrors is probably just an identity operation (see ignoreMirrors). Conversely, HTTP implementations of repositories may have other, out-of-band information (for example, coming from a cabal config file) that they may use to influence mirror selection.

  • repLog :: LogMessage -> IO ()

    Logging

  • repLayout :: RepoLayout

    Layout of this repository

  • repIndexLayout :: IndexLayout

    Layout of the index

    Since the repository hosts the index, the layout of the index is not independent of the layout of the repository.

  • repDescription :: String

    Description of the repository (used in the show instance)

Instances

Instances details
Show (Repository down) Source # 
Instance details

Defined in Hackage.Security.Client.Repository

Methods

showsPrec :: Int -> Repository down -> ShowS #

show :: Repository down -> String #

showList :: [Repository down] -> ShowS #

newtype AttemptNr Source #

Are we requesting this information because of a previous validation error?

Clients can take advantage of this to tell caches to revalidate files.

Constructors

AttemptNr Int 

data LogMessage Source #

Log messages

We use a RemoteFile rather than a RepoPath here because we might not have a RepoPath for the file that we were trying to download (that is, for example if the server does not provide an uncompressed tarball, it doesn't make much sense to list the path to that non-existing uncompressed tarball).

Constructors

LogRootUpdated

Root information was updated

This message is issued when the root information is updated as part of the normal check for updates procedure. If the root information is updated because of a verification error WarningVerificationError is issued instead.

LogVerificationError VerificationError

A verification error

Verification errors can be temporary, and may be resolved later; hence these are just warnings. (Verification errors that cannot be resolved are thrown as exceptions.)

forall fs typ. LogDownloading (RemoteFile fs typ)

Download a file from a repository

forall fs. LogUpdating (RemoteFile fs Binary)

Incrementally updating a file from a repository

LogSelectedMirror MirrorDescription

Selected a particular mirror

forall fs. LogCannotUpdate (RemoteFile fs Binary) UpdateFailure

Updating a file failed (we will instead download it whole)

LogMirrorFailed MirrorDescription SomeException

We got an exception with a particular mirror (we will try with a different mirror if any are available)

LogLockWait (Path Absolute)

This log event is triggered before invoking a filesystem lock operation that may block for a significant amount of time; once the possibly blocking call completes successfully, LogLockWaitDone will be emitted.

Since: 0.6.0

LogLockWaitDone (Path Absolute)

Denotes completion of the operation that advertised a LogLockWait event

Since: 0.6.0

LogUnlock (Path Absolute)

Denotes the filesystem lock previously acquired (signaled by LogLockWait) has been released.

Since: 0.6.0

Instances

Instances details
Pretty LogMessage Source # 
Instance details

Defined in Hackage.Security.Client.Repository

data UpdateFailure Source #

Records why we are downloading a file rather than updating it.

Constructors

UpdateImpossibleUnsupported

Server does not support incremental downloads

UpdateImpossibleNoLocalCopy

We don't have a local copy of the file to update

UpdateFailedTwice

Update failed twice

If we attempt an incremental update the first time, and it fails, we let it go round the loop, update local security information, and try again. But if an incremental update then fails _again_, we instead attempt a regular download.

UpdateFailed SomeException

Update failed (for example: perhaps the local file got corrupted)

Instances

Instances details
Pretty UpdateFailure Source # 
Instance details

Defined in Hackage.Security.Client.Repository

data SomeRemoteError :: * where Source #

Repository-specific exceptions

For instance, for repositories using HTTP this might correspond to a 404; for local repositories this might correspond to file-not-found, etc.

Constructors

SomeRemoteError :: Exception e => e -> SomeRemoteError 

Downloaded files

class DownloadedFile (down :: * -> *) where Source #

Methods

downloadedVerify :: down a -> Trusted FileInfo -> IO Bool Source #

Verify a download file

downloadedRead :: down Metadata -> IO ByteString Source #

Read the file we just downloaded into memory

We never read binary data, only metadata.

downloadedCopyTo :: down a -> Path Absolute -> IO () Source #

Copy a downloaded file to its destination

Helpers

mirrorsUnsupported :: Maybe [Mirror] -> IO a -> IO a Source #

Helper function to implement repWithMirrors.

Paths

Utility

data IsCached :: * -> * where Source #

Is a particular remote file cached?

Instances

Instances details
Show (IsCached typ) Source # 
Instance details

Defined in Hackage.Security.Client.Repository

Methods

showsPrec :: Int -> IsCached typ -> ShowS #

show :: IsCached typ -> String #

showList :: [IsCached typ] -> ShowS #

Eq (IsCached typ) Source # 
Instance details

Defined in Hackage.Security.Client.Repository

Methods

(==) :: IsCached typ -> IsCached typ -> Bool #

(/=) :: IsCached typ -> IsCached typ -> Bool #

mustCache :: RemoteFile fs typ -> IsCached typ Source #

Which remote files should we cache locally?