hopenssl-1.0: FFI bindings to OpenSSL's EVP digest interfaceSource codeContentsIndex
OpenSSL.Digest
Portabilityportable
Stabilityprovisional
Maintainersimons@cryp.to
Contents
High-level API
Low-level API
Message Digest Engines
Helper Functions
Description

This module proivdes a high-level API to the message digest algorithms found in OpenSSL's crypto library. Link with -lcrypto when using this module.

Here is a short example program which runs all available digests on a string:

 example :: (Enum a) => [a] -> IO [String]
 example input = mapM hash [minBound .. maxBound]
   where
   hash f = fmap (fmt f) (digest f (toWord input))
   fmt f  = shows f . (":    \t"++) . (>>=toHex)
   toWord = map (toEnum . fromEnum)

And when called, the function prints:

 *Digest> example "open sesame" >>= putStr . unlines
 Null:
 MD2:       a22a0b245bdddb00b5293ad590297b25
 MD5:       54ef36ec71201fdf9d1423fd26f97f6b
 SHA:       2ccefef64c76ac0d42ca1657457977675890c42f
 SHA1:      5bcaff7f22ff533ca099b3408ead876c0ebba9a7
 DSS:       5bcaff7f22ff533ca099b3408ead876c0ebba9a7
 DSS1:      5bcaff7f22ff533ca099b3408ead876c0ebba9a7
 MDC2:      112db2200ce1e9db3c2d132aea4ef7d0
 RIPEMD160: bdb2bba6ec93bd566dc1181cadbc92176aa78382
Synopsis
data MessageDigest
= Null
| MD2
| MD5
| SHA
| SHA1
| DSS
| DSS1
| MDC2
| RIPEMD160
digest :: MessageDigest -> [Word8] -> IO [Word8]
type Digest a = StateT DigestState IO a
newtype DigestState = DST (Ptr OpaqueContext)
mkDigest :: MessageDigest -> (DigestState -> IO a) -> IO a
update :: [Word8] -> Digest ()
update' :: (Ptr Word8, Int) -> Digest ()
final :: Digest [Word8]
data OpaqueContext = OpaqueContext
type Context = Ptr OpaqueContext
data OpaqueMDEngine = OpaqueMDEngine
type MDEngine = Ptr OpaqueMDEngine
maxMDSize :: Int
ctxCreate :: IO Context
ctxInit :: Context -> IO ()
ctxDestroy :: Context -> IO ()
digestInit :: Context -> MDEngine -> IO CInt
digestUpdate :: Context -> Ptr Word8 -> CUInt -> IO CInt
digestFinal :: Context -> Ptr Word8 -> Ptr CUInt -> IO CInt
mdNull :: IO MDEngine
mdMD2 :: IO MDEngine
mdMD5 :: IO MDEngine
mdSHA :: IO MDEngine
mdSHA1 :: IO MDEngine
mdDSS :: IO MDEngine
mdDSS1 :: IO MDEngine
mdMDC2 :: IO MDEngine
mdRIPEMD160 :: IO MDEngine
toMDEngine :: MessageDigest -> IO MDEngine
toHex :: Word8 -> String
High-level API
data MessageDigest Source
The message digest algorithms we support.
Constructors
Null0 bit
MD2128 bit
MD5128 bit
SHA160 bit
SHA1160 bit
DSS160 bit (SHA1)
DSS1160 bit (SHA1)
MDC2128 bit
RIPEMD160160 bit
show/hide Instances
digest :: MessageDigest -> [Word8] -> IO [Word8]Source
A convenience wrapper which computes the given digest over a list of Word8. Unlike the monadic interface, this function does not allow the computation to be restarted.
type Digest a = StateT DigestState IO aSource
A monadic interface to the digest computation.
newtype DigestState Source
The internal EVP context.
Constructors
DST (Ptr OpaqueContext)
show/hide Instances
mkDigest :: MessageDigest -> (DigestState -> IO a) -> IO aSource
Run an IO computation with an initialized DigestState. All resources will be freed when the computation returns.
update :: [Word8] -> Digest ()Source
Update the internal state with a block of data. This function is just a wrapper for update', which creates an array in memory using withArray.
update' :: (Ptr Word8, Int) -> Digest ()Source
Update the internal state with a block of data from memory. This is the faster version of update.
final :: Digest [Word8]Source
Wrap up the computation, add padding, do whatever has to be done, and return the final hash. The length of the result depends on the chosen MessageDigest. Do not call more than once!
Low-level API
data OpaqueContext Source
The EVP context used by OpenSSL is opaque for us; we only access it through a Ptr.
Constructors
OpaqueContext
type Context = Ptr OpaqueContextSource
data OpaqueMDEngine Source
The message digest engines are opaque for us as well.
Constructors
OpaqueMDEngine
type MDEngine = Ptr OpaqueMDEngineSource
maxMDSize :: IntSource
Maximum size of all message digests supported by OpenSSL. Allocate a buffer of this size for digestFinal if you want to stay generic.
ctxCreate :: IO ContextSource
Create an EVP context. May be nullPtr.
ctxInit :: Context -> IO ()Source
Initialize an EVP context.
ctxDestroy :: Context -> IO ()Source
Destroy an EVP context and free the allocated resources.
digestInit :: Context -> MDEngine -> IO CIntSource
Set the message digest engine for digestUpdate calls. Returns /=0 in case of an error.
digestUpdate :: Context -> Ptr Word8 -> CUInt -> IO CIntSource
Update the internal context with a block of input. Returns /=0 in case of an error.
digestFinal :: Context -> Ptr Word8 -> Ptr CUInt -> IO CIntSource
Wrap up the digest computation and return the final digest. Do not call repeatedly on the same context! Returns /=0 in case of an error. The pointer to the unsigned integer may be nullPtr. If it is not, digestFinal will store the length of the computed digest there.
Message Digest Engines
mdNull :: IO MDEngineSource
mdMD2 :: IO MDEngineSource
mdMD5 :: IO MDEngineSource
mdSHA :: IO MDEngineSource
mdSHA1 :: IO MDEngineSource
mdDSS :: IO MDEngineSource
mdDSS1 :: IO MDEngineSource
mdMDC2 :: IO MDEngineSource
mdRIPEMD160 :: IO MDEngineSource
toMDEngine :: MessageDigest -> IO MDEngineSource
Map a MessageDigest type into the the corresponding MDEngine.
Helper Functions
toHex :: Word8 -> StringSource
Neat helper to print digests with: \ws :: [Word8] -> ws >>= toHex
Produced by Haddock version 2.4.2