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

Hackage.Security.Server

Description

Main entry point into the Hackage Security framework for clients

Synopsis

Re-exports

class FromJSON m a where Source #

Methods

fromJSON :: JSValue -> m a Source #

Instances

Instances details
ReportSchemaErrors m => FromJSON m KeyEnv Source # 
Instance details

Defined in Hackage.Security.Key.Env

Methods

fromJSON :: JSValue -> m KeyEnv Source #

ReportSchemaErrors m => FromJSON m FileLength Source # 
Instance details

Defined in Hackage.Security.TUF.Common

ReportSchemaErrors m => FromJSON m Hash Source # 
Instance details

Defined in Hackage.Security.TUF.Common

Methods

fromJSON :: JSValue -> m Hash Source #

ReportSchemaErrors m => FromJSON m KeyThreshold Source # 
Instance details

Defined in Hackage.Security.TUF.Common

ReportSchemaErrors m => FromJSON m FileInfo Source # 
Instance details

Defined in Hackage.Security.TUF.FileInfo

ReportSchemaErrors m => FromJSON m FileMap Source # 
Instance details

Defined in Hackage.Security.TUF.FileMap

ReportSchemaErrors m => FromJSON m FileExpires Source # 
Instance details

Defined in Hackage.Security.TUF.Header

ReportSchemaErrors m => FromJSON m FileVersion Source # 
Instance details

Defined in Hackage.Security.TUF.Header

ReportSchemaErrors m => FromJSON m Header Source # 
Instance details

Defined in Hackage.Security.TUF.Header

Methods

fromJSON :: JSValue -> m Header Source #

ReportSchemaErrors m => FromJSON m Mirror Source # 
Instance details

Defined in Hackage.Security.TUF.Mirrors

Methods

fromJSON :: JSValue -> m Mirror Source #

(MonadError DeserializationError m, ReportSchemaErrors m) => FromJSON m Mirrors Source # 
Instance details

Defined in Hackage.Security.TUF.Mirrors

MonadKeys m => FromJSON m RootRoles Source # 
Instance details

Defined in Hackage.Security.TUF.Root

ReportSchemaErrors m => FromJSON m PreSignature Source # 
Instance details

Defined in Hackage.Security.TUF.Signed

MonadKeys m => FromJSON m Signatures Source # 
Instance details

Defined in Hackage.Security.TUF.Signed

(MonadReader RepoLayout m, MonadError DeserializationError m, ReportSchemaErrors m) => FromJSON m Snapshot Source # 
Instance details

Defined in Hackage.Security.TUF.Snapshot

MonadKeys m => FromJSON m DelegationSpec Source # 
Instance details

Defined in Hackage.Security.TUF.Targets

MonadKeys m => FromJSON m Delegations Source # 
Instance details

Defined in Hackage.Security.TUF.Targets

MonadKeys m => FromJSON m Targets Source # 
Instance details

Defined in Hackage.Security.TUF.Targets

(MonadReader RepoLayout m, MonadError DeserializationError m, ReportSchemaErrors m) => FromJSON m Timestamp Source # 
Instance details

Defined in Hackage.Security.TUF.Timestamp

ReportSchemaErrors m => FromJSON m Int54 Source # 
Instance details

Defined in Hackage.Security.Util.JSON

Methods

fromJSON :: JSValue -> m Int54 Source #

Monad m => FromJSON m JSValue Source # 
Instance details

Defined in Hackage.Security.Util.JSON

ReportSchemaErrors m => FromJSON m URI Source # 
Instance details

Defined in Hackage.Security.Util.JSON

Methods

fromJSON :: JSValue -> m URI Source #

ReportSchemaErrors m => FromJSON m UTCTime Source # 
Instance details

Defined in Hackage.Security.Util.JSON

ReportSchemaErrors m => FromJSON m String Source # 
Instance details

Defined in Hackage.Security.Util.JSON

Methods

fromJSON :: JSValue -> m String Source #

MonadKeys m => FromJSON m (RoleSpec a) Source # 
Instance details

Defined in Hackage.Security.TUF.Root

Methods

fromJSON :: JSValue -> m (RoleSpec a) Source #

MonadKeys m => FromJSON m (Signed Mirrors) Source # 
Instance details

Defined in Hackage.Security.TUF.Mirrors

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.

Instance details

Defined in Hackage.Security.TUF.Root

Methods

fromJSON :: JSValue -> m (Signed Root) Source #

(MonadKeys m, MonadReader RepoLayout m) => FromJSON m (Signed Snapshot) Source # 
Instance details

Defined in Hackage.Security.TUF.Snapshot

MonadKeys m => FromJSON m (Signed Targets) Source # 
Instance details

