-- Common.hs: hOpenPGP-tools common functions -- Copyright © 2012-2014 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 . module HOpenPGP.Tools.Common ( banner , versioner , warranty , keyMatchesFingerprint , keyMatchesEightOctetKeyId , keyMatchesExactUIDString , keyMatchesUIDSubString , keyMatchesPKPred -- hmm , pkpGetPKVersion , pkpGetPKAlgo , pkpGetKeysize , pkpGetTimestamp , pkpGetFingerprint , pkpGetEOKI , tkUsingPKP , pUsingPKP , pUsingSP , withReaderTK , tkGetUIDs , tkGetSubs , anyOrAll , anyReader , oGetTag , oGetLength , spGetSigVersion , spGetSigType , spGetPKAlgo , spGetHashAlgo , maybeR ) where import Paths_hopenpgp_tools (version) import Data.Version (showVersion) import Codec.Encryption.OpenPGP.Fingerprint (eightOctetKeyID, fingerprint) import Codec.Encryption.OpenPGP.Types import Control.Lens ((^..)) import Data.Char (toLower) import Data.Data.Lens (biplate) import Data.List (isInfixOf) import Data.Monoid ((<>)) import Options.Applicative.Builder (help, infoOption, long, short) import Options.Applicative.Types (Parser) import Text.PrettyPrint.ANSI.Leijen (Doc, (<+>), hardline, text) -- hmm -- import qualified Data.ByteString as B import Data.Conduit.OpenPGP.Filter (Exp(..)) import Data.Maybe (fromMaybe, mapMaybe) import Data.Serialize (runPut, put) import Codec.Encryption.OpenPGP.KeyInfo (pubkeySize) import Control.Error.Util (hush) import Control.Monad.Trans.Reader (ask, withReader, reader, Reader, runReader) banner :: String -> Doc {-# INLINE banner #-} banner name = text name <+> text "(hopenpgp-tools)" <+> text (showVersion version) <> hardline <> text "Copyright (C) 2012-2014 Clint Adams" warranty :: String -> Doc {-# INLINE warranty #-} warranty name = text name <+> text "comes with ABSOLUTELY NO WARRANTY." <+> text "This is free software, and you are welcome to redistribute it" <+> text "under certain conditions." versioner :: Parser (a -> a) {-# INLINE versioner #-} versioner = infoOption (showVersion version) $ long "version" <> short 'V' <> help "Show version information" keyMatchesFingerprint :: Bool -> TK -> TwentyOctetFingerprint -> Bool keyMatchesFingerprint = keyMatchesPKPred fingerprint keyMatchesEightOctetKeyId :: Bool -> TK -> Either String EightOctetKeyId -> Bool -- FIXME: refactor this somehow keyMatchesEightOctetKeyId = keyMatchesPKPred eightOctetKeyID keyMatchesExactUIDString :: String -> TK -> Bool keyMatchesExactUIDString uidstr = any (==uidstr) . map fst . _tkUIDs keyMatchesUIDSubString :: String -> TK -> Bool keyMatchesUIDSubString uidstr = any (map toLower uidstr `isInfixOf`) . map (map toLower . fst) . _tkUIDs keyMatchesPKPred :: Eq a => (PKPayload -> a) -> Bool -> TK -> a -> Bool keyMatchesPKPred p False = (==) . p . fst . _tkKey keyMatchesPKPred p True = \tk v -> any (== v) (map p (tk ^.. biplate)) -- The following should probably be moved elsewhere tkUsingPKP :: Reader PKPayload a -> Reader TK a tkUsingPKP = withReader (fst . _tkKey) pkpGetPKVersion :: PKPayload -> Integer pkpGetPKVersion t = if _keyVersion t == DeprecatedV3 then 3 else 4 pkpGetPKAlgo :: PKPayload -> Integer pkpGetPKAlgo = fromIntegral . fromFVal . _pkalgo pkpGetKeysize :: PKPayload -> Integer pkpGetKeysize = fromIntegral . fromMaybe 0 . hush . pubkeySize . _pubkey pkpGetTimestamp :: PKPayload -> Integer pkpGetTimestamp = fromIntegral . _timestamp pkpGetFingerprint :: PKPayload -> TwentyOctetFingerprint pkpGetFingerprint = fingerprint pkpGetEOKI :: PKPayload -> String pkpGetEOKI = either (const "UNKNOWN") show . eightOctetKeyID withReaderTK :: (TK -> c) -> Exp (Reader TK) c withReaderTK x = Lift x `Ap` MA ask tkGetUIDs :: TK -> [String] tkGetUIDs = map fst . _tkUIDs tkGetSubs :: TK -> [PKPayload] tkGetSubs = mapMaybe (grabPKP . fst) . _tkSubs where grabPKP (PublicSubkeyPkt p) = Just p grabPKP (SecretSubkeyPkt p _) = Just p grabPKP _ = Nothing anyOrAll aa op = ask >>= aa (op . return) anyReader :: Reader a Bool -> Reader [a] Bool anyReader p = any (runReader p) `fmap` ask oGetTag :: Pkt -> Integer oGetTag = fromIntegral . pktTag oGetLength :: Pkt -> Integer oGetLength = fromIntegral . B.length . runPut . put -- FIXME: this should be a length that makes sense spGetSigVersion :: Pkt -> Maybe Integer spGetSigVersion (SignaturePkt s) = Just (sigVersion s) where sigVersion (SigV3 {}) = 3 sigVersion (SigV4 {}) = 4 sigVersion (SigVOther v _) = fromIntegral v spGetSigVersion _ = Nothing spGetSigType :: Pkt -> Maybe Integer spGetSigType (SignaturePkt s) = fmap (fromIntegral . fromFVal) (sigType s) where -- FIXME: deduplicate this and hOpenPGP .Internal sigType :: SignaturePayload -> Maybe SigType sigType (SigV3 st _ _ _ _ _ _) = Just st sigType (SigV4 st _ _ _ _ _ _) = Just st sigType _ = Nothing -- this includes v2 sigs, which don't seem to be specified in the RFCs but exist in the wild spGetSigType _ = Nothing spGetPKAlgo :: Pkt -> Maybe Integer spGetPKAlgo (SignaturePkt s) = fmap (fromIntegral . fromFVal) (sigPKA s) where sigPKA (SigV3 _ _ _ pka _ _ _) = Just pka sigPKA (SigV4 _ pka _ _ _ _ _) = Just pka sigPKA _ = Nothing -- this includes v2 sigs, which don't seem to be specified in the RFCs but exist in the wild spGetPKAlgo _ = Nothing spGetHashAlgo :: Pkt -> Maybe Integer spGetHashAlgo (SignaturePkt s) = fmap (fromIntegral . fromFVal) (sigHA s) where sigHA (SigV3 _ _ _ _ ha _ _) = Just ha sigHA (SigV4 _ _ ha _ _ _ _) = Just ha sigHA _ = Nothing -- this includes v2 sigs, which don't seem to be specified in the RFCs but exist in the wild spGetHashAlgo _ = Nothing pUsingPKP :: Reader (Maybe PKPayload) a -> Reader Pkt a pUsingPKP = withReader grabPayload where grabPayload (SecretKeyPkt p _) = Just p grabPayload (PublicKeyPkt p) = Just p grabPayload (SecretSubkeyPkt p _) = Just p grabPayload (PublicSubkeyPkt p) = Just p grabPayload _ = Nothing pUsingSP :: Reader (Maybe SignaturePayload) a -> Reader Pkt a pUsingSP = withReader grabPayload where grabPayload (SignaturePkt s ) = Just s grabPayload _ = Nothing maybeR :: a -> Reader r a -> Reader (Maybe r) a maybeR = \x r -> reader (maybe x (runReader r))