HsOpenSSL-0.11.7.6: Partial OpenSSL binding for Haskell
Safe HaskellNone
LanguageHaskell2010

OpenSSL.EVP.Internal

Synopsis

Documentation

newtype Cipher Source #

Cipher is an opaque object that represents an algorithm of symmetric cipher.

Constructors

Cipher (Ptr EVP_CIPHER) 

withCipherPtr :: Cipher -> (Ptr EVP_CIPHER -> IO a) -> IO a Source #

newtype CipherCtx Source #

Constructors

CipherCtx (ForeignPtr EVP_CIPHER_CTX) 

withCipherCtxPtr :: CipherCtx -> (Ptr EVP_CIPHER_CTX -> IO a) -> IO a Source #

withNewCipherCtxPtr :: (Ptr EVP_CIPHER_CTX -> IO a) -> IO a Source #

data CryptoMode Source #

CryptoMode represents instruction to cipher and such like.

Constructors

Encrypt 
Decrypt 

cipherInitBS Source #

Arguments

:: Cipher 
-> ByteString

key

-> ByteString

IV

-> CryptoMode 
-> IO CipherCtx 

cipherUpdateBS :: CipherCtx -> ByteString -> IO ByteString Source #

cipherFinalBS :: CipherCtx -> IO ByteString Source #

cipherStrictly :: CipherCtx -> ByteString -> IO ByteString Source #

cipherLazily :: CipherCtx -> ByteString -> IO ByteString Source #

newtype Digest Source #

Digest is an opaque object that represents an algorithm of message digest.

Constructors

Digest (Ptr EVP_MD) 

withMDPtr :: Digest -> (Ptr EVP_MD -> IO a) -> IO a Source #

newtype DigestCtx Source #

Constructors

DigestCtx (ForeignPtr EVP_MD_CTX) 

withDigestCtxPtr :: DigestCtx -> (Ptr EVP_MD_CTX -> IO a) -> IO a Source #

digestUpdateBS :: DigestCtx -> ByteString -> IO () Source #

digestFinalBS :: DigestCtx -> IO ByteString Source #

digestFinal :: DigestCtx -> IO String Source #

digestStrictly :: Digest -> ByteString -> IO DigestCtx Source #

digestLazily :: Digest -> ByteString -> IO DigestCtx Source #

newtype HmacCtx Source #

Constructors

HmacCtx (ForeignPtr HMAC_CTX) 

withHmacCtxPtr :: HmacCtx -> (Ptr HMAC_CTX -> IO a) -> IO a Source #

hmacUpdateBS :: HmacCtx -> ByteString -> IO () Source #

hmacFinalBS :: HmacCtx -> IO ByteString Source #

hmacLazily :: Digest -> ByteString -> ByteString -> IO HmacCtx Source #

newtype VaguePKey Source #

VaguePKey is a ForeignPtr to EVP_PKEY, that is either public key or a ker pair. We can't tell which at compile time.

Constructors

VaguePKey (ForeignPtr EVP_PKEY) 

class PKey k where Source #

Instances of class PKey can be converted back and forth to VaguePKey.

Methods

toPKey :: k -> IO VaguePKey Source #

Wrap the key (i.g. RSA) into EVP_PKEY.

fromPKey :: VaguePKey -> IO (Maybe k) Source #

Extract the concrete key from the EVP_PKEY. Returns Nothing if the type mismatches.

pkeySize :: k -> Int Source #

Do the same as EVP_PKEY_size().

pkeyDefaultMD :: k -> IO Digest Source #

Return the default digesting algorithm for the key.

Instances

Instances details
PKey DSAKeyPair Source # 
Instance details

Defined in OpenSSL.EVP.PKey

PKey DSAPubKey Source # 
Instance details

Defined in OpenSSL.EVP.PKey

PKey SomeKeyPair Source # 
Instance details

Defined in OpenSSL.EVP.PKey

PKey SomePublicKey Source # 
Instance details

Defined in OpenSSL.EVP.PKey

PKey RSAKeyPair Source # 
Instance details

Defined in OpenSSL.EVP.PKey

PKey RSAPubKey Source # 
Instance details

Defined in OpenSSL.EVP.PKey

createPKey :: (Ptr EVP_PKEY -> IO a) -> IO VaguePKey Source #

withPKeyPtr :: VaguePKey -> (Ptr EVP_PKEY -> IO a) -> IO a Source #

withPKeyPtr' :: PKey k => k -> (Ptr EVP_PKEY -> IO a) -> IO a Source #