Defined in Hackage.Security.TUF.Targets

(MonadKeys m, MonadReader RepoLayout m) => FromJSON m (Signed Timestamp) Source # 
Instance details

Defined in Hackage.Security.TUF.Timestamp

(ReportSchemaErrors m, FromJSON m a) => FromJSON m (UninterpretedSignatures a) Source # 
Instance details

Defined in Hackage.Security.TUF.Signed

ReportSchemaErrors m => FromJSON m (Some Key) Source # 
Instance details

Defined in Hackage.Security.Key

Methods

fromJSON :: JSValue -> m (Some Key) Source #

ReportSchemaErrors m => FromJSON m (Some KeyType) Source # 
Instance details

Defined in Hackage.Security.Key

Methods

fromJSON :: JSValue -> m (Some KeyType) Source #

ReportSchemaErrors m => FromJSON m (Some PublicKey) Source # 
Instance details

Defined in Hackage.Security.Key

(ReportSchemaErrors m, FromJSON m a) => FromJSON m [a] Source # 
Instance details

Defined in Hackage.Security.Util.JSON

Methods

fromJSON :: JSValue -> m [a] Source #

(ReportSchemaErrors m, Ord k, FromObjectKey m k, FromJSON m a) => FromJSON m (Map k a) Source # 
Instance details

Defined in Hackage.Security.Util.JSON

Methods

fromJSON :: JSValue -> m (Map k a) Source #

class ToJSON m a where Source #

Methods

toJSON :: a -> m JSValue Source #

Instances

Instances details
Monad m => ToJSON m KeyEnv Source # 
Instance details

Defined in Hackage.Security.Key.Env

Methods

toJSON :: KeyEnv -> m JSValue Source #

Monad m => ToJSON m FileLength Source # 
Instance details

Defined in Hackage.Security.TUF.Common

Monad m => ToJSON m Hash Source # 
Instance details

Defined in Hackage.Security.TUF.Common

Methods

toJSON :: Hash -> m JSValue Source #

Monad m => ToJSON m KeyThreshold Source # 
Instance details

Defined in Hackage.Security.TUF.Common

Monad m => ToJSON m FileInfo Source # 
Instance details

Defined in Hackage.Security.TUF.FileInfo

Methods

toJSON :: FileInfo -> m JSValue Source #

Monad m => ToJSON m FileMap Source # 
Instance details

Defined in Hackage.Security.TUF.FileMap

Methods

toJSON :: FileMap -> m JSValue Source #

Monad m => ToJSON m FileExpires Source # 
Instance details

Defined in Hackage.Security.TUF.Header

Monad m => ToJSON m FileVersion Source # 
Instance details

Defined in Hackage.Security.TUF.Header

Monad m => ToJSON m Mirror Source # 
Instance details

Defined in Hackage.Security.TUF.Mirrors

Methods

toJSON :: Mirror -> m JSValue Source #

Monad m => ToJSON m Mirrors Source # 
Instance details

Defined in Hackage.Security.TUF.Mirrors

Methods

toJSON :: Mirrors -> m JSValue Source #

Monad m => ToJSON m Root Source # 
Instance details

Defined in Hackage.Security.TUF.Root

Methods

toJSON :: Root -> m JSValue Source #

Monad m => ToJSON m RootRoles Source # 
Instance details

Defined in Hackage.Security.TUF.Root

Monad m => ToJSON m PreSignature Source # 
Instance details

Defined in Hackage.Security.TUF.Signed

Monad m => ToJSON m Signatures Source # 
Instance details

Defined in Hackage.Security.TUF.Signed

MonadReader RepoLayout m => ToJSON m Snapshot Source # 
Instance details

Defined in Hackage.Security.TUF.Snapshot

Methods

toJSON :: Snapshot -> m JSValue Source #

Monad m => ToJSON m DelegationSpec Source # 
Instance details

Defined in Hackage.Security.TUF.Targets

Monad m => ToJSON m Delegations Source # 
Instance details

Defined in Hackage.Security.TUF.Targets

Monad m => ToJSON m Targets Source # 
Instance details

Defined in Hackage.Security.TUF.Targets

Methods

toJSON :: Targets -> m JSValue Source #

MonadReader RepoLayout m => ToJSON m Timestamp Source # 
Instance details

Defined in Hackage.Security.TUF.Timestamp

Monad m => ToJSON m Int54 Source # 
Instance details

Defined in Hackage.Security.Util.JSON

Methods

toJSON :: Int54 -> m JSValue Source #

Monad m => ToJSON m JSValue Source # 
Instance details

Defined in Hackage.Security.Util.JSON

Methods

toJSON :: JSValue -> m JSValue Source #

Monad m => ToJSON m URI Source # 
Instance details

