-- Base.hs: OpenPGP (RFC4880) data types -- Copyright © 2012-2016 Clint Adams -- This software is released under the terms of the Expat license. -- (See the LICENSE file). {-# LANGUAGE CPP #-} {-# LANGUAGE DataKinds #-} {-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE ExistentialQuantification #-} {-# LANGUAGE GeneralizedNewtypeDeriving #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE TemplateHaskell #-} module Codec.Encryption.OpenPGP.Types.Internal.Base where import GHC.Generics (Generic) #if !MIN_VERSION_base(4,8,0) import Control.Applicative ((<$>)) #endif import Control.Applicative ((<|>)) import Control.Arrow ((***)) import Control.Lens (makeLenses) import Control.Monad (mzero) import Control.Newtype (Newtype(..)) import Data.Aeson ((.=), object) import qualified Data.Aeson as A import qualified Data.Aeson.TH as ATH import Data.ByteArray (ByteArrayAccess) import Data.ByteString.Lazy (ByteString) import qualified Data.ByteString as B import qualified Data.ByteString.Base16.Lazy as B16L import qualified Data.ByteString.Lazy as BL import qualified Data.ByteString.Lazy.Char8 as BLC8 import Data.Char (toLower, toUpper) import Data.Data (Data) import Data.Hashable (Hashable(..)) import Data.List (unfoldr) import Data.List.NonEmpty (NonEmpty) import qualified Data.List.NonEmpty as NE import Data.List.Split (chunksOf) import Data.Maybe (fromMaybe) #if !MIN_VERSION_base(4,8,0) import Data.Monoid (Monoid, mempty) #endif import Data.Monoid ((<>)) import Data.Ord (comparing) import Data.Semigroup (Semigroup) import Data.Set (Set) import qualified Data.Set as Set import Data.Text (Text) import qualified Data.Text as T import Data.Time.Clock.POSIX (posixSecondsToUTCTime) import Data.Time.Format (formatTime) import Data.Typeable (Typeable) import Data.Word (Word8, Word16, Word32) import Network.URI (URI(..), uriToString, nullURI, parseURI) import Numeric (readHex) import Data.Time.Locale.Compat (defaultTimeLocale) import Text.PrettyPrint.Free (Pretty(..), (<+>), char, hsep, punctuate, space, text) type Exportability = Bool type TrustLevel = Word8 type TrustAmount = Word8 type AlmostPublicDomainRegex = ByteString type Revocability = Bool type RevocationReason = Text type KeyServer = ByteString type SignatureHash = ByteString type PacketVersion = Word8 type V3Expiration = Word16 type CompressedDataPayload = ByteString type FileName = ByteString type ImageData = ByteString type NestedFlag = Bool class (Eq a, Ord a) => FutureFlag a where fromFFlag :: a -> Int toFFlag :: Int -> a class (Eq a, Ord a) => FutureVal a where fromFVal :: a -> Word8 toFVal :: Word8 -> a data SymmetricAlgorithm = Plaintext | IDEA | TripleDES | CAST5 | Blowfish | ReservedSAFER | ReservedDES | AES128 | AES192 | AES256 | Twofish | Camellia128 | Camellia192 | Camellia256 | OtherSA Word8 deriving (Data, Generic, Show, Typeable) instance Eq SymmetricAlgorithm where (==) a b = fromFVal a == fromFVal b instance Ord SymmetricAlgorithm where compare = comparing fromFVal instance FutureVal SymmetricAlgorithm where fromFVal Plaintext = 0 fromFVal IDEA = 1 fromFVal TripleDES = 2 fromFVal CAST5 = 3 fromFVal Blowfish = 4 fromFVal ReservedSAFER = 5 fromFVal ReservedDES = 6 fromFVal AES128 = 7 fromFVal AES192 = 8 fromFVal AES256 = 9 fromFVal Twofish = 10 fromFVal Camellia128 = 11 fromFVal Camellia192 = 12 fromFVal Camellia256 = 13 fromFVal (OtherSA o) = o toFVal 0 = Plaintext toFVal 1 = IDEA toFVal 2 = TripleDES toFVal 3 = CAST5 toFVal 4 = Blowfish toFVal 5 = ReservedSAFER toFVal 6 = ReservedDES toFVal 7 = AES128 toFVal 8 = AES192 toFVal 9 = AES256 toFVal 10 = Twofish toFVal 11 = Camellia128 toFVal 12 = Camellia192 toFVal 13 = Camellia256 toFVal o = OtherSA o instance Hashable SymmetricAlgorithm instance Pretty SymmetricAlgorithm where pretty Plaintext = text "plaintext" pretty IDEA = text "IDEA" pretty TripleDES = text "3DES" pretty CAST5 = text "CAST-128" pretty Blowfish = text "Blowfish" pretty ReservedSAFER = text "(reserved) SAFER" pretty ReservedDES = text "(reserved) DES" pretty AES128 = text "AES-128" pretty AES192 = text "AES-192" pretty AES256 = text "AES-256" pretty Twofish = text "Twofish" pretty Camellia128 = text "Camellia-128" pretty Camellia192 = text "Camellia-192" pretty Camellia256 = text "Camellia-256" pretty (OtherSA sa) = text "unknown symmetric algorithm" <+> pretty sa $(ATH.deriveJSON ATH.defaultOptions ''SymmetricAlgorithm) data NotationFlag = HumanReadable | OtherNF Word8 -- FIXME: this should be constrained to 4 bits? deriving (Data, Generic, Show, Typeable) instance Eq NotationFlag where (==) a b = fromFFlag a == fromFFlag b instance Ord NotationFlag where compare = comparing fromFFlag instance FutureFlag NotationFlag where fromFFlag HumanReadable = 0 fromFFlag (OtherNF o) = fromIntegral o toFFlag 0 = HumanReadable toFFlag o = OtherNF (fromIntegral o) instance Hashable NotationFlag instance Pretty NotationFlag where pretty HumanReadable = text "human-readable" pretty (OtherNF o) = text "unknown notation flag type" <+> pretty o $(ATH.deriveJSON ATH.defaultOptions ''NotationFlag) newtype ThirtyTwoBitTimeStamp = ThirtyTwoBitTimeStamp {unThirtyTwoBitTimeStamp :: Word32} deriving (Bounded, Data, Enum, Eq, Generic, Hashable, Integral, Num, Ord, Real, Show, Typeable) instance Newtype ThirtyTwoBitTimeStamp Word32 where pack = ThirtyTwoBitTimeStamp unpack (ThirtyTwoBitTimeStamp o) = o instance Pretty ThirtyTwoBitTimeStamp where pretty = text . formatTime defaultTimeLocale "%Y%m%d-%H%M%S" . posixSecondsToUTCTime . realToFrac $(ATH.deriveJSON ATH.defaultOptions ''ThirtyTwoBitTimeStamp) durU :: (Integral a, Show a) => a -> Maybe (String, a) durU x | x >= 31557600 = Just ((++"y") . show $ x `div` 31557600, x `mod` 31557600) | x >= 2629800 = Just ((++"m") . show $ x `div` 2629800, x `mod` 2629800) | x >= 86400 = Just ((++"d") . show $ x `div` 86400, x `mod` 86400) | x > 0 = Just ((++"s") . show $ x, 0) | otherwise = Nothing newtype ThirtyTwoBitDuration = ThirtyTwoBitDuration {unThirtyTwoBitDuration :: Word32} deriving (Bounded, Data, Enum, Eq, Generic, Hashable, Integral, Num, Ord, Real, Show, Typeable) instance Newtype ThirtyTwoBitDuration Word32 where pack = ThirtyTwoBitDuration unpack (ThirtyTwoBitDuration o) = o instance Pretty ThirtyTwoBitDuration where pretty = text . concat . unfoldr durU . unpack $(ATH.deriveJSON ATH.defaultOptions ''ThirtyTwoBitDuration) data RevocationClass = SensitiveRK | RClOther Word8 -- FIXME: this should be constrained to 3 bits deriving (Data, Generic, Show, Typeable) instance Eq RevocationClass where (==) a b = fromFFlag a == fromFFlag b instance Ord RevocationClass where compare = comparing fromFFlag instance FutureFlag RevocationClass where fromFFlag SensitiveRK = 1 fromFFlag (RClOther i) = fromIntegral i toFFlag 1 = SensitiveRK toFFlag i = RClOther (fromIntegral i) instance Hashable RevocationClass instance Pretty RevocationClass where pretty SensitiveRK = text "sensitive" pretty (RClOther o) = text "unknown revocation class" <+> pretty o $(ATH.deriveJSON ATH.defaultOptions ''RevocationClass) data PubKeyAlgorithm = RSA | DeprecatedRSAEncryptOnly | DeprecatedRSASignOnly | ElgamalEncryptOnly | DSA | ECDH | ECDSA | ForbiddenElgamal | DH | OtherPKA Word8 deriving (Show, Data, Generic, Typeable) instance Eq PubKeyAlgorithm where (==) a b = fromFVal a == fromFVal b instance Ord PubKeyAlgorithm where compare = comparing fromFVal instance FutureVal PubKeyAlgorithm where fromFVal RSA = 1 fromFVal DeprecatedRSAEncryptOnly = 2 fromFVal DeprecatedRSASignOnly = 3 fromFVal ElgamalEncryptOnly = 16 fromFVal DSA = 17 fromFVal ECDH = 18 fromFVal ECDSA = 19 fromFVal ForbiddenElgamal = 20 fromFVal DH = 21 fromFVal (OtherPKA o) = o toFVal 1 = RSA toFVal 2 = DeprecatedRSAEncryptOnly toFVal 3 = DeprecatedRSASignOnly toFVal 16 = ElgamalEncryptOnly toFVal 17 = DSA toFVal 18 = ECDH toFVal 19 = ECDSA toFVal 20 = ForbiddenElgamal toFVal 21 = DH toFVal o = OtherPKA o instance Hashable PubKeyAlgorithm instance Pretty PubKeyAlgorithm where pretty RSA = text "RSA" pretty DeprecatedRSAEncryptOnly = text "(deprecated) RSA encrypt-only" pretty DeprecatedRSASignOnly = text "(deprecated) RSA sign-only" pretty ElgamalEncryptOnly = text "Elgamal encrypt-only" pretty DSA = text "DSA" pretty ECDH = text "ECDH" pretty ECDSA = text "ECDSA" pretty ForbiddenElgamal = text "(forbidden) Elgamal" pretty DH = text "DH" pretty (OtherPKA pka) = text "unknown pubkey algorithm type" <+> pretty pka $(ATH.deriveJSON ATH.defaultOptions ''PubKeyAlgorithm) newtype TwentyOctetFingerprint = TwentyOctetFingerprint {unTOF :: ByteString} deriving (Data, Eq, Generic, Ord, Show, Typeable) instance Newtype TwentyOctetFingerprint ByteString where pack = TwentyOctetFingerprint unpack (TwentyOctetFingerprint o) = o -- FIXME: read-show instance Read TwentyOctetFingerprint where readsPrec _ = map ((TwentyOctetFingerprint . BL.pack *** concat) . unzip) . chunksOf 20 . hexToW8s . filter (/= ' ') instance Hashable TwentyOctetFingerprint instance Pretty TwentyOctetFingerprint where pretty = pretty . take 40 . bsToHexUpper . unTOF instance A.ToJSON TwentyOctetFingerprint where toJSON e = object [T.pack "fpr" .= (A.toJSON . show . pretty) e] instance A.FromJSON TwentyOctetFingerprint where parseJSON (A.Object v) = TwentyOctetFingerprint . read <$> v A..: T.pack "fpr" parseJSON _ = mzero newtype SpacedFingerprint = SpacedFingerprint { unSpacedFingerprint :: TwentyOctetFingerprint } instance Newtype SpacedFingerprint TwentyOctetFingerprint where pack = SpacedFingerprint unpack (SpacedFingerprint o) = o instance Pretty SpacedFingerprint where pretty = hsep . punctuate space . map hsep . chunksOf 5 . map text . chunksOf 4 . take 40 . bsToHexUpper . unTOF . unpack bsToHexUpper :: ByteString -> String bsToHexUpper = map toUpper . BLC8.unpack . B16L.encode hexToW8s :: ReadS Word8 hexToW8s = concatMap readHex . chunksOf 2 . map toLower newtype EightOctetKeyId = EightOctetKeyId {unEOKI :: ByteString} deriving (Data, Eq, Generic, Ord, Show, Typeable) instance Newtype EightOctetKeyId ByteString where pack = EightOctetKeyId unpack (EightOctetKeyId o) = o instance Pretty EightOctetKeyId where pretty = pretty . bsToHexUpper . unpack -- FIXME: read-show instance Read EightOctetKeyId where readsPrec _ = map ((EightOctetKeyId . BL.pack *** concat) . unzip) . chunksOf 8 . hexToW8s instance Hashable EightOctetKeyId instance A.ToJSON EightOctetKeyId where toJSON e = object [T.pack "eoki" .= (bsToHexUpper . unpack) e] instance A.FromJSON EightOctetKeyId where parseJSON (A.Object v) = EightOctetKeyId . read <$> v A..: T.pack "eoki" parseJSON _ = mzero newtype NotationName = NotationName {unNotationName :: ByteString} deriving (Data, Eq, Generic, Hashable, Ord, Pretty, Show, Typeable) instance Newtype NotationName ByteString where pack = NotationName unpack (NotationName nn) = nn instance A.ToJSON NotationName where toJSON nn = object [T.pack "notationname" .= show (unpack nn)] instance A.FromJSON NotationName where parseJSON (A.Object v) = NotationName . read <$> v A..: T.pack "notationname" parseJSON _ = mzero newtype NotationValue = NotationValue {unNotationValue :: ByteString} deriving (Data, Eq, Generic, Hashable, Ord, Pretty, Show, Typeable) instance Newtype NotationValue ByteString where pack = NotationValue unpack (NotationValue nv) = nv instance A.ToJSON NotationValue where toJSON nv = object [T.pack "notationvalue" .= show (unpack nv)] instance A.FromJSON NotationValue where parseJSON (A.Object v) = NotationValue . read <$> v A..: T.pack "notationvalue" parseJSON _ = mzero data HashAlgorithm = DeprecatedMD5 | SHA1 | RIPEMD160 | SHA256 | SHA384 | SHA512 | SHA224 | OtherHA Word8 deriving (Data, Generic, Show, Typeable) instance Eq HashAlgorithm where (==) a b = fromFVal a == fromFVal b instance Ord HashAlgorithm where compare = comparing fromFVal instance FutureVal HashAlgorithm where fromFVal DeprecatedMD5 = 1 fromFVal SHA1 = 2 fromFVal RIPEMD160 = 3 fromFVal SHA256 = 8 fromFVal SHA384 = 9 fromFVal SHA512 = 10 fromFVal SHA224 = 11 fromFVal (OtherHA o) = o toFVal 1 = DeprecatedMD5 toFVal 2 = SHA1 toFVal 3 = RIPEMD160 toFVal 8 = SHA256 toFVal 9 = SHA384 toFVal 10 = SHA512 toFVal 11 = SHA224 toFVal o = OtherHA o instance Hashable HashAlgorithm instance Pretty HashAlgorithm where pretty DeprecatedMD5 = text "(deprecated) MD5" pretty SHA1 = text "SHA-1" pretty RIPEMD160 = text "RIPEMD-160" pretty SHA256 = text "SHA-256" pretty SHA384 = text "SHA-384" pretty SHA512 = text "SHA-512" pretty SHA224 = text "SHA-224" pretty (OtherHA ha) = text "unknown hash algorithm type" <+> pretty ha $(ATH.deriveJSON ATH.defaultOptions ''HashAlgorithm) data CompressionAlgorithm = Uncompressed | ZIP | ZLIB | BZip2 | OtherCA Word8 deriving (Show, Data, Generic, Typeable) instance Eq CompressionAlgorithm where (==) a b = fromFVal a == fromFVal b instance Ord CompressionAlgorithm where compare = comparing fromFVal instance FutureVal CompressionAlgorithm where fromFVal Uncompressed = 0 fromFVal ZIP = 1 fromFVal ZLIB = 2 fromFVal BZip2 = 3 fromFVal (OtherCA o) = o toFVal 0 = Uncompressed toFVal 1 = ZIP toFVal 2 = ZLIB toFVal 3 = BZip2 toFVal o = OtherCA o instance Hashable CompressionAlgorithm instance Pretty CompressionAlgorithm where pretty Uncompressed = text "uncompressed" pretty ZIP = text "ZIP" pretty ZLIB = text "zlib" pretty BZip2 = text "bzip2" pretty (OtherCA ca) = text "unknown compression algorithm type" <+> pretty ca $(ATH.deriveJSON ATH.defaultOptions ''CompressionAlgorithm) data KSPFlag = NoModify | KSPOther Int deriving (Data, Generic, Show, Typeable) instance Eq KSPFlag where (==) a b = fromFFlag a == fromFFlag b instance Ord KSPFlag where compare = comparing fromFFlag instance FutureFlag KSPFlag where fromFFlag NoModify = 0 fromFFlag (KSPOther i) = fromIntegral i toFFlag 0 = NoModify toFFlag i = KSPOther (fromIntegral i) instance Hashable KSPFlag instance Pretty KSPFlag where pretty NoModify = text "no-modify" pretty (KSPOther o) = text "unknown keyserver preference flag type" <+> pretty o $(ATH.deriveJSON ATH.defaultOptions ''KSPFlag) data KeyFlag = GroupKey | AuthKey | SplitKey | EncryptStorageKey | EncryptCommunicationsKey | SignDataKey | CertifyKeysKey | KFOther Int deriving (Data, Generic, Show, Typeable) instance Eq KeyFlag where (==) a b = fromFFlag a == fromFFlag b instance Ord KeyFlag where compare = comparing fromFFlag instance FutureFlag KeyFlag where fromFFlag GroupKey = 0 fromFFlag AuthKey = 2 fromFFlag SplitKey = 3 fromFFlag EncryptStorageKey = 4 fromFFlag EncryptCommunicationsKey = 5 fromFFlag SignDataKey = 6 fromFFlag CertifyKeysKey = 7 fromFFlag (KFOther i) = fromIntegral i toFFlag 0 = GroupKey toFFlag 2 = AuthKey toFFlag 3 = SplitKey toFFlag 4 = EncryptStorageKey toFFlag 5 = EncryptCommunicationsKey toFFlag 6 = SignDataKey toFFlag 7 = CertifyKeysKey toFFlag i = KFOther (fromIntegral i) instance Hashable KeyFlag instance Pretty KeyFlag where pretty GroupKey = text "group" pretty AuthKey = text "auth" pretty SplitKey = text "split" pretty EncryptStorageKey = text "encrypt-storage" pretty EncryptCommunicationsKey = text "encrypt-communications" pretty SignDataKey = text "sign-data" pretty CertifyKeysKey = text "certify-keys" pretty (KFOther o) = text "unknown key flag type" <+> pretty o $(ATH.deriveJSON ATH.defaultOptions ''KeyFlag) data RevocationCode = NoReason | KeySuperseded | KeyMaterialCompromised | KeyRetiredAndNoLongerUsed | UserIdInfoNoLongerValid | RCoOther Word8 deriving (Data, Generic, Show, Typeable) instance Eq RevocationCode where (==) a b = fromFVal a == fromFVal b instance Ord RevocationCode where compare = comparing fromFVal instance FutureVal RevocationCode where fromFVal NoReason = 0 fromFVal KeySuperseded = 1 fromFVal KeyMaterialCompromised = 2 fromFVal KeyRetiredAndNoLongerUsed = 3 fromFVal UserIdInfoNoLongerValid = 32 fromFVal (RCoOther o) = o toFVal 0 = NoReason toFVal 1 = KeySuperseded toFVal 2 = KeyMaterialCompromised toFVal 3 = KeyRetiredAndNoLongerUsed toFVal 32 = UserIdInfoNoLongerValid toFVal o = RCoOther o instance Hashable RevocationCode instance Pretty RevocationCode where pretty NoReason = text "no reason" pretty KeySuperseded = text "key superseded" pretty KeyMaterialCompromised = text "key material compromised" pretty KeyRetiredAndNoLongerUsed = text "key retired and no longer used" pretty UserIdInfoNoLongerValid = text "user-ID info no longer valid" pretty (RCoOther o) = text "unknown revocation code" <+> pretty o $(ATH.deriveJSON ATH.defaultOptions ''RevocationCode) data FeatureFlag = ModificationDetection | FeatureOther Int deriving (Data, Generic, Show, Typeable) instance Eq FeatureFlag where (==) a b = fromFFlag a == fromFFlag b instance Ord FeatureFlag where compare = comparing fromFFlag instance FutureFlag FeatureFlag where fromFFlag ModificationDetection = 7 fromFFlag (FeatureOther i) = fromIntegral i toFFlag 7 = ModificationDetection toFFlag i = FeatureOther (fromIntegral i) instance Hashable FeatureFlag instance Hashable a => Hashable (Set a) where hashWithSalt salt = hashWithSalt salt . Set.toList instance Pretty FeatureFlag where pretty ModificationDetection = text "modification-detection" pretty (FeatureOther o) = text "unknown feature flag type" <+> pretty o $(ATH.deriveJSON ATH.defaultOptions ''FeatureFlag) newtype URL = URL {unURL :: URI} deriving (Data, Eq, Generic, Ord, Show, Typeable) instance Newtype URL URI where pack = URL unpack (URL o) = o instance Hashable URL where hashWithSalt salt (URL (URI s a p q f)) = salt `hashWithSalt` s `hashWithSalt` show a `hashWithSalt` p `hashWithSalt` q `hashWithSalt` f instance Pretty URL where pretty = pretty . (\uri -> uriToString id uri "") . unpack instance A.ToJSON URL where toJSON u = object [T.pack "uri" .= (\uri -> uriToString id uri "") (unpack u)] instance A.FromJSON URL where parseJSON (A.Object v) = URL . fromMaybe nullURI . parseURI <$> v A..: T.pack "uri" parseJSON _ = mzero data SigType = BinarySig | CanonicalTextSig | StandaloneSig | GenericCert | PersonaCert | CasualCert | PositiveCert | SubkeyBindingSig | PrimaryKeyBindingSig | SignatureDirectlyOnAKey | KeyRevocationSig | SubkeyRevocationSig | CertRevocationSig | TimestampSig | ThirdPartyConfirmationSig | OtherSig Word8 deriving (Data, Generic, Show, Typeable) instance Eq SigType where (==) a b = fromFVal a == fromFVal b instance Ord SigType where compare = comparing fromFVal instance FutureVal SigType where fromFVal BinarySig = 0x00 fromFVal CanonicalTextSig = 0x01 fromFVal StandaloneSig = 0x02 fromFVal GenericCert = 0x10 fromFVal PersonaCert = 0x11 fromFVal CasualCert = 0x12 fromFVal PositiveCert = 0x13 fromFVal SubkeyBindingSig = 0x18 fromFVal PrimaryKeyBindingSig = 0x19 fromFVal SignatureDirectlyOnAKey = 0x1F fromFVal KeyRevocationSig = 0x20 fromFVal SubkeyRevocationSig = 0x28 fromFVal CertRevocationSig = 0x30 fromFVal TimestampSig = 0x40 fromFVal ThirdPartyConfirmationSig = 0x50 fromFVal (OtherSig o) = o toFVal 0x00 = BinarySig toFVal 0x01 = CanonicalTextSig toFVal 0x02 = StandaloneSig toFVal 0x10 = GenericCert toFVal 0x11 = PersonaCert toFVal 0x12 = CasualCert toFVal 0x13 = PositiveCert toFVal 0x18 = SubkeyBindingSig toFVal 0x19 = PrimaryKeyBindingSig toFVal 0x1F = SignatureDirectlyOnAKey toFVal 0x20 = KeyRevocationSig toFVal 0x28 = SubkeyRevocationSig toFVal 0x30 = CertRevocationSig toFVal 0x40 = TimestampSig toFVal 0x50 = ThirdPartyConfirmationSig toFVal o = OtherSig o instance Hashable SigType instance Pretty SigType where pretty BinarySig = text "binary" pretty CanonicalTextSig = text "canonical-text" pretty StandaloneSig = text "standalone" pretty GenericCert = text "generic" pretty PersonaCert = text "persona" pretty CasualCert = text "casual" pretty PositiveCert = text "positive" pretty SubkeyBindingSig = text "subkey-binding" pretty PrimaryKeyBindingSig = text "primary-key-binding" pretty SignatureDirectlyOnAKey = text "signature directly on a key" pretty KeyRevocationSig = text "key-revocation" pretty SubkeyRevocationSig = text "subkey-revocation" pretty CertRevocationSig = text "cert-revocation" pretty TimestampSig = text "timestamp" pretty ThirdPartyConfirmationSig = text "third-party-confirmation" pretty (OtherSig o) = text "unknown signature type" <+> pretty o $(ATH.deriveJSON ATH.defaultOptions ''SigType) newtype MPI = MPI {unMPI :: Integer} deriving (Data, Eq, Generic, Show, Typeable) instance Newtype MPI Integer where pack = MPI unpack (MPI o) = o instance Hashable MPI instance Pretty MPI where pretty = pretty . unpack $(ATH.deriveJSON ATH.defaultOptions ''MPI) data SignaturePayload = SigV3 SigType ThirtyTwoBitTimeStamp EightOctetKeyId PubKeyAlgorithm HashAlgorithm Word16 (NonEmpty MPI) | SigV4 SigType PubKeyAlgorithm HashAlgorithm [SigSubPacket] [SigSubPacket] Word16 (NonEmpty MPI) | SigVOther Word8 ByteString deriving (Data, Eq, Generic, Show, Typeable) instance Hashable SignaturePayload instance Pretty SignaturePayload where pretty (SigV3 st ts eoki pka ha w16 mpis) = text "signature v3" <> char ':' <+> pretty st <+> pretty ts <+> pretty eoki <+> pretty pka <+> pretty ha <+> pretty w16 <+> (pretty . NE.toList) mpis pretty (SigV4 st pka ha hsps usps w16 mpis) = text "signature v4" <> char ':' <+> pretty st <+> pretty pka <+> pretty ha <+> pretty hsps <+> pretty usps <+> pretty w16 <+> (pretty . NE.toList) mpis pretty (SigVOther t bs) = text "unknown signature v" <> pretty t <> char ':' <+> pretty (BL.unpack bs) instance A.ToJSON SignaturePayload where toJSON (SigV3 st ts eoki pka ha w16 mpis) = A.toJSON (st, ts, eoki, pka, ha, w16, NE.toList mpis) toJSON (SigV4 st pka ha hsps usps w16 mpis) = A.toJSON (st, pka, ha, hsps, usps, w16, NE.toList mpis) toJSON (SigVOther t bs) = A.toJSON (t, BL.unpack bs) data SigSubPacketPayload = SigCreationTime ThirtyTwoBitTimeStamp | SigExpirationTime ThirtyTwoBitDuration | ExportableCertification Exportability | TrustSignature TrustLevel TrustAmount | RegularExpression AlmostPublicDomainRegex | Revocable Revocability | KeyExpirationTime ThirtyTwoBitDuration | PreferredSymmetricAlgorithms [SymmetricAlgorithm] | RevocationKey (Set RevocationClass) PubKeyAlgorithm TwentyOctetFingerprint | Issuer EightOctetKeyId | NotationData (Set NotationFlag) NotationName NotationValue | PreferredHashAlgorithms [HashAlgorithm] | PreferredCompressionAlgorithms [CompressionAlgorithm] | KeyServerPreferences (Set KSPFlag) | PreferredKeyServer KeyServer | PrimaryUserId Bool | PolicyURL URL | KeyFlags (Set KeyFlag) | SignersUserId Text | ReasonForRevocation RevocationCode RevocationReason | Features (Set FeatureFlag) | SignatureTarget PubKeyAlgorithm HashAlgorithm SignatureHash | EmbeddedSignature SignaturePayload | UserDefinedSigSub Word8 ByteString | OtherSigSub Word8 ByteString deriving (Data, Eq, Generic, Show, Typeable) -- FIXME instance Hashable SigSubPacketPayload instance Pretty SigSubPacketPayload where pretty (SigCreationTime ts) = text "creation-time" <+> pretty ts pretty (SigExpirationTime d) = text "sig expiration time" <+> pretty d pretty (ExportableCertification e) = text "exportable certification" <+> pretty e pretty (TrustSignature tl ta) = text "trust signature" <+> pretty tl <+> pretty ta pretty (RegularExpression apdre) = text "regular expression" <+> pretty apdre pretty (Revocable r) = text "revocable" <+> pretty r pretty (KeyExpirationTime d) = text "key expiration time" <+> pretty d pretty (PreferredSymmetricAlgorithms sas) = text "preferred symmetric algorithms" <+> pretty sas pretty (RevocationKey rcs pka tof) = text "revocation key" <+> pretty (Set.toList rcs) <+> pretty pka <+> pretty tof pretty (Issuer eoki) = text "issuer" <+> pretty eoki pretty (NotationData nfs nn nv) = text "notation data" <+> pretty (Set.toList nfs) <+> pretty nn <+> pretty nv pretty (PreferredHashAlgorithms phas) = text "preferred hash algorithms" <+> pretty phas pretty (PreferredCompressionAlgorithms pcas) = text "preferred compression algorithms" <+> pretty pcas pretty (KeyServerPreferences kspfs) = text "keyserver preferences" <+> pretty (Set.toList kspfs) pretty (PreferredKeyServer ks) = text "preferred keyserver" <+> pretty ks pretty (PrimaryUserId p) = (if p then mempty else text "NOT ") <> text "primary user-ID" pretty (PolicyURL u) = text "policy URL" <+> pretty u pretty (KeyFlags kfs) = text "key flags" <+> pretty (Set.toList kfs) pretty (SignersUserId u) = text "signer's user-ID" <+> pretty u pretty (ReasonForRevocation rc rr) = text "reason for revocation" <+> pretty rc <+> pretty rr pretty (Features ffs) = text "features" <+> pretty (Set.toList ffs) pretty (SignatureTarget pka ha sh) = text "signature target" <+> pretty pka <+> pretty ha <+> pretty sh pretty (EmbeddedSignature sp) = text "embedded signature" <+> pretty sp pretty (UserDefinedSigSub t bs) = text "user-defined signature subpacket type" <+> pretty t <+> pretty (BL.unpack bs) pretty (OtherSigSub t bs) = text "unknown signature subpacket type" <+> pretty t <+> pretty bs instance A.ToJSON SigSubPacketPayload where toJSON (SigCreationTime ts) = object [T.pack "sigCreationTime" .= ts] toJSON (SigExpirationTime d) = object [T.pack "sigExpirationTime" .= d] toJSON (ExportableCertification e) = object [T.pack "exportableCertification" .= e] toJSON (TrustSignature tl ta) = object [T.pack "trustSignature" .= (tl, ta)] toJSON (RegularExpression apdre) = object [T.pack "regularExpression" .= BL.unpack apdre] toJSON (Revocable r) = object [T.pack "revocable" .= r] toJSON (KeyExpirationTime d) = object [T.pack "keyExpirationTime" .= d] toJSON (PreferredSymmetricAlgorithms sas) = object [T.pack "preferredSymmetricAlgorithms" .= sas] toJSON (RevocationKey rcs pka tof) = object [T.pack "revocationKey" .= (rcs, pka, tof)] toJSON (Issuer eoki) = object [T.pack "issuer" .= eoki] toJSON (NotationData nfs (NotationName nn) (NotationValue nv)) = object [T.pack "notationData" .= (nfs, BL.unpack nn, BL.unpack nv)] toJSON (PreferredHashAlgorithms phas) = object [T.pack "preferredHashAlgorithms" .= phas] toJSON (PreferredCompressionAlgorithms pcas) = object [T.pack "preferredCompressionAlgorithms" .= pcas] toJSON (KeyServerPreferences kspfs) = object [T.pack "keyServerPreferences" .= kspfs] toJSON (PreferredKeyServer ks) = object [T.pack "preferredKeyServer" .= show ks] toJSON (PrimaryUserId p) = object [T.pack "primaryUserId" .= p] toJSON (PolicyURL u) = object [T.pack "policyURL" .= u] toJSON (KeyFlags kfs) = object [T.pack "keyFlags" .= kfs] toJSON (SignersUserId u) = object [T.pack "signersUserId" .= u] toJSON (ReasonForRevocation rc rr) = object [T.pack "reasonForRevocation" .= (rc, rr)] toJSON (Features ffs) = object [T.pack "features" .= ffs] toJSON (SignatureTarget pka ha sh) = object [T.pack "signatureTarget" .= (pka, ha, BL.unpack sh)] toJSON (EmbeddedSignature sp) = object [T.pack "embeddedSignature" .= sp] toJSON (UserDefinedSigSub t bs) = object [T.pack "userDefinedSigSub" .= (t, BL.unpack bs)] toJSON (OtherSigSub t bs) = object [T.pack "otherSigSub" .= (t, BL.unpack bs)] uc3 :: (a -> b -> c -> d) -> (a, b, c) -> d uc3 f ~(a,b,c) = f a b c instance A.FromJSON SigSubPacketPayload where parseJSON (A.Object v) = (SigCreationTime <$> v A..: T.pack "sigCreationTime") <|> (SigExpirationTime <$> v A..: T.pack "sigExpirationTime") <|> (ExportableCertification <$> v A..: T.pack "exportableCertification") <|> (uncurry TrustSignature <$> v A..: T.pack "trustSignature") <|> (RegularExpression . BL.pack <$> v A..: T.pack "regularExpression") <|> (Revocable <$> v A..: T.pack "revocable") <|> (KeyExpirationTime <$> v A..: T.pack "keyExpirationTime") <|> (PreferredSymmetricAlgorithms <$> v A..: T.pack "preferredSymmetricAlgorithms") <|> (uc3 RevocationKey <$> v A..: T.pack "revocationKey") <|> (Issuer <$> v A..: T.pack "issuer") <|> (uc3 NotationData <$> v A..: T.pack "notationData") parseJSON _ = mzero data SigSubPacket = SigSubPacket { _sspCriticality :: Bool , _sspPayload :: SigSubPacketPayload } deriving (Data, Eq, Generic, Show, Typeable) instance Pretty SigSubPacket where pretty x = (if _sspCriticality x then char '*' else mempty) <> (pretty . _sspPayload) x instance Hashable SigSubPacket $(ATH.deriveJSON ATH.defaultOptions ''SigSubPacket) $(makeLenses ''SigSubPacket) data KeyVersion = DeprecatedV3 | V4 deriving (Data, Eq, Generic, Ord, Show, Typeable) instance Hashable KeyVersion instance Pretty KeyVersion where pretty DeprecatedV3 = text "(deprecated) v3" pretty V4 = text "v4" $(ATH.deriveJSON ATH.defaultOptions ''KeyVersion) newtype IV = IV {unIV :: B.ByteString} deriving (ByteArrayAccess, Data, Eq, Generic, Hashable, Semigroup, Monoid, Show, Typeable) instance Newtype IV B.ByteString where pack = IV unpack (IV o) = o instance Pretty IV where pretty = pretty . ("iv:"++) . bsToHexUpper . BL.fromStrict . unpack instance A.ToJSON IV where toJSON = A.toJSON . show . unpack data DataType = BinaryData | TextData | UTF8Data | OtherData Word8 deriving (Show, Data, Generic, Typeable) instance Hashable DataType instance Eq DataType where (==) a b = fromFVal a == fromFVal b instance Ord DataType where compare = comparing fromFVal instance FutureVal DataType where fromFVal BinaryData = fromIntegral . fromEnum $ 'b' fromFVal TextData = fromIntegral . fromEnum $ 't' fromFVal UTF8Data = fromIntegral . fromEnum $ 'u' fromFVal (OtherData o) = o toFVal 0x62 = BinaryData toFVal 0x74 = TextData toFVal 0x75 = UTF8Data toFVal o = OtherData o instance Pretty DataType where pretty BinaryData = text "binary" pretty TextData = text "text" pretty UTF8Data = text "UTF-8" pretty (OtherData o) = text "other data type " <+> pretty o $(ATH.deriveJSON ATH.defaultOptions ''DataType) newtype Salt = Salt {unSalt :: B.ByteString} deriving (Data, Eq, Generic, Hashable, Show, Typeable) instance Newtype Salt B.ByteString where pack = Salt unpack (Salt o) = o instance Pretty Salt where pretty = pretty . ("salt:"++) . bsToHexUpper . BL.fromStrict . unpack instance A.ToJSON Salt where toJSON = A.toJSON . show . unpack newtype IterationCount = IterationCount {unIterationCount :: Int} deriving (Bounded, Data, Enum, Eq, Generic, Hashable, Integral, Num, Ord, Real, Show, Typeable) instance Newtype IterationCount Int where pack = IterationCount unpack (IterationCount o) = o instance Pretty IterationCount where pretty = pretty . unpack $(ATH.deriveJSON ATH.defaultOptions ''IterationCount) data S2K = Simple HashAlgorithm | Salted HashAlgorithm Salt | IteratedSalted HashAlgorithm Salt IterationCount | OtherS2K Word8 ByteString deriving (Data, Eq, Generic, Show, Typeable) instance Hashable S2K instance Pretty S2K where pretty (Simple ha) = text "simple S2K," <+> pretty ha pretty (Salted ha salt) = text "salted S2K," <+> pretty ha <+> pretty salt pretty (IteratedSalted ha salt icount) = text "iterated-salted S2K," <+> pretty ha <+> pretty salt <+> pretty icount pretty (OtherS2K t bs) = text "unknown S2K type" <+> pretty t <+> pretty (bsToHexUpper bs) instance A.ToJSON S2K where toJSON (Simple ha) = A.toJSON ha toJSON (Salted ha salt) = A.toJSON (ha, salt) toJSON (IteratedSalted ha salt icount) = A.toJSON (ha, salt, icount) toJSON (OtherS2K t bs) = A.toJSON (t, BL.unpack bs) data ImageFormat = JPEG | OtherImage Word8 deriving (Data, Generic, Show, Typeable) instance Eq ImageFormat where (==) a b = fromFVal a == fromFVal b instance Ord ImageFormat where compare = comparing fromFVal instance FutureVal ImageFormat where fromFVal JPEG = 1 fromFVal (OtherImage o) = o toFVal 1 = JPEG toFVal o = OtherImage o instance Hashable ImageFormat instance Pretty ImageFormat where pretty JPEG = text "JPEG" pretty (OtherImage o) = text "unknown image format" <+> pretty o $(ATH.deriveJSON ATH.defaultOptions ''ImageFormat) data ImageHeader = ImageHV1 ImageFormat deriving (Data, Eq, Generic, Show, Typeable) instance Ord ImageHeader where compare (ImageHV1 a) (ImageHV1 b) = compare a b instance Hashable ImageHeader instance Pretty ImageHeader where pretty (ImageHV1 f) = text "imghdr v1" <+> pretty f $(ATH.deriveJSON ATH.defaultOptions ''ImageHeader) data UserAttrSubPacket = ImageAttribute ImageHeader ImageData | OtherUASub Word8 ByteString deriving (Data, Eq, Generic, Show, Typeable) instance Hashable UserAttrSubPacket instance Ord UserAttrSubPacket where compare (ImageAttribute h1 d1) (ImageAttribute h2 d2) = compare h1 h2 <> compare d1 d2 compare (ImageAttribute _ _) (OtherUASub _ _) = LT compare (OtherUASub _ _) (ImageAttribute _ _) = GT compare (OtherUASub t1 b1) (OtherUASub t2 b2) = compare t1 t2 <> compare b1 b2 instance Pretty UserAttrSubPacket where pretty (ImageAttribute ih d) = text "image-attribute" <+> pretty ih <+> pretty (BL.unpack d) pretty (OtherUASub t bs) = text "unknown attribute type" <> pretty t <+> pretty (BL.unpack bs) instance A.ToJSON UserAttrSubPacket where toJSON (ImageAttribute ih d) = A.toJSON (ih, BL.unpack d) toJSON (OtherUASub t bs) = A.toJSON (t, BL.unpack bs) data ECCCurve = BrokenNISTP256 | BrokenNISTP384 | BrokenNISTP521 deriving (Data, Eq, Generic, Ord, Show, Typeable) instance Hashable ECCCurve newtype Block a = Block {unBlock :: [a]} -- so we can override cereal instance deriving (Show, Eq)