summaryrefslogtreecommitdiff
path: root/Data
diff options
context:
space:
mode:
authorjoe <joe@blackbird>2014-01-04 19:38:36 -0500
committerjoe <joe@blackbird>2014-01-04 19:38:36 -0500
commit62114b3b3a35fb17a987c68e752b0597c7251761 (patch)
tree7c5657babb23747a9f8a5e045193357b364c290f /Data
parent395f75c6b7f66d313b4d44be4ed1317f9d7c7042 (diff)
Build against older libs
Diffstat (limited to 'Data')
-rw-r--r--Data/OpenPGP/Util/DecryptSecretKey.hs22
1 files changed, 18 insertions, 4 deletions
diff --git a/Data/OpenPGP/Util/DecryptSecretKey.hs b/Data/OpenPGP/Util/DecryptSecretKey.hs
index b3f5640..6bfc2af 100644
--- a/Data/OpenPGP/Util/DecryptSecretKey.hs
+++ b/Data/OpenPGP/Util/DecryptSecretKey.hs
@@ -1,3 +1,4 @@
1{-# LANGUAGE CPP #-}
1module Data.OpenPGP.Util.DecryptSecretKey where 2module Data.OpenPGP.Util.DecryptSecretKey where
2 3
3import qualified Data.OpenPGP as OpenPGP 4import qualified Data.OpenPGP as OpenPGP
@@ -6,7 +7,13 @@ import qualified Data.ByteString.Lazy as LZ
6import Data.Word (Word16) 7import Data.Word (Word16)
7import Control.Monad (foldM) 8import Control.Monad (foldM)
8import Data.Binary (get,Binary,Get,encode) 9import Data.Binary (get,Binary,Get,encode)
10#if MIN_VERSION_binary(0,6,4)
9import Data.Binary.Get (runGetOrFail) 11import Data.Binary.Get (runGetOrFail)
12#else
13import Control.Exception as Exception (handle,ErrorCall(..))
14import System.IO.Unsafe
15import Data.Binary.Get (runGet)
16#endif
10import Control.Applicative ( (<$>) ) 17import Control.Applicative ( (<$>) )
11 18
12import Crypto.Hash.SHA1 as SHA1 19import Crypto.Hash.SHA1 as SHA1
@@ -69,16 +76,23 @@ decryptSecretKey pass k@(OpenPGP.SecretKeyPacket {
69 checksum key = fromIntegral $ 76 checksum key = fromIntegral $
70 BS.foldl' (\x y -> x + fromIntegral y) (0::Integer) key `mod` 65536 77 BS.foldl' (\x y -> x + fromIntegral y) (0::Integer) key `mod` 65536
71 78
72 maybeGet :: (Binary a) => Get a -> LZ.ByteString -> Maybe a 79decryptSecretKey _ _ = Nothing
73 maybeGet g bs = (\(_,_,x) -> x) <$> hush (runGetOrFail g bs) 80
74 81
82#if MIN_VERSION_binary(0,6,4)
83maybeGet :: (Binary a) => Get a -> LZ.ByteString -> Maybe a
84maybeGet g bs = (\(_,_,x) -> x) <$> hush (runGetOrFail g bs)
85 where
75 hush :: Either a b -> Maybe b 86 hush :: Either a b -> Maybe b
76 hush (Left _) = Nothing 87 hush (Left _) = Nothing
77 hush (Right x) = Just x 88 hush (Right x) = Just x
89#else
90maybeGet :: (Binary a) => Get a -> LZ.ByteString -> Maybe a
91maybeGet g bs = unsafePerformIO $
92 handle (\(ErrorCall _)-> return Nothing) $ return . Just $ runGet g bs
93#endif
78 94
79 95
80decryptSecretKey _ _ = Nothing
81
82 96
83string2sdecrypt :: OpenPGP.SymmetricAlgorithm -> OpenPGP.S2K -> LZ.ByteString -> Enciphered -> LZ.ByteString 97string2sdecrypt :: OpenPGP.SymmetricAlgorithm -> OpenPGP.S2K -> LZ.ByteString -> Enciphered -> LZ.ByteString
84string2sdecrypt OpenPGP.AES128 s2k s = withIV $ simpleUnCFB (string2key s2k s :: Vincent.AES128) 98string2sdecrypt OpenPGP.AES128 s2k s = withIV $ simpleUnCFB (string2key s2k s :: Vincent.AES128)