Defined in Hackage.Security.Util.JSON

Methods

toJSON :: URI -> m JSValue Source #

Monad m => ToJSON m UTCTime Source # 
Instance details

Defined in Hackage.Security.Util.JSON

Methods

toJSON :: UTCTime -> m JSValue Source #

Monad m => ToJSON m String Source # 
Instance details

Defined in Hackage.Security.Util.JSON

Methods

toJSON :: String -> m JSValue Source #

Monad m => ToJSON m (Key typ) Source # 
Instance details

Defined in Hackage.Security.Key

Methods

toJSON :: Key typ -> m JSValue Source #

Monad m => ToJSON m (KeyType typ) Source # 
Instance details

Defined in Hackage.Security.Key

Methods

toJSON :: KeyType typ -> m JSValue Source #

Monad m => ToJSON m (PublicKey typ) Source # 
Instance details

Defined in Hackage.Security.Key

Methods

toJSON :: PublicKey typ -> m JSValue Source #

Monad m => ToJSON m (RoleSpec a) Source # 
Instance details

Defined in Hackage.Security.TUF.Root

Methods

toJSON :: RoleSpec a -> m JSValue Source #

(Monad m, ToJSON m a) => ToJSON m (Signed a) Source # 
Instance details

Defined in Hackage.Security.TUF.Signed

Methods

toJSON :: Signed a -> m JSValue Source #

(Monad m, ToJSON m a) => ToJSON m (UninterpretedSignatures a) Source # 
Instance details

Defined in Hackage.Security.TUF.Signed

Monad m => ToJSON m (Some Key) Source # 
Instance details

Defined in Hackage.Security.Key

Methods

toJSON :: Some Key -> m JSValue Source #

Monad m => ToJSON m (Some KeyType) Source # 
Instance details

Defined in Hackage.Security.Key

Monad m => ToJSON m (Some PublicKey) Source # 
Instance details

Defined in Hackage.Security.Key

(Monad m, ToJSON m a) => ToJSON m [a] Source # 
Instance details

Defined in Hackage.Security.Util.JSON

Methods

toJSON :: [a] -> m JSValue Source #

(Monad m, ToObjectKey m k, ToJSON m a) => ToJSON m (Map k a) Source # 
Instance details

Defined in Hackage.Security.Util.JSON

Methods

toJSON :: Map k a -> m JSValue Source #

data WriteJSON a Source #

Instances

Instances details
Applicative WriteJSON Source # 
Instance details

Defined in Hackage.Security.JSON

Methods

pure :: a -> WriteJSON a #

(<*>) :: WriteJSON (a -> b) -> WriteJSON a -> WriteJSON b #

liftA2 :: (a -> b -> c) -> WriteJSON a -> WriteJSON b -> WriteJSON c #

(*>) :: WriteJSON a -> WriteJSON b -> WriteJSON b #

(<*) :: WriteJSON a -> WriteJSON b -> WriteJSON a #

Functor WriteJSON Source # 
Instance details

Defined in Hackage.Security.JSON

Methods

fmap :: (a -> b) -> WriteJSON a -> WriteJSON b #

(<$) :: a -> WriteJSON b -> WriteJSON a #

Monad WriteJSON Source # 
Instance details

Defined in Hackage.Security.JSON

Methods

(>>=) :: WriteJSON a -> (a -> WriteJSON b) -> WriteJSON b #

(>>) :: WriteJSON a -> WriteJSON b -> WriteJSON b #

return :: a -> WriteJSON a #

MonadReader RepoLayout WriteJSON Source # 
Instance details

Defined in Hackage.Security.JSON

data ReadJSON_NoKeys_NoLayout a Source #

Instances

Instances details
Applicative ReadJSON_NoKeys_NoLayout Source # 
Instance details

Defined in Hackage.Security.JSON

Functor ReadJSON_NoKeys_NoLayout Source # 
Instance details

Defined in Hackage.Security.JSON

Monad ReadJSON_NoKeys_NoLayout Source # 
Instance details

Defined in Hackage.Security.JSON

ReportSchemaErrors ReadJSON_NoKeys_NoLayout Source # 
Instance details

Defined in Hackage.Security.JSON

MonadError DeserializationError ReadJSON_NoKeys_NoLayout Source # 
Instance details

Defined in Hackage.Security.JSON

data ReadJSON_Keys_NoLayout a Source #

Instances

Instances details
Applicative ReadJSON_Keys_NoLayout Source # 
Instance details

Defined in Hackage.Security.JSON

Functor ReadJSON_Keys_NoLayout Source # 
Instance details

Defined in Hackage.Security.JSON

Monad ReadJSON_Keys_NoLayout Source # 
Instance details

