Safe Haskell | None |
---|---|
Language | Haskell2010 |
Hackage.Security.Client
Contents
- Checking for updates
- Downloading targets
- Access to the Hackage index
- Bootstrapping
- Re-exports
- Types
- Utility
- Cache layout
- Repository layout
- Repository layout
- TUF types
- Repository
- Index
- Cache
- Datatypes
- TUF types
- Construction and verification
- JSON aids
- Avoid interpreting signatures
- TUF types
- Key types
- Types abstracting over key types
- Key types in isolation
- Hiding key types
- Operations on keys
- Key IDs
- Signing
- Exceptions
Description
Main entry point into the Hackage Security framework for clients
- checkForUpdates :: (Throws VerificationError, Throws SomeRemoteError) => Repository down -> Maybe UTCTime -> IO HasUpdates
- data HasUpdates
- downloadPackage :: (Throws SomeRemoteError, Throws VerificationError, Throws InvalidPackageException) => Repository down -> PackageIdentifier -> Path Absolute -> IO ()
- downloadPackage' :: (Throws SomeRemoteError, Throws VerificationError, Throws InvalidPackageException) => Repository down -> PackageIdentifier -> FilePath -> IO ()
- data Directory = Directory {
- directoryFirst :: DirectoryEntry
- directoryNext :: DirectoryEntry
- directoryLookup :: forall dec. IndexFile dec -> Maybe DirectoryEntry
- directoryEntries :: [(DirectoryEntry, IndexPath, Maybe (Some IndexFile))]
- newtype DirectoryEntry = DirectoryEntry {}
- getDirectory :: Repository down -> IO Directory
- data IndexFile :: * -> * where
- IndexPkgMetadata :: PackageIdentifier -> IndexFile (Signed Targets)
- IndexPkgCabal :: PackageIdentifier -> IndexFile ()
- IndexPkgPrefs :: PackageName -> IndexFile ()
- data IndexEntry dec = IndexEntry {}
- data IndexCallbacks = IndexCallbacks {
- indexLookupEntry :: DirectoryEntry -> IO (Some IndexEntry, Maybe DirectoryEntry)
- indexLookupFile :: forall dec. IndexFile dec -> IO (Maybe (IndexEntry dec))
- indexLookupFileEntry :: forall dec. DirectoryEntry -> IndexFile dec -> IO (IndexEntry dec)
- indexLookupCabal :: Throws InvalidPackageException => PackageIdentifier -> IO (Trusted ByteString)
- indexLookupMetadata :: Throws InvalidPackageException => PackageIdentifier -> IO (Trusted Targets)
- indexLookupFileInfo :: (Throws InvalidPackageException, Throws VerificationError) => PackageIdentifier -> IO (Trusted FileInfo)
- indexLookupHash :: (Throws InvalidPackageException, Throws VerificationError) => PackageIdentifier -> IO (Trusted Hash)
- indexDirectory :: Directory
- withIndex :: Repository down -> (IndexCallbacks -> IO a) -> IO a
- requiresBootstrap :: Repository down -> IO Bool
- bootstrap :: (Throws SomeRemoteError, Throws VerificationError) => Repository down -> [KeyId] -> KeyThreshold -> IO ()
- newtype FileLength = FileLength {
- fileLength :: Int54
- newtype Hash = Hash String
- newtype KeyThreshold = KeyThreshold Int54
- data FileInfo = FileInfo {}
- data HashFn
- newtype Hash = Hash String
- fileInfo :: ByteString -> FileInfo
- computeFileInfo :: FsRoot root => Path root -> IO FileInfo
- compareTrustedFileInfo :: FileInfo -> FileInfo -> Bool
- knownFileInfoEqual :: FileInfo -> FileInfo -> Bool
- fileInfoSHA256 :: FileInfo -> Maybe Hash
- data Int54
- module Hackage.Security.TUF.FileMap
- class HasHeader a where
- fileExpires :: Lens' a FileExpires
- fileVersion :: Lens' a FileVersion
- newtype FileVersion = FileVersion Int54
- newtype FileExpires = FileExpires (Maybe UTCTime)
- data Header = Header {}
- expiresInDays :: UTCTime -> Integer -> FileExpires
- expiresNever :: FileExpires
- isExpired :: UTCTime -> FileExpires -> Bool
- versionInitial :: FileVersion
- versionIncrement :: FileVersion -> FileVersion
- data CacheLayout = CacheLayout {}
- cabalCacheLayout :: CacheLayout
- data IndexLayout = IndexLayout {
- indexFileToPath :: forall dec. IndexFile dec -> IndexPath
- indexFileFromPath :: IndexPath -> Maybe (Some IndexFile)
- data IndexFile :: * -> * where
- IndexPkgMetadata :: PackageIdentifier -> IndexFile (Signed Targets)
- IndexPkgCabal :: PackageIdentifier -> IndexFile ()
- IndexPkgPrefs :: PackageName -> IndexFile ()
- hackageIndexLayout :: IndexLayout
- indexLayoutPkgMetadata :: IndexLayout -> PackageIdentifier -> IndexPath
- indexLayoutPkgCabal :: IndexLayout -> PackageIdentifier -> IndexPath
- indexLayoutPkgPrefs :: IndexLayout -> PackageName -> IndexPath
- data RepoLayout = RepoLayout {}
- hackageRepoLayout :: RepoLayout
- cabalLocalRepoLayout :: RepoLayout
- data Mirrors = Mirrors {}
- data Mirror = Mirror {}
- data MirrorContent = MirrorFull
- type MirrorDescription = String
- describeMirror :: Mirror -> MirrorDescription
- data RepoRoot
- type RepoPath = Path RepoRoot
- anchorRepoPathLocally :: Path root -> RepoPath -> Path root
- anchorRepoPathRemotely :: Path Web -> RepoPath -> Path Web
- data IndexRoot
- type IndexPath = Path IndexRoot
- data CacheRoot
- type CachePath = Path CacheRoot
- anchorCachePath :: Path root -> CachePath -> Path root
- data Root = Root {}
- data RootRoles = RootRoles {}
- data RoleSpec a = RoleSpec {}
- data Signed a = Signed {
- signed :: a
- signatures :: Signatures
- newtype Signatures = Signatures [Signature]
- data Signature = Signature {}
- unsigned :: a -> Signed a
- withSignatures :: ToJSON WriteJSON a => RepoLayout -> [Some Key] -> a -> Signed a
- withSignatures' :: ToJSON Identity a => [Some Key] -> a -> Signed a
- signRendered :: [Some Key] -> ByteString -> Signatures
- verifySignature :: ByteString -> Signature -> Bool
- signedFromJSON :: (MonadKeys m, FromJSON m a) => JSValue -> m (Signed a)
- verifySignatures :: JSValue -> Signatures -> Bool
- data UninterpretedSignatures a = UninterpretedSignatures {}
- data PreSignature = PreSignature {}
- fromPreSignature :: MonadKeys m => PreSignature -> m Signature
- fromPreSignatures :: MonadKeys m => [PreSignature] -> m Signatures
- toPreSignature :: Signature -> PreSignature
- toPreSignatures :: Signatures -> [PreSignature]
- data Snapshot = Snapshot {}
- data Targets = Targets {}
- data Delegations = Delegations {}
- data DelegationSpec = DelegationSpec {}
- data Delegation = forall a . Delegation (Pattern a) (Replacement a)
- targetsLookup :: TargetPath -> Targets -> Maybe FileInfo
- data Timestamp = Timestamp {}
- data Ed25519
- data Key a where
- KeyEd25519 :: PublicKey -> SecretKey -> Key Ed25519
- data PublicKey a where
- data PrivateKey a where
- data KeyType typ where
- somePublicKey :: Some Key -> Some PublicKey
- somePublicKeyType :: Some PublicKey -> Some KeyType
- someKeyId :: HasKeyId key => Some key -> KeyId
- publicKey :: Key a -> PublicKey a
- privateKey :: Key a -> PrivateKey a
- createKey :: KeyType key -> IO (Key key)
- createKey' :: KeyType key -> IO (Some Key)
- newtype KeyId = KeyId {}
- class HasKeyId key where
- sign :: PrivateKey typ -> ByteString -> ByteString
- verify :: PublicKey typ -> ByteString -> ByteString -> Bool
- trusted :: Trusted a -> a
- data Repository down
- class DownloadedFile down where
- downloadedVerify :: down a -> Trusted FileInfo -> IO Bool
- downloadedRead :: down Metadata -> IO ByteString
- downloadedCopyTo :: down a -> Path Absolute -> IO ()
- data SomeRemoteError :: * where
- SomeRemoteError :: Exception e => e -> SomeRemoteError
- data LogMessage
- = LogRootUpdated
- | LogVerificationError VerificationError
- | forall fs typ . LogDownloading (RemoteFile fs typ)
- | forall fs . LogUpdating (RemoteFile fs Binary)
- | LogSelectedMirror MirrorDescription
- | forall fs . LogCannotUpdate (RemoteFile fs Binary) UpdateFailure
- | LogMirrorFailed MirrorDescription SomeException
- uncheckClientErrors :: ((Throws VerificationError, Throws SomeRemoteError, Throws InvalidPackageException) => IO a) -> IO a
- data VerificationError
- = VerificationErrorSignatures TargetPath
- | VerificationErrorExpired TargetPath
- | VerificationErrorVersion TargetPath
- | VerificationErrorFileInfo TargetPath
- | VerificationErrorUnknownTarget TargetPath
- | VerificationErrorMissingSHA256 TargetPath
- | VerificationErrorDeserialization TargetPath DeserializationError
- | VerificationErrorLoop VerificationHistory
- type VerificationHistory = [Either RootUpdated VerificationError]
- data RootUpdated = RootUpdated
- data InvalidPackageException = InvalidPackageException PackageIdentifier
- data InvalidFileInIndex = forall dec . InvalidFileInIndex {}
- data LocalFileCorrupted = LocalFileCorrupted DeserializationError
Checking for updates
Arguments
:: (Throws VerificationError, Throws SomeRemoteError) | |
=> Repository down | |
-> Maybe UTCTime | To check expiry times against (if using) |
-> IO HasUpdates |
Generic logic for checking if there are updates
This implements the logic described in Section 5.1, "The client application", of the TUF spec. It checks which of the server metadata has changed, and downloads all changed metadata to the local cache. (Metadata here refers both to the TUF security metadata as well as the Hackage packge index.)
You should pass Nothing
for the UTCTime _only_ under exceptional
circumstances (such as when the main server is down for longer than the
expiry dates used in the timestamp files on mirrors).
Downloading targets
Arguments
:: (Throws SomeRemoteError, Throws VerificationError, Throws InvalidPackageException) | |
=> Repository down | Repository |
-> PackageIdentifier | Package to download |
-> Path Absolute | Destination (see also |
-> IO () |
Download a package
Arguments
:: (Throws SomeRemoteError, Throws VerificationError, Throws InvalidPackageException) | |
=> Repository down | Repository |
-> PackageIdentifier | Package to download |
-> FilePath | Destination |
-> IO () |
Variation on downloadPackage
that takes a FilePath instead.
Access to the Hackage index
Index directory
Constructors
Directory | |
Fields
|
newtype DirectoryEntry Source
Entry into the Hackage index.
Constructors
DirectoryEntry | |
Fields
|
getDirectory :: Repository down -> IO Directory Source
Read the Hackage index directory
Should only be called after checkForUpdates
.
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..
Constructors
IndexPkgMetadata :: PackageIdentifier -> IndexFile (Signed Targets) | |
IndexPkgCabal :: PackageIdentifier -> IndexFile () | |
IndexPkgPrefs :: PackageName -> IndexFile () |
data IndexEntry dec Source
Entry from the Hackage index; see withIndex
.
Constructors
IndexEntry | |
Fields
|
data IndexCallbacks Source
Various operations that we can perform on the index once its open
Note that IndexEntry
contains a fields both for the raw file contents and
the parsed file contents; clients can choose which to use.
In principle these callbacks will do verification (once we have implemented author signing). Right now they don't need to do that, because the index as a whole will have been verified.
Constructors
IndexCallbacks | |
Fields
|
withIndex :: Repository down -> (IndexCallbacks -> IO a) -> IO a Source
Look up entries in the Hackage index
This is in withFile
style so that clients can efficiently look up multiple
files from the index.
Should only be called after checkForUpdates
.
Bootstrapping
requiresBootstrap :: Repository down -> IO Bool Source
Check if we need to bootstrap (i.e., if we have root info)
bootstrap :: (Throws SomeRemoteError, Throws VerificationError) => Repository down -> [KeyId] -> KeyThreshold -> IO () Source
Bootstrap the chain of trust
New clients might need to obtain a copy of the root metadata. This however represents a chicken-and-egg problem: how can we verify the root metadata we downloaded? The only possibility is to be provided with a set of an out-of-band set of root keys and an appropriate threshold.
Clients who provide a threshold of 0 can do an initial "unsafe" update of the root information, if they wish.
The downloaded root information will _only_ be verified against the
provided keys, and _not_ against previously downloaded root info (if any).
It is the responsibility of the client to call bootstrap
only when this
is the desired behaviour.
Re-exports
Types
newtype FileLength Source
File length
Having verified file length information means we can protect against endless data attacks and similar.
Constructors
FileLength | |
Fields
|
Instances
File hash
newtype KeyThreshold Source
Key threshold
The key threshold is the minimum number of keys a document must be signed
with. Key thresholds are specified in RoleSpec
or DelegationsSpec
.
Constructors
KeyThreshold Int54 |
Instances
File information
This intentionally does not have an Eq
instance; see knownFileInfoEqual
and verifyFileInfo
instead.
NOTE: Throughout we compute file information always over the raw bytes.
For example, when timestamp.json
lists the hash of snapshot.json
, this
hash is computed over the actual snapshot.json
file (as opposed to the
canonical form of the embedded JSON). This brings it in line with the hash
computed over target files, where that is the only choice available.
Constructors
FileInfo | |
Fields |
Constructors
HashFnSHA256 | |
HashFnMD5 |
File hash
Utility
fileInfo :: ByteString -> FileInfo Source
Compute FileInfo
TODO: Currently this will load the entire input bytestring into memory. We need to make this incremental, by computing the length and all hashes in a single traversal over the input.
knownFileInfoEqual :: FileInfo -> FileInfo -> Bool Source
Re-exports
54-bit integer values
JavaScript can only safely represent numbers between -(2^53 - 1)
and
2^53 - 1
.
TODO: Although we introduce the type here, we don't actually do any bounds
checking and just inherit all type class instance from Int64. We should
probably define fromInteger
to do bounds checking, give different instances
for type classes such as Bounded
and FiniteBits
, etc.
Instances
module Hackage.Security.TUF.FileMap
class HasHeader a where Source
Methods
fileExpires :: Lens' a FileExpires Source
File expiry date
fileVersion :: Lens' a FileVersion Source
File version (monotonically increasing counter)
newtype FileVersion Source
File version
The file version is a flat integer which must monotonically increase on every file update.
Show
and Read
instance are defined in terms of the underlying Int
(this is use for example by hackage during the backup process).
Constructors
FileVersion Int54 |
Instances
newtype FileExpires Source
File expiry date
A Nothing
value here means no expiry. That makes it possible to set some
files to never expire. (Note that not having the Maybe in the type here still
allows that, because you could set an expiry date 2000 years into the future.
By having the Maybe here we avoid the _need_ for such encoding issues.)
Constructors
FileExpires (Maybe UTCTime) |
Instances
Occassionally it is useful to read only a header from a file.
HeaderOnly
intentionally only has a FromJSON
instance (no ToJSON
).
Constructors
Header | |
Fields |
Utility
expiresInDays :: UTCTime -> Integer -> FileExpires Source
isExpired :: UTCTime -> FileExpires -> Bool Source
Cache layout
data CacheLayout Source
Location of the various files we cache
Although the generic TUF algorithms do not care how we organize the cache,
we nonetheless specity this here because as long as there are tools which
access files in the cache directly we need to define the cache layout.
See also comments for defaultCacheLayout
.
Constructors
CacheLayout | |
Fields
|
cabalCacheLayout :: CacheLayout Source
The cache layout cabal-install uses
We cache the index as cache/00-index.tar
; this is important because
`cabal-install` expects to find it there (and does not currently go through
the hackage-security library to get files from the index).
Repository layout
data IndexLayout Source
Layout of the files within the index tarball
Constructors
IndexLayout | |
Fields
|
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..
Constructors
IndexPkgMetadata :: PackageIdentifier -> IndexFile (Signed Targets) | |
IndexPkgCabal :: PackageIdentifier -> IndexFile () | |
IndexPkgPrefs :: PackageName -> IndexFile () |
hackageIndexLayout :: IndexLayout Source
The layout of the index as maintained on Hackage
Utility
Repository layout
data RepoLayout Source
Layout of a repository
Constructors
RepoLayout | |
Fields
|
hackageRepoLayout :: RepoLayout Source
The layout used on Hackage
cabalLocalRepoLayout :: RepoLayout Source
Layout used by cabal for ("legacy") local repos
Obviously, such repos do not normally contain any of the TUF files, so their location is more or less arbitrary here.
TUF types
Constructors
Mirrors | |
Fields |
Definition of a mirror
NOTE: Unlike the TUF specification, we require that all mirrors must have
the same format. That is, we omit metapath
and targetspath
.
Constructors
Mirror | |
Fields |
data MirrorContent Source
Full versus partial mirrors
The TUF spec explicitly allows for partial mirrors, with the mirrors file specifying (through patterns) what is available from partial mirrors.
For now we only support full mirrors; if we wanted to add partial mirrors,
we would add a second MirrorPartial
constructor here with arguments
corresponding to TUF's metacontent
and targetscontent
fields.
Constructors
MirrorFull |
Instances
Utility
type MirrorDescription = String Source
describeMirror :: Mirror -> MirrorDescription Source
Give a human-readable description of a particular mirror
(for use in error messages)
Repository
The root of the repository
Repository roots can be anchored at a remote URL or a local directory.
Note that even for remote repos RepoRoot
is (potentially) different from
Web
-- for a repository located at, say, http://hackage.haskell.org
they happen to coincide, but for one location at
http://example.com/some/subdirectory
they do not.
anchorRepoPathLocally :: Path root -> RepoPath -> Path root Source
Index
Cache
anchorCachePath :: Path root -> CachePath -> Path root Source
Anchor a cache path to the location of the cache
Datatypes
The root metadata
NOTE: We must have the invariant that ALL keys (apart from delegation keys)
must be listed in rootKeys
. (Delegation keys satisfy a similar invariant,
see Targets.)
Constructors
Root | |
Fields
|
Constructors
RootRoles | |
Role specification
The phantom type indicates what kind of type this role is meant to verify.
Constructors
RoleSpec | |
Fields |
TUF types
Constructors
Signed | |
Fields
|
Instances
MonadKeys m => FromJSON m (Signed Mirrors) Source | |
(MonadKeys m, MonadReader RepoLayout m) => FromJSON m (Signed Snapshot) Source | |
(MonadKeys m, MonadReader RepoLayout m) => FromJSON m (Signed Timestamp) Source | |
MonadKeys m => FromJSON m (Signed Targets) Source | |
MonadKeys m => FromJSON m (Signed Root) Source | We give an instance for Signed Root rather than Root because the key environment from the root data is necessary to resolve the explicit sharing in the signatures. |
(Monad m, ToJSON m a) => ToJSON m (Signed a) Source |
newtype Signatures Source
A list of signatures
Invariant: each signature must be made with a different key.
We enforce this invariant for incoming untrusted data (fromPreSignatures
)
but not for lists of signatures that we create in code.
Constructors
Signatures [Signature] |
Instances
MonadKeys m => FromJSON m Signatures Source | |
Monad m => ToJSON m Signatures Source |
Constructors
Signature | |
Fields |
Construction and verification
withSignatures :: ToJSON WriteJSON a => RepoLayout -> [Some Key] -> a -> Signed a Source
Sign a document
withSignatures' :: ToJSON Identity a => [Some Key] -> a -> Signed a Source
Variation on withSignatures
that doesn't need the repo layout
signRendered :: [Some Key] -> ByteString -> Signatures Source
Construct signatures for already rendered value
verifySignature :: ByteString -> Signature -> Bool Source
JSON aids
signedFromJSON :: (MonadKeys m, FromJSON m a) => JSValue -> m (Signed a) Source
General FromJSON instance for signed datatypes
We don't give a general FromJSON instance for Signed because for some datatypes we need to do something special (datatypes where we need to read key environments); for instance, see the "Signed Root" instance.
verifySignatures :: JSValue -> Signatures -> Bool Source
Signature verification
NOTES: 1. By definition, the signature must be verified against the canonical JSON format. This means we _must_ parse and then pretty print (as we do here) because the document as stored may or may not be in canonical format. 2. However, it is important that we NOT translate from the JSValue to whatever internal datatype we are using and then back to JSValue, because that may not roundtrip: we must allow for additional fields in the JSValue that we ignore (and would therefore lose when we attempt to roundtrip). 3. We verify that all signatures are valid, but we cannot verify (here) that these signatures are signed with the right key, or that we have a sufficient number of signatures. This will be the responsibility of the calling code.
Avoid interpreting signatures
data UninterpretedSignatures a Source
File with uninterpreted signatures
Sometimes we want to be able to read a file without interpreting the signatures (that is, resolving the key IDs) or doing any kind of checks on them. One advantage of this is that this allows us to read many file types without any key environment at all, which is sometimes useful.
Constructors
UninterpretedSignatures | |
Fields |
Instances
(ReportSchemaErrors m, FromJSON m a) => FromJSON m (UninterpretedSignatures a) Source | |
(Monad m, ToJSON m a) => ToJSON m (UninterpretedSignatures a) Source | |
Show a => Show (UninterpretedSignatures a) Source |
data PreSignature Source
A signature with a key ID (rather than an actual key)
This corresponds precisely to the TUF representation of a signature.
Constructors
PreSignature | |
Fields |
Instances
Show PreSignature Source | |
ReportSchemaErrors m => FromJSON m PreSignature Source | |
Monad m => ToJSON m PreSignature Source |
Utility
fromPreSignature :: MonadKeys m => PreSignature -> m Signature Source
Convert a pre-signature to a signature
Verifies that the key type matches the advertised method.
fromPreSignatures :: MonadKeys m => [PreSignature] -> m Signatures Source
Convert a list of PreSignature
s to a list of Signature
s
This verifies the invariant that all signatures are made with different keys. We do this on the presignatures rather than the signatures so that we can do the check on key IDs, rather than keys (the latter don't have an Ord instance).
toPreSignature :: Signature -> PreSignature Source
Convert signature to pre-signature
toPreSignatures :: Signatures -> [PreSignature] Source
Convert list of pre-signatures to a list of signatures
Constructors
Snapshot | |
Fields
|
Instances
HasHeader Snapshot Source | |
VerifyRole Snapshot Source | |
(MonadReader RepoLayout m, MonadError DeserializationError m, ReportSchemaErrors m) => FromJSON m Snapshot Source | |
MonadReader RepoLayout m => ToJSON m Snapshot Source | |
(MonadKeys m, MonadReader RepoLayout m) => FromJSON m (Signed Snapshot) Source |
TUF types
Target metadata
Most target files do not need expiry dates because they are not subject to change (and hence attacks like freeze attacks are not a concern).
Constructors
Targets | |
data Delegations Source
Delegations
Much like the Root datatype, this must have an invariant that ALL used keys
(apart from the global keys, which are in the root key environment) must
be listed in delegationsKeys
.
Constructors
Delegations | |
Fields |
Instances
Show Delegations Source | |
MonadKeys m => FromJSON m Delegations Source | |
Monad m => ToJSON m Delegations Source |
data DelegationSpec Source
Delegation specification
NOTE: This is a close analogue of RoleSpec
.
Constructors
DelegationSpec | |
Fields |
Instances
Show DelegationSpec Source | |
MonadKeys m => FromJSON m DelegationSpec Source | |
Monad m => ToJSON m DelegationSpec Source |
data Delegation Source
A delegation
A delegation is a pair of a pattern and a replacement.
See match
for an example.
Constructors
forall a . Delegation (Pattern a) (Replacement a) |
Instances
Util
targetsLookup :: TargetPath -> Targets -> Maybe FileInfo Source
Constructors
Timestamp | |
Instances
HasHeader Timestamp Source | |
VerifyRole Timestamp Source | |
(MonadReader RepoLayout m, MonadError DeserializationError m, ReportSchemaErrors m) => FromJSON m Timestamp Source | |
MonadReader RepoLayout m => ToJSON m Timestamp Source | |
(MonadKeys m, MonadReader RepoLayout m) => FromJSON m (Signed Timestamp) Source |
Key types
Types abstracting over key types
Constructors
KeyEd25519 :: PublicKey -> SecretKey -> Key Ed25519 |
Constructors
PublicKeyEd25519 :: PublicKey -> PublicKey Ed25519 |
data PrivateKey a where Source
Constructors
PrivateKeyEd25519 :: SecretKey -> PrivateKey Ed25519 |
Instances
SomeShow PrivateKey Source | |
SomeEq PrivateKey Source | |
Eq (PrivateKey typ) Source | |
Show (PrivateKey typ) Source |
Key types in isolation
Constructors
KeyTypeEd25519 :: KeyType Ed25519 |
Hiding key types
Operations on keys
privateKey :: Key a -> PrivateKey a Source
Key IDs
The key ID of a key, by definition, is the hexdigest of the SHA-256 hash of the canonical JSON form of the key where the private object key is excluded.
NOTE: The FromJSON and ToJSON instances for KeyId are ntentially omitted. Use writeKeyAsId instead.
Constructors
KeyId | |
Fields |
Signing
sign :: PrivateKey typ -> ByteString -> ByteString Source
Sign a bytestring and return the signature
TODO: It is unfortunate that we have to convert to a strict bytestring for ed25519
verify :: PublicKey typ -> ByteString -> ByteString -> Bool Source
We only a few bits from .Repository
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.
Instances
Show (Repository down) Source |
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
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 |
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) |
Instances
Exceptions
uncheckClientErrors :: ((Throws VerificationError, Throws SomeRemoteError, Throws InvalidPackageException) => IO a) -> IO a Source
Re-throw all exceptions thrown by the client API as unchecked exceptions
data VerificationError Source
Errors thrown during role validation
Constructors
VerificationErrorSignatures TargetPath | Not enough signatures signed with the appropriate keys |
VerificationErrorExpired TargetPath | The file is expired |
VerificationErrorVersion TargetPath | The file version is less than the previous version |
VerificationErrorFileInfo TargetPath | File information mismatch |
VerificationErrorUnknownTarget TargetPath | We tried to lookup file information about a particular target file,
but the information wasn't in the corresponding |
VerificationErrorMissingSHA256 TargetPath | The metadata for the specified target is missing a SHA256 |
VerificationErrorDeserialization TargetPath DeserializationError | Some verification errors materialize as deserialization errors For example: if we try to deserialize a timestamp file but the timestamp
key has been rolled over, deserialization of the file will fail with
|
VerificationErrorLoop VerificationHistory | The spec stipulates that if a verification error occurs during the check for updates, we must download new root information and start over. However, we limit how often we attempt this. We record all verification errors that occurred before we gave up. |
data RootUpdated Source
Root metadata updated (as part of the normal update process)
Constructors
RootUpdated |
data InvalidPackageException Source
Constructors
InvalidPackageException PackageIdentifier |
data InvalidFileInIndex Source
Constructors
forall dec . InvalidFileInIndex | |