Maintainer | simons@cryp.to |
---|---|
Stability | provisional |
Portability | portable |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
This module provides a generic high-level API to the message digest
algorithms found in OpenSSL's crypto
library. There are two functions of
particular interest: digestByName
and digest
. The former can be used to
retrieve an Algorithm
, i.e. an OpenSSL object that implements a particular
algorithm. That type can then be used to compute actual message digests with
the latter function:
>>>
import Data.ByteString.Char8 ( pack )
>>>
digest (digestByName "md5") (pack "Hello, world.")
"\b\n\239\131\155\149\250\207s\236Y\147u\233-G"
Neat pretty-printing can be achieved with toHex
, which converts the binary
representation of a message digest into the common hexadecimal one:
>>>
toHex $ digest (digestByName "md5") (pack "Hello, world.")
"080aef839b95facf73ec599375e92d47">>>
toHex $ digest (digestByName "sha1") (pack "Hello, world.")
"2ae01472317d1935a84797ec1983ae243fc6aa28"
The precise set of available digest algorithms provided by OpenSSL depends
on the version of the library installed into the system, obviously, but it's
reasonable to expect the following algorithms to be present: MD5, RIPEMD160,
SHA1, SHA224, SHA256, SHA384, and SHA512. If an algorithm is not available,
digestByName
will throw an DigestAlgorithmNotAvailableInOpenSSL
exception. If you don't like exceptions, use the tamer digestByName'
variant:
>>>
digestByName' "i bet this algorithm won't exist"
Nothing
Algorithm
is an instance of IsString
, so with the proper GHC extensions
enabled it's possible to simplify the call to digest
even further:
>>>
:set -XOverloadedStrings
>>>
toHex $ digest "sha256" (pack "The 'Through the Universe' podcast rules.")
"73624694a9435095c8fdaad711273a23c02226196c452f817cfd86f965895614"
Last but not least, digest
is actually a class method of Digestable
,
which collects things we can compute digests of. The defaults are
conservative, i.e. we support all things that correspond roughly to C's
construct of "void pointer plus a length". digest
can use with any of the
following signatures:
>>>
let shape1 = digest :: Algorithm -> (Ptr (), CSize) -> MessageDigest
>>>
let shape2 = digest :: Algorithm -> (Ptr Word8, CSize) -> MessageDigest
>>>
let shape3 = digest :: Algorithm -> (Ptr Word8, CUInt) -> MessageDigest
>>>
let shape4 = digest :: Algorithm -> (Ptr (), Int) -> MessageDigest
>>>
let shape5 = digest :: Algorithm -> StrictByteString -> MessageDigest
>>>
let shape6 = digest :: Algorithm -> LazyByteString -> MessageDigest
StrictByteString
and LazyByteString
are also instances of IsString
and
therefore subject to implicit construction from string literals:
>>>
shape5 "sha256" "hello" == shape6 "sha256" "hello"
True
Note that this code offers no overloaded digest
version for String
,
because that function would produce non-deterministic results for Unicode
characters. There is an instance for [Word8]
, though, so strings can be
hashed after a proper encoding has been applied. For those who don't care
about determinism, there is the following specialized function:
>>>
toHex $ digestString "md5" "no Digestable instance for this sucker"
"a74827f849005794565f83fbd68ad189"
If you don't mind orphaned instances, however, feel free to shoot yourself in the foot:
>>>
:set -XFlexibleInstances
>>>
instance Digestable String where updateChunk ctx str = withCStringLen str (updateChunk ctx)
>>>
toHex $ digest "sha256" ("now we can hash strings" :: String)
"7f2989f173125810aa917c4ffe0e26ae1b5f7fb852274829c210297a43dfc7f9"
Synopsis
- type MessageDigest = StrictByteString
- digest :: Digestable a => Algorithm -> a -> MessageDigest
- class Digestable a where
- updateChunk :: Context -> a -> IO ()
- digestByName :: String -> Algorithm
- digestByName' :: String -> Maybe Algorithm
- data Algorithm
- digestString :: Algorithm -> String -> MessageDigest
- toHex :: MessageDigest -> StrictByteString
- type StrictByteString = ByteString
- type LazyByteString = ByteString
Generic digest API
type MessageDigest = StrictByteString Source #
A message digest is essentially an array of Word8
octets.
digest :: Digestable a => Algorithm -> a -> MessageDigest Source #
Compute the given message digest of any Digestable
thing, i.e. any type
that can be converted efficiently and unambiguously into a continuous
memory buffer or a sequence of continuous memory buffers. Note that String
does not have that property, because the binary representation chosen for
Unicode characters during the marshaling process is determined by the
system's locale and is therefore non-deterministic.
class Digestable a where Source #
A class of things that can be part of a digest computations. By default, we define instances only for various representations of plain memory buffers, but in theory that class can be extended to contain all kinds of complex data types.
updateChunk :: Context -> a -> IO () Source #
Instances
Digestable LazyByteString Source # | |
Defined in OpenSSL.Digest updateChunk :: Context -> LazyByteString -> IO () Source # | |
Digestable StrictByteString Source # | |
Defined in OpenSSL.Digest updateChunk :: Context -> StrictByteString -> IO () Source # | |
Digestable [Word8] Source # | |
Defined in OpenSSL.Digest | |
Digestable (Ptr a, CInt) Source # | |
Defined in OpenSSL.Digest | |
Digestable (Ptr a, CSize) Source # | |
Defined in OpenSSL.Digest | |
Digestable (Ptr a, CUInt) Source # | |
Defined in OpenSSL.Digest | |
Digestable (Ptr a, Int) Source # | |
Defined in OpenSSL.Digest |
digestByName :: String -> Algorithm Source #
Look up a digest algorithm engine by name. Algorithms usually offered by
OpenSSL are "md2", "md5", "sha1", "mdc2", "ripemd160", "blake2b512",
"blake2s256", "sha224", "sha256", "sha384", and "sha512", but the exact set
may vary between platforms. Throws UnknownAlgorithm
if the requested
algorithm is not known.
digestByName' :: String -> Maybe Algorithm Source #
Variant of digestByName
that signals failure by evaluating to Nothing
rather than failing.
>>>
digestByName' "sha256" == Just (digestByName "sha256")
True>>>
digestByName' "Guess what?" :: Maybe Algorithm
Nothing
An opaque handle into OpenSSL's collection of message digest algorithms.
Use digestByName
to look up any of the available algorithms by name. For
the sake of convenience, Algorithm
is an instance of IsString
so
that the compiler can transparently map String
literals to algorithms via
fromString
if the XOverloadedStrings
extension is enabled.
>>>
fromString "sha256" == digestByName "sha256"
True
Special instances
digestString :: Algorithm -> String -> MessageDigest Source #
We do not define a Digestable
instance for String
, because there is
no one obviously correct way to encode Unicode characters for purposes of
calculating a digest. We have, however, this specialized function which
computes a digest over a String
by means of withCStrinLen
. This means
that the representation of Unicode characters depends on the process locale
a.k.a. it's non-deterministc!
>>>
toHex $ digestString (digestByName "sha1") "Hello, world."
"2ae01472317d1935a84797ec1983ae243fc6aa28"
Helper Types and Functions
toHex :: MessageDigest -> StrictByteString Source #
Pretty-print a given message digest from binary into hexadecimal representation.
>>>
toHex (Data.ByteString.pack [0..15])
"000102030405060708090a0b0c0d0e0f"
type StrictByteString = ByteString Source #
Synonym for the strict ByteString
variant to improve readability.
type LazyByteString = ByteString Source #
Synonym for the lazy ByteString
variant to improve readability.