module Crypto.Gpgme.Ctx where
import Bindings.Gpgme
import Control.Monad (when)
import Data.List (isPrefixOf)
import Foreign
import Foreign.C.String
import Foreign.C.Types
import Crypto.Gpgme.Types
import Crypto.Gpgme.Internal
newCtx :: String
-> String
-> Protocol
-> IO Ctx
newCtx homedir localeStr protocol =
do homedirPtr <- newCString homedir
version <- c'gpgme_check_version nullPtr >>= peekCString
ctxPtr <- malloc
checkError "gpgme_new" =<< c'gpgme_new ctxPtr
ctx <- peek ctxPtr
engInfo <- c'gpgme_ctx_get_engine_info ctx >>= peek
engVersion <- peekCString $ c'_gpgme_engine_info'version engInfo
locale <- newCString localeStr
checkError "set_locale" =<< c'gpgme_set_locale ctx lcCtype locale
checkError "set_protocol" =<< c'gpgme_set_protocol ctx
(fromProtocol protocol)
checkError "set_engine_info" =<< c'gpgme_ctx_set_engine_info ctx
(fromProtocol protocol) nullPtr homedirPtr
return (Ctx ctxPtr version protocol engVersion)
where lcCtype :: CInt
lcCtype = 0
freeCtx :: Ctx -> IO ()
freeCtx (Ctx {_ctx=ctxPtr}) =
do ctx <- peek ctxPtr
c'gpgme_release ctx
free ctxPtr
withCtx :: String
-> String
-> Protocol
-> (Ctx -> IO a)
-> IO a
withCtx homedir localeStr prot f = do
ctx <- newCtx homedir localeStr prot
res <- f ctx
freeCtx ctx
return res
setArmor :: Bool -> Ctx -> IO ()
setArmor armored (Ctx {_ctx = ctxPtr}) = do
ctx <- peek ctxPtr
c'gpgme_set_armor ctx (if armored then 1 else 0)
isPassphraseCbSupported :: Ctx -> Bool
isPassphraseCbSupported ctx
| OpenPGP <- _protocol ctx =
case () of
_ | "2.0" `isPrefixOf` ver -> False
| "1." `isPrefixOf` ver -> False
| otherwise -> True
| otherwise = True
where
ver = _engineVersion ctx
type PassphraseCb =
String
-> String
-> Bool
-> IO (Maybe String)
passphraseCb :: PassphraseCb -> IO C'gpgme_passphrase_cb_t
passphraseCb callback = do
let go _ hint info prev_bad fd = do
hint' <- peekCString hint
info' <- peekCString info
result <- callback hint' info' (prev_bad /= 0)
let phrase = maybe "" id result
err <- withCStringLen (phrase++"\n") $ \(s,len) ->
c'gpgme_io_writen fd (castPtr s) (fromIntegral len)
when (err /= 0) $ checkError "passphraseCb" (fromIntegral err)
return $ maybe errCanceled (const 0) result
errCanceled = 99
mk'gpgme_passphrase_cb_t go
setPassphraseCallback :: Ctx
-> Maybe PassphraseCb
-> IO ()
setPassphraseCallback (Ctx {_ctx=ctxPtr}) callback = do
ctx <- peek ctxPtr
let mode = case callback of
Nothing -> c'GPGME_PINENTRY_MODE_DEFAULT
Just _ -> c'GPGME_PINENTRY_MODE_LOOPBACK
c'gpgme_set_pinentry_mode ctx mode >>= checkError "setPassphraseCallback"
cb <- maybe (return nullFunPtr) passphraseCb callback
c'gpgme_set_passphrase_cb ctx cb nullPtr