Defined in Hackage.Security.JSON

MonadKeys ReadJSON_Keys_NoLayout Source # 
Instance details

Defined in Hackage.Security.JSON

ReportSchemaErrors ReadJSON_Keys_NoLayout Source # 
Instance details

Defined in Hackage.Security.JSON

MonadError DeserializationError ReadJSON_Keys_NoLayout Source # 
Instance details

Defined in Hackage.Security.JSON

data ReadJSON_Keys_Layout a Source #

Instances

Instances details
Applicative ReadJSON_Keys_Layout Source # 
Instance details

Defined in Hackage.Security.JSON

Functor ReadJSON_Keys_Layout Source # 
Instance details

Defined in Hackage.Security.JSON

Monad ReadJSON_Keys_Layout Source # 
Instance details

Defined in Hackage.Security.JSON

MonadKeys ReadJSON_Keys_Layout Source # 
Instance details

Defined in Hackage.Security.JSON

ReportSchemaErrors ReadJSON_Keys_Layout Source # 
Instance details

Defined in Hackage.Security.JSON

MonadError DeserializationError ReadJSON_Keys_Layout Source # 
Instance details

Defined in Hackage.Security.JSON

MonadReader RepoLayout ReadJSON_Keys_Layout Source # 
Instance details

Defined in Hackage.Security.JSON

data DeserializationError Source #

Constructors

DeserializationErrorMalformed String

Malformed JSON has syntax errors in the JSON itself (i.e., we cannot even parse it to a JSValue)

DeserializationErrorSchema String

Invalid JSON has valid syntax but invalid structure

The string gives a hint about what we expected instead

DeserializationErrorUnknownKey KeyId

The JSON file contains a key ID of an unknown key

DeserializationErrorValidation String

Some verification step failed

DeserializationErrorFileType String String

Wrong file type

Records actual and expected types.

Instances

Instances details
Exception DeserializationError Source # 
Instance details

Defined in Hackage.Security.JSON

Show DeserializationError Source # 
Instance details

Defined in Hackage.Security.JSON

Pretty DeserializationError Source # 
Instance details

Defined in Hackage.Security.JSON

MonadError DeserializationError ReadJSON_Keys_Layout Source # 
Instance details

Defined in Hackage.Security.JSON

MonadError DeserializationError ReadJSON_Keys_NoLayout Source # 
Instance details

Defined in Hackage.Security.JSON

MonadError DeserializationError ReadJSON_NoKeys_NoLayout Source # 
Instance details

Defined in Hackage.Security.JSON

renderJSON :: ToJSON WriteJSON a => RepoLayout -> a -> ByteString Source #

Render to canonical JSON format

renderJSON_NoLayout :: ToJSON Identity a => a -> ByteString Source #

Variation on renderJSON for files that don't require the repo layout

Key types

Types abstracting over key types

data Key a where Source #

Constructors

KeyEd25519 :: PublicKey -> SecretKey -> Key Ed25519 

Instances

Instances details
HasKeyId Key Source # 
Instance details

Defined in Hackage.Security.Key

Methods

keyId :: Key typ -> KeyId Source #

SomeEq Key Source # 
Instance details

Defined in Hackage.Security.Key

Methods

someEq :: DictEq (Key a) Source #

SomeShow Key Source # 
Instance details

Defined in Hackage.Security.Key

Methods

someShow :: DictShow (Key a) Source #

ReportSchemaErrors m => FromJSON m (Some Key) Source # 
Instance details

Defined in Hackage.Security.Key

Methods

fromJSON :: JSValue -> m (Some Key) Source #

Monad m => ToJSON m (Key typ) Source # 
Instance details

Defined in Hackage.Security.Key

Methods

toJSON :: Key typ -> m JSValue Source #

Monad m => ToJSON m (Some Key) Source # 
Instance details

Defined in Hackage.Security.Key

Methods

toJSON :: Some Key -> m JSValue Source #

Show (Key typ) Source # 
Instance details

Defined in Hackage.Security.Key

Methods

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

show :: Key typ -> String #

showList :: [Key typ] -> ShowS #

Eq (Key typ) Source # 
Instance details

Defined in Hackage.Security.Key

Methods

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

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

data PublicKey a where Source #

Instances

Instances details
HasKeyId PublicKey Source # 
Instance details

Defined in Hackage.Security.Key

Methods

keyId :: PublicKey typ -> KeyId Source #

SomeEq PublicKey Source # 
Instance details

Defined in Hackage.Security.Key

SomeShow PublicKey Source # 
Instance details

Defined in Hackage.Security.Key

ReportSchemaErrors m => FromJSON m (Some PublicKey) Source # 
Instance details

