| License | BSD-style | 
|---|---|
| Maintainer | Vincent Hanquez <vincent@snarc.org> | 
| Stability | experimental | 
| Portability | unknown | 
| Safe Haskell | None | 
| Language | Haskell2010 | 
Crypto.Hash.Algorithms
Contents
Description
Definitions of known hash algorithms
Synopsis
- class HashAlgorithm 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 = SHAKE128
- data SHAKE256 bitlen = SHAKE256
- 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.
Minimal complete definition
hashBlockSize, hashDigestSize, hashInternalContextSize, hashInternalInit, hashInternalUpdate, hashInternalFinalize
Instances
hash algorithms
data Blake2s_160 Source #
Blake2s (160 bits) cryptographic hash algorithm
Constructors
| Blake2s_160 | 
Instances
data Blake2s_224 Source #
Blake2s (224 bits) cryptographic hash algorithm
Constructors
| Blake2s_224 | 
Instances
data Blake2s_256 Source #
Blake2s (256 bits) cryptographic hash algorithm
Constructors
| Blake2s_256 | 
Instances
data Blake2sp_224 Source #
Blake2sp (224 bits) cryptographic hash algorithm
Constructors
| Blake2sp_224 | 
Instances
data Blake2sp_256 Source #
Blake2sp (256 bits) cryptographic hash algorithm
Constructors
| Blake2sp_256 | 
Instances
data Blake2b_160 Source #
Blake2b (160 bits) cryptographic hash algorithm
Constructors
| Blake2b_160 | 
Instances
data Blake2b_224 Source #
Blake2b (224 bits) cryptographic hash algorithm
Constructors
| Blake2b_224 | 
Instances
data Blake2b_256 Source #
Blake2b (256 bits) cryptographic hash algorithm
Constructors
| Blake2b_256 | 
Instances
data Blake2b_384 Source #
Blake2b (384 bits) cryptographic hash algorithm
Constructors
| Blake2b_384 | 
Instances
data Blake2b_512 Source #
Blake2b (512 bits) cryptographic hash algorithm
Constructors
| Blake2b_512 | 
Instances
data Blake2bp_512 Source #
Blake2bp (512 bits) cryptographic hash algorithm
Constructors
| Blake2bp_512 | 
Instances
MD2 cryptographic hash algorithm
Constructors
| MD2 | 
Instances
| Data MD2 Source # | |
| Methods 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 :: (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 # | |
| Methods 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 # | |
| Methods hashDigestASN1 :: ByteArray out => Digest MD2 -> out | |
MD4 cryptographic hash algorithm
Constructors
| MD4 | 
Instances
| Data MD4 Source # | |
| Methods 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 :: (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 # | |
| Methods 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 # | |
MD5 cryptographic hash algorithm
Constructors
| MD5 | 
Instances
| Data MD5 Source # | |
| Methods 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 :: (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 # | |
| HashAlgorithm MD5 Source # | |
| Methods 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 # | |
| Methods hashDigestASN1 :: ByteArray out => Digest MD5 -> out | |
SHA1 cryptographic hash algorithm
Constructors
| SHA1 | 
Instances
| Data SHA1 Source # | |
| Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SHA1 -> c SHA1 # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SHA1 # dataTypeOf :: SHA1 -> DataType # dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c SHA1) # dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SHA1) # gmapT :: (forall b. Data b => b -> b) -> SHA1 -> SHA1 # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SHA1 -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SHA1 -> r # gmapQ :: (forall d. Data d => d -> u) -> SHA1 -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> SHA1 -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> SHA1 -> m SHA1 # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SHA1 -> m SHA1 # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SHA1 -> m SHA1 # | |
| Show SHA1 Source # | |
| HashAlgorithm SHA1 Source # | |
| Methods hashBlockSize :: SHA1 -> Int Source # hashDigestSize :: SHA1 -> Int Source # hashInternalContextSize :: SHA1 -> Int Source # hashInternalInit :: Ptr (Context SHA1) -> IO () Source # hashInternalUpdate :: Ptr (Context SHA1) -> Ptr Word8 -> Word32 -> IO () Source # hashInternalFinalize :: Ptr (Context SHA1) -> Ptr (Digest SHA1) -> IO () Source # | |
| HashAlgorithmASN1 SHA1 Source # | |
| Methods hashDigestASN1 :: ByteArray out => Digest SHA1 -> out | |
SHA224 cryptographic hash algorithm
Constructors
| SHA224 | 
Instances
| Data SHA224 Source # | |
| Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SHA224 -> c SHA224 # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SHA224 # toConstr :: SHA224 -> Constr # dataTypeOf :: SHA224 -> DataType # dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c SHA224) # dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SHA224) # gmapT :: (forall b. Data b => b -> b) -> SHA224 -> SHA224 # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SHA224 -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SHA224 -> r # gmapQ :: (forall d. Data d => d -> u) -> SHA224 -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> SHA224 -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> SHA224 -> m SHA224 # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SHA224 -> m SHA224 # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SHA224 -> m SHA224 # | |
| Show SHA224 Source # | |
| HashAlgorithm SHA224 Source # | |
| Methods hashBlockSize :: SHA224 -> Int Source # hashDigestSize :: SHA224 -> Int Source # hashInternalContextSize :: SHA224 -> Int Source # hashInternalInit :: Ptr (Context SHA224) -> IO () Source # hashInternalUpdate :: Ptr (Context SHA224) -> Ptr Word8 -> Word32 -> IO () Source # hashInternalFinalize :: Ptr (Context SHA224) -> Ptr (Digest SHA224) -> IO () Source # | |
| HashAlgorithmASN1 SHA224 Source # | |
| Methods hashDigestASN1 :: ByteArray out => Digest SHA224 -> out | |
SHA256 cryptographic hash algorithm
Constructors
| SHA256 | 
Instances
| Data SHA256 Source # | |
| Methods 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 :: (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 Source # | |
| HashAlgorithm SHA256 Source # | |
| Methods hashBlockSize :: SHA256 -> Int Source # hashDigestSize :: SHA256 -> Int Source # hashInternalContextSize :: SHA256 -> Int Source # hashInternalInit :: Ptr (Context SHA256) -> IO () Source # hashInternalUpdate :: Ptr (Context SHA256) -> Ptr Word8 -> Word32 -> IO () Source # hashInternalFinalize :: Ptr (Context SHA256) -> Ptr (Digest SHA256) -> IO () Source # | |
| HashAlgorithmASN1 SHA256 Source # | |
| Methods hashDigestASN1 :: ByteArray out => Digest SHA256 -> out | |
SHA384 cryptographic hash algorithm
Constructors
| SHA384 | 
Instances
| Data SHA384 Source # | |
| Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SHA384 -> c SHA384 # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SHA384 # toConstr :: SHA384 -> Constr # dataTypeOf :: SHA384 -> DataType # dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c SHA384) # dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SHA384) # gmapT :: (forall b. Data b => b -> b) -> SHA384 -> SHA384 # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SHA384 -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SHA384 -> r # gmapQ :: (forall d. Data d => d -> u) -> SHA384 -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> SHA384 -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> SHA384 -> m SHA384 # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SHA384 -> m SHA384 # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SHA384 -> m SHA384 # | |
| Show SHA384 Source # | |
| HashAlgorithm SHA384 Source # | |
| Methods hashBlockSize :: SHA384 -> Int Source # hashDigestSize :: SHA384 -> Int Source # hashInternalContextSize :: SHA384 -> Int Source # hashInternalInit :: Ptr (Context SHA384) -> IO () Source # hashInternalUpdate :: Ptr (Context SHA384) -> Ptr Word8 -> Word32 -> IO () Source # hashInternalFinalize :: Ptr (Context SHA384) -> Ptr (Digest SHA384) -> IO () Source # | |
| HashAlgorithmASN1 SHA384 Source # | |
| Methods hashDigestASN1 :: ByteArray out => Digest SHA384 -> out | |
SHA512 cryptographic hash algorithm
Constructors
| SHA512 | 
Instances
| Data SHA512 Source # | |
| Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SHA512 -> c SHA512 # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SHA512 # toConstr :: SHA512 -> Constr # dataTypeOf :: SHA512 -> DataType # dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c SHA512) # dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SHA512) # gmapT :: (forall b. Data b => b -> b) -> SHA512 -> SHA512 # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SHA512 -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SHA512 -> r # gmapQ :: (forall d. Data d => d -> u) -> SHA512 -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> SHA512 -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> SHA512 -> m SHA512 # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SHA512 -> m SHA512 # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SHA512 -> m SHA512 # | |
| Show SHA512 Source # | |
| HashAlgorithm SHA512 Source # | |
| Methods hashBlockSize :: SHA512 -> Int Source # hashDigestSize :: SHA512 -> Int Source # hashInternalContextSize :: SHA512 -> Int Source # hashInternalInit :: Ptr (Context SHA512) -> IO () Source # hashInternalUpdate :: Ptr (Context SHA512) -> Ptr Word8 -> Word32 -> IO () Source # hashInternalFinalize :: Ptr (Context SHA512) -> Ptr (Digest SHA512) -> IO () Source # | |
| HashAlgorithmASN1 SHA512 Source # | |
| Methods hashDigestASN1 :: ByteArray out => Digest SHA512 -> out | |
data SHA512t_224 Source #
SHA512t (224 bits) cryptographic hash algorithm
Constructors
| SHA512t_224 | 
Instances
data SHA512t_256 Source #
SHA512t (256 bits) cryptographic hash algorithm
Constructors
| SHA512t_256 | 
Instances
RIPEMD160 cryptographic hash algorithm
Constructors
| RIPEMD160 | 
Instances
| Data RIPEMD160 Source # | |
| Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RIPEMD160 -> c RIPEMD160 # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RIPEMD160 # toConstr :: RIPEMD160 -> Constr # dataTypeOf :: RIPEMD160 -> DataType # dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c RIPEMD160) # dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RIPEMD160) # gmapT :: (forall b. Data b => b -> b) -> RIPEMD160 -> RIPEMD160 # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RIPEMD160 -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RIPEMD160 -> r # gmapQ :: (forall d. Data d => d -> u) -> RIPEMD160 -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> RIPEMD160 -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> RIPEMD160 -> m RIPEMD160 # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RIPEMD160 -> m RIPEMD160 # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RIPEMD160 -> m RIPEMD160 # | |
| Show RIPEMD160 Source # | |
| HashAlgorithm RIPEMD160 Source # | |
| Methods hashBlockSize :: RIPEMD160 -> Int Source # hashDigestSize :: RIPEMD160 -> Int Source # hashInternalContextSize :: RIPEMD160 -> Int Source # hashInternalInit :: Ptr (Context RIPEMD160) -> IO () Source # hashInternalUpdate :: Ptr (Context RIPEMD160) -> Ptr Word8 -> Word32 -> IO () Source # hashInternalFinalize :: Ptr (Context RIPEMD160) -> Ptr (Digest RIPEMD160) -> IO () Source # | |
| HashAlgorithmASN1 RIPEMD160 Source # | |
| Methods hashDigestASN1 :: ByteArray out => Digest RIPEMD160 -> out | |
Tiger cryptographic hash algorithm
Constructors
| Tiger | 
Instances
| Data Tiger Source # | |
| Methods 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 :: (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 # | |
| Methods 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 # | |
data Keccak_224 Source #
Keccak (224 bits) cryptographic hash algorithm
Constructors
| Keccak_224 | 
Instances
data Keccak_256 Source #
Keccak (256 bits) cryptographic hash algorithm
Constructors
| Keccak_256 | 
Instances
data Keccak_384 Source #
Keccak (384 bits) cryptographic hash algorithm
Constructors
| Keccak_384 | 
Instances
data Keccak_512 Source #
Keccak (512 bits) cryptographic hash algorithm
Constructors
| Keccak_512 | 
Instances
SHA3 (224 bits) cryptographic hash algorithm
Constructors
| SHA3_224 | 
Instances
| Data SHA3_224 Source # | |
| Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SHA3_224 -> c SHA3_224 # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SHA3_224 # toConstr :: SHA3_224 -> Constr # dataTypeOf :: SHA3_224 -> DataType # dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c SHA3_224) # dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SHA3_224) # gmapT :: (forall b. Data b => b -> b) -> SHA3_224 -> SHA3_224 # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SHA3_224 -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SHA3_224 -> r # gmapQ :: (forall d. Data d => d -> u) -> SHA3_224 -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> SHA3_224 -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> SHA3_224 -> m SHA3_224 # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SHA3_224 -> m SHA3_224 # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SHA3_224 -> m SHA3_224 # | |
| Show SHA3_224 Source # | |
| HashAlgorithm SHA3_224 Source # | |
| Methods hashBlockSize :: SHA3_224 -> Int Source # hashDigestSize :: SHA3_224 -> Int Source # hashInternalContextSize :: SHA3_224 -> Int Source # hashInternalInit :: Ptr (Context SHA3_224) -> IO () Source # hashInternalUpdate :: Ptr (Context SHA3_224) -> Ptr Word8 -> Word32 -> IO () Source # hashInternalFinalize :: Ptr (Context SHA3_224) -> Ptr (Digest SHA3_224) -> IO () Source # | |
SHA3 (256 bits) cryptographic hash algorithm
Constructors
| SHA3_256 | 
Instances
| Data SHA3_256 Source # | |
| Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SHA3_256 -> c SHA3_256 # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SHA3_256 # toConstr :: SHA3_256 -> Constr # dataTypeOf :: SHA3_256 -> DataType # dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c SHA3_256) # dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SHA3_256) # gmapT :: (forall b. Data b => b -> b) -> SHA3_256 -> SHA3_256 # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SHA3_256 -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SHA3_256 -> r # gmapQ :: (forall d. Data d => d -> u) -> SHA3_256 -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> SHA3_256 -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> SHA3_256 -> m SHA3_256 # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SHA3_256 -> m SHA3_256 # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SHA3_256 -> m SHA3_256 # | |
| Show SHA3_256 Source # | |
| HashAlgorithm SHA3_256 Source # | |
| Methods hashBlockSize :: SHA3_256 -> Int Source # hashDigestSize :: SHA3_256 -> Int Source # hashInternalContextSize :: SHA3_256 -> Int Source # hashInternalInit :: Ptr (Context SHA3_256) -> IO () Source # hashInternalUpdate :: Ptr (Context SHA3_256) -> Ptr Word8 -> Word32 -> IO () Source # hashInternalFinalize :: Ptr (Context SHA3_256) -> Ptr (Digest SHA3_256) -> IO () Source # | |
SHA3 (384 bits) cryptographic hash algorithm
Constructors
| SHA3_384 | 
Instances
| Data SHA3_384 Source # | |
| Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SHA3_384 -> c SHA3_384 # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SHA3_384 # toConstr :: SHA3_384 -> Constr # dataTypeOf :: SHA3_384 -> DataType # dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c SHA3_384) # dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SHA3_384) # gmapT :: (forall b. Data b => b -> b) -> SHA3_384 -> SHA3_384 # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SHA3_384 -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SHA3_384 -> r # gmapQ :: (forall d. Data d => d -> u) -> SHA3_384 -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> SHA3_384 -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> SHA3_384 -> m SHA3_384 # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SHA3_384 -> m SHA3_384 # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SHA3_384 -> m SHA3_384 # | |
| Show SHA3_384 Source # | |
| HashAlgorithm SHA3_384 Source # | |
| Methods hashBlockSize :: SHA3_384 -> Int Source # hashDigestSize :: SHA3_384 -> Int Source # hashInternalContextSize :: SHA3_384 -> Int Source # hashInternalInit :: Ptr (Context SHA3_384) -> IO () Source # hashInternalUpdate :: Ptr (Context SHA3_384) -> Ptr Word8 -> Word32 -> IO () Source # hashInternalFinalize :: Ptr (Context SHA3_384) -> Ptr (Digest SHA3_384) -> IO () Source # | |
SHA3 (512 bits) cryptographic hash algorithm
Constructors
| SHA3_512 | 
Instances
| Data SHA3_512 Source # | |
| Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SHA3_512 -> c SHA3_512 # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SHA3_512 # toConstr :: SHA3_512 -> Constr # dataTypeOf :: SHA3_512 -> DataType # dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c SHA3_512) # dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SHA3_512) # gmapT :: (forall b. Data b => b -> b) -> SHA3_512 -> SHA3_512 # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SHA3_512 -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SHA3_512 -> r # gmapQ :: (forall d. Data d => d -> u) -> SHA3_512 -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> SHA3_512 -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> SHA3_512 -> m SHA3_512 # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SHA3_512 -> m SHA3_512 # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SHA3_512 -> m SHA3_512 # | |
| Show SHA3_512 Source # | |
| HashAlgorithm SHA3_512 Source # | |
| Methods hashBlockSize :: SHA3_512 -> Int Source # hashDigestSize :: SHA3_512 -> Int Source # hashInternalContextSize :: SHA3_512 -> Int Source # hashInternalInit :: Ptr (Context SHA3_512) -> IO () Source # hashInternalUpdate :: Ptr (Context SHA3_512) -> Ptr Word8 -> Word32 -> IO () Source # hashInternalFinalize :: Ptr (Context SHA3_512) -> Ptr (Digest SHA3_512) -> IO () Source # | |
SHAKE128 (128 bits) extendable output function.  Supports an arbitrary
 digest size (multiple of 8 bits), to be specified as a type parameter
 of kind Nat.
Note: outputs from SHAKE128 nSHAKE128 mSHAKE256 results.
Constructors
| SHAKE128 | 
Instances
| Show (SHAKE128 bitlen) Source # | |
| (IsDivisibleBy8 bitLen, KnownNat bitLen) => HashAlgorithm (SHAKE128 bitLen) Source # | |
| Methods 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 # | |
SHAKE256 (256 bits) extendable output function.  Supports an arbitrary
 digest size (multiple of 8 bits), to be specified as a type parameter
 of kind Nat.
Note: outputs from SHAKE256 nSHAKE256 mSHAKE128 results.
Constructors
| SHAKE256 | 
Instances
| Show (SHAKE256 bitlen) Source # | |
| (IsDivisibleBy8 bitLen, KnownNat bitLen) => HashAlgorithm (SHAKE256 bitLen) Source # | |
| Methods 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 # | |
data Skein256_224 Source #
Skein256 (224 bits) cryptographic hash algorithm
Constructors
| Skein256_224 | 
Instances
data Skein256_256 Source #
Skein256 (256 bits) cryptographic hash algorithm
Constructors
| Skein256_256 | 
Instances
data Skein512_224 Source #
Skein512 (224 bits) cryptographic hash algorithm
Constructors
| Skein512_224 | 
Instances
data Skein512_256 Source #
Skein512 (256 bits) cryptographic hash algorithm
Constructors
| Skein512_256 | 
Instances
data Skein512_384 Source #
Skein512 (384 bits) cryptographic hash algorithm
Constructors
| Skein512_384 | 
Instances
data Skein512_512 Source #
Skein512 (512 bits) cryptographic hash algorithm
Constructors
| Skein512_512 | 
Instances
Whirlpool cryptographic hash algorithm
Constructors
| Whirlpool | 
Instances
| Data Whirlpool Source # | |
| Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Whirlpool -> c Whirlpool # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Whirlpool # toConstr :: Whirlpool -> Constr # dataTypeOf :: Whirlpool -> DataType # dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Whirlpool) # dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Whirlpool) # gmapT :: (forall b. Data b => b -> b) -> Whirlpool -> Whirlpool # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Whirlpool -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Whirlpool -> r # gmapQ :: (forall d. Data d => d -> u) -> Whirlpool -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Whirlpool -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Whirlpool -> m Whirlpool # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Whirlpool -> m Whirlpool # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Whirlpool -> m Whirlpool # | |
| Show Whirlpool Source # | |
| HashAlgorithm Whirlpool Source # | |
| Methods hashBlockSize :: Whirlpool -> Int Source # hashDigestSize :: Whirlpool -> Int Source # hashInternalContextSize :: Whirlpool -> Int Source # hashInternalInit :: Ptr (Context Whirlpool) -> IO () Source # hashInternalUpdate :: Ptr (Context Whirlpool) -> Ptr Word8 -> Word32 -> IO () Source # hashInternalFinalize :: Ptr (Context Whirlpool) -> Ptr (Digest Whirlpool) -> IO () Source # | |