Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data StaticPtr a
- type VerificationHistory = [Either RootUpdated VerificationError]
- data RootUpdated = RootUpdated
- data VerificationError
- = VerificationErrorSignatures TargetPath
- | VerificationErrorExpired TargetPath
- | VerificationErrorVersion TargetPath
- | VerificationErrorFileInfo TargetPath
- | VerificationErrorUnknownTarget TargetPath
- | VerificationErrorMissingSHA256 TargetPath
- | VerificationErrorDeserialization TargetPath DeserializationError
- | VerificationErrorLoop VerificationHistory
- data SignaturesVerified a
- data Trusted a
- trustStatic :: StaticPtr a -> Trusted a
- trustVerified :: SignaturesVerified a -> Trusted a
- trustApply :: Trusted (a -> b) -> Trusted a -> Trusted b
- trustElems :: Traversable f => Trusted (f a) -> f (Trusted a)
- verifyRole' :: forall a. HasHeader a => Trusted (RoleSpec a) -> TargetPath -> Maybe FileVersion -> Maybe UTCTime -> Signed a -> Either VerificationError (SignaturesVerified a)
- verifyFingerprints :: [KeyId] -> KeyThreshold -> TargetPath -> Signed Root -> Either VerificationError (SignaturesVerified Root)
- (<$$>) :: StaticPtr (a -> b) -> Trusted a -> Trusted b
- class VerifyRole a where
- verifyRole :: Trusted Root -> TargetPath -> Maybe FileVersion -> Maybe UTCTime -> Signed a -> Either VerificationError (SignaturesVerified a)
- trustedFileInfoEqual :: Trusted FileInfo -> Trusted FileInfo -> Bool
Documentation
A reference to a value of type a
.
Instances
IsStatic StaticPtr | Since: base-4.9.0.0 |
Defined in GHC.StaticPtr fromStaticPtr :: StaticPtr a -> StaticPtr a # |
data RootUpdated Source #
Root metadata updated (as part of the normal update process)
Instances
Show RootUpdated Source # | |
Defined in Hackage.Security.Trusted.TCB showsPrec :: Int -> RootUpdated -> ShowS # show :: RootUpdated -> String # showList :: [RootUpdated] -> ShowS # | |
Exception RootUpdated Source # | |
Defined in Hackage.Security.Trusted.TCB | |
Pretty RootUpdated Source # | |
Defined in Hackage.Security.Trusted.TCB pretty :: RootUpdated -> String Source # |
data VerificationError Source #
Errors thrown during role validation
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. |
Instances
Show VerificationError Source # | |
Defined in Hackage.Security.Trusted.TCB showsPrec :: Int -> VerificationError -> ShowS # show :: VerificationError -> String # showList :: [VerificationError] -> ShowS # | |
Exception VerificationError Source # | |
Defined in Hackage.Security.Trusted.TCB | |
Pretty VerificationError Source # | |
Defined in Hackage.Security.Trusted.TCB pretty :: VerificationError -> String Source # |
data SignaturesVerified a Source #
Trusted values
Trusted values originate in only two ways:
- Anything that is statically known is trusted (
trustStatic
) - If we have "dynamic" data we can trust it once we have verified the the signatures (trustSigned).
NOTE: Trusted is NOT a functor. If it was we could define
trustAnything :: a -> Trusted a trustAnything a = fmap (const a) (trustStatic (static ()))
Consequently, it is neither a monad nor a comonad. However, we _can_ apply
trusted functions to trusted arguments (trustApply
).
The DeclareTrusted
constructor is exported, but any use of it should be
verified.
trustStatic :: StaticPtr a -> Trusted a Source #
trustVerified :: SignaturesVerified a -> Trusted a Source #
trustElems :: Traversable f => Trusted (f a) -> f (Trusted a) Source #
Trust all elements of some trusted (traversable) container
If we have, say, a trusted list of values, we should be able to get a list of trusted values out of it.
trustElems :: Trusted [a] -> [Trusted a]
NOTE. It might appear that the more natural primitive to offer is a
sequenceA
-like operator such as
trustSeq :: Applicative f => Trusted (f a) -> f (Trusted a)
However, this is unsound. To see this, consider that ((->) a)
is
Applicative
(it's the reader monad); hence, we can instantiate trustSeq
at
trustSeq :: Trusted (a -> a) -> a -> Trusted a
and by passing trustStatic (static id)
make Trusted
a functor, which we
certainly don't want to do (see comments for Trusted
).
So why is it okay when we insist on Traversable
rather than Applicative
?
To see this, it's instructive to consider how we might make a ((->) a)
an
instance of Traversable
. If we define the domain of enumerable types as
class Eq a => Enumerable a where enumerate :: [a]
then we can make ((->) r)
traversable by
instance Enumerable r => Traversable ((->) r) where sequenceA f = rebuild <$> sequenceA ((\r -> (r,) <$> f r) <$> enumerate) where rebuild :: [(r, a)] -> r -> a rebuild fun arg = fromJust (lookup arg fun)
The idea is that if the domain of a function is enumerable, we can apply the function to each possible input, collect the outputs, and construct a new function by pairing the inputs with the outputs. I.e., if we had something of type
a -> IO b
and a
is enumerable, we just run the IO
action on each possible a
and
collect all b
s to get a pure function a -> b
. Of course, you probably
don't want to be doing that, but the point is that as far as the type system
is concerned you could.
In the context of Trusted
, this means that we can derive
enumPure :: Enumerable a => a -> Trusted a
but in a way this this makes sense anyway. If a domain is enumerable, it
would not be unreasonable to change Enumerable
to
class Eq a => Enumerable a where enumerate :: [StaticPtr a]
so we could define enumPure
as
enumPure :: Enumerable a => a -> Trusted a enumPure x = trustStatic $ fromJust (find ((== x) . deRefStaticPtr) enumerate)
In other words, we just enumerate the entire domain as trusted values (because we defined them locally) and then return the one that matched the untrusted value.
The conclusion from all of this is that the types of untrusted input (like the types of the TUF files we download from the server) should probably not be considered enumerable.
:: HasHeader a | |
=> Trusted (RoleSpec a) | For signature validation |
-> TargetPath | File source (for error messages) |
-> Maybe FileVersion | Previous version (if available) |
-> Maybe UTCTime | Time now (if checking expiry) |
-> Signed a | |
-> Either VerificationError (SignaturesVerified a) |
Role verification
NOTE: We throw an error when the version number _decreases_, but allow it to be the same. This is sufficient: the file number is there so that attackers cannot replay old files. It cannot protect against freeze attacks (that's what the expiry date is for), so "replaying" the same file is not a problem. If an attacker changes the contents of the file but not the version number we have an inconsistent situation, but this is not something we need to worry about: in this case the attacker will need to resign the file or otherwise the signature won't match, and if the attacker has compromised the key then he might just as well increase the version number and resign.
NOTE 2: We are not actually verifying the signatures _themselves_ here (we did that when we parsed the JSON). We are merely verifying the provenance of the keys.
:: [KeyId] | |
-> KeyThreshold | |
-> TargetPath | For error messages |
-> Signed Root | |
-> Either VerificationError (SignaturesVerified Root) |
Variation on verifyRole
that uses key IDs rather than keys
This is used during the bootstrap process.
Derived functions
(<$$>) :: StaticPtr (a -> b) -> Trusted a -> Trusted b Source #
Apply a static function to a trusted argument
Role verification
class VerifyRole a where Source #
:: Trusted Root | Root data |
-> TargetPath | Source (for error messages) |
-> Maybe FileVersion | Previous version (if available) |
-> Maybe UTCTime | Time now (if checking expiry) |
-> Signed a | Mirrors to verify |
-> Either VerificationError (SignaturesVerified a) |
Instances
VerifyRole Mirrors Source # | |
Defined in Hackage.Security.Trusted verifyRole :: Trusted Root -> TargetPath -> Maybe FileVersion -> Maybe UTCTime -> Signed Mirrors -> Either VerificationError (SignaturesVerified Mirrors) Source # | |
VerifyRole Timestamp Source # | |
Defined in Hackage.Security.Trusted verifyRole :: Trusted Root -> TargetPath -> Maybe FileVersion -> Maybe UTCTime -> Signed Timestamp -> Either VerificationError (SignaturesVerified Timestamp) Source # | |
VerifyRole Snapshot Source # | |
Defined in Hackage.Security.Trusted verifyRole :: Trusted Root -> TargetPath -> Maybe FileVersion -> Maybe UTCTime -> Signed Snapshot -> Either VerificationError (SignaturesVerified Snapshot) Source # | |
VerifyRole Root Source # | |
Defined in Hackage.Security.Trusted verifyRole :: Trusted Root -> TargetPath -> Maybe FileVersion -> Maybe UTCTime -> Signed Root -> Either VerificationError (SignaturesVerified Root) Source # |