hackage-security-0.3.0.0: Hackage security library

Safe HaskellNone
LanguageHaskell2010

Hackage.Security.Server

Contents

Description

Main entry point into the Hackage Security framework for clients

Synopsis

Re-exports

Key types

Types abstracting over key types

data Key a where Source

Constructors

KeyEd25519 :: PublicKey -> SecretKey -> Key Ed25519 

Instances

SomeShow Key 
SomeEq Key 
HasKeyId Key 
ReportSchemaErrors m => FromJSON m (Some Key) 
Monad m => ToJSON m (Some Key) 
Monad m => ToJSON m (Key typ) 
Eq (Key typ) 
Show (Key typ) 
Typeable (* -> *) Key 

Key types in isolation

data KeyType typ where Source

Constructors

KeyTypeEd25519 :: KeyType Ed25519 

Hiding key types

Operations on keys

createKey :: KeyType key -> IO (Key key) Source

Key IDs

newtype KeyId Source

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

keyIdString :: String
 

class HasKeyId key where Source

Compute the key ID of a key

Methods

keyId :: key typ -> KeyId Source

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

Types

newtype FileLength Source

File length

Having verified file length information means we can protect against endless data attacks and similar.

Constructors

FileLength 

Fields

fileLength :: Int
 

newtype Hash Source

File hash

Constructors

Hash String 

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 Int 

data FileInfo Source

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.

newtype Hash Source

File hash

Constructors

Hash String 

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

Compare known file info

This should be used only when the FileInfo is already known. If we want to compare known FileInfo against a file on disk we should delay until we know have confirmed that the file lengths don't match (see verifyFileInfo).

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 Int 

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) 

data Header Source

Occassionally it is useful to read only a header from a file.

HeaderOnly intentionally only has a FromJSON instance (no ToJSON).

Utility

Repository layout

data RepoRoot Source

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 WebRoot -- 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.

Instances

type RepoPath = Path (Rooted RepoRoot) Source

Paths relative to the root of the repository

data RepoLayout Source

Layout of a repository

Constructors

RepoLayout 

Fields

repoLayoutRoot :: RepoPath

TUF root metadata

repoLayoutTimestamp :: RepoPath

TUF timestamp

repoLayoutSnapshot :: RepoPath

TUF snapshot

repoLayoutMirrors :: RepoPath

TUF mirrors list

repoLayoutIndexTarGz :: RepoPath

Compressed index tarball

repoLayoutIndexTar :: RepoPath

Uncompressed index tarball

repoLayoutPkgTarGz :: PackageIdentifier -> RepoPath

Path to the package tarball

repoIndexLayout :: 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.

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.

Index tarball layout

data IndexRoot Source

The root of the index tarball

Instances

type IndexPath = Path (Rooted RepoRoot) Source

Paths relative to the root of the index tarball

data IndexLayout Source

Layout of the files within the index tarball

Constructors

IndexLayout 

Fields

indexLayoutPkgMetadata :: PackageIdentifier -> IndexPath

TUF metadata for a package

indexLayoutPkgCabal :: PackageIdentifier -> IndexPath

Package .cabal file

hackageIndexLayout :: IndexLayout Source

The layout of the index as maintained on Hackage

Cache layout

data CacheRoot Source

The cache directory

Instances

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

cacheLayoutRoot :: CachePath

TUF root metadata

cacheLayoutTimestamp :: CachePath

TUF timestamp

cacheLayoutSnapshot :: CachePath

TUF snapshot

cacheLayoutMirrors :: CachePath

TUF mirrors list

cacheLayoutIndexTar :: CachePath

Uncompressed index tarball

cacheLayoutIndexIdx :: CachePath

Index to the uncompressed index tarball

cacheLayoutIndexTarGz :: Maybe CachePath

Compressed index tarball (if cached)

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).

anchorCachePath :: IsFileSystemRoot root => Path (Rooted root) -> CachePath -> Path (Rooted root) Source

Anchor a cache path to the location of the cache

TUF types

data Mirror Source

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 

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

describeMirror :: Mirror -> MirrorDescription Source

Give a human-readable description of a particular mirror

(for use in error messages)

Patterns and replacements

data Pattern a where Source

Structured patterns over paths

The type argument indicates what kind of function we expect when the pattern matches. For example, we have the pattern "*/*.txt":

PathPatternDirAny (PathPatternFileExt ".txt")
  :: PathPattern (Directory :- BaseName :- ())

TODOs (see README.md):

  • Update this to work with Path rather than 'FilePath'/'String'
  • Add different kinds of wildcards
  • Add path roots

Currently this is a proof of concept more than anything else; the right structure is here, but it needs updating. However, until we add author signing (or out-of-tarball targets) we don't actually use this yet.

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

Instances

data Replacement a where Source

Replacement patterns

These constructors match the ones in Pattern: wildcards must be used in the same order as they appear in the pattern, but they don't all have to be used (that's why the base constructors are polymorphic in the stack tail).

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) 

Utility

identityReplacement :: Pattern typ -> Replacement typ Source

The identity replacement replaces a matched pattern with itself

Parsing and quasi-quoting

qqd :: String -> String -> Q Exp Source

Quasi-quoter for delegations to make them easier to write in code

This allows to write delegations as

$(qqd "targets/*/*/*.cabal" "targets/*/*/revisions.json")

(The alternative syntax which actually uses a quasi-quoter doesn't work very well because the /* bits confuse CPP: "unterminated comment")

Datatypes

data Root Source

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.)

Instances

HasHeader Root 
Monad m => ToJSON m Root 
MonadKeys m => FromJSON m (Signed Root)

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.

data RoleSpec a Source

Role specification

The phantom type indicates what kind of type this role is meant to verify.

Instances

TUF types

data Signed a Source

Constructors

Signed 

Fields

signed :: a
 
signatures :: Signatures
 

Instances

MonadKeys m => FromJSON m (Signed Mirrors) 
(MonadKeys m, MonadReader RepoLayout m) => FromJSON m (Signed Snapshot) 
MonadKeys m => FromJSON m (Signed Targets) 
(MonadKeys m, MonadReader RepoLayout m) => FromJSON m (Signed Timestamp) 
MonadKeys m => FromJSON m (Signed Root)

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) 

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] 

Construction and verification

unsigned :: a -> Signed a Source

Create a new document without any signatures

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

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.

data PreSignature Source

A signature with a key ID (rather than an actual key)

This corresponds precisely to the TUF representation of a signature.

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 PreSignatures to a list of Signatures

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

data Snapshot Source

Constructors

Snapshot 

Fields

snapshotVersion :: FileVersion
 
snapshotExpires :: FileExpires
 
snapshotInfoRoot :: FileInfo

File info for the root metadata

We list this explicitly in the snapshot so that we can check if we need to update the root metadata without first having to download the entire index tarball.

snapshotInfoMirrors :: FileInfo

File info for the mirror metadata

snapshotInfoTarGz :: FileInfo

Compressed index tarball

snapshotInfoTar :: Maybe FileInfo

Uncompressed index tarball

Repositories are not required to provide this.

TUF types

data Targets Source

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).

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.

data DelegationSpec Source

Delegation specification

NOTE: This is a close analogue of RoleSpec.

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) 

Util