h-gpgme-0.6.2.0: High Level Binding for GnuPG Made Easy (gpgme)
Copyright(c) Reto Hablützel 2015
LicenseMIT
Maintainerrethab@rethab.ch
Stabilityexperimental
Portabilityuntested
Safe HaskellNone
LanguageHaskell2010

Crypto.Gpgme

Description

High Level Binding for GnuPG Made Easy (gpgme)

Most of these functions are a one-to-one translation from GnuPG API with some Haskell idiomatics to make the API more convenient.

See the GnuPG manual for more information: https://www.gnupg.org/documentation/manuals/gpgme.pdf

Example (from the tests):

let alice_pub_fpr = "EAACEB8A"

Just enc <- withCtx "test/bob" "C" OpenPGP $ \bCtx -> runMaybeT $ do
        aPubKey <- MaybeT $ getKey bCtx alice_pub_fpr NoSecret
        fromRight $ encrypt bCtx [aPubKey] NoFlag plain

-- decrypt
dec <- withCtx "test/alice" "C" OpenPGP $ \aCtx ->
        decrypt aCtx enc
Synopsis

Context

data Ctx Source #

Context to be passed around with operations. Use newCtx or withCtx in order to obtain an instance.

newCtx Source #

Arguments

:: String

path to gpg homedirectory

-> String

locale

-> Protocol

protocol

-> IO Ctx 

Creates a new Ctx from a homedirectory, a locale and a protocol. Needs to be freed with freeCtx, which is why you are encouraged to use withCtx.

freeCtx :: Ctx -> IO () Source #

Free a previously created Ctx

withCtx Source #

Arguments

:: String

path to gpg homedirectory

-> String

locale

-> Protocol

protocol

-> (Ctx -> IO a)

action to be run with ctx

-> IO a 

Runs the action with a new Ctx and frees it afterwards

See newCtx for a descrption of the parameters.

setArmor :: Bool -> Ctx -> IO () Source #

Sets armor output on ctx

setKeyListingMode :: [KeyListingMode] -> Ctx -> IO () Source #

Sets the key listing mode on ctx

Passphrase callbacks

isPassphraseCbSupported :: Ctx -> Bool Source #

Are passphrase callbacks supported?

This functionality is known to be broken in some gpg versions, see setPassphraseCb for details.

type PassphraseCb Source #

Arguments

 = String

user ID hint

-> String

passphrase info

-> Bool

True if the previous attempt was bad

-> IO (Maybe String) 

A callback invoked when the engine requires a passphrase to proceed. The callback should return Just the requested passphrase, or Nothing to cancel the operation.

setPassphraseCallback Source #

Arguments

:: Ctx

context

-> Maybe PassphraseCb

a callback, or Nothing to disable

-> IO () 

Set the callback invoked when a passphrase is required from the user.

