| Maintainer | simons@cryp.to | 
|---|---|
| Stability | provisional | 
| Portability | portable | 
| Safe Haskell | None | 
| Language | Haskell98 | 
OpenSSL.EVP.Digest
Contents
Description
Computing message digests with OpenSSL's EVP interface involves the following types:
- Every digest algorithm has an description, OpaqueDigestDescriptionthat can be looked up by name. We can do very few things with that type. We can use it to retrieve the size of the algorithm's output,_digestSize
- TODO: complete this when I know what the high-level API looks like.
- _addAllDigests :: IO ()
- data OpaqueDigestDescription
- _digestByName :: CString -> Ptr OpaqueDigestDescription
- _digestSize :: Ptr OpaqueDigestDescription -> CInt
- _digestBlockSize :: Ptr OpaqueDigestDescription -> CInt
- maxDigestSize :: Int
- data OpaqueDigestEngine
- data OpaqueDigestContext
- _createContext :: IO (Ptr OpaqueDigestContext)
- _initContext :: Ptr OpaqueDigestContext -> IO ()
- _cleanupContext :: Ptr OpaqueDigestContext -> IO CInt
- _destroyContext :: Ptr OpaqueDigestContext -> IO ()
- _initDigest :: Ptr OpaqueDigestContext -> Ptr OpaqueDigestDescription -> Ptr OpaqueDigestEngine -> IO CInt
- _updateDigest :: Ptr OpaqueDigestContext -> Ptr a -> CSize -> IO CInt
- _finalizeDigest :: Ptr OpaqueDigestContext -> Ptr Word8 -> Ptr CUInt -> IO CInt
- newtype DigestDescription = DigestDescription {}
- digestByName :: String -> DigestDescription
- digestByName' :: String -> Maybe DigestDescription
- newtype DigestContext = DigestContext {}
- digestContext :: Ptr OpaqueDigestContext -> DigestContext
- initContext :: DigestContext -> IO ()
- createContext :: IO DigestContext
- initDigest :: DigestDescription -> DigestContext -> IO ()
- cleanupContext :: DigestContext -> IO ()
- destroyContext :: DigestContext -> IO ()
- updateDigest :: DigestContext -> Ptr a -> CSize -> IO ()
- finalizeDigest :: DigestContext -> Ptr Word8 -> IO ()
- throwIfZero :: String -> IO CInt -> IO ()
- toHex :: Word8 -> String
- isDigestEngineInitialized :: MVar Bool
- newtype DigestAlgorithmNotAvailableInOpenSSL = DigestAlgorithmNotAvailableInOpenSSL String
- data AttemptToConstructDigestContextFromNullPointer = AttemptToConstructDigestContextFromNullPointer
Low-level API
OpenSSL Library Initialization
_addAllDigests :: IO () Source #
Initialize the OpenSSL EVP engine and register all known digest types in
 the internal data structures. This function must be called before
 _digestByName can succeed. Calling it multiple times is probably not
 harmful, but it certainly unnecessary and should be avoided. Users of
 digestByName' and digestByName don't have to worry about this.
Accessing the Supported Digest Types
_digestByName :: CString -> Ptr OpaqueDigestDescription Source #
Look up a Digest by name. Be sure to call _addAllDigests before you
 use this function.
_digestSize :: Ptr OpaqueDigestDescription -> CInt Source #
Return the size of the digest the given algorithm will produce.
_digestBlockSize :: Ptr OpaqueDigestDescription -> CInt Source #
Return the block size the the given algorithm operates with.
maxDigestSize :: Int Source #
The largest possible digest size of any of the algorithms supported by
 this library. So if you want to store a digest without bothering to retrieve
 the appropriate size with _digestSize first, allocate a buffer of that
 size.
data OpaqueDigestEngine Source #
We don't support choosing specific engines. Always pass nullPtr where
 such a thing is expected to get the default engine for the given algorithm.
Digest Contexts
data OpaqueDigestContext Source #
A context in which -- when initialized -- digest computations can be run.
 There is a Storable solely for the benefit of being able to create that
 type with alloca and _init instead of having to use _create, which
 uses the heap. Anyway, that instance does not define peek nor poke since
 those make no sense.