Defined in Hackage.Security.Key

Monad m => ToJSON m (PublicKey typ) Source # 
Instance details

Defined in Hackage.Security.Key

Methods

toJSON :: PublicKey typ -> m JSValue Source #

Monad m => ToJSON m (Some PublicKey) Source # 
Instance details

Defined in Hackage.Security.Key

Show (PublicKey typ) Source # 
Instance details

Defined in Hackage.Security.Key

Methods

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

show :: PublicKey typ -> String #

showList :: [PublicKey typ] -> ShowS #

Eq (PublicKey typ) Source # 
Instance details

Defined in Hackage.Security.Key

Methods

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

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

data PrivateKey a where Source #

Instances

Instances details
SomeEq PrivateKey Source # 
Instance details

Defined in Hackage.Security.Key

SomeShow PrivateKey Source # 
Instance details

Defined in Hackage.Security.Key

Show (PrivateKey typ) Source # 
Instance details

Defined in Hackage.Security.Key

Methods

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

show :: PrivateKey typ -> String #

showList :: [PrivateKey typ] -> ShowS #

Eq (PrivateKey typ) Source # 
Instance details

Defined in Hackage.Security.Key

Methods

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

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

Key types in isolation

data KeyType typ where Source #

Constructors

KeyTypeEd25519 :: KeyType Ed25519 

Instances

Instances details
SomeEq KeyType Source # 
Instance details

Defined in Hackage.Security.Key

Methods

someEq :: DictEq (KeyType a) Source #

SomeShow KeyType Source # 
Instance details

Defined in Hackage.Security.Key

ReportSchemaErrors m => FromJSON m (Some KeyType) Source # 
Instance details

Defined in Hackage.Security.Key

Methods

fromJSON :: JSValue -> m (Some KeyType) Source #

Monad m => ToJSON m (KeyType typ) Source # 
Instance details

Defined in Hackage.Security.Key

Methods

toJSON :: KeyType typ -> m JSValue Source #

Monad m => ToJSON m (Some KeyType) Source # 
Instance details

Defined in Hackage.Security.Key

Show (KeyType typ) Source # 
Instance details

Defined in Hackage.Security.Key

Methods

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

show :: KeyType typ -> String #

showList :: [KeyType typ] -> ShowS #

Eq (KeyType typ) Source # 
Instance details

Defined in Hackage.Security.Key

Methods

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

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

Hiding key types

someKeyId :: HasKeyId key => Some key -> KeyId Source #

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 intentionally omitted. Use writeKeyAsId instead.

Constructors

KeyId 

Fields

Instances

Instances details
Show KeyId Source # 
Instance details

Defined in Hackage.Security.Key

Methods

showsPrec :: Int -> KeyId -> ShowS #

show :: KeyId -> String #

showList :: [KeyId] -> ShowS #

Eq KeyId Source # 
Instance details

Defined in Hackage.Security.Key

Methods

(==) :: KeyId -> KeyId -> Bool #

(/=) :: KeyId -> KeyId -> Bool #

Ord KeyId Source # 
Instance details

Defined in Hackage.Security.Key

Methods

compare :: KeyId -> KeyId -> Ordering #

(<) :: KeyId -> KeyId -> Bool #

(<=) :: KeyId -> KeyId -> Bool #

(>) :: KeyId -> KeyId -> Bool #

(>=) :: KeyId -> KeyId -> Bool #

max :: KeyId -> KeyId -> KeyId #

min :: KeyId -> KeyId -> KeyId #

Monad m => FromObjectKey m KeyId Source # 
Instance details

Defined in Hackage.Security.Key

Monad m => ToObjectKey m KeyId Source # 
Instance details

Defined in Hackage.Security.Key

class HasKeyId key where Source #

Compute the key ID of a key

Methods

keyId :: key typ -> KeyId Source #

Instances

Instances details
HasKeyId Key Source # 
Instance details

Defined in Hackage.Security.Key

Methods

keyId :: Key typ -> KeyId Source #

HasKeyId PublicKey Source # 
Instance details

Defined in Hackage.Security.Key

Methods

keyId :: PublicKey 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

newtype Hash Source #

File hash

Constructors

Hash String 

Instances

Instances details
Show Hash Source # 
Instance details

Defined in Hackage.Security.TUF.Common

Methods

showsPrec :: Int -> Hash -> ShowS #

show :: Hash -> String #

showList :: [Hash] -> ShowS #

Eq Hash Source # 
Instance details

Defined in Hackage.Security.TUF.Common

Methods

(==) :: Hash -> Hash -> Bool #

(/=) :: Hash -> Hash -> Bool #

Ord Hash Source # 
Instance details

Defined in Hackage.Security.TUF.Common

