module Crypto.Gpgme.Types where
import Bindings.Gpgme
import qualified Data.ByteString as BS
import Data.Maybe(catMaybes)
import Foreign
import qualified Foreign.Concurrent as FC
import Foreign.C.String (peekCString)
import System.IO.Unsafe (unsafePerformIO)
import Control.Exception (SomeException, Exception)
data Protocol =
CMS
| GPGCONF
| OpenPGP
| UNKNOWN
deriving (Show, Eq, Ord)
data Ctx = Ctx {
_ctx :: Ptr C'gpgme_ctx_t
, _version :: String
, _protocol :: Protocol
, _engineVersion :: String
}
data SignMode = Normal | Detach | Clear deriving Show
type Fpr = BS.ByteString
type Plain = BS.ByteString
type Encrypted = BS.ByteString
type Signature = BS.ByteString
data SignatureSummary =
BadPolicy
| CrlMissing
| CrlTooOld
| Green
| KeyExpired
| KeyMissing
| KeyRevoked
| Red
| SigExpired
| SysError
| UnknownSummary C'gpgme_sigsum_t
| Valid
deriving (Show, Eq, Ord)
toSignatureSummaries :: C'gpgme_sigsum_t -> [SignatureSummary]
toSignatureSummaries x = catMaybes $ map (\(mask, val) -> if mask .&. x == 0 then Nothing else Just val)
[ (c'GPGME_SIGSUM_BAD_POLICY , BadPolicy)
, (c'GPGME_SIGSUM_CRL_MISSING, CrlMissing)
, (c'GPGME_SIGSUM_CRL_TOO_OLD, CrlTooOld)
, (c'GPGME_SIGSUM_GREEN , Green)
, (c'GPGME_SIGSUM_KEY_EXPIRED, KeyExpired)
, (c'GPGME_SIGSUM_KEY_MISSING, KeyMissing)
, (c'GPGME_SIGSUM_KEY_REVOKED, KeyRevoked)
, (c'GPGME_SIGSUM_RED , Red)
, (c'GPGME_SIGSUM_SIG_EXPIRED, SigExpired)
, (c'GPGME_SIGSUM_SYS_ERROR , SysError)
, (c'GPGME_SIGSUM_VALID , Valid)
]
type VerificationResult = [(GpgmeError, [SignatureSummary], Fpr)]
type InvalidKey = (String, Int)
newtype Key = Key { unKey :: ForeignPtr C'gpgme_key_t }
allocKey :: IO Key
allocKey = do
keyPtr <- malloc
let finalize = do
peek keyPtr >>= c'gpgme_key_unref
free keyPtr
Key `fmap` FC.newForeignPtr keyPtr finalize
withKeyPtr :: Key -> (Ptr C'gpgme_key_t -> IO a) -> IO a
withKeyPtr (Key fPtr) f = withForeignPtr fPtr f
data IncludeSecret =
WithSecret
| NoSecret
deriving (Show, Eq, Ord)
data Flag =
AlwaysTrust
| NoFlag
deriving (Show, Eq, Ord)
newtype GpgmeError = GpgmeError C'gpgme_error_t
deriving (Show, Ord, Eq)
errorString :: GpgmeError -> String
errorString (GpgmeError n) =
unsafePerformIO $ c'gpgme_strerror n >>= peekCString
sourceString :: GpgmeError -> String
sourceString (GpgmeError n) =
unsafePerformIO $ c'gpgme_strsource n >>= peekCString
data DecryptError =
NoData
| Failed
| BadPass
| Unknown GpgmeError
deriving (Show, Eq, Ord)
toDecryptError :: C'gpgme_error_t -> DecryptError
toDecryptError n =
case unsafePerformIO $ c'gpgme_err_code n of
58 -> NoData
152 -> Failed
11 -> BadPass
x -> Unknown (GpgmeError x)
data Validity =
ValidityUnknown
| ValidityUndefined
| ValidityNever
| ValidityMarginal
| ValidityFull
| ValidityUltimate
deriving (Show, Ord, Eq)
data PubKeyAlgo =
Rsa
| RsaE
| RsaS
| ElgE
| Dsa
| Elg
deriving (Show, Ord, Eq)
newtype HgpgmeException = HgpgmeException SomeException deriving (Show)
instance Exception HgpgmeException