summaryrefslogtreecommitdiff
path: root/lib/GnuPGAgent.hs
diff options
context:
space:
mode:
Diffstat (limited to 'lib/GnuPGAgent.hs')
-rw-r--r--lib/GnuPGAgent.hs24
1 files changed, 2 insertions, 22 deletions
diff --git a/lib/GnuPGAgent.hs b/lib/GnuPGAgent.hs
index 1e40269..d73ceed 100644
--- a/lib/GnuPGAgent.hs
+++ b/lib/GnuPGAgent.hs
@@ -1,6 +1,6 @@
1{-# LANGUAGE LambdaCase #-} 1{-# LANGUAGE LambdaCase #-}
2{-# LANGUAGE CPP #-} 2{-# LANGUAGE PatternGuards #-}
3{-# LANGUAGE PatternGuards #-} {-# LANGUAGE TupleSections #-} 3{-# LANGUAGE TupleSections #-}
4module GnuPGAgent 4module GnuPGAgent
5 ( session 5 ( session
6 , GnuPGAgent 6 , GnuPGAgent
@@ -26,21 +26,11 @@ import System.Posix.User
26import System.Environment 26import System.Environment
27import System.IO 27import System.IO
28import Text.Printf 28import Text.Printf
29#if defined(VERSION_memory)
30import qualified Data.ByteString.Char8 as S8 29import qualified Data.ByteString.Char8 as S8
31import Data.ByteArray.Encoding 30import Data.ByteArray.Encoding
32#elif defined(VERSION_dataenc)
33import qualified Codec.Binary.Base16 as Base16
34#endif
35import LengthPrefixedBE 31import LengthPrefixedBE
36import qualified Data.ByteString.Lazy as L 32import qualified Data.ByteString.Lazy as L
37#if defined(VERSION_hourglass)
38import Data.Hourglass 33import Data.Hourglass
39#else
40import Data.Time.Calendar
41import Data.Time.Clock
42import Data.Time.Clock.POSIX
43#endif
44import ProcessUtils 34import ProcessUtils
45import Control.Monad.Fix 35import Control.Monad.Fix
46import Control.Concurrent (threadDelay) 36import Control.Concurrent (threadDelay)
@@ -166,18 +156,12 @@ getPassphrase agent ask (Query key uid masterkey) = do
166 "OK" | not (null $ drop 3 r0) -> return r0 >>= unhex . drop 3 -- . (\x -> trace (show x) x) 156 "OK" | not (null $ drop 3 r0) -> return r0 >>= unhex . drop 3 -- . (\x -> trace (show x) x)
167 | otherwise -> hGetLine (agentHandle agent) >>= unhex . drop 3 -- . (\x -> trace (show x) x) 157 | otherwise -> hGetLine (agentHandle agent) >>= unhex . drop 3 -- . (\x -> trace (show x) x)
168 where 158 where
169#if defined(VERSION_memory)
170 unhex hx = case convertFromBase Base16 (S8.pack hx) of 159 unhex hx = case convertFromBase Base16 (S8.pack hx) of
171 Left e -> do 160 Left e -> do
172 -- Useful for debugging but insecure generally ;) 161 -- Useful for debugging but insecure generally ;)
173 -- putStrLn $ "convertFromBase error for input "++show hx++": "++show e 162 -- putStrLn $ "convertFromBase error for input "++show hx++": "++show e
174 return Nothing 163 return Nothing
175 Right bs -> return $ Just $ S8.unpack bs 164 Right bs -> return $ Just $ S8.unpack bs
176#elif defined(VERSION_dataenc)
177 unhex hx = maybe (return () {- putStrLn $ "dataenc error for input "++show hx -})
178 return
179 $ fmap (map $ chr . fromIntegral) $ Base16.decode hx
180#endif
181 "ERR" -> return Nothing 165 "ERR" -> return Nothing
182 166
183quit :: GnuPGAgent -> IO () 167quit :: GnuPGAgent -> IO ()
@@ -232,12 +216,8 @@ envhomedir opt home = do
232timeString :: Word32 -> String 216timeString :: Word32 -> String
233timeString t = printf "%d-%d-%d" year month day 217timeString t = printf "%d-%d-%d" year month day
234 where 218 where
235#if defined(VERSION_hourglass)
236 Date year m day = timeFromElapsed (Elapsed (Seconds $ fromIntegral t)) 219 Date year m day = timeFromElapsed (Elapsed (Seconds $ fromIntegral t))
237 month = fromEnum m + 1 220 month = fromEnum m + 1
238#else
239 (year,month,day) = toGregorian . utctDay $ posixSecondsToUTCTime (realToFrac t)
240#endif
241 221
242key_nbits :: Packet -> Int 222key_nbits :: Packet -> Int
243key_nbits p@(SecretKeyPacket {}) = _key_nbits (key_algorithm p) (key p) 223key_nbits p@(SecretKeyPacket {}) = _key_nbits (key_algorithm p) (key p)