Methods

compare :: Hash -> Hash -> Ordering #

(<) :: Hash -> Hash -> Bool #

(<=) :: Hash -> Hash -> Bool #

(>) :: Hash -> Hash -> Bool #

(>=) :: Hash -> Hash -> Bool #

max :: Hash -> Hash -> Hash #

min :: Hash -> Hash -> Hash #

ReportSchemaErrors m => FromJSON m Hash Source # 
Instance details

Defined in Hackage.Security.TUF.Common

Methods

fromJSON :: JSValue -> m Hash Source #

Monad m => ToJSON m Hash Source # 
Instance details

Defined in Hackage.Security.TUF.Common

Methods

toJSON :: Hash -> m JSValue Source #

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 

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.

Instances

Instances details
Show FileInfo Source # 
Instance details

Defined in Hackage.Security.TUF.FileInfo

ReportSchemaErrors m => FromJSON m FileInfo Source # 
Instance details

Defined in Hackage.Security.TUF.FileInfo

Monad m => ToJSON m FileInfo Source # 
Instance details

Defined in Hackage.Security.TUF.FileInfo

Methods

toJSON :: FileInfo -> m JSValue Source #

data HashFn Source #

Constructors

HashFnSHA256 
HashFnMD5 

Instances

Instances details
Show HashFn Source # 
Instance details

Defined in Hackage.Security.TUF.FileInfo

Eq HashFn Source # 
Instance details

Defined in Hackage.Security.TUF.FileInfo

Methods

(==) :: HashFn -> HashFn -> Bool #

(/=) :: HashFn -> HashFn -> Bool #

Ord HashFn Source # 
Instance details

Defined in Hackage.Security.TUF.FileInfo

ReportSchemaErrors m => FromObjectKey m HashFn Source # 
Instance details

Defined in Hackage.Security.TUF.FileInfo

Monad m => ToObjectKey m HashFn Source # 
Instance details

Defined in Hackage.Security.TUF.FileInfo

newtype Hash Source #

File hash

Constructors

Hash String 

Instances

Instances details
Show Hash Source # 
Instance details

Defined in Hackage.Security.TUF.Common

Methods

showsPrec :: Int -> Hash -> ShowS #

show :: Hash -> String #

showList :: [Hash] -> ShowS #

Eq Hash Source # 
Instance details

Defined in Hackage.Security.TUF.Common

Methods

(==) :: Hash -> Hash -> Bool #

(/=) :: Hash -> Hash -> Bool #

Ord Hash Source # 
Instance details

Defined in Hackage.Security.TUF.Common

Methods

compare :: Hash -> Hash -> Ordering #

(<) :: Hash -> Hash -> Bool #

(<=) :: Hash -> Hash -> Bool #

(>) :: Hash -> Hash -> Bool #

(>=) :: Hash -> Hash -> Bool #

max :: Hash -> Hash -> Hash #

min :: Hash -> Hash -> Hash #

ReportSchemaErrors m => FromJSON m Hash Source # 
Instance details

Defined in Hackage.Security.TUF.Common

Methods

fromJSON :: JSValue -> m Hash Source #

Monad m => ToJSON m Hash Source # 
Instance details

Defined in Hackage.Security.TUF.Common

Methods

toJSON :: Hash -> m JSValue Source #

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.

compareTrustedFileInfo Source #

Arguments

:: FileInfo

expected (from trusted TUF files)

-> FileInfo

actual (from fileInfo on target file)

-> Bool 

Compare the expected trusted file info against the actual file info of a target file.

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 have confirmed that the file lengths match (see downloadedVerify).

fileInfoSHA256 :: FileInfo -> Maybe Hash Source #

Extract SHA256 hash from FileInfo (if present)

Re-exports

data Int54 Source #

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

Instances details
Data Int54 Source # 
Instance details

Defined in Text.JSON.Canonical

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Int54 -> c Int54 #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Int54 #

toConstr :: Int54 -> Constr #

dataTypeOf :: Int54 -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Int54) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Int54) #

gmapT :: (forall b. Data b => b -> b) -> Int54 -> Int54 #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Int54 -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Int54 -> r #

gmapQ :: (forall d. Data d => d -> u) -> Int54 -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Int54 -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Int54 -> m Int54 #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Int54 -> m Int54 #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Int54 -> m Int54 #

Storable Int54 Source # 
Instance details

Defined in Text.JSON.Canonical

Methods

sizeOf :: Int54 -> Int #

alignment :: Int54 -> Int #

peekElemOff :: Ptr Int54 -> Int -> IO Int54 #

pokeElemOff :: Ptr Int54 -> Int -> Int54 -> IO () #

peekByteOff :: Ptr b -> Int -> IO Int54 #

