License | BSD-style |
---|---|
Maintainer | Vincent Hanquez <vincent@snarc.org> |
Stability | experimental |
Portability | unknown |
Safe Haskell | None |
Language | Haskell2010 |
Definitions of known hash algorithms
Synopsis
- class HashAlgorithm a
- class HashAlgorithm a => HashAlgorithmPrefix a
- data Blake2s_160 = Blake2s_160
- data Blake2s_224 = Blake2s_224
- data Blake2s_256 = Blake2s_256
- data Blake2sp_224 = Blake2sp_224
- data Blake2sp_256 = Blake2sp_256
- data Blake2b_160 = Blake2b_160
- data Blake2b_224 = Blake2b_224
- data Blake2b_256 = Blake2b_256
- data Blake2b_384 = Blake2b_384
- data Blake2b_512 = Blake2b_512
- data Blake2bp_512 = Blake2bp_512
- data MD2 = MD2
- data MD4 = MD4
- data MD5 = MD5
- data SHA1 = SHA1
- data SHA224 = SHA224
- data SHA256 = SHA256
- data SHA384 = SHA384
- data SHA512 = SHA512
- data SHA512t_224 = SHA512t_224
- data SHA512t_256 = SHA512t_256
- data RIPEMD160 = RIPEMD160
- data Tiger = Tiger
- data Keccak_224 = Keccak_224
- data Keccak_256 = Keccak_256
- data Keccak_384 = Keccak_384
- data Keccak_512 = Keccak_512
- data SHA3_224 = SHA3_224
- data SHA3_256 = SHA3_256
- data SHA3_384 = SHA3_384
- data SHA3_512 = SHA3_512
- data SHAKE128 (bitlen :: Nat) = SHAKE128
- data SHAKE256 (bitlen :: Nat) = SHAKE256
- data Blake2b (bitlen :: Nat) = Blake2b
- data Blake2bp (bitlen :: Nat) = Blake2bp
- data Blake2s (bitlen :: Nat) = Blake2s
- data Blake2sp (bitlen :: Nat) = Blake2sp
- data Skein256_224 = Skein256_224
- data Skein256_256 = Skein256_256
- data Skein512_224 = Skein512_224
- data Skein512_256 = Skein512_256
- data Skein512_384 = Skein512_384
- data Skein512_512 = Skein512_512
- data Whirlpool = Whirlpool
Documentation
class HashAlgorithm a Source #
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
class HashAlgorithm a => HashAlgorithmPrefix a Source #
Hashing algorithms with a constant-time implementation.
hashInternalFinalizePrefix
Hash algorithms
data Blake2s_160 Source #
Blake2s (160 bits) cryptographic hash algorithm
Instances
data Blake2s_224 Source #
Blake2s (224 bits) cryptographic hash algorithm
Instances
data Blake2s_256 Source #
Blake2s (256 bits) cryptographic hash algorithm
Instances
data Blake2sp_224 Source #
Blake2sp (224 bits) cryptographic hash algorithm
Instances
data Blake2sp_256 Source #
Blake2sp (256 bits) cryptographic hash algorithm
Instances
data Blake2b_160 Source #
Blake2b (160 bits) cryptographic hash algorithm
Instances
data Blake2b_224 Source #
Blake2b (224 bits) cryptographic hash algorithm
Instances
data Blake2b_256 Source #
Blake2b (256 bits) cryptographic hash algorithm
Instances
data Blake2b_384 Source #
Blake2b (384 bits) cryptographic hash algorithm
Instances
data Blake2b_512 Source #
Blake2b (512 bits) cryptographic hash algorithm
Instances
data Blake2bp_512 Source #
Blake2bp (512 bits) cryptographic hash algorithm
Instances
MD2 cryptographic hash algorithm
Instances
Data MD2 Source # | |
Defined in Crypto.Hash.MD2 gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MD2 -> c MD2 # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MD2 # dataTypeOf :: MD2 -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c MD2) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MD2) # gmapT :: (forall b. Data b => b -> b) -> MD2 -> MD2 # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MD2 -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MD2 -> r # gmapQ :: (forall d. Data d => d -> u) -> MD2 -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> MD2 -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> MD2 -> m MD2 # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MD2 -> m MD2 # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MD2 -> m MD2 # | |
Show MD2 Source # | |
HashAlgorithm MD2 Source # | |
Defined in Crypto.Hash.MD2 type HashBlockSize MD2 :: Nat Source # type HashDigestSize MD2 :: Nat Source # type HashInternalContextSize MD2 :: Nat Source # hashBlockSize :: MD2 -> Int Source # hashDigestSize :: MD2 -> Int Source # hashInternalContextSize :: MD2 -> Int Source # hashInternalInit :: Ptr (Context MD2) -> IO () Source # hashInternalUpdate :: Ptr (Context MD2) -> Ptr Word8 -> Word32 -> IO () Source # hashInternalFinalize :: Ptr (Context MD2) -> Ptr (Digest MD2) -> IO () Source # | |
HashAlgorithmASN1 MD2 Source # | |
Defined in Crypto.PubKey.RSA.PKCS15 hashDigestASN1 :: ByteArray out => Digest MD2 -> out | |
type HashBlockSize MD2 Source # | |
Defined in Crypto.Hash.MD2 | |
type HashDigestSize MD2 Source # | |
Defined in Crypto.Hash.MD2 | |
type HashInternalContextSize MD2 Source # | |
Defined in Crypto.Hash.MD2 |
MD4 cryptographic hash algorithm
Instances
Data MD4 Source # | |
Defined in Crypto.Hash.MD4 gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MD4 -> c MD4 # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MD4 # dataTypeOf :: MD4 -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c MD4) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MD4) # gmapT :: (forall b. Data b => b -> b) -> MD4 -> MD4 # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MD4 -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MD4 -> r # gmapQ :: (forall d. Data d => d -> u) -> MD4 -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> MD4 -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> MD4 -> m MD4 # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MD4 -> m MD4 # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MD4 -> m MD4 # | |
Show MD4 Source # | |
HashAlgorithm MD4 Source # | |
Defined in Crypto.Hash.MD4 type HashBlockSize MD4 :: Nat Source # type HashDigestSize MD4 :: Nat Source # type HashInternalContextSize MD4 :: Nat Source # hashBlockSize :: MD4 -> Int Source # hashDigestSize :: MD4 -> Int Source # hashInternalContextSize :: MD4 -> Int Source # hashInternalInit :: Ptr (Context MD4) -> IO () Source # hashInternalUpdate :: Ptr (Context MD4) -> Ptr Word8 -> Word32 -> IO () Source # hashInternalFinalize :: Ptr (Context MD4) -> Ptr (Digest MD4) -> IO () Source # | |
type HashBlockSize MD4 Source # | |
Defined in Crypto.Hash.MD4 | |
type HashDigestSize MD4 Source # | |
Defined in Crypto.Hash.MD4 | |
type HashInternalContextSize MD4 Source # | |
Defined in Crypto.Hash.MD4 |
MD5 cryptographic hash algorithm
Instances
Data MD5 Source # | |
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 Source # | |
HashAlgorithmPrefix MD5 Source # | |
HashAlgorithm MD5 Source # | |
Defined in Crypto.Hash.MD5 type HashBlockSize MD5 :: Nat Source # type HashDigestSize MD5 :: Nat Source # type HashInternalContextSize MD5 :: Nat Source # hashBlockSize :: MD5 -> Int Source # hashDigestSize :: MD5 -> Int Source # hashInternalContextSize :: MD5 -> Int Source # hashInternalInit :: Ptr (Context MD5) -> IO () Source # hashInternalUpdate :: Ptr (Context MD5) -> Ptr Word8 -> Word32 -> IO () Source # hashInternalFinalize :: Ptr (Context MD5) -> Ptr (Digest MD5) -> IO () Source # | |
HashAlgorithmASN1 MD5 Source # | |
Defined in Crypto.PubKey.RSA.PKCS15 hashDigestASN1 :: ByteArray out => Digest MD5 -> out | |
type HashBlockSize MD5 Source # | |
Defined in Crypto.Hash.MD5 | |
type HashDigestSize MD5 Source # | |
Defined in Crypto.Hash.MD5 | |
type HashInternalContextSize MD5 Source # | |
Defined in Crypto.Hash.MD5 |
SHA1 cryptographic hash algorithm
Instances
SHA224 cryptographic hash algorithm
Instances
SHA256 cryptographic hash algorithm
Instances
SHA384 cryptographic hash algorithm
Instances
SHA512 cryptographic hash algorithm
Instances
data SHA512t_224 Source #
SHA512t (224 bits) cryptographic hash algorithm
Instances
data SHA512t_256 Source #
SHA512t (256 bits) cryptographic hash algorithm
Instances
RIPEMD160 cryptographic hash algorithm
Instances
Tiger cryptographic hash algorithm
Instances
Data Tiger Source # | |
Defined in Crypto.Hash.Tiger gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Tiger -> c Tiger # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Tiger # dataTypeOf :: Tiger -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Tiger) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Tiger) # gmapT :: (forall b. Data b => b -> b) -> Tiger -> Tiger # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Tiger -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Tiger -> r # gmapQ :: (forall d. Data d => d -> u) -> Tiger -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Tiger -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Tiger -> m Tiger # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Tiger -> m Tiger # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Tiger -> m Tiger # | |
Show Tiger Source # | |
HashAlgorithm Tiger Source # | |
Defined in Crypto.Hash.Tiger type HashBlockSize Tiger :: Nat Source # type HashDigestSize Tiger :: Nat Source # type HashInternalContextSize Tiger :: Nat Source # hashBlockSize :: Tiger -> Int Source # hashDigestSize :: Tiger -> Int Source # hashInternalContextSize :: Tiger -> Int Source # hashInternalInit :: Ptr (Context Tiger) -> IO () Source # hashInternalUpdate :: Ptr (Context Tiger) -> Ptr Word8 -> Word32 -> IO () Source # hashInternalFinalize :: Ptr (Context Tiger) -> Ptr (Digest Tiger) -> IO () Source # | |
type HashBlockSize Tiger Source # | |
Defined in Crypto.Hash.Tiger | |
type HashDigestSize Tiger Source # | |
Defined in Crypto.Hash.Tiger | |
type HashInternalContextSize Tiger Source # | |
Defined in Crypto.Hash.Tiger |
data Keccak_224 Source #
Keccak (224 bits) cryptographic hash algorithm
Instances
data Keccak_256 Source #
Keccak (256 bits) cryptographic hash algorithm
Instances
data Keccak_384 Source #
Keccak (384 bits) cryptographic hash algorithm
Instances
data Keccak_512 Source #
Keccak (512 bits) cryptographic hash algorithm
Instances
SHA3 (224 bits) cryptographic hash algorithm
Instances
SHA3 (256 bits) cryptographic hash algorithm
Instances
SHA3 (384 bits) cryptographic hash algorithm
Instances
SHA3 (512 bits) cryptographic hash algorithm
Instances
data SHAKE128 (bitlen :: Nat) Source #
SHAKE128 (128 bits) extendable output function. Supports an arbitrary
digest size, to be specified as a type parameter of kind Nat
.
Note: outputs from
and SHAKE128
n
for the same input are
correlated (one being a prefix of the other). Results are unrelated to
SHAKE128
mSHAKE256
results.
Instances
KnownNat bitlen => Data (SHAKE128 bitlen) Source # | |
Defined in Crypto.Hash.SHAKE gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SHAKE128 bitlen -> c (SHAKE128 bitlen) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (SHAKE128 bitlen) # toConstr :: SHAKE128 bitlen -> Constr # dataTypeOf :: SHAKE128 bitlen -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (SHAKE128 bitlen)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (SHAKE128 bitlen)) # gmapT :: (forall b. Data b => b -> b) -> SHAKE128 bitlen -> SHAKE128 bitlen # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SHAKE128 bitlen -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SHAKE128 bitlen -> r # gmapQ :: (forall d. Data d => d -> u) -> SHAKE128 bitlen -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> SHAKE128 bitlen -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> SHAKE128 bitlen -> m (SHAKE128 bitlen) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SHAKE128 bitlen -> m (SHAKE128 bitlen) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SHAKE128 bitlen -> m (SHAKE128 bitlen) # | |
Show (SHAKE128 bitlen) Source # | |
KnownNat bitlen => HashAlgorithm (SHAKE128 bitlen) Source # | |
Defined in Crypto.Hash.SHAKE type HashBlockSize (SHAKE128 bitlen) :: Nat Source # type HashDigestSize (SHAKE128 bitlen) :: Nat Source # type HashInternalContextSize (SHAKE128 bitlen) :: Nat Source # hashBlockSize :: SHAKE128 bitlen -> Int Source # hashDigestSize :: SHAKE128 bitlen -> Int Source # hashInternalContextSize :: SHAKE128 bitlen -> Int Source # hashInternalInit :: Ptr (Context (SHAKE128 bitlen)) -> IO () Source # hashInternalUpdate :: Ptr (Context (SHAKE128 bitlen)) -> Ptr Word8 -> Word32 -> IO () Source # hashInternalFinalize :: Ptr (Context (SHAKE128 bitlen)) -> Ptr (Digest (SHAKE128 bitlen)) -> IO () Source # | |
KnownNat bitlen => HashSHAKE (SHAKE128 bitlen) Source # | |
Defined in Crypto.Hash.SHAKE | |
type HashBlockSize (SHAKE128 bitlen) Source # | |
Defined in Crypto.Hash.SHAKE | |
type HashDigestSize (SHAKE128 bitlen) Source # | |
Defined in Crypto.Hash.SHAKE | |
type HashInternalContextSize (SHAKE128 bitlen) Source # | |
Defined in Crypto.Hash.SHAKE |
data SHAKE256 (bitlen :: Nat) Source #
SHAKE256 (256 bits) extendable output function. Supports an arbitrary
digest size, to be specified as a type parameter of kind Nat
.
Note: outputs from
and SHAKE256
n
for the same input are
correlated (one being a prefix of the other). Results are unrelated to
SHAKE256
mSHAKE128
results.
Instances
KnownNat bitlen => Data (SHAKE256 bitlen) Source # | |
Defined in Crypto.Hash.SHAKE gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SHAKE256 bitlen -> c (SHAKE256 bitlen) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (SHAKE256 bitlen) # toConstr :: SHAKE256 bitlen -> Constr # dataTypeOf :: SHAKE256 bitlen -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (SHAKE256 bitlen)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (SHAKE256 bitlen)) # gmapT :: (forall b. Data b => b -> b) -> SHAKE256 bitlen -> SHAKE256 bitlen # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SHAKE256 bitlen -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SHAKE256 bitlen -> r # gmapQ :: (forall d. Data d => d -> u) -> SHAKE256 bitlen -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> SHAKE256 bitlen -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> SHAKE256 bitlen -> m (SHAKE256 bitlen) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SHAKE256 bitlen -> m (SHAKE256 bitlen) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SHAKE256 bitlen -> m (SHAKE256 bitlen) # | |
Show (SHAKE256 bitlen) Source # | |
KnownNat bitlen => HashAlgorithm (SHAKE256 bitlen) Source # | |
Defined in Crypto.Hash.SHAKE type HashBlockSize (SHAKE256 bitlen) :: Nat Source # type HashDigestSize (SHAKE256 bitlen) :: Nat Source # type HashInternalContextSize (SHAKE256 bitlen) :: Nat Source # hashBlockSize :: SHAKE256 bitlen -> Int Source # hashDigestSize :: SHAKE256 bitlen -> Int Source # hashInternalContextSize :: SHAKE256 bitlen -> Int Source # hashInternalInit :: Ptr (Context (SHAKE256 bitlen)) -> IO () Source # hashInternalUpdate :: Ptr (Context (SHAKE256 bitlen)) -> Ptr Word8 -> Word32 -> IO () Source # hashInternalFinalize :: Ptr (Context (SHAKE256 bitlen)) -> Ptr (Digest (SHAKE256 bitlen)) -> IO () Source # | |
KnownNat bitlen => HashSHAKE (SHAKE256 bitlen) Source # | |
Defined in Crypto.Hash.SHAKE | |
type HashBlockSize (SHAKE256 bitlen) Source # | |
Defined in Crypto.Hash.SHAKE | |
type HashDigestSize (SHAKE256 bitlen) Source # | |
Defined in Crypto.Hash.SHAKE | |
type HashInternalContextSize (SHAKE256 bitlen) Source # | |
Defined in Crypto.Hash.SHAKE |
data Blake2b (bitlen :: Nat) Source #
Fast cryptographic hash.
It is especially known to target 64bits architectures.
Known supported digest sizes:
- Blake2b 160
- Blake2b 224
- Blake2b 256
- Blake2b 384
- Blake2b 512
Instances
KnownNat bitlen => Data (Blake2b bitlen) Source # | |
Defined in Crypto.Hash.Blake2 gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Blake2b bitlen -> c (Blake2b bitlen) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Blake2b bitlen) # toConstr :: Blake2b bitlen -> Constr # dataTypeOf :: Blake2b bitlen -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Blake2b bitlen)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Blake2b bitlen)) # gmapT :: (forall b. Data b => b -> b) -> Blake2b bitlen -> Blake2b bitlen # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Blake2b bitlen -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Blake2b bitlen -> r # gmapQ :: (forall d. Data d => d -> u) -> Blake2b bitlen -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Blake2b bitlen -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Blake2b bitlen -> m (Blake2b bitlen) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Blake2b bitlen -> m (Blake2b bitlen) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Blake2b bitlen -> m (Blake2b bitlen) # | |
Show (Blake2b bitlen) Source # | |
(IsDivisibleBy8 bitlen, KnownNat bitlen, IsAtLeast bitlen 8, IsAtMost bitlen 512) => HashAlgorithm (Blake2b bitlen) Source # | |
Defined in Crypto.Hash.Blake2 type HashBlockSize (Blake2b bitlen) :: Nat Source # type HashDigestSize (Blake2b bitlen) :: Nat Source # type HashInternalContextSize (Blake2b bitlen) :: Nat Source # hashBlockSize :: Blake2b bitlen -> Int Source # hashDigestSize :: Blake2b bitlen -> Int Source # hashInternalContextSize :: Blake2b bitlen -> Int Source # hashInternalInit :: Ptr (Context (Blake2b bitlen)) -> IO () Source # hashInternalUpdate :: Ptr (Context (Blake2b bitlen)) -> Ptr Word8 -> Word32 -> IO () Source # hashInternalFinalize :: Ptr (Context (Blake2b bitlen)) -> Ptr (Digest (Blake2b bitlen)) -> IO () Source # | |
type HashBlockSize (Blake2b bitlen) Source # | |
Defined in Crypto.Hash.Blake2 | |
type HashDigestSize (Blake2b bitlen) Source # | |
Defined in Crypto.Hash.Blake2 | |
type HashInternalContextSize (Blake2b bitlen) Source # | |
Defined in Crypto.Hash.Blake2 |
data Blake2bp (bitlen :: Nat) Source #
Instances
KnownNat bitlen => Data (Blake2bp bitlen) Source # | |
Defined in Crypto.Hash.Blake2 gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Blake2bp bitlen -> c (Blake2bp bitlen) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Blake2bp bitlen) # toConstr :: Blake2bp bitlen -> Constr # dataTypeOf :: Blake2bp bitlen -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Blake2bp bitlen)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Blake2bp bitlen)) # gmapT :: (forall b. Data b => b -> b) -> Blake2bp bitlen -> Blake2bp bitlen # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Blake2bp bitlen -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Blake2bp bitlen -> r # gmapQ :: (forall d. Data d => d -> u) -> Blake2bp bitlen -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Blake2bp bitlen -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Blake2bp bitlen -> m (Blake2bp bitlen) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Blake2bp bitlen -> m (Blake2bp bitlen) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Blake2bp bitlen -> m (Blake2bp bitlen) # | |
Show (Blake2bp bitlen) Source # | |
(IsDivisibleBy8 bitlen, KnownNat bitlen, IsAtLeast bitlen 8, IsAtMost bitlen 512) => HashAlgorithm (Blake2bp bitlen) Source # | |
Defined in Crypto.Hash.Blake2 type HashBlockSize (Blake2bp bitlen) :: Nat Source # type HashDigestSize (Blake2bp bitlen) :: Nat Source # type HashInternalContextSize (Blake2bp bitlen) :: Nat Source # hashBlockSize :: Blake2bp bitlen -> Int Source # hashDigestSize :: Blake2bp bitlen -> Int Source # hashInternalContextSize :: Blake2bp bitlen -> Int Source # hashInternalInit :: Ptr (Context (Blake2bp bitlen)) -> IO () Source # hashInternalUpdate :: Ptr (Context (Blake2bp bitlen)) -> Ptr Word8 -> Word32 -> IO () Source # hashInternalFinalize :: Ptr (Context (Blake2bp bitlen)) -> Ptr (Digest (Blake2bp bitlen)) -> IO () Source # | |
type HashBlockSize (Blake2bp bitlen) Source # | |
Defined in Crypto.Hash.Blake2 | |
type HashDigestSize (Blake2bp bitlen) Source # | |
Defined in Crypto.Hash.Blake2 | |
type HashInternalContextSize (Blake2bp bitlen) Source # | |
Defined in Crypto.Hash.Blake2 |
data Blake2s (bitlen :: Nat) Source #
Fast and secure alternative to SHA1 and HMAC-SHA1
It is espacially known to target 32bits architectures.
Known supported digest sizes:
- Blake2s 160
- Blake2s 224
- Blake2s 256
Instances
KnownNat bitlen => Data (Blake2s bitlen) Source # | |
Defined in Crypto.Hash.Blake2 gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Blake2s bitlen -> c (Blake2s bitlen) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Blake2s bitlen) # toConstr :: Blake2s bitlen -> Constr # dataTypeOf :: Blake2s bitlen -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Blake2s bitlen)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Blake2s bitlen)) # gmapT :: (forall b. Data b => b -> b) -> Blake2s bitlen -> Blake2s bitlen # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Blake2s bitlen -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Blake2s bitlen -> r # gmapQ :: (forall d. Data d => d -> u) -> Blake2s bitlen -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Blake2s bitlen -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Blake2s bitlen -> m (Blake2s bitlen) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Blake2s bitlen -> m (Blake2s bitlen) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Blake2s bitlen -> m (Blake2s bitlen) # | |
Show (Blake2s bitlen) Source # | |
(IsDivisibleBy8 bitlen, KnownNat bitlen, IsAtLeast bitlen 8, IsAtMost bitlen 256) => HashAlgorithm (Blake2s bitlen) Source # | |
Defined in Crypto.Hash.Blake2 type HashBlockSize (Blake2s bitlen) :: Nat Source # type HashDigestSize (Blake2s bitlen) :: Nat Source # type HashInternalContextSize (Blake2s bitlen) :: Nat Source # hashBlockSize :: Blake2s bitlen -> Int Source # hashDigestSize :: Blake2s bitlen -> Int Source # hashInternalContextSize :: Blake2s bitlen -> Int Source # hashInternalInit :: Ptr (Context (Blake2s bitlen)) -> IO () Source # hashInternalUpdate :: Ptr (Context (Blake2s bitlen)) -> Ptr Word8 -> Word32 -> IO () Source # hashInternalFinalize :: Ptr (Context (Blake2s bitlen)) -> Ptr (Digest (Blake2s bitlen)) -> IO () Source # | |
type HashBlockSize (Blake2s bitlen) Source # | |
Defined in Crypto.Hash.Blake2 | |
type HashDigestSize (Blake2s bitlen) Source # | |
Defined in Crypto.Hash.Blake2 | |
type HashInternalContextSize (Blake2s bitlen) Source # | |
Defined in Crypto.Hash.Blake2 |
data Blake2sp (bitlen :: Nat) Source #
Instances
KnownNat bitlen => Data (Blake2sp bitlen) Source # | |
Defined in Crypto.Hash.Blake2 gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Blake2sp bitlen -> c (Blake2sp bitlen) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Blake2sp bitlen) # toConstr :: Blake2sp bitlen -> Constr # dataTypeOf :: Blake2sp bitlen -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Blake2sp bitlen)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Blake2sp bitlen)) # gmapT :: (forall b. Data b => b -> b) -> Blake2sp bitlen -> Blake2sp bitlen # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Blake2sp bitlen -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Blake2sp bitlen -> r # gmapQ :: (forall d. Data d => d -> u) -> Blake2sp bitlen -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Blake2sp bitlen -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Blake2sp bitlen -> m (Blake2sp bitlen) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Blake2sp bitlen -> m (Blake2sp bitlen) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Blake2sp bitlen -> m (Blake2sp bitlen) # | |
Show (Blake2sp bitlen) Source # | |
(IsDivisibleBy8 bitlen, KnownNat bitlen, IsAtLeast bitlen 8, IsAtMost bitlen 256) => HashAlgorithm (Blake2sp bitlen) Source # | |
Defined in Crypto.Hash.Blake2 type HashBlockSize (Blake2sp bitlen) :: Nat Source # type HashDigestSize (Blake2sp bitlen) :: Nat Source # type HashInternalContextSize (Blake2sp bitlen) :: Nat Source # hashBlockSize :: Blake2sp bitlen -> Int Source # hashDigestSize :: Blake2sp bitlen -> Int Source # hashInternalContextSize :: Blake2sp bitlen -> Int Source # hashInternalInit :: Ptr (Context (Blake2sp bitlen)) -> IO () Source # hashInternalUpdate :: Ptr (Context (Blake2sp bitlen)) -> Ptr Word8 -> Word32 -> IO () Source # hashInternalFinalize :: Ptr (Context (Blake2sp bitlen)) -> Ptr (Digest (Blake2sp bitlen)) -> IO () Source # | |
type HashBlockSize (Blake2sp bitlen) Source # | |
Defined in Crypto.Hash.Blake2 | |
type HashDigestSize (Blake2sp bitlen) Source # | |
Defined in Crypto.Hash.Blake2 | |
type HashInternalContextSize (Blake2sp bitlen) Source # | |
Defined in Crypto.Hash.Blake2 |
data Skein256_224 Source #
Skein256 (224 bits) cryptographic hash algorithm
Instances
data Skein256_256 Source #
Skein256 (256 bits) cryptographic hash algorithm
Instances
data Skein512_224 Source #
Skein512 (224 bits) cryptographic hash algorithm
Instances
data Skein512_256 Source #
Skein512 (256 bits) cryptographic hash algorithm
Instances
data Skein512_384 Source #
Skein512 (384 bits) cryptographic hash algorithm
Instances
data Skein512_512 Source #
Skein512 (512 bits) cryptographic hash algorithm
Instances
Whirlpool cryptographic hash algorithm