Note that the operation of this feature is a bit inconsistent between GPG versions. GPG 1.4 using the use-agent option and GPG >= 2.1 require that the gpg-agent for the session has the allow-loopback-pinentry option enabled (this can be achieved by adding allow-loopback-pinentry to gpg-agent.conf. GPG versions between 2.0 and 2.1 do not support the --pinentry-mode option necessary for this support.

See http://lists.gnupg.org/pipermail/gnupg-devel/2013-February/027345.html and the gpgme-tool example included in the gpgme tree for details.

Progress callbacks

progressCb :: ProgressCb -> IO C'gpgme_progress_cb_t Source #

Construct a progress callback

setProgressCallback Source #

Arguments

:: Ctx

context

-> Maybe ProgressCb 
-> IO () 

Set the callback invoked when a progress feedback is available.

Keys

data Key Source #

A key from the context

importKeyFromFile Source #

Arguments

:: Ctx

context to operate in

-> FilePath

file path to read from

-> IO (Maybe GpgmeError) 

Import a key from a file, this happens in two steps: populate a gpgme_data_t with the contents of the file, import the gpgme_data_t

getKey Source #

Arguments

:: Ctx

context to operate in

-> Fpr

fingerprint

-> IncludeSecret

whether to include secrets when searching for the key

-> IO (Maybe Key) 

Returns a Key from the context based on its fingerprint. Returns Nothing if no Key with this Fpr exists.

listKeys Source #

Arguments

:: Ctx

context to operate in

-> IncludeSecret

whether to include the secrets

-> IO [Key] 

Returns a list of all known Keys from the context.

removeKey Source #

Arguments

:: Ctx

context to operate in

-> Key

key to delete

-> RemoveKeyFlags

flags for remove operation

-> IO (Maybe GpgmeError) 

Removes the Key from context

data RemoveKeyFlags Source #

Flags for removeKey function

Constructors

RemoveKeyFlags 

Fields

  • allowSecret :: Bool

    if False, only public keys are removed, otherwise secret keys are removed as well

  • force :: Bool

    if True, don't ask for confirmation

searchKeys Source #

Arguments

:: Ctx

context to operate in

-> IncludeSecret

whether to include the secrets

-> String

The pattern to look for; It is typically matched against the user ids of a key.

-> IO [Key] 

Returns a list of known Keys from the context that match a given pattern.

Information about keys

data Validity Source #

The validity of a user identity

Instances

Instances details
Eq Validity Source # 
Instance details

Defined in Crypto.Gpgme.Types

Ord Validity Source # 
Instance details

Defined in Crypto.Gpgme.Types

Show Validity Source # 
Instance details

Defined in Crypto.Gpgme.Types

data PubKeyAlgo Source #

A public-key encryption algorithm

Constructors

Rsa 
RsaE 
RsaS 
ElgE 
Dsa 
Elg 

data UserId Source #

A user ID consisting of a name, comment, and email address.

Constructors

UserId 

Instances

Instances details
Eq UserId Source # 
Instance details

Defined in Crypto.Gpgme.Key

Methods

(==) :: UserId -> UserId -> Bool #

(/=) :: UserId -> UserId -> Bool #

Ord UserId Source # 
Instance details

Defined in Crypto.Gpgme.Key

Show UserId Source # 
Instance details

Defined in Crypto.Gpgme.Key

keyUserIds :: Key -> [KeyUserId] Source #

Extract KeyUserIds from Key. Uses unsafePerformIO to bypass IO monad! Use keyUserIds instead if possible.

keySubKeys :: Key -> [SubKey] Source #

Extract SubKeys from Key. Uses unsafePerformIO to bypass IO monad! Use keySubKeys instead if possible.

keySubKeys' :: Key -> IO [SubKey] Source #

Extract SubKeys from Key.

Encryption

type Signature = ByteString Source #

a signature

data SignatureSummary Source #

the summary of a signature status

Constructors

BadPolicy

A policy requirement was not met

CrlMissing

The CRL is not available

CrlTooOld

Available CRL is too old

Green

The signature is good but one might want to display some extra information

KeyExpired

The key or one of the certificates has expired

KeyMissing

Can’t verify due to a missing key or certificate

KeyRevoked

The key or at least one certificate has been revoked

Red

The signature is bad

SigExpired

The signature has expired

SysError

A system error occured

UnknownSummary C'gpgme_sigsum_t

The summary is something else

Valid

The signature is fully valid

encrypt :: Ctx -> [Key] -> Flag -> Plain -> IO (Either [InvalidKey] Encrypted) Source #

encrypt for a list of recipients

encryptSign :: Ctx -> [Key] -> Flag -> Plain -> IO (Either [InvalidKey] Encrypted) Source #

encrypt and sign for a list of recipients

encryptFd :: Ctx -> [Key] -> Flag -> Fd -> Fd -> IO (Either [InvalidKey] ()) Source #

Encrypt plaintext

encryptSignFd :: Ctx -> [Key] -> Flag -> Fd -> Fd -> IO (Either [InvalidKey] ()) Source #

Encrypt and sign plaintext

encrypt' :: String -> Fpr -> Plain -> IO (Either String Encrypted) Source #

Convenience wrapper around withCtx and withKey to encrypt a single plaintext for a single recipient with its homedirectory.

encryptSign' :: String -> Fpr -> Plain -> IO (Either String Encrypted) Source #

Convenience wrapper around withCtx and withKey to encrypt and sign a single plaintext for a single recipient with its homedirectory.

decrypt :: Ctx -> Encrypted -> IO (Either DecryptError Plain) Source #

Decrypts a ciphertext

decryptFd :: Ctx -> Fd -> Fd -> IO (Either DecryptError ()) Source #

Decrypt a ciphertext

decryptVerifyFd :: Ctx -> Fd -> Fd -> IO (Either DecryptError ()) Source #

Decrypt and verify ciphertext

decrypt' :: String -> Encrypted -> IO (Either DecryptError Plain) Source #

Convenience wrapper around withCtx and withKey to decrypt a single ciphertext with its homedirectory.

decryptVerify :: Ctx -> Encrypted -> IO (Either DecryptError Plain) Source #

Decrypts and verifies a ciphertext

decryptVerify' :: String -> Encrypted -> IO (Either DecryptError Plain) Source #

Convenience wrapper around withCtx and withKey to decrypt and verify a single ciphertext with its homedirectory.

verify :: Ctx -> Signature -> IO (Either GpgmeError (VerificationResult, ByteString)) Source #

Verify a payload with a plain signature

verify' :: String -> Signature -> IO (Either GpgmeError (VerificationResult, ByteString)) Source #

Convenience wrapper around withCtx to verify a single plain signature with its homedirectory.

verifyDetached Source #

Arguments

:: Ctx

GPG context

-> Signature

Detached signature

-> ByteString

Signed text

-> IO (Either GpgmeError VerificationResult) 

Verify a payload with a detached signature

verifyDetached' Source #

Arguments

:: String

GPG context home directory

-> Signature

Detached signature

-> ByteString

Signed text

-> IO (Either GpgmeError VerificationResult) 

Convenience wrapper around withCtx to verify a single detached signature with its homedirectory.

sign Source #

Arguments

:: Ctx

Context to sign

-> [Key]

Keys to used for signing. An empty list will use context's default key.

-> SignMode

Signing mode

-> Plain

Plain text to sign

-> IO (Either [InvalidKey] Plain) 

Sign plaintext for a list of signers

Error handling

data GpgmeError Source #

A GPGME error.

Errors in GPGME consist of two parts: a code indicating the nature of the fault, and a source indicating from which subsystem the error originated.

errorString :: GpgmeError -> String Source #

An explanatory string for a GPGME error.

sourceString :: GpgmeError -> String Source #

An explanatory string describing the source of a GPGME error

Other Types

data SignMode Source #

Modes for signing with GPG

Constructors

Normal 
Detach 
Clear 

Instances

Instances details
Show SignMode Source # 
Instance details

Defined in Crypto.Gpgme.Types

type Fpr = ByteString Source #

a fingerprint

type Encrypted = ByteString Source #

an ciphertext

type Plain = ByteString Source #

a plaintext

data Protocol Source #

the protocol to be used in the crypto engine

Constructors

CMS 
GPGCONF 
OpenPGP 
UNKNOWN 

Instances

Instances details
Eq Protocol Source # 
Instance details

Defined in Crypto.Gpgme.Types

Ord Protocol Source # 
Instance details

Defined in Crypto.Gpgme.Types

Show Protocol Source # 
Instance details

Defined in Crypto.Gpgme.Types

type InvalidKey = (String, Int) Source #

The fingerprint and an error code

data IncludeSecret Source #

Whether to include secret keys when searching

Constructors

WithSecret

do not include secret keys

NoSecret

include secret keys

data Flag Source #

Constructors

AlwaysTrust 
NoFlag 

Instances

Instances details
Eq Flag Source # 
Instance details

Defined in Crypto.Gpgme.Types

Methods

(==) :: Flag -> Flag -> Bool #

(/=) :: Flag -> Flag -> Bool #

Ord Flag Source # 
Instance details

Defined in Crypto.Gpgme.Types

Methods

compare :: Flag -> Flag -> Ordering #

(<) :: Flag -> Flag -> Bool #

(<=) :: Flag -> Flag -> Bool #

(>) :: Flag -> Flag -> Bool #

(>=) :: Flag -> Flag -> Bool #

max :: Flag -> Flag -> Flag #

min :: Flag -> Flag -> Flag #

Show Flag Source # 
Instance details

Defined in Crypto.Gpgme.Types

Methods

showsPrec :: Int -> Flag -> ShowS #

show :: Flag -> String #

showList :: [Flag] -> ShowS #

data DecryptError Source #

error indicating what went wrong in decryption

Constructors

NoData

no data to decrypt

Failed

not a valid cipher

BadPass

passphrase for secret was wrong

Unknown GpgmeError

something else went wrong

newtype HgpgmeException Source #

h-gpgme exception for wrapping exception which occur outside of the control of h-gpgme