pokeByteOff :: Ptr b -> Int -> Int54 -> IO () #

peek :: Ptr Int54 -> IO Int54 #

poke :: Ptr Int54 -> Int54 -> IO () #

Bits Int54 Source # 
Instance details

Defined in Text.JSON.Canonical

FiniteBits Int54 Source # 
Instance details

Defined in Text.JSON.Canonical

Bounded Int54 Source # 
Instance details

Defined in Text.JSON.Canonical

Enum Int54 Source # 
Instance details

Defined in Text.JSON.Canonical

Ix Int54 Source # 
Instance details

Defined in Text.JSON.Canonical

Num Int54 Source # 
Instance details

Defined in Text.JSON.Canonical

Read Int54 Source # 
Instance details

Defined in Text.JSON.Canonical

Integral Int54 Source # 
Instance details

Defined in Text.JSON.Canonical

Real Int54 Source # 
Instance details

Defined in Text.JSON.Canonical

Methods

toRational :: Int54 -> Rational #

Show Int54 Source # 
Instance details

Defined in Text.JSON.Canonical

Methods

showsPrec :: Int -> Int54 -> ShowS #

show :: Int54 -> String #

showList :: [Int54] -> ShowS #

PrintfArg Int54 Source # 
Instance details

Defined in Text.JSON.Canonical

Eq Int54 Source # 
Instance details

Defined in Text.JSON.Canonical

Methods

(==) :: Int54 -> Int54 -> Bool #

(/=) :: Int54 -> Int54 -> Bool #

Ord Int54 Source # 
Instance details

Defined in Text.JSON.Canonical

Methods

compare :: Int54 -> Int54 -> Ordering #

(<) :: Int54 -> Int54 -> Bool #

(<=) :: Int54 -> Int54 -> Bool #

(>) :: Int54 -> Int54 -> Bool #

(>=) :: Int54 -> Int54 -> Bool #

max :: Int54 -> Int54 -> Int54 #

min :: Int54 -> Int54 -> Int54 #

ReportSchemaErrors m => FromJSON m Int54 Source # 
Instance details

Defined in Hackage.Security.Util.JSON

Methods

fromJSON :: JSValue -> m Int54 Source #

Monad m => ToJSON m Int54 Source # 
Instance details

Defined in Hackage.Security.Util.JSON

Methods

toJSON :: Int54 -> m JSValue Source #

data FileChange Source #

Constructors

FileChanged FileInfo

File got added or modified; we record the new file info

FileDeleted

File got deleted

Instances

Instances details
Show FileChange Source # 
Instance details

Defined in Hackage.Security.TUF.FileMap

data FileMap Source #

Mapping from paths to file info

File maps are used in target files; the paths are relative to the location of the target files containing the file map.

Instances

Instances details
Show FileMap Source # 
Instance details

Defined in Hackage.Security.TUF.FileMap

ReportSchemaErrors m => FromJSON m FileMap Source # 
Instance details

Defined in Hackage.Security.TUF.FileMap

Monad m => ToJSON m FileMap Source # 
Instance details

Defined in Hackage.Security.TUF.FileMap

Methods

toJSON :: FileMap -> m JSValue Source #

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 used for example by Hackage during the backup process).

Constructors

FileVersion Int54 

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 #

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

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

Instances

Instances details
HasHeader Header Source # 
Instance details

Defined in Hackage.Security.TUF.Header

ReportSchemaErrors m => FromJSON m Header Source # 
Instance details

Defined in Hackage.Security.TUF.Header

Methods

fromJSON :: JSValue -> m Header Source #

Utility

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

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 #

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

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 

Instances

Instances details
Show Mirror Source # 
Instance details

Defined in Hackage.Security.TUF.Mirrors

ReportSchemaErrors m => FromJSON m Mirror Source # 
Instance details

Defined in Hackage.Security.TUF.Mirrors

Methods

fromJSON :: JSValue -> m Mirror Source #

Monad m => ToJSON m Mirror Source # 
Instance details

Defined in Hackage.Security.TUF.Mirrors

Methods

toJSON :: Mirror -> m JSValue Source #

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

Instances details
Show MirrorContent Source # 
Instance details

Defined in Hackage.Security.TUF.Mirrors

Utility

describeMirror :: Mirror -> MirrorDescription Source #

Give a human-readable description of a particular mirror

(for use in error messages)

Repository

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

Instances

Instances details
Pretty (Path RepoRoot) Source # 
Instance details

Defined in Hackage.Security.TUF.Paths

type RepoPath = Path RepoRoot Source #

Paths relative to the root of the repository

Index

data IndexRoot Source #

The root of the index tarball

Instances

