{-# LANGUAGE OverloadedStrings, RecordWildCards #-} -- hot.hs: hOpenPGP Tool -- 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 . import Paths_hopenpgp_tools (version) import HOpenPGP.Tools.Common (banner, versioner, warranty) import HOpenPGP.Tools.ExpressionParsing (pPE) import qualified Codec.Encryption.OpenPGP.ASCIIArmor as AA import Codec.Encryption.OpenPGP.ASCIIArmor.Types (Armor(..), ArmorType(..)) import Codec.Encryption.OpenPGP.Serialize () import Codec.Encryption.OpenPGP.Types import Control.Applicative ((<$>), (<*>), (*>), (<|>), optional, pure) import Control.Error.Util (note) import Control.Monad.IO.Class (MonadIO, liftIO) import Control.Monad.Trans.Resource (runResourceT) import qualified Data.Attoparsec.Text as A import qualified Data.ByteString as B import qualified Data.ByteString.Lazy as BL import Data.Conduit (($=), ($$), Sink) import Data.Conduit.Cereal (conduitGet, conduitPut) import qualified Data.Conduit.Binary as CB import qualified Data.Conduit.List as CL import Data.Conduit.OpenPGP.Filter (conduitFilter, Expr(..), FilterPredicates(..), SPPredicate(..), SPVar(..), SPOp(..), SPValue(..), OPredicate(..), OVar(..), OOp(..), OValue(..)) import Data.Serialize (get, put) import Data.Serialize.Get (Get) import Data.Monoid ((<>)) import qualified Data.Text as T import Data.Version (showVersion) import System.IO (stdin, stderr, stdout, Handle, hFlush, hPutStrLn, hSetBuffering, BufferMode(..)) import Options.Applicative.Builder (command, footer, header, help, helpDoc, info, long, metavar, option, eitherReader, prefs, progDesc, showHelpOnError, strOption, subparser) import Options.Applicative.Extra (customExecParser, helper) import Options.Applicative.Types (Parser) import Text.PrettyPrint.ANSI.Leijen ((<+>), list, softline, text) data Command = DumpC | DeArmorC | ArmorC ArmoringOptions | FilterC FilteringOptions data ArmoringOptions = ArmoringOptions { comment :: Maybe String , armortype :: ArmorType } data FilteringOptions = FilteringOptions { pkpExpression :: Maybe String , spExpression :: Maybe String , oExpression :: Maybe String } doDump :: IO () doDump = runResourceT $ CB.sourceHandle stdin $= conduitGet (get :: Get Pkt) $$ printer -- Print every input value to standard output. printer :: (Show a, MonadIO m) => Sink a m () printer = CL.mapM_ (liftIO . print) doDeArmor :: IO () doDeArmor = do a <- runResourceT $ CB.sourceHandle stdin $$ CL.consume case AA.decode (B.concat a) of Left e -> hPutStrLn stderr $ "Failure to decode ASCII Armor:" ++ e Right msgs -> BL.putStr $ BL.concat (map (\(Armor _ _ bs) -> bs) msgs) doArmor :: ArmoringOptions -> IO () doArmor ArmoringOptions{..} = do m <- runResourceT $ CB.sourceHandle stdin $$ CL.consume let a = Armor armortype (("Version", "hot " ++ showVersion version):maybe [] (\x -> [("Comment", x)]) comment ) (BL.fromChunks m) BL.putStr $ AA.encodeLazy [a] armorTypes :: [(String, ArmorType)] armorTypes = [ ("message", ArmorMessage) , ("pubkeyblock", ArmorPublicKeyBlock) , ("privkeyblock", ArmorPrivateKeyBlock) , ("signature", ArmorSignature) ] armorTypeReader :: String -> Either String ArmorType armorTypeReader = note "unknown armor type" . flip lookup armorTypes doFilter :: FilteringOptions -> IO () doFilter fo = runResourceT $ CB.sourceHandle stdin $= conduitGet (get :: Get Pkt) $= conduitFilter (parseExpressions fo) $= conduitPut put $$ CB.sinkHandle stdout aoP :: Parser ArmoringOptions aoP = ArmoringOptions <$> optional (strOption (long "comment" <> metavar "COMMENT" <> help "ASCII armor Comment field")) <*> option (eitherReader armorTypeReader) (long "armor-type" <> metavar "ARMORTYPE" <> armortypeHelp) where armortypeHelp = helpDoc . Just $ text "ASCII armor type" <> softline <> list (map (text . fst) armorTypes) foP :: Parser FilteringOptions foP = FilteringOptions <$> optional (strOption (long "pubkey" <> metavar "EXPR" <> help "pubkey filtering expression")) <*> optional (strOption (long "sig" <> metavar "EXPR" <> help "sig filtering expression")) <*> optional (strOption (long "other" <> metavar "EXPR" <> help "other-packet filtering expression")) dispatch :: Command -> IO () dispatch c = (banner' stderr >> hFlush stderr) >> dispatch' c where dispatch' DumpC = doDump dispatch' DeArmorC = doDeArmor dispatch' (ArmorC o) = doArmor o dispatch' (FilterC o) = doFilter o main :: IO () main = do hSetBuffering stderr LineBuffering customExecParser (prefs showHelpOnError) (info (helper <*> versioner <*> cmd) (header (banner "hot") <> progDesc "hOpenPGP OpenPGP-message Tool" <> footer (warranty "hot"))) >>= dispatch cmd :: Parser Command cmd = subparser ( command "armor" (info ( ArmorC <$> aoP ) ( progDesc "Armor stdin to stdout" )) <> command "dearmor" (info ( pure DeArmorC ) ( progDesc "Dearmor stdin to stdout" )) <> command "dump" (info ( pure DumpC ) ( progDesc "Dump OpenPGP packets from stdin" )) <> command "filter" (info ( FilterC <$> foP ) ( progDesc "Filter some packets from stdin to stdout" )) ) banner' :: Handle -> IO () banner' h = hPutStrLn h (banner "hot" ++ "\n" ++ warranty "hot") parseExpressions :: FilteringOptions -> FilterPredicates parseExpressions FilteringOptions{..} = FilterPredicates (mp parsePE pkpExpression) (mp parseSE spExpression) (mp parseOE oExpression) where mp p e = maybe EAny p (T.pack <$> e) parsePE e = either (error . ("pubkey filter parse error: "++)) id (A.parseOnly pPE e) parseSE e = either (error . ("signature filter parse error: "++)) id (A.parseOnly pSE e) parseOE e = either (error . ("otherpacket filter parse error: "++)) id (A.parseOnly pOE e) pSE :: A.Parser (Expr SPPredicate) pSE = complex (anyP <|> simpleSE) pOE :: A.Parser (Expr OPredicate) pOE = complex (anyP <|> simpleOE) complex :: A.Parser (Expr a) -> A.Parser (Expr a) complex p = andP p <|> orP p <|> notP p <|> p notP :: A.Parser (Expr a) -> A.Parser (Expr a) notP p = ENot <$> (A.skipSpace *> A.string "not" *> A.skipSpace *> p) andP :: A.Parser (Expr a) -> A.Parser (Expr a) andP p = EAnd <$> p <*> (A.skipSpace *> A.string "and" *> A.skipSpace *> p) orP :: A.Parser (Expr a) -> A.Parser (Expr a) orP p = EAnd <$> p <*> (A.skipSpace *> A.string "or" *> A.skipSpace *> p) anyP :: A.Parser (Expr a) anyP = A.string "any" *> pure EAny hexordec :: A.Parser Int hexordec = (A.string "0x" *> A.hexadecimal) <|> A.decimal simpleSE :: A.Parser (Expr SPPredicate) simpleSE = do _ <- A.skipSpace lhs <- sVarToken _ <- A.skipSpace op <- sOpToken _ <- A.skipSpace rhs <- sValToken return (E (SPPredicate lhs op rhs)) where sVarToken = (A.string "version" *> pure SPVVersion) <|> (A.string "sigtype" *> pure SPVSigType) <|> (A.string "pkalgo" *> pure SPVPKA) <|> (A.string "hashalgo" *> pure SPVHA) sOpToken = (A.string "==" *> pure SPEquals) <|> (A.string "=" *> pure SPEquals) <|> (A.string "<" *> pure SPLessThan) <|> (A.string ">" *> pure SPGreaterThan) sValToken = (A.asciiCI "rsa" *> pure (SPPKA RSA)) <|> (A.asciiCI "dsa" *> pure (SPPKA DSA)) <|> (A.asciiCI "elgamal" *> pure (SPPKA ElgamalEncryptOnly)) <|> (A.asciiCI "ecdsa" *> pure (SPPKA ECDSA)) <|> (A.asciiCI "ecdh" *> pure (SPPKA ECDH)) <|> (A.asciiCI "dh" *> pure (SPPKA DH)) <|> (A.asciiCI "binary" *> pure (SPSigType BinarySig)) <|> (A.asciiCI "canonicaltext" *> pure (SPSigType CanonicalTextSig)) <|> (A.asciiCI "standalone" *> pure (SPSigType StandaloneSig)) <|> (A.asciiCI "genericcert" *> pure (SPSigType GenericCert)) <|> (A.asciiCI "personacert" *> pure (SPSigType PersonaCert)) <|> (A.asciiCI "casualcert" *> pure (SPSigType CasualCert)) <|> (A.asciiCI "positivecert" *> pure (SPSigType PositiveCert)) <|> (A.asciiCI "subkeybindingsig" *> pure (SPSigType SubkeyBindingSig)) <|> (A.asciiCI "primarykeybindingsig" *> pure (SPSigType PrimaryKeyBindingSig)) <|> (A.asciiCI "signaturedirectlyonakey" *> pure (SPSigType SignatureDirectlyOnAKey)) <|> (A.asciiCI "keyrevocationsig" *> pure (SPSigType KeyRevocationSig)) <|> (A.asciiCI "subkeyrevocationsig" *> pure (SPSigType SubkeyRevocationSig)) <|> (A.asciiCI "certrevocationsig" *> pure (SPSigType CertRevocationSig)) <|> (A.asciiCI "timestampsig" *> pure (SPSigType TimestampSig)) <|> (A.asciiCI "md5" *> pure (SPHA DeprecatedMD5)) <|> (A.asciiCI "sha1" *> pure (SPHA SHA1)) <|> (A.asciiCI "ripemd160" *> pure (SPHA RIPEMD160)) <|> (A.asciiCI "sha256" *> pure (SPHA SHA256)) <|> (A.asciiCI "sha384" *> pure (SPHA SHA384)) <|> (A.asciiCI "sha512" *> pure (SPHA SHA512)) <|> (A.asciiCI "sha224" *> pure (SPHA SHA224)) <|> (SPInt <$> hexordec) simpleOE :: A.Parser (Expr OPredicate) simpleOE = do _ <- A.skipSpace lhs <- oVarToken _ <- A.skipSpace op <- oOpToken _ <- A.skipSpace rhs <- oValToken return (E (OPredicate lhs op rhs)) where oVarToken = A.string "tag" *> pure OVTag oOpToken = (A.string "==" *> pure OEquals) <|> (A.string "=" *> pure OEquals) <|> (A.string "<" *> pure OLessThan) <|> (A.string ">" *> pure OGreaterThan) oValToken = OInt <$> hexordec