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)
Synopsis
- 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
.
Instances
Eq (Digest a) Source # | |
Data a => Data (Digest a) Source # | |
Defined in Crypto.Hash.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Digest a -> c (Digest a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Digest a) # toConstr :: Digest a -> Constr # dataTypeOf :: Digest a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Digest a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Digest a)) # gmapT :: (forall b. Data b => b -> b) -> Digest a -> Digest a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Digest a -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Digest a -> r # gmapQ :: (forall d. Data d => d -> u) -> Digest a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Digest a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Digest a -> m (Digest a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Digest a -> m (Digest a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Digest a -> m (Digest a) # | |
Ord (Digest a) Source # | |
Defined in Crypto.Hash.Types | |
HashAlgorithm a => Read (Digest a) Source # | |
Show (Digest a) Source # | |
NFData (Digest a) Source # | |
Defined in Crypto.Hash.Types | |
ByteArrayAccess (Digest a) Source # | |
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