Copyright | (c) 2013-2023 Brendan Hay |
---|---|
License | Mozilla Public License, v. 2.0. |
Maintainer | Brendan Hay <brendan.g.hay+amazonka@gmail.com> |
Stability | provisional |
Portability | non-portable (GHC extensions) |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Synopsis
- type Key = ByteString
- hmacSHA1 :: ByteArrayAccess a => Key -> a -> HMAC SHA1
- hmacSHA256 :: ByteArrayAccess a => Key -> a -> HMAC SHA256
- hashSHA1 :: ByteArrayAccess a => a -> Digest SHA1
- hashSHA256 :: ByteArrayAccess a => a -> Digest SHA256
- hashMD5 :: ByteArrayAccess a => a -> Digest MD5
- hash :: (ByteArrayAccess ba, HashAlgorithm a) => ba -> Digest a
- sinkSHA256 :: Monad m => ConduitM ByteString o m (Digest SHA256)
- sinkMD5 :: Monad m => ConduitM ByteString o m (Digest MD5)
- class HashAlgorithm a
- data Digest a
- data SHA256
- data MD5
HMAC
type Key = ByteString Source #
hmacSHA256 :: ByteArrayAccess a => Key -> a -> HMAC SHA256 Source #
Hashing
hashSHA256 :: ByteArrayAccess a => a -> Digest SHA256 Source #
hash :: (ByteArrayAccess ba, HashAlgorithm a) => ba -> Digest a #
Hash a strict bytestring into a digest.
sinkSHA256 :: Monad m => ConduitM ByteString o m (Digest SHA256) Source #
Incrementally calculate a SHA256
Digest
.
sinkMD5 :: Monad m => ConduitM ByteString o m (Digest MD5) Source #
Incrementally calculate a MD5
Digest
.
Re-exported
class HashAlgorithm a #
Class representing hashing algorithms.
The interface presented here is update in place and lowlevel. the Hash module takes care of hidding the mutable interface properly.
hashBlockSize, hashDigestSize, hashInternalContextSize, hashInternalInit, hashInternalUpdate, hashInternalFinalize
Instances
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
ToText (Digest a) Source # | |
Data a => Data (Digest a) | |
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 :: forall r r'. (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) # | |
HashAlgorithm a => Read (Digest a) | |
Show (Digest a) | |
NFData (Digest a) | |
Defined in Crypto.Hash.Types | |
Eq (Digest a) | |
Ord (Digest a) | |
Defined in Crypto.Hash.Types | |
ByteArrayAccess (Digest a) | |
SHA256 cryptographic hash algorithm
Instances
Data SHA256 | |
Defined in Crypto.Hash.SHA256 gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SHA256 -> c SHA256 # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SHA256 # toConstr :: SHA256 -> Constr # dataTypeOf :: SHA256 -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SHA256) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SHA256) # gmapT :: (forall b. Data b => b -> b) -> SHA256 -> SHA256 # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SHA256 -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SHA256 -> r # gmapQ :: (forall d. Data d => d -> u) -> SHA256 -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> SHA256 -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> SHA256 -> m SHA256 # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SHA256 -> m SHA256 # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SHA256 -> m SHA256 # | |
Show SHA256 | |
HashAlgorithm SHA256 | |
Defined in Crypto.Hash.SHA256 type HashBlockSize SHA256 :: Nat # type HashDigestSize SHA256 :: Nat # type HashInternalContextSize SHA256 :: Nat # hashBlockSize :: SHA256 -> Int # hashDigestSize :: SHA256 -> Int # hashInternalContextSize :: SHA256 -> Int # hashInternalInit :: Ptr (Context SHA256) -> IO () # hashInternalUpdate :: Ptr (Context SHA256) -> Ptr Word8 -> Word32 -> IO () # hashInternalFinalize :: Ptr (Context SHA256) -> Ptr (Digest SHA256) -> IO () # | |
HashAlgorithmPrefix SHA256 | |
type HashBlockSize SHA256 | |
Defined in Crypto.Hash.SHA256 | |
type HashDigestSize SHA256 | |
Defined in Crypto.Hash.SHA256 | |
type HashInternalContextSize SHA256 | |
Defined in Crypto.Hash.SHA256 |
MD5 cryptographic hash algorithm
Instances
Data MD5 | |
Defined in Crypto.Hash.MD5 gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MD5 -> c MD5 # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MD5 # dataTypeOf :: MD5 -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c MD5) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MD5) # gmapT :: (forall b. Data b => b -> b) -> MD5 -> MD5 # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MD5 -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MD5 -> r # gmapQ :: (forall d. Data d => d -> u) -> MD5 -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> MD5 -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> MD5 -> m MD5 # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MD5 -> m MD5 # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MD5 -> m MD5 # | |
Show MD5 | |
HashAlgorithm MD5 | |
Defined in Crypto.Hash.MD5 type HashBlockSize MD5 :: Nat # type HashDigestSize MD5 :: Nat # type HashInternalContextSize MD5 :: Nat # | |
HashAlgorithmPrefix MD5 | |
type HashBlockSize MD5 | |
Defined in Crypto.Hash.MD5 | |
type HashDigestSize MD5 | |
Defined in Crypto.Hash.MD5 | |
type HashInternalContextSize MD5 | |
Defined in Crypto.Hash.MD5 |