module Crypto.Gpgme.Types where
import Bindings.Gpgme
import qualified Data.ByteString as BS
import Foreign.C.Types (CInt, CUInt)
import Foreign
newtype Protocol = Protocol Int
openPGP :: Protocol
openPGP = Protocol c'GPGME_PROTOCOL_OpenPGP
data Ctx = Ctx {
_ctx :: Ptr C'gpgme_ctx_t
, _version :: String
}
type Fpr = BS.ByteString
type Plain = BS.ByteString
type Encrypted = BS.ByteString
type InvalidKey = (String, Int)
newtype Key = Key { unKey :: Ptr C'gpgme_key_t }
newtype IncludeSecret = IncludeSecret CInt
noSecret :: IncludeSecret
noSecret = IncludeSecret 0
secret :: IncludeSecret
secret = IncludeSecret 1
newtype Flag = Flag CUInt
alwaysTrust :: Flag
alwaysTrust = Flag c'GPGME_ENCRYPT_ALWAYS_TRUST
noFlag :: Flag
noFlag = Flag 0
data DecryptError =
NoData
| Failed
| BadPass
| Unknown Int
deriving (Eq, Show)
toDecryptError :: C'gpgme_err_code_t -> DecryptError
toDecryptError 58 = NoData
toDecryptError 152 = Failed
toDecryptError 11 = BadPass
toDecryptError x = Unknown (fromIntegral x)