-- Expirations.hs: OpenPGP (RFC4880) expiration checking
-- Copyright © 2014  Clint Adams
-- This software is released under the terms of the Expat license.
-- (See the LICENSE file).

module Codec.Encryption.OpenPGP.Expirations (
   isTKTimeValid
 , getKeyExpirationTimesFromSignature
) where

import Control.Lens ((&), (^.), _1)
import Data.List (sort)
import Data.Time.Clock (UTCTime)
import Data.Time.Clock.POSIX (posixSecondsToUTCTime)

import Codec.Encryption.OpenPGP.Types

-- this assumes that all key expiration time subpackets are valid
isTKTimeValid :: UTCTime -> TK -> Bool
isTKTimeValid ct key = ct >= keyCreationTime && ct < keyExpirationTime
    where
        keyCreationTime = key^.tkKey._1.timestamp & posixSecondsToUTCTime . realToFrac
        keyExpirationTime = posixSecondsToUTCTime . realToFrac . ((+) (key^.tkKey._1.timestamp)) . newest . concatMap getKeyExpirationTimesFromSignature $ (concatMap snd (key^.tkUIDs) ++ concatMap snd (key^.tkUAts))
	newest [] = maxBound
	newest xs = last (sort xs)

getKeyExpirationTimesFromSignature :: SignaturePayload -> [TimeStamp]
getKeyExpirationTimesFromSignature (SigV4 _ _ _ xs _ _ _) = map (\(SigSubPacket _ (KeyExpirationTime x)) -> x) $ filter isKET xs
    where
        isKET (SigSubPacket _ (KeyExpirationTime _)) = True
        isKET _ = False
getKeyExpirationTimesFromSignature _ = []