{-# 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
(<$$>) = Trusted (a -> b) -> Trusted a -> Trusted b
forall a b. Trusted (a -> b) -> Trusted a -> Trusted b
trustApply (Trusted (a -> b) -> Trusted a -> Trusted b)
-> (StaticPtr (a -> b) -> Trusted (a -> b))
-> StaticPtr (a -> b)
-> Trusted a
-> Trusted b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StaticPtr (a -> b) -> Trusted (a -> b)
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 = Trusted (RoleSpec Root)
-> TargetPath
-> Maybe FileVersion
-> Maybe UTCTime
-> Signed Root
-> Either VerificationError (SignaturesVerified Root)
forall a.
HasHeader a =>
Trusted (RoleSpec a)
-> TargetPath
-> Maybe FileVersion
-> Maybe UTCTime
-> Signed a
-> Either VerificationError (SignaturesVerified a)
verifyRole' (Trusted (RoleSpec Root)
-> TargetPath
-> Maybe FileVersion
-> Maybe UTCTime
-> Signed Root
-> Either VerificationError (SignaturesVerified Root))
-> (Trusted Root -> Trusted (RoleSpec Root))
-> Trusted Root
-> TargetPath
-> Maybe FileVersion
-> Maybe UTCTime
-> Signed Root
-> Either VerificationError (SignaturesVerified Root)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (static (RootRoles -> RoleSpec Root
rootRolesRoot (RootRoles -> RoleSpec Root)
-> (Root -> RootRoles) -> Root -> RoleSpec Root
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Root -> RootRoles
rootRoles) StaticPtr (Root -> RoleSpec Root)
-> Trusted Root -> Trusted (RoleSpec Root)
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 = Trusted (RoleSpec Timestamp)
-> TargetPath
-> Maybe FileVersion
-> Maybe UTCTime
-> Signed Timestamp
-> Either VerificationError (SignaturesVerified Timestamp)
forall a.
HasHeader a =>
Trusted (RoleSpec a)
-> TargetPath
-> Maybe FileVersion
-> Maybe UTCTime
-> Signed a
-> Either VerificationError (SignaturesVerified a)
verifyRole' (Trusted (RoleSpec Timestamp)
-> TargetPath
-> Maybe FileVersion
-> Maybe UTCTime
-> Signed Timestamp
-> Either VerificationError (SignaturesVerified Timestamp))
-> (Trusted Root -> Trusted (RoleSpec Timestamp))
-> Trusted Root
-> TargetPath
-> Maybe FileVersion
-> Maybe UTCTime
-> Signed Timestamp
-> Either VerificationError (SignaturesVerified Timestamp)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (static (RootRoles -> RoleSpec Timestamp
rootRolesTimestamp (RootRoles -> RoleSpec Timestamp)
-> (Root -> RootRoles) -> Root -> RoleSpec Timestamp
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Root -> RootRoles
rootRoles) StaticPtr (Root -> RoleSpec Timestamp)
-> Trusted Root -> Trusted (RoleSpec Timestamp)
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 = Trusted (RoleSpec Snapshot)
-> TargetPath
-> Maybe FileVersion
-> Maybe UTCTime
-> Signed Snapshot
-> Either VerificationError (SignaturesVerified Snapshot)
forall a.
HasHeader a =>
Trusted (RoleSpec a)
-> TargetPath
-> Maybe FileVersion
-> Maybe UTCTime
-> Signed a
-> Either VerificationError (SignaturesVerified a)
verifyRole' (Trusted (RoleSpec Snapshot)
-> TargetPath
-> Maybe FileVersion
-> Maybe UTCTime
-> Signed Snapshot
-> Either VerificationError (SignaturesVerified Snapshot))
-> (Trusted Root -> Trusted (RoleSpec Snapshot))
-> Trusted Root
-> TargetPath
-> Maybe FileVersion
-> Maybe UTCTime
-> Signed Snapshot
-> Either VerificationError (SignaturesVerified Snapshot)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (static (RootRoles -> RoleSpec Snapshot
rootRolesSnapshot (RootRoles -> RoleSpec Snapshot)
-> (Root -> RootRoles) -> Root -> RoleSpec Snapshot
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Root -> RootRoles
rootRoles) StaticPtr (Root -> RoleSpec Snapshot)
-> Trusted Root -> Trusted (RoleSpec Snapshot)
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 = Trusted (RoleSpec Mirrors)
-> TargetPath
-> Maybe FileVersion
-> Maybe UTCTime
-> Signed Mirrors
-> Either VerificationError (SignaturesVerified Mirrors)
forall a.
HasHeader a =>
Trusted (RoleSpec a)
-> TargetPath
-> Maybe FileVersion
-> Maybe UTCTime
-> Signed a
-> Either VerificationError (SignaturesVerified a)
verifyRole' (Trusted (RoleSpec Mirrors)
-> TargetPath
-> Maybe FileVersion
-> Maybe UTCTime
-> Signed Mirrors
-> Either VerificationError (SignaturesVerified Mirrors))
-> (Trusted Root -> Trusted (RoleSpec Mirrors))
-> Trusted Root
-> TargetPath
-> Maybe FileVersion
-> Maybe UTCTime
-> Signed Mirrors
-> Either VerificationError (SignaturesVerified Mirrors)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (static (RootRoles -> RoleSpec Mirrors
rootRolesMirrors (RootRoles -> RoleSpec Mirrors)
-> (Root -> RootRoles) -> Root -> RoleSpec Mirrors
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Root -> RootRoles
rootRoles) StaticPtr (Root -> RoleSpec Mirrors)
-> Trusted Root -> Trusted (RoleSpec Mirrors)
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 (FileInfo -> FileInfo -> Bool)
-> (Trusted FileInfo -> FileInfo)
-> Trusted FileInfo
-> Trusted FileInfo
-> Bool
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` Trusted FileInfo -> FileInfo
forall a. Trusted a -> a
trusted