{-# LANGUAGE RecordWildCards #-} -- Armor.hs: hOpenPGP-tools common ASCII de-Armor function -- Copyright © 2012-2021 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.Armor ( doDeArmor ) where import qualified Codec.Encryption.OpenPGP.ASCIIArmor as AA import Codec.Encryption.OpenPGP.ASCIIArmor.Types (Armor(..)) import qualified Data.ByteString as B 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 System.IO (hPutStrLn, stderr, stdin) doDeArmor :: IO () doDeArmor = do a <- runConduitRes $ 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)