-- hokey.hs: hOpenPGP key tool -- Copyright © 2013-2022 Clint Adams -- -- vim: softtabstop=4:shiftwidth=4:expandtab -- -- This program is free software: you can redistribute it and/or modify -- it under the terms of the GNU Affero General Public License as -- published by the Free Software Foundation, either version 3 of the -- License, or (at your option) any later version. -- -- This program is distributed in the hope that it will be useful, -- but WITHOUT ANY WARRANTY; without even the implied warranty of -- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the -- GNU Affero General Public License for more details. -- -- You should have received a copy of the GNU Affero General Public License -- along with this program. If not, see . {-# LANGUAGE DeriveFunctor #-} {-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE TypeApplications #-} import Codec.Encryption.OpenPGP.Expirations (getKeyExpirationTimesFromSignature) import Codec.Encryption.OpenPGP.Fingerprint (eightOctetKeyID, fingerprint) import Codec.Encryption.OpenPGP.KeyInfo (pkalgoAbbrev, pubkeySize) import Codec.Encryption.OpenPGP.KeySelection (parseFingerprint) import Codec.Encryption.OpenPGP.Ontology ( isCT , isCertRevocationSig , isKUF , isPHA , isPKBindingSig , isSKBindingSig ) import Codec.Encryption.OpenPGP.Serialize () import Codec.Encryption.OpenPGP.Types import Control.Arrow ((***)) import Control.Error.Util (hush) import Control.Lens ((&), (^.), _1, _2, mapped, over) import Control.Monad.Trans.Except (runExceptT) import Control.Monad.Trans.Writer.Lazy (execWriter, tell) import qualified Crypto.Hash as CH import qualified Crypto.Hash.Algorithms as CHA import qualified Data.Aeson as A import Data.Binary (get, put) import qualified Data.ByteArray as BA import qualified Data.ByteString as B import qualified Data.ByteString.Base16 as Base16 import qualified Data.ByteString.Char8 as BC8 import qualified Data.ByteString.Lazy as BL import Data.Conduit ((.|), runConduitRes) import qualified Data.Conduit.Binary as CB import qualified Data.Conduit.List as CL import Data.Conduit.OpenPGP.Keyring (conduitToTKsDropping) import Data.Conduit.Serialization.Binary (conduitGet, conduitPut) import Data.Foldable (find) import Data.List (elemIndex, findIndex, intercalate, nub, sort, sortOn) import qualified Data.Map as Map import Data.Maybe (fromMaybe, listToMaybe, mapMaybe) import Data.Ord (Down(..)) import Data.Semigroup (Semigroup, (<>)) import qualified Data.Set as Set import Data.Text (Text) import qualified Data.Text as T import Data.Time.Clock.POSIX (POSIXTime, getPOSIXTime, posixSecondsToUTCTime) import Data.Time.Format (formatTime) import qualified Data.Yaml as Y import GHC.Generics import HOpenPGP.Tools.Common (banner, versioner, warranty) import HOpenPGP.Tools.HKP (FetchValidationMethod(..), fetchKeys, rearmorKeys) import HOpenPGP.Tools.TKUtils (processTK) import Options.Applicative.Builder ( argument , auto , command , eitherReader , footerDoc , headerDoc , help , helpDoc , info , long , metavar , option , prefs , progDesc , showDefault , showHelpOnError , str , value ) import Options.Applicative.Extra (customExecParser, helper, hsubparser) import Options.Applicative.Types (Parser) import Data.Time.Locale.Compat (defaultTimeLocale) import System.IO ( BufferMode(..) , Handle , hFlush , hPutStrLn , hSetBuffering , stderr , stdin , stdout ) import Prettyprinter.Convert.AnsiWlPprint (toAnsiWlPprint) import Prettyprinter ( Doc , (<+>) , annotate , colon , flatAlt , hardline , indent , line , list , pretty ) import qualified Prettyprinter.Render.Terminal as PPA linebreak = flatAlt line mempty green = annotate (PPA.color PPA.Green) yellow = annotate (PPA.color PPA.Yellow) red = annotate (PPA.color PPA.Red) data KAS = KAS { pubkeyalgo :: Colored PubKeyAlgorithm , pubkeysize :: Colored (Maybe Int) , stringrep :: String } deriving (Generic) data Color = Green | Yellow | Red deriving (Eq, Generic, Ord) data Colored a = Colored { color :: Maybe Color , explanation :: Maybe String , val :: a } deriving (Functor, Generic) newtype FakeMap a b = FakeMap { unFakeMap :: [(a, b)] } data KeyReport = KeyReport { keyStatus :: String , keyFingerprint :: TwentyOctetFingerprint , keyVer :: Colored KeyVersion , keyCreationTime :: ThirtyTwoBitTimeStamp , keyAlgorithmAndSize :: KAS , keyUIDsAndUAts :: FakeMap Text (Colored UIDReport) , keyBestOf :: Maybe UIDReport , keySubkeys :: [SubkeyReport] , keyHasEncryptionCapableSubkey :: Colored Bool } deriving (Generic) data UIDReport = UIDReport { uidSelfSigHashAlgorithms :: [Colored HashAlgorithm] , uidPreferredHashAlgorithms :: [Colored [HashAlgorithm]] , uidKeyExpirationTimes :: [Colored [ThirtyTwoBitDuration]] , uidKeyUsageFlags :: [Colored (Set.Set KeyFlag)] , uidRevocationStatus :: [RevocationStatus] } deriving (Generic) data SubkeyReport = SubkeyReport { skFingerprint :: Colored TwentyOctetFingerprint , skVer :: Colored KeyVersion , skCreationTime :: ThirtyTwoBitTimeStamp , skAlgorithmAndSize :: KAS , skBindingSigHashAlgorithms :: [Colored HashAlgorithm] , skUsageFlags :: [Colored (Set.Set KeyFlag)] , skCrossCerts :: CrossCertReport } deriving (Generic) data CrossCertReport = CrossCertReport { ccPresent :: Colored Bool , ccHashAlgorithms :: [Colored HashAlgorithm] } deriving (Generic) data RevocationStatus = RevocationStatus { isRevoked :: Bool , revocationCode :: String , revocationReason :: Text } deriving (Generic) instance A.ToJSON KAS instance A.ToJSON Color instance (A.ToJSON a) => A.ToJSON (Colored a) instance A.ToJSON KeyReport instance A.ToJSON UIDReport instance A.ToJSON SubkeyReport instance A.ToJSON CrossCertReport instance A.ToJSON b => A.ToJSON (FakeMap Text b) where toJSON = A.toJSON . Map.fromList . unFakeMap instance A.ToJSON RevocationStatus instance Semigroup UIDReport where (<>) (UIDReport a b c d e) (UIDReport a' b' c' d' e') = UIDReport (a <> a') (b <> b') (c <> c') (d <> d') (e <> e') instance Monoid UIDReport where mempty = UIDReport [] [] [] [] [] mappend = (<>) checkKey :: Maybe POSIXTime -> TK -> KeyReport checkKey mpt key = (\x -> x { keyBestOf = populateBestOf x , keyHasEncryptionCapableSubkey = hasEncryptionCapableSubkey (concatMap skUsageFlags (keySubkeys x)) }) KeyReport { keyStatus = either id (const "good") processedTK , keyFingerprint = key ^. tkKey . _1 & fingerprint , keyVer = key ^. tkKey . _1 . keyVersion & colorizeKV , keyCreationTime = key ^. tkKey . _1 . timestamp , keyAlgorithmAndSize = kasIt (key ^. tkKey . _1) , keyUIDsAndUAts = FakeMap (map (\(x, y) -> (x, uidr (Just x) y)) (processedOrOrig ^. tkUIDs) ++ map (uatspsToText *** uidr Nothing) (processedOrOrig ^. tkUAts)) , keyBestOf = Nothing , keySubkeys = map (checkSK (key ^. tkKey . _1 & fingerprint)) (key ^. tkSubs) , keyHasEncryptionCapableSubkey = Colored Nothing Nothing False } where processedOrOrig = either (const key) id processedTK processedTK = processTK mpt key kasIt :: PKPayload -> KAS kasIt pkp = kasIt' (pkp ^. pkalgo) (pkp ^. pubkey & pubkeySize) kasIt' :: PubKeyAlgorithm -> Either String Int -> KAS kasIt' pka epks = KAS { pubkeyalgo = colorizePKA pka , pubkeysize = colorizePKS pka epks , stringrep = (either (const "unknown") show epks) ++ (pkalgoAbbrev pka) } colorizeKV kv = uncurry Colored (if kv == V4 then (Just Green, Nothing) else (Just Red, Just "not a V4 key")) kv colorizePKA pka | pka `elem` [RSA, EdDSA, ECDH] = Colored (Just Green) Nothing pka | otherwise = Colored (Just Yellow) (Just "public key algorithm neither RSA nor EdDSA") pka colorizePKS pka epks = uncurry Colored (colorizePKS' pka epks) (hush epks) colorizePKS' pka (Right pks) | pka `elem` [EdDSA, ECDH] && pks >= 256 = (Just Green, Nothing) | pka `elem` [EdDSA, ECDH] = (Just Yellow, Just "Public key size under 256 bits") | pka == RSA && pks >= 3072 = (Just Green, Nothing) | pka == RSA && pks >= 2048 = (Just Yellow, Just "Public key size between 2048 and 3072 bits") | pka == RSA = (Just Red, Just "Public key size under 2048 bits") | otherwise = (Nothing, Nothing) colorizePKS' _ (Left _) = (Just Red, Just "public key algorithm not understood") colorizePHAs x = uncurry Colored (if fSHA2Family x < ei DeprecatedMD5 x && fSHA2Family x < ei SHA1 x then (Just Green, Nothing) else (Just Red, Just "weak hash with higher preference")) x fSHA2Family = fi (`elem` [SHA512, SHA384, SHA256, SHA224]) ei x y = fromMaybe maxBound (elemIndex x y) fi x y = fromMaybe maxBound (findIndex x y) colorizeKETs ct ts kes | null kes = Colored (Just Red) (Just "no expiration set") kes | any (\ke -> realToFrac ts + realToFrac ke < ct) kes = Colored (Just Red) (Just "expiration passed") kes | any (\ke -> realToFrac ts + realToFrac ke > ct + (5 * 31557600)) kes = Colored (Just Yellow) (Just "expiration too far in future") kes | otherwise = Colored (Just Green) Nothing kes eoki pkp | pkp ^. keyVersion == V4 = hush . eightOctetKeyID $ pkp | pkp ^. keyVersion == DeprecatedV3 && elem (pkp ^. pkalgo) [RSA, DeprecatedRSASignOnly] = hush . eightOctetKeyID $ pkp | otherwise = Nothing phas (SigV4 _ _ _ xs _ _ _) = colorizePHAs . concatMap (\(SigSubPacket _ (PreferredHashAlgorithms x)) -> x) $ filter isPHA xs phas _ = Colored Nothing Nothing [] has = map (colorizeHA . hashAlgo) . alleged colorizeHA ha = uncurry Colored (if ha `elem` [DeprecatedMD5, SHA1] then (Just Red, Just "weak hash algorithm") else (Nothing, Nothing)) ha sigcts (SigV4 _ _ _ xs _ _ _) = map (\(SigSubPacket _ (SigCreationTime x)) -> x) $ filter isCT xs alleged = filter (\x -> ((==) <$> sigissuer x <*> eoki (key ^. tkKey . _1)) == Just True) uatspsToText = T.pack . uatspsToString uatspsToString us = "" uaspToString (ImageAttribute hdr d) = hdrToString hdr ++ ':' : show (BL.length d) ++ ':' : BC8.unpack (Base16.encode (BA.convert (CH.hashlazy @CHA.SHA3_512 d))) uaspToString (OtherUASub t d) = "other-" ++ show t ++ ':' : show (BL.length d) ++ ':' : BC8.unpack (Base16.encode (BA.convert (CH.hashlazy @CHA.SHA3_512 d))) hdrToString (ImageHV1 JPEG) = "jpeg" hdrToString (ImageHV1 fmt) = "image-" ++ show (fromFVal fmt) uidr Nothing sps = Colored Nothing Nothing (UIDReport (has sps) (map phas sps) (map (colorizeKETs (fromMaybe 0 mpt) (key ^. tkKey . _1 . timestamp & unThirtyTwoBitTimeStamp) . getKeyExpirationTimesFromSignature) sps -- should that be 0? ) (kufs False sps) (findRevocationReason sps)) uidr (Just u) sps = colorizeUID u (UIDReport (has sps) (map phas sps) (map (colorizeKETs (fromMaybe 0 mpt) (key ^. tkKey . _1 . timestamp & unThirtyTwoBitTimeStamp) . getKeyExpirationTimesFromSignature) sps -- should that be 0? ) (kufs False sps) (findRevocationReason sps)) populateBestOf krep = Just (UIDReport <$> best . uidSelfSigHashAlgorithms <*> best . uidPreferredHashAlgorithms <*> best . uidKeyExpirationTimes <*> best . uidKeyUsageFlags <*> pure [] $ mconcat (justTheUIDRs krep)) justTheUIDRs = map (decolorize . snd) . unFakeMap . keyUIDsAndUAts best = take 1 . sortOn color decolorize (Colored _ _ x) = x colorizeUID u | '(' `elem` T.unpack u = Colored (Just Yellow) (Just "parenthesis in uid") -- FIXME: be more discerning | '<' `notElem` T.unpack u = Colored (Just Yellow) (Just "no left angle bracket in uid") -- FIXME: be more discerning | otherwise = Colored Nothing Nothing findRevocationReason = concatMap grabReasons . filter isCertRevocationSig grabReasons (SigV4 CertRevocationSig _ _ has _ _ _) = mapMaybe (grabReasons' . _sspPayload) has grabReasons _ = [] grabReasons' (ReasonForRevocation a b) = Just (RevocationStatus True (show a) b) grabReasons' _ = Nothing kufs s = map (colorizeKUFs s . (\(SigSubPacket _ (KeyFlags x)) -> x) . fromMaybe undefined . find isKUF . hasheds) . newestWith (any isKUF . hasheds) colorizeKUFs False x = uncurry Colored (if (Set.member EncryptStorageKey x || Set.member EncryptCommunicationsKey x) && (Set.member SignDataKey x || Set.member CertifyKeysKey x) then (Just Yellow, Just "both signing & encryption") else (Just Green, Nothing)) x colorizeKUFs True x = uncurry Colored (if Set.member CertifyKeysKey x then (Just Red, Just "certification-capable subkey") else (if (Set.member EncryptStorageKey x || Set.member EncryptCommunicationsKey x) && Set.member SignDataKey x then (Just Yellow, Just "both signing & encryption") else (Just Green, Nothing))) x newestWith p = take 1 . sortOn (Down . take 1 . sigcts) . filter p -- FIXME: this is terrible hasheds (SigV4 _ _ _ xs _ _ _) = xs hasheds _ = [] checkSK :: TwentyOctetFingerprint -> (Pkt, [SignaturePayload]) -> SubkeyReport checkSK pf (PublicSubkeyPkt pkp, sigs) = checkSK' pf pkp sigs checkSK pf (SecretSubkeyPkt pkp _, sigs) = checkSK' pf pkp sigs checkSK' pf pkp sigs = (\x -> x {skCrossCerts = ccr (map decolorize (skUsageFlags x)) sigs}) SubkeyReport { skFingerprint = colorizeF pf (fingerprint pkp) , skVer = colorizeKV (pkp ^. keyVersion) , skCreationTime = pkp ^. timestamp , skAlgorithmAndSize = kasIt pkp , skBindingSigHashAlgorithms = has (filter isSKBindingSig sigs) , skUsageFlags = kufs True (filter isSKBindingSig sigs) , skCrossCerts = CrossCertReport (Colored Nothing Nothing False) [] } hasEncryptionCapableSubkey skrs = if any ((\x -> Set.member EncryptStorageKey x || Set.member EncryptCommunicationsKey x) . decolorize) skrs then Colored (Just Green) Nothing True else Colored (Just Red) (Just "no encryption-capable subkey present") False embeddedSigs = filter isPKBindingSig . concatMap getEmbeds . filter isSKBindingSig getEmbeds (SigV4 _ _ _ xs ys _ _) = concatMap getEmbed (xs ++ ys) getEmbeds _ = [] getEmbed (SigSubPacket _ (EmbeddedSignature sp)) = [sp] getEmbed _ = [] ccr kufs sigs = CrossCertReport (colorES kufs sigs) (map (colorizeHA . hashAlgo) sigs) colorES kufs sigs = case ( null (embeddedSigs sigs) , any (Set.member SignDataKey) kufs , any (Set.member AuthKey) kufs) of (True, True, True) -> Colored (Just Red) (Just "signing- and auth-capable subkey without cross-cert") False (True, True, False) -> Colored (Just Red) (Just "signing-capable subkey without cross-cert") False (True, False, True) -> Colored (Just Yellow) (Just "auth-capable subkey without cross-cert") False (False, True, True) -> Colored (Just Green) Nothing True (False, True, False) -> Colored (Just Green) Nothing True (False, False, True) -> Colored (Just Green) Nothing True (False, False, False) -> Colored Nothing Nothing True (True, _, _) -> Colored Nothing Nothing False colorizeF pf fp = uncurry Colored (if pf == fp then (Just Red, Just "subkey has same fingerprint as primary key") else (Just Green, Nothing)) fp prettyKeyReport :: POSIXTime -> TK -> Doc PPA.AnsiStyle prettyKeyReport cpt key = do let keyReport = checkKey (Just cpt) key execWriter $ tell (linebreak <> pretty "Key has potential validity" <> colon <+> pretty (keyStatus keyReport) <> linebreak <> pretty "Key has fingerprint" <> colon <+> pretty (SpacedFingerprint (keyFingerprint keyReport)) <> linebreak <> pretty "Checking to see if key is OpenPGPv4" <> colon <+> coloredToColor (pretty . show) (keyVer keyReport) <> linebreak <> (\kas -> pretty "Checking the strength of your primary asymmetric key" <> colon <+> coloredToColor pretty (pubkeyalgo kas) <+> coloredToColor (maybe (pretty "unknown") pretty) (pubkeysize kas)) (keyAlgorithmAndSize keyReport) <> linebreak <> pretty "Checking user-ID- and user-attribute-related items" <> colon <> mconcat (map (uidtrip (keyCreationTime keyReport) . gottabeabetterway) (unFakeMap (keyUIDsAndUAts keyReport))) <> linebreak <> pretty "Checking subkeys" <> colon <> linebreak <> indent 2 (pretty "one of the subkeys is encryption-capable" <> colon <+> coloredToColor pretty (keyHasEncryptionCapableSubkey keyReport)) <> mconcat (map subkeyrep (keySubkeys keyReport)) <> linebreak) where coloredToColor f (Colored (Just Green) _ x) = green (f x) coloredToColor f (Colored (Just Yellow) _ x) = yellow (f x) coloredToColor f (Colored (Just Red) _ x) = red (f x) coloredToColor f (Colored Nothing _ x) = f x uidtrip ts (u, ur) | null (uidRevocationStatus ur) = linebreak <> indent 2 (coloredToColor pretty (fmap T.unpack u)) <> colon <> linebreak <> indent 4 (pretty "Self-sig hash algorithms" <> colon <+> (list . map (coloredToColor pretty) . uidSelfSigHashAlgorithms) ur) <> linebreak <> indent 4 (pretty "Preferred hash algorithms" <> colon <+> mconcat (map (coloredToColor pretty) (uidPreferredHashAlgorithms ur))) <> linebreak <> indent 4 (pretty "Key expiration times" <> colon <+> mconcat (map (coloredToColor list . fmap (map (pretty . keyExp ts))) (uidKeyExpirationTimes ur))) <> linebreak <> indent 4 (pretty "Key usage flags" <> colon <+> (list . map (coloredToColor (pretty . Set.toList))) (uidKeyUsageFlags ur)) | otherwise = linebreak <> indent 2 (coloredToColor pretty (fmap T.unpack u)) <> colon <+> pretty "[revoked]" <> linebreak <> indent 4 (pretty "Revocation code" <> colon <+> list (map (pretty . revocationCode) (uidRevocationStatus ur))) <> linebreak <> indent 4 (pretty "Revocation reason" <> colon <+> list (map (pretty . T.unpack . revocationReason) (uidRevocationStatus ur))) keyExp ts ke = (show . pretty) ke ++ " = " ++ formatTime defaultTimeLocale "%c" (posixSecondsToUTCTime (realToFrac ts + realToFrac ke)) gottabeabetterway (a, Colored x y z) = (Colored x y a, z) subkeyrep skr = linebreak <> indent 2 (pretty "fpr" <> colon <+> coloredToColor pretty (fmap SpacedFingerprint (skFingerprint skr))) <> linebreak <> indent 4 (pretty "version" <> colon <+> coloredToColor pretty (skVer skr)) <> linebreak <> indent 4 (pretty "timestamp" <> colon <+> pretty (skCreationTime skr)) <> linebreak <> indent 4 ((\kas -> pretty "algo/size" <> colon <+> coloredToColor pretty (pubkeyalgo kas) <+> coloredToColor (maybe (pretty "unknown") pretty) (pubkeysize kas)) (skAlgorithmAndSize skr)) <> linebreak <> indent 4 (pretty "binding sig hash algorithms" <> colon <+> (list . map (coloredToColor pretty) . skBindingSigHashAlgorithms) skr) <> linebreak <> indent 4 (pretty "usage flags" <> colon <+> (list . map (coloredToColor (pretty . Set.toList))) (skUsageFlags skr)) <> linebreak <> indent 4 (pretty "embedded cross-cert" <> colon <+> (coloredToColor pretty . ccPresent . skCrossCerts) skr) <> linebreak <> indent 4 (pretty "cross-cert hash algorithms" <> colon <+> (list . map (coloredToColor pretty) . ccHashAlgorithms . skCrossCerts) skr) jsonReport :: POSIXTime -> TK -> BL.ByteString jsonReport ps = A.encode . checkKey (Just ps) yamlReport :: POSIXTime -> TK -> B.ByteString yamlReport ps = Y.encode . (: []) . checkKey (Just ps) data LintOutputFormat = Pretty | JSON | YAML deriving (Bounded, Enum, Eq, Read, Show) data LintOptions = LintOptions { lintOutputFormat :: LintOutputFormat } data FetchOptions = FetchOptions { keyServer :: String , fetchValidation :: FetchValidationMethod , fetchQuery :: TwentyOctetFingerprint } data Command = CmdLint LintOptions | CmdCanonicalize | CmdFetch FetchOptions lintO :: Parser LintOptions lintO = LintOptions <$> option auto (long "output-format" <> metavar "FORMAT" <> value Pretty <> showDefault <> ofHelp) where ofHelp = helpDoc . Just . toAnsiWlPprint $ pretty "output format" <> hardline <> list (map (pretty . show) ofchoices) ofchoices = [minBound .. maxBound] :: [LintOutputFormat] fetchO :: Parser FetchOptions fetchO = FetchOptions <$> option str (long "keyserver" <> metavar "URL" <> value "http://pool.sks-keyservers.net:11371" <> showDefault <> help "HKP server") <*> option auto (long "validation-method" <> metavar "METHOD" <> value MatchPrimaryKeyFingerprint <> showDefault <> vmHelp) <*> argument (eitherReader strToFP) (metavar "FINGERPRINT") where vmHelp = helpDoc . Just . toAnsiWlPprint $ pretty "validation method" <> hardline <> list (map (pretty . show) vmchoices) vmchoices = [minBound .. maxBound] :: [FetchValidationMethod] strToFP = parseFingerprint . T.pack dispatch :: Command -> IO () dispatch (CmdFetch o) = banner' stderr >> hFlush stderr >> doFetch o dispatch (CmdLint o) = banner' stderr >> hFlush stderr >> doLint o dispatch CmdCanonicalize = banner' stderr >> hFlush stderr >> doCanonicalize main :: IO () main = do hSetBuffering stderr LineBuffering customExecParser (prefs showHelpOnError) (info (helper <*> versioner "hokey" <*> cmd) (headerDoc (Just (toAnsiWlPprint (banner "hokey"))) <> progDesc "hOpenPGP Key utility" <> footerDoc (Just (toAnsiWlPprint (warranty "hokey"))))) >>= dispatch cmd :: Parser Command cmd = hsubparser (command "canonicalize" (info (pure CmdCanonicalize) (progDesc "arrange key components in a canonical ordering")) <> command "fetch" (info (CmdFetch <$> fetchO) (progDesc "fetch key(s) from keyserver")) <> command "lint" (info (CmdLint <$> lintO) (progDesc "check key(s) for 'best practices'"))) doLint :: LintOptions -> IO () doLint o = do cpt <- getPOSIXTime keys <- runConduitRes $ CB.sourceHandle stdin .| conduitGet get .| conduitToTKsDropping .| CL.consume output (lintOutputFormat o) cpt keys where output Pretty cpt = mapM_ (PPA.putDoc . prettyKeyReport cpt) output JSON cpt = mapM_ (BL.putStr . flip BL.append (BL.singleton 0x0a) . jsonReport cpt) output YAML cpt = mapM_ (B.putStr . yamlReport cpt) doCanonicalize :: IO () doCanonicalize = runConduitRes $ CB.sourceHandle stdin .| conduitGet get .| conduitToTKsDropping .| CL.map canonicalize .| CL.map put .| conduitPut .| CB.sinkHandle stdout where canonicalize (TK k r ui ua s) = TK k (sort r) (indepthsort ui) (indepthsort ua) (indepthsort s) indepthsort :: (Ord a, Ord b) => [(a, [b])] -> [(a, [b])] indepthsort = nub . sort . over (mapped . _2) sort doFetch :: FetchOptions -> IO () doFetch o = do ekeys <- runExceptT $ fetchKeys (keyServer o) (fetchValidation o) (fetchQuery o) case ekeys of Left e -> hPutStrLn stderr $ "error fetching keys: " ++ e Right ks -> B.putStr $ rearmorKeys ks banner' :: Handle -> IO () banner' h = PPA.hPutDoc h (banner "hokey" <> hardline <> warranty "hokey" <> hardline) sigissuer :: SignaturePayload -> Maybe EightOctetKeyId getIssuer :: SigSubPacketPayload -> Maybe EightOctetKeyId hashAlgo :: SignaturePayload -> HashAlgorithm sigissuer (SigVOther 2 _) = Nothing sigissuer SigV3 {} = Nothing sigissuer (SigV4 _ _ _ ys xs _ _) = listToMaybe . mapMaybe (getIssuer . _sspPayload) $ (ys ++ xs) -- FIXME: what should this be if there are multiple matches? sigissuer (SigVOther _ _) = error "We're in the future." -- FIXME getIssuer (Issuer i) = Just i getIssuer _ = Nothing hashAlgo (SigV4 _ _ x _ _ _ _) = x hashAlgo _ = error "V3 sig not supported here"