Instances
_createContext :: IO (Ptr OpaqueDigestContext) Source #
Allocate an (initialized) OpaqueDigestContext for use in a digest
 computation on the heap. Release its underlying memory after use with
 _destroy.
_initContext :: Ptr OpaqueDigestContext -> IO () Source #
Initialize an OpaqueDigestContext for use in a digest computation. The
 type can be allocated on the stack with alloca or on the heap with
 _create.
_cleanupContext :: Ptr OpaqueDigestContext -> IO CInt Source #
Release all resources associated with a digest computation's context, but don't release the underlying digest context structure. This allows the context to be re-initiaized for use another computation.
_destroyContext :: Ptr OpaqueDigestContext -> IO () Source #
Release all resources associated with a digest computation's context and the
 context structure itself. Use this only for context's acquired with _create.
State of a Digest Computation
_initDigest :: Ptr OpaqueDigestContext -> Ptr OpaqueDigestDescription -> Ptr OpaqueDigestEngine -> IO CInt Source #
Configure the given initialized digest context to use the given message
 digest algorithm. The third parameter allows developers to choose a specific
 engine for that digest, too, but these bindings don't support choosing any
 specific engine, so pass nullPtr here to the default choice determined by
 OpenSSL.
_updateDigest :: Ptr OpaqueDigestContext -> Ptr a -> CSize -> IO CInt Source #
Hash the given block of memory and update the digest state accordingly.
 Naturally, this function can be called many times. Then use
 _finalizeDigest to retrieve the actual hash value.
_finalizeDigest :: Ptr OpaqueDigestContext -> Ptr Word8 -> Ptr CUInt -> IO CInt Source #
Finalize the digest calculation and return the result in the Word8 array
 passed as an argument. Naturally, that array is expected to be large enough
 to contain the digest. _digestSize or maxDigestSize are your friends. If
 the CUInt pointer is not nullPtr, then the actual size of the generated
 digest is written into that integer. This function does not clean up the
 digest context; this has to be done with an explicit call to
 _cleanupContext or _destroyContext. However, it does invalidate the
 digest state so that no further calls of _digestUpdate can be made without
 re-initializing the state with _initDigest first.
High-level interface
newtype DigestDescription Source #
Constructors
| DigestDescription | |
Instances
| Eq DigestDescription Source # | |
| Show DigestDescription Source # | |
| IsString DigestDescription Source # | This instance allows the compiler to translate the string  | 
newtype DigestContext Source #
Constructors
| DigestContext | |
| Fields | |
initContext :: DigestContext -> IO () Source #
initDigest :: DigestDescription -> DigestContext -> IO () Source #
Simplified variant of _initDigest that (a) always chooses the default
 digest engine and (b) reports failure by means of an exception.
cleanupContext :: DigestContext -> IO () Source #
destroyContext :: DigestContext -> IO () Source #
updateDigest :: DigestContext -> Ptr a -> CSize -> IO () Source #
finalizeDigest :: DigestContext -> Ptr Word8 -> IO () Source #
Helper Types and Functions
throwIfZero :: String -> IO CInt -> IO () Source #
Most OpenSSL functions return an approximation of Bool to signify
 failure. This wrapper makes it easier to move the error handling to the
 exception layer where appropriate.
toHex :: Word8 -> String Source #
Neat helper to pretty-print digests into the common hexadecimal notation:
>>>[0..15] >>= toHex"000102030405060708090a0b0c0d0e0f"
newtype DigestAlgorithmNotAvailableInOpenSSL Source #
A custom exception type which is thrown by digestByName in case the
 requested digest algorithm is not available in the OpenSSL system library.
Constructors
| DigestAlgorithmNotAvailableInOpenSSL String | 
data AttemptToConstructDigestContextFromNullPointer Source #
A custom exception type thrown by digestContext if the function is used
 to construct a DigestContext from a nullPtr.
Constructors
| AttemptToConstructDigestContextFromNullPointer |