{-# LANGUAGE CPP #-}
#if __GLASGOW_HASKELL__ >= 710
{-# LANGUAGE StaticPointers #-}
#endif
module Hackage.Security.Trusted (
module Hackage.Security.Trusted.TCB
, (<$$>)
, VerifyRole(..)
, trustedFileInfoEqual
) where
import MyPrelude
import Data.Function (on)
import Data.Time
import Hackage.Security.TUF
import Hackage.Security.Trusted.TCB hiding (DeclareTrusted)
(<$$>) :: StaticPtr (a -> b) -> Trusted a -> Trusted b
<$$> :: forall a b. StaticPtr (a -> b) -> Trusted a -> Trusted b
(<$$>) = forall a b. Trusted (a -> b) -> Trusted a -> Trusted b
trustApply forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. StaticPtr a -> Trusted a
trustStatic
class VerifyRole a where
verifyRole :: Trusted Root
-> TargetPath
-> Maybe FileVersion
-> Maybe UTCTime
-> Signed a
-> Either VerificationError (SignaturesVerified a)
instance VerifyRole Root where
verifyRole :: Trusted Root
-> TargetPath
-> Maybe FileVersion
-> Maybe UTCTime
-> Signed Root
-> Either VerificationError (SignaturesVerified Root)
verifyRole = forall a.
HasHeader a =>
Trusted (RoleSpec a)
-> TargetPath
-> Maybe FileVersion
-> Maybe UTCTime
-> Signed a
-> Either VerificationError (SignaturesVerified a)
verifyRole' forall b c a. (b -> c) -> (a -> b) -> a -> c
. (static (RootRoles -> RoleSpec Root
rootRolesRoot forall b c a. (b -> c) -> (a -> b) -> a -> c
. Root -> RootRoles
rootRoles) forall a b. StaticPtr (a -> b) -> Trusted a -> Trusted b
<$$>)
instance VerifyRole Timestamp where
verifyRole :: Trusted Root
-> TargetPath
-> Maybe FileVersion
-> Maybe UTCTime
-> Signed Timestamp
-> Either VerificationError (SignaturesVerified Timestamp)
verifyRole = forall a.
HasHeader a =>
Trusted (RoleSpec a)
-> TargetPath
-> Maybe FileVersion
-> Maybe UTCTime
-> Signed a
-> Either VerificationError (SignaturesVerified a)
verifyRole' forall b c a. (b -> c) -> (a -> b) -> a -> c
. (static (RootRoles -> RoleSpec Timestamp
rootRolesTimestamp forall b c a. (b -> c) -> (a -> b) -> a -> c
. Root -> RootRoles
rootRoles) forall a b. StaticPtr (a -> b) -> Trusted a -> Trusted b
<$$>)
instance VerifyRole Snapshot where
verifyRole :: Trusted Root
-> TargetPath
-> Maybe FileVersion
-> Maybe UTCTime
-> Signed Snapshot
-> Either VerificationError (SignaturesVerified Snapshot)
verifyRole = forall a.
HasHeader a =>
Trusted (RoleSpec a)
-> TargetPath
-> Maybe FileVersion
-> Maybe UTCTime
-> Signed a
-> Either VerificationError (SignaturesVerified a)
verifyRole' forall b c a. (b -> c) -> (a -> b) -> a -> c
. (static (RootRoles -> RoleSpec Snapshot
rootRolesSnapshot forall b c a. (b -> c) -> (a -> b) -> a -> c
. Root -> RootRoles
rootRoles) forall a b. StaticPtr (a -> b) -> Trusted a -> Trusted b
<$$>)
instance VerifyRole Mirrors where
verifyRole :: Trusted Root
-> TargetPath
-> Maybe FileVersion
-> Maybe UTCTime
-> Signed Mirrors
-> Either VerificationError (SignaturesVerified Mirrors)
verifyRole = forall a.
HasHeader a =>
Trusted (RoleSpec a)
-> TargetPath
-> Maybe FileVersion
-> Maybe UTCTime
-> Signed a
-> Either VerificationError (SignaturesVerified a)
verifyRole' forall b c a. (b -> c) -> (a -> b) -> a -> c
. (static (RootRoles -> RoleSpec Mirrors
rootRolesMirrors forall b c a. (b -> c) -> (a -> b) -> a -> c
. Root -> RootRoles
rootRoles) forall a b. StaticPtr (a -> b) -> Trusted a -> Trusted b
<$$>)
trustedFileInfoEqual :: Trusted FileInfo -> Trusted FileInfo -> Bool
trustedFileInfoEqual :: Trusted FileInfo -> Trusted FileInfo -> Bool
trustedFileInfoEqual = FileInfo -> FileInfo -> Bool
knownFileInfoEqual forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` forall a. Trusted a -> a
trusted