Instances details
Pretty (Path IndexRoot) Source # 
Instance details

Defined in Hackage.Security.TUF.Paths

type IndexPath = Path IndexRoot Source #

Paths relative to the root of the index tarball

Cache

data CacheRoot Source #

The cache directory

Instances

Instances details
Pretty (Path CacheRoot) Source # 
Instance details

Defined in Hackage.Security.TUF.Paths

anchorCachePath :: Path root -> CachePath -> Path root Source #

Anchor a cache path to the location of the cache

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

Instances details
HasHeader Root Source # 
Instance details

Defined in Hackage.Security.TUF.Root

VerifyRole Root Source # 
Instance details

Defined in Hackage.Security.Trusted

Monad m => ToJSON m Root Source # 
Instance details

Defined in Hackage.Security.TUF.Root

Methods

toJSON :: Root -> m JSValue 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.

Instance details

Defined in Hackage.Security.TUF.Root

Methods

fromJSON :: JSValue -> m (Signed Root) Source #

data RoleSpec a Source #

Role specification

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

Instances

Instances details
MonadKeys m => FromJSON m (RoleSpec a) Source # 
Instance details

Defined in Hackage.Security.TUF.Root

Methods

fromJSON :: JSValue -> m (RoleSpec a) Source #

Monad m => ToJSON m (RoleSpec a) Source # 
Instance details

Defined in Hackage.Security.TUF.Root

Methods

toJSON :: RoleSpec a -> m JSValue Source #

Show (RoleSpec a) Source # 
Instance details

Defined in Hackage.Security.TUF.Root

Methods

showsPrec :: Int -> RoleSpec a -> ShowS #

show :: RoleSpec a -> String #

showList :: [RoleSpec a] -> ShowS #

TUF types

data Signed a Source #

Constructors

Signed 

Fields

Instances

Instances details
MonadKeys m => FromJSON m (Signed Mirrors) Source # 
Instance details

Defined in Hackage.Security.TUF.Mirrors

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.

Instance details

Defined in Hackage.Security.TUF.Root

Methods

fromJSON :: JSValue -> m (Signed Root) Source #

(MonadKeys m, MonadReader RepoLayout m) => FromJSON m (Signed Snapshot) Source # 
Instance details

Defined in Hackage.Security.TUF.Snapshot

MonadKeys m => FromJSON m (Signed Targets) Source # 
Instance details

Defined in Hackage.Security.TUF.Targets

(MonadKeys m, MonadReader RepoLayout m) => FromJSON m (Signed Timestamp) Source # 
Instance details

Defined in Hackage.Security.TUF.Timestamp

(Monad m, ToJSON m a) => ToJSON m (Signed a) Source # 
Instance details

Defined in Hackage.Security.TUF.Signed

Methods

toJSON :: Signed a -> m JSValue 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

Instances details
MonadKeys m => FromJSON m Signatures Source # 
Instance details

Defined in Hackage.Security.TUF.Signed

Monad m => ToJSON m Signatures Source # 
Instance details

Defined in Hackage.Security.TUF.Signed

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.

Instances

Instances details
Show PreSignature Source # 
Instance details

Defined in Hackage.Security.TUF.Signed

ReportSchemaErrors m => FromJSON m PreSignature Source # 
Instance details

Defined in Hackage.Security.TUF.Signed

Monad m => ToJSON m PreSignature Source # 
Instance details

Defined in Hackage.Security.TUF.Signed

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

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

Instances

Instances details
Show Targets Source # 
Instance details

Defined in Hackage.Security.TUF.Targets

HasHeader Targets Source # 
Instance details

Defined in Hackage.Security.TUF.Targets

MonadKeys m => FromJSON m Targets Source # 
Instance details

Defined in Hackage.Security.TUF.Targets

Monad m => ToJSON m Targets Source # 
Instance details

Defined in Hackage.Security.TUF.Targets

Methods

toJSON :: Targets -> m JSValue Source #

MonadKeys m => FromJSON m (Signed Targets) Source # 
Instance details

Defined in Hackage.Security.TUF.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.

Instances

Instances details
Show Delegations Source # 
Instance details

Defined in Hackage.Security.TUF.Targets

MonadKeys m => FromJSON m Delegations Source # 
Instance details

Defined in Hackage.Security.TUF.Targets

Monad m => ToJSON m Delegations Source # 
Instance details

Defined in Hackage.Security.TUF.Targets

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) 

Instances

Instances details
Show Delegation Source # 
Instance details

Defined in Hackage.Security.TUF.Patterns

Lift Delegation Source # 
Instance details

Defined in Hackage.Security.TUF.Patterns

Methods

lift :: Quote m => Delegation -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Delegation -> Code m Delegation #

Util