Safe Haskell | None |
---|---|
Language | Haskell2010 |
Abstract definition of a Repository
Most clients should only need to import this module if they wish to define their own Repository implementations.
- data Metadata
- data Binary
- data RemoteFile :: * -> * -> * where
- RemoteTimestamp :: RemoteFile (FormatUn :- ()) Metadata
- RemoteRoot :: Maybe (Trusted FileInfo) -> RemoteFile (FormatUn :- ()) Metadata
- RemoteSnapshot :: Trusted FileInfo -> RemoteFile (FormatUn :- ()) Metadata
- RemoteMirrors :: Trusted FileInfo -> RemoteFile (FormatUn :- ()) Metadata
- RemoteIndex :: HasFormat fs FormatGz -> Formats fs (Trusted FileInfo) -> RemoteFile fs Binary
- RemotePkgTarGz :: PackageIdentifier -> Trusted FileInfo -> RemoteFile (FormatGz :- ()) Binary
- data CachedFile
- data IndexFile :: * -> * where
- IndexPkgMetadata :: PackageIdentifier -> IndexFile (Signed Targets)
- IndexPkgCabal :: PackageIdentifier -> IndexFile ()
- IndexPkgPrefs :: PackageName -> IndexFile ()
- remoteFileDefaultFormat :: RemoteFile fs typ -> Some (HasFormat fs)
- remoteFileDefaultInfo :: RemoteFile fs typ -> Maybe (Trusted FileInfo)
- data Repository down = DownloadedFile down => Repository {
- repGetRemote :: forall fs typ. Throws SomeRemoteError => AttemptNr -> RemoteFile fs typ -> Verify (Some (HasFormat fs), down typ)
- repGetCached :: CachedFile -> IO (Maybe (Path Absolute))
- repGetCachedRoot :: IO (Path Absolute)
- repClearCache :: IO ()
- repWithIndex :: forall a. (Handle -> IO a) -> IO a
- repGetIndexIdx :: IO TarIndex
- repLockCache :: IO () -> IO ()
- repWithMirror :: forall a. Maybe [Mirror] -> IO a -> IO a
- repLog :: LogMessage -> IO ()
- repLayout :: RepoLayout
- repIndexLayout :: IndexLayout
- repDescription :: String
- newtype AttemptNr = AttemptNr Int
- data LogMessage
- data UpdateFailure
- data SomeRemoteError :: * where
- SomeRemoteError :: Exception e => e -> SomeRemoteError
- class DownloadedFile (down :: * -> *) where
- mirrorsUnsupported :: Maybe [Mirror] -> IO a -> IO a
- remoteRepoPath :: RepoLayout -> RemoteFile fs typ -> Formats fs RepoPath
- remoteRepoPath' :: RepoLayout -> RemoteFile fs typ -> HasFormat fs f -> RepoPath
- data IsCached :: * -> * where
- mustCache :: RemoteFile fs typ -> IsCached typ
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.
RemoteTimestamp :: RemoteFile (FormatUn :- ()) Metadata | |
RemoteRoot :: Maybe (Trusted FileInfo) -> RemoteFile (FormatUn :- ()) Metadata | |
RemoteSnapshot :: Trusted FileInfo -> RemoteFile (FormatUn :- ()) Metadata | |
RemoteMirrors :: Trusted FileInfo -> RemoteFile (FormatUn :- ()) Metadata | |
RemoteIndex :: HasFormat fs FormatGz -> Formats fs (Trusted FileInfo) -> RemoteFile fs Binary | |
RemotePkgTarGz :: PackageIdentifier -> Trusted FileInfo -> RemoteFile (FormatGz :- ()) Binary |
Show (RemoteFile fs typ) Source # | |
Pretty (RemoteFile fs typ) Source # | |
data CachedFile Source #
Files that we might request from the local cache
CachedTimestamp | Timestamp metadata ( |
CachedRoot | Root metadata ( |
CachedSnapshot | Snapshot metadata ( |
CachedMirrors | Mirrors list ( |
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..
IndexPkgMetadata :: PackageIdentifier -> IndexFile (Signed Targets) | |
IndexPkgCabal :: PackageIdentifier -> IndexFile () | |
IndexPkgPrefs :: PackageName -> IndexFile () |
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.
remoteFileDefaultInfo :: RemoteFile fs typ -> Maybe (Trusted FileInfo) Source #
Default file info (see also remoteFileDefaultFormat
)
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.
DownloadedFile down => Repository | |
|
Show (Repository down) Source # | |
Are we requesting this information because of a previous validation error?
Clients can take advantage of this to tell caches to revalidate files.
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).
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.) |
LogDownloading (RemoteFile fs typ) | Download a file from a repository |
LogUpdating (RemoteFile fs Binary) | Incrementally updating a file from a repository |
LogSelectedMirror MirrorDescription | Selected a particular mirror |
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) |
data UpdateFailure Source #
Records why we are downloading a file rather than updating it.
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) |
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.
SomeRemoteError :: Exception e => e -> SomeRemoteError |
Downloaded files
class DownloadedFile (down :: * -> *) where Source #
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
remoteRepoPath :: RepoLayout -> RemoteFile fs typ -> Formats fs RepoPath Source #
remoteRepoPath' :: RepoLayout -> RemoteFile fs typ -> HasFormat fs f -> RepoPath Source #
Utility
data IsCached :: * -> * where Source #
Is a particular remote file cached?
CacheAs :: CachedFile -> IsCached Metadata | |
DontCache :: IsCached Binary | |
CacheIndex :: IsCached Binary |
mustCache :: RemoteFile fs typ -> IsCached typ Source #
Which remote files should we cache locally?