License | BSD-style |
---|---|
Maintainer | Vincent Hanquez <vincent@snarc.org> |
Stability | experimental |
Portability | unknown |
Safe Haskell | None |
Language | Haskell2010 |
Generalized cryptographic hash interface, that you can use with cryptographic hash algorithm that belong to the HashAlgorithm type class.
import Crypto.Hash sha1 :: ByteString -> Digest SHA1 sha1 = hash hexSha3_512 :: ByteString -> String hexSha3_512 bs = show (hash bs :: Digest SHA3_512)
- data Context a
- data Digest a
- digestFromByteString :: forall a ba. (HashAlgorithm a, ByteArrayAccess ba) => ba -> Maybe (Digest a)
- hashInitWith :: HashAlgorithm alg => alg -> Context alg
- hashWith :: (ByteArrayAccess ba, HashAlgorithm alg) => alg -> ba -> Digest alg
- hashInit :: forall a. HashAlgorithm a => Context a
- hashUpdates :: forall a ba. (HashAlgorithm a, ByteArrayAccess ba) => Context a -> [ba] -> Context a
- hashUpdate :: (ByteArrayAccess ba, HashAlgorithm a) => Context a -> ba -> Context a
- hashFinalize :: forall a. HashAlgorithm a => Context a -> Digest a
- hashBlockSize :: HashAlgorithm a => a -> Int
- hashDigestSize :: HashAlgorithm a => a -> Int
- hash :: (ByteArrayAccess ba, HashAlgorithm a) => ba -> Digest a
- hashlazy :: HashAlgorithm a => ByteString -> Digest a
- module Crypto.Hash.Algorithms
Types
Represent a context for a given hash algorithm.
Represent a digest for a given hash algorithm.
This type is an instance of ByteArrayAccess
from package
memory.
Module Data.ByteArray provides many primitives to work with those values
including conversion to other types.
Creating a digest from a bytearray is also possible with function
digestFromByteString
.
Functions
digestFromByteString :: forall a ba. (HashAlgorithm a, ByteArrayAccess ba) => ba -> Maybe (Digest a) Source #
Try to transform a bytearray into a Digest of specific algorithm.
If the digest is not the right size for the algorithm specified, then Nothing is returned.
Hash methods parametrized by algorithm
hashInitWith :: HashAlgorithm alg => alg -> Context alg Source #
Initialize a new context for a specified hash algorithm
hashWith :: (ByteArrayAccess ba, HashAlgorithm alg) => alg -> ba -> Digest alg Source #
Run the hash
function but takes an explicit hash algorithm parameter
Hash methods
hashInit :: forall a. HashAlgorithm a => Context a Source #
Initialize a new context for this hash algorithm
hashUpdates :: forall a ba. (HashAlgorithm a, ByteArrayAccess ba) => Context a -> [ba] -> Context a Source #
Update the context with a list of strict bytestring, and return a new context with the updates.
hashUpdate :: (ByteArrayAccess ba, HashAlgorithm a) => Context a -> ba -> Context a Source #
run hashUpdates on one single bytestring and return the updated context.
hashFinalize :: forall a. HashAlgorithm a => Context a -> Digest a Source #
Finalize a context and return a digest.
hashBlockSize :: HashAlgorithm a => a -> Int Source #
Get the block size of a hash algorithm
hashDigestSize :: HashAlgorithm a => a -> Int Source #
Get the digest size of a hash algorithm
hash :: (ByteArrayAccess ba, HashAlgorithm a) => ba -> Digest a Source #
Hash a strict bytestring into a digest.
hashlazy :: HashAlgorithm a => ByteString -> Digest a Source #
Hash a lazy bytestring into a digest.
Hash algorithms
module Crypto.Hash.Algorithms