Copyright | Dong Han 2021 |
---|---|
License | BSD |
Maintainer | winterland1989@gmail.com |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
This module provides raw block cipher and various cipher mode.
Block ciphers are a n-bit permutation for some small n, typically 64 or 128 bits. They are a cryptographic primitive used to generate higher level operations such as authenticated encryption.
A block cipher by itself, is only able to securely encrypt a single data block. To be able to securely encrypt data of arbitrary length, a mode of operation applies the block cipher’s single block operation repeatedly to encrypt an entire message.
Synopsis
- data BlockCipherType
- = AES128
- | AES192
- | AES256
- | ARIA128
- | ARIA192
- | ARIA256
- | Blowfish
- | Camellia128
- | Camellia192
- | Camellia256
- | Cascade BlockCipherType BlockCipherType
- | CAST128
- | CAST256
- | DES
- | DESX
- | TripleDES
- | IDEA
- | KASUMI
- | Lion HashType StreamCipherType Int
- | MISTY1
- | Noekeon
- | SEED
- | Serpent
- | SHACAL2
- | Twofish
- | SM4
- | Threefish512
- | XTEA
- data KeySpec = KeySpec {}
- data BlockCipher
- blockCipherName :: BlockCipher -> CBytes
- blockCipherKeySpec :: BlockCipher -> KeySpec
- blockCipherSize :: BlockCipher -> Int
- newBlockCipher :: HasCallStack => BlockCipherType -> IO BlockCipher
- setBlockCipherKey :: HasCallStack => BlockCipher -> Secret -> IO ()
- clearBlockCipher :: HasCallStack => BlockCipher -> IO ()
- encryptBlocks :: HasCallStack => BlockCipher -> Bytes -> Int -> IO Bytes
- decryptBlocks :: HasCallStack => BlockCipher -> Bytes -> Int -> IO Bytes
- data CipherMode
- = ChaCha20Poly1305
- | GCM BlockCipherType
- | GCM' BlockCipherType Int
- | OCB BlockCipherType
- | OCB' BlockCipherType Int
- | EAX BlockCipherType
- | EAX' BlockCipherType Int
- | SIV BlockCipherType
- | CCM BlockCipherType
- | CCM' BlockCipherType Int Int
- | CFB BlockCipherType
- | CFB' BlockCipherType Int
- | XTS BlockCipherType
- | CBC_PKCS7 BlockCipherType
- | CBC_OneAndZeros BlockCipherType
- | CBC_X9'23 BlockCipherType
- | CBC_ESP BlockCipherType
- | CBC_CTS BlockCipherType
- | CBC_NoPadding BlockCipherType
- data CipherDirection
- data Cipher
- cipherName :: Cipher -> CBytes
- cipherKeySpec :: Cipher -> KeySpec
- cipherTagLength :: Cipher -> Int
- defaultNonceLength :: Cipher -> Int
- newCipher :: HasCallStack => CipherMode -> CipherDirection -> IO Cipher
- setCipherKey :: HasCallStack => Cipher -> Secret -> IO ()
- clearCipher :: HasCallStack => Cipher -> IO ()
- runCipher :: HasCallStack => Cipher -> Nonce -> Bytes -> Bytes -> IO Bytes
- data StreamCipherType
- data StreamCipher
- streamCipherName :: StreamCipher -> CBytes
- streamCipherKeySpec :: StreamCipher -> KeySpec
- defaultIVLength :: StreamCipher -> Int
- newStreamCipher :: HasCallStack => StreamCipherType -> IO StreamCipher
- setStreamCipherKey :: HasCallStack => StreamCipher -> Secret -> IO ()
- clearStreamCipher :: HasCallStack => StreamCipher -> IO ()
- setStreamCipherIV :: StreamCipher -> Nonce -> IO ()
- seekStreamCipher :: StreamCipher -> Int -> IO ()
- runStreamCipher :: HasCallStack => StreamCipher -> Bytes -> IO Bytes
- streamCipherKeyStream :: HasCallStack => StreamCipher -> Int -> IO Bytes
- streamCipherBIO :: HasCallStack => StreamCipher -> BIO Bytes Bytes
- keyStreamSource :: HasCallStack => StreamCipher -> Int -> Source Bytes
- blockCipherTypeToCBytes :: BlockCipherType -> CBytes
- withBlockCipher :: BlockCipher -> (BotanStructT -> IO r) -> IO r
- withCipher :: Cipher -> (BotanStructT -> IO r) -> IO r
- withStreamCipher :: StreamCipher -> (BotanStructT -> IO r) -> IO r
- data HashType
- = BLAKE2b Int
- | BLAKE2b256
- | BLAKE2b512
- | Keccak1600_224
- | Keccak1600_256
- | Keccak1600_384
- | Keccak1600_512
- | MD4
- | MD5
- | RIPEMD160
- | SHA160
- | SHA256
- | SHA224
- | SHA512
- | SHA384
- | SHA512_256
- | SHA3_224
- | SHA3_256
- | SHA3_384
- | SHA3_512
- | SHAKE128 Int
- | SHAKE256 Int
- | SM3
- | Skein512 Int CBytes
- | Streebog256
- | Streebog512
- | Whirlpool
- | Parallel HashType HashType
- | Comb4P HashType HashType
- | Adler32
- | CRC24
- | CRC32
- module Z.Crypto.SafeMem
Block Cipher
data BlockCipherType Source #
Available Block Ciphers
Botan includes a number of block ciphers that are specific to particular countries, as well as a few that are included mostly due to their use in specific protocols such as PGP but not widely used elsewhere. If you are developing new code and have no particular opinion, use AES-256. If you desire an alternative to AES, consider Serpent, SHACAL2 or Threefish.
Warning: Avoid any 64-bit block cipher in new designs. There are combinatoric issues that affect any 64-bit cipher that render it insecure when large amounts of data are processed.
AES128 | AES Comes in three variants, AES-128, AES-192, and AES-256. The standard 128-bit block cipher. Many modern platforms offer hardware acceleration. However, on platforms without hardware support, AES implementations typically are vulnerable to side channel attacks. For x86 systems with SSSE3 but without AES-NI, Botan has an implementation which avoids known side channels. |
AES192 | |
AES256 | |
ARIA128 | ARIA South Korean cipher used in industry there. No reason to use it otherwise. |
ARIA192 | |
ARIA256 | |
Blowfish | Blowfish A 64-bit cipher popular in the pre-AES era. Very slow key setup. Also used (with bcrypt) for password hashing. |
Camellia128 | Camellia Comes in three variants, Camellia-128, Camellia-192, and Camellia-256. A Japanese design standardized by ISO, NESSIE and CRYPTREC. Rarely used outside of Japan. |
Camellia192 | |
Camellia256 | |
Cascade BlockCipherType BlockCipherType | Cascade Creates a block cipher cascade, where each block is encrypted by two ciphers with independent keys. Useful if you're very paranoid. In practice any single good cipher (such as Serpent, SHACAL2, or AES-256) is more than sufficient. Please set a key with size = max_key_size_A + max_key_size_B. |
CAST128 | CAST-128 A 64-bit cipher, commonly used in OpenPGP. |
CAST256 | CAST-256 A 128-bit cipher that was a contestant in the NIST AES competition. Almost never used in practice. Prefer AES or Serpent. Warning: Support for CAST-256 is deprecated and will be removed in a future major release. |
DES | DES, 3DES, DESX Originally designed by IBM and NSA in the 1970s. Today, DES's 56-bit key renders it insecure to any well-resourced attacker. DESX and 3DES extend the key length, and are still thought to be secure, modulo the limitation of a 64-bit block. All are somewhat common in some industries such as finance. Avoid in new code. Warning: Support for DESX is deprecated and it will be removed in a future major release. |
DESX | |
TripleDES | |
IDEA | IDEA An older but still unbroken 64-bit cipher with a 128-bit key. Somewhat common due to its use in PGP. Avoid in new designs. |
KASUMI | Kasumi A 64-bit cipher used in 3GPP mobile phone protocols. There is no reason to use it outside of this context. Warning: Support for Kasumi is deprecated and will be removed in a future major release. |
Lion HashType StreamCipherType Int | Lion A "block cipher construction" which can encrypt blocks of nearly arbitrary length. Built from a stream cipher and a hash function. Useful in certain protocols where being able to encrypt large or arbitrary length blocks is necessary. |
MISTY1 | MISTY1 A 64-bit Japanese cipher standardized by NESSIE and ISO. Seemingly secure, but quite slow and saw little adoption. No reason to use it in new code. Warning: Support for MISTY1 is deprecated and will be removed in a future major release. |
Noekeon | Noekeon A fast 128-bit cipher by the designers of AES. Easily secured against side channels. |
SEED | SEED A older South Korean cipher, widely used in industry there. No reason to choose it otherwise. |
Serpent | Serpent An AES contender. Widely considered the most conservative design. Fairly slow unless SIMD instructions are available. |
SHACAL2 | SHACAL2 The 256-bit block cipher used inside SHA-256. Accepts up to a 512-bit key. Fast, especially when SIMD or SHA-2 acceleration instructions are available. Standardized by NESSIE but otherwise obscure. |
Twofish | Twofish A 128-bit block cipher that was one of the AES finalists. Has a somewhat complicated key setup and a "kitchen sink" design. |
SM4 | SM4 A 128-bit Chinese national cipher, required for use in certain commercial applications in China. Quite slow. Probably no reason to use it outside of legal requirements. |
Threefish512 | Threefish-512 A 512-bit tweakable block cipher that was used in the Skein hash function. Very fast on 64-bit processors. |
XTEA | XTEA A 64-bit cipher popular for its simple implementation. Avoid in new code. |
Instances
Instances
Eq KeySpec Source # | |
Ord KeySpec Source # | |
Show KeySpec Source # | |
Generic KeySpec Source # | |
Print KeySpec Source # | |
Defined in Z.Crypto.Cipher toUTF8BuilderP :: Int -> KeySpec -> Builder () # | |
type Rep KeySpec Source # | |
Defined in Z.Crypto.Cipher type Rep KeySpec = D1 ('MetaData "KeySpec" "Z.Crypto.Cipher" "Z-Botan-0.4.0.0-Cymuol1BxyD6d85e6LsrR5" 'False) (C1 ('MetaCons "KeySpec" 'PrefixI 'True) (S1 ('MetaSel ('Just "keyLenMin") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Int) :*: (S1 ('MetaSel ('Just "keyLenMax") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Int) :*: S1 ('MetaSel ('Just "keyLenMod") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Int)))) |
data BlockCipher Source #
A Botan block cipher.
In almost all cases, a bare block cipher is not what you should be using.
You probably want an authenticated cipher mode instead (see CipherMode
),
This interface is used to build higher level operations (such as cipher modes or MACs),
or in the very rare situation where ECB is required, eg for compatibility with an existing system.
Instances
blockCipherName :: BlockCipher -> CBytes Source #
block cipher algo name
blockCipherKeySpec :: BlockCipher -> KeySpec Source #
block cipher keyspec
blockCipherSize :: BlockCipher -> Int Source #
block cipher block size
newBlockCipher :: HasCallStack => BlockCipherType -> IO BlockCipher Source #
Create a new block cipher.
setBlockCipherKey :: HasCallStack => BlockCipher -> Secret -> IO () Source #
Set the cipher key, which is required before encrypting or decrypting.
clearBlockCipher :: HasCallStack => BlockCipher -> IO () Source #
Clear the internal state (such as keys) of this cipher object.
:: HasCallStack | |
=> BlockCipher | |
-> Bytes | blocks of data, length must be equal to block_size * number_of_blocks |
-> Int | number of blocks |
-> IO Bytes |
Encrypt blocks of data.
The key must have been set first with setBlockCipherKey
.
:: HasCallStack | |
=> BlockCipher | |
-> Bytes | blocks of data, length must be equal to block_size * number_of_blocks |
-> Int | number of blocks |
-> IO Bytes |
Decrypt blocks of data.
The key must have been set first with setBlockCipherKey
.
Cipher Mode
data CipherMode Source #
All available cipher types.
A block cipher by itself, is only able to securely encrypt a single data block. To be able to securely encrypt data of arbitrary length, a mode of operation applies the block cipher’s single block operation repeatedly to encrypt an entire message.
Notes on the AEAD modes(CCM, ChaCha20Poly1305, EAX, GCM, OCB, SIV):
AEAD (Authenticated Encryption with Associated Data) modes provide message encryption, message authentication, and the ability to authenticate additional data that is not included in the ciphertext (such as a sequence number or header).
ChaCha20Poly1305 | ChaCha20Poly1305 Unlike the other AEADs which are based on block ciphers, this mode is based on the ChaCha stream cipher and the Poly1305 authentication code. It is very fast on all modern platforms. ChaCha20Poly1305 supports 64-bit, 96-bit, and (since 2.8) 192-bit nonces. 64-bit nonces are the “classic” ChaCha20Poly1305 design. 96-bit nonces are used by the IETF standard version of ChaCha20Poly1305. And 192-bit nonces is the XChaCha20Poly1305 construction, which is somewhat less common. For best interop use the IETF version with 96-bit nonces. However 96 bits is small enough that it can be dangerous to generate nonces randomly if more than ~ 2^32 messages are encrypted under a single key, since if a nonce is ever reused ChaCha20Poly1305 becomes insecure. It is better to use a counter for the nonce in this case. If you are encrypting many messages under a single key and cannot maintain a counter for the nonce, prefer XChaCha20Poly1305 since a 192 bit nonce is large enough that randomly chosen nonces are extremely unlikely to repeat. |
GCM BlockCipherType | GCM NIST standard, commonly used. Requires a 128-bit block cipher. Fairly slow, unless hardware support for carryless multiplies is available. Default tag size is 16 |
GCM' BlockCipherType Int | tag size |
OCB BlockCipherType | OCB A block cipher based AEAD. Supports 128-bit, 256-bit and 512-bit block ciphers. This mode is very fast and easily secured against side channels. Adoption has been poor because it is patented in the United States, though a license is available allowing it to be freely used by open source software. Default tag size is 16 |
OCB' BlockCipherType Int | tag size |
EAX BlockCipherType | EAX A secure composition of CTR mode and CMAC. Supports 128-bit, 256-bit and 512-bit block ciphers. Default tag size is the block size |
EAX' BlockCipherType Int | tag size |
SIV BlockCipherType | SIV Requires a 128-bit block cipher. Unlike other AEADs, SIV is “misuse resistant”; if a nonce is repeated, SIV retains security, with the exception that if the same nonce is used to encrypt the same message multiple times, an attacker can detect the fact that the message was duplicated (this is simply because if both the nonce and the message are reused, SIV will output identical ciphertexts). |
CCM BlockCipherType | CCM A composition of CTR mode and CBC-MAC. Requires a 128-bit block cipher. This is a NIST standard mode, but that is about all to recommend it. Prefer EAX. Default tag size is 16 and L is 3 |
CCM' | CCM with custom tag size |
| |
CFB BlockCipherType | CFB CFB uses a block cipher to create a self-synchronizing stream cipher. It is used for example in the OpenPGP protocol. There is no reason to prefer it, as it has worse performance characteristics than modes such as CTR or CBC. The default feedback bits size are 8*blocksize |
CFB' BlockCipherType Int | feedback bits size |
XTS BlockCipherType | XTS XTS is a mode specialized for encrypting disk or database storage where ciphertext expansion is not possible. XTS requires all inputs be at least one full block (16 bytes for AES), however for any acceptable input length, there is no ciphertext expansion. |
CBC_PKCS7 BlockCipherType | CBC CBC requires the plaintext be padded using a reversible rule. The following padding schemes are implemented
|
CBC_OneAndZeros BlockCipherType | CBC
|
CBC_X9'23 BlockCipherType | CBC
|
CBC_ESP BlockCipherType | CBC
|
CBC_CTS BlockCipherType | CTS This scheme allows the ciphertext to have the same length as the plaintext, however using CTS requires the input be at least one full block plus one byte. It is also less commonly implemented. |
CBC_NoPadding BlockCipherType | No padding CBC Only use this mode when input length is a multipler of cipher block size. |
Instances
data CipherDirection Source #
Instances
A Botan cipher.
Instances
Show Cipher Source # | |
Generic Cipher Source # | |
Print Cipher Source # | |
Defined in Z.Crypto.Cipher toUTF8BuilderP :: Int -> Cipher -> Builder () # | |
type Rep Cipher Source # | |
Defined in Z.Crypto.Cipher type Rep Cipher = D1 ('MetaData "Cipher" "Z.Crypto.Cipher" "Z-Botan-0.4.0.0-Cymuol1BxyD6d85e6LsrR5" 'False) (C1 ('MetaCons "Cipher" 'PrefixI 'True) ((S1 ('MetaSel ('Just "cipher") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 BotanStruct) :*: S1 ('MetaSel ('Just "cipherName") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 CBytes)) :*: (S1 ('MetaSel ('Just "cipherKeySpec") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 KeySpec) :*: (S1 ('MetaSel ('Just "cipherTagLength") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Int) :*: S1 ('MetaSel ('Just "defaultNonceLength") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Int))))) |
cipherName :: Cipher -> CBytes Source #
cipher algo name
cipherKeySpec :: Cipher -> KeySpec Source #
cipher keyspec
cipherTagLength :: Cipher -> Int Source #
AEAD tag length, will be 0 for non-authenticated ciphers.
defaultNonceLength :: Cipher -> Int Source #
a proper default nonce length.
newCipher :: HasCallStack => CipherMode -> CipherDirection -> IO Cipher Source #
Create a new cipher.
setCipherKey :: HasCallStack => Cipher -> Secret -> IO () Source #
Set the key for this cipher object
clearCipher :: HasCallStack => Cipher -> IO () Source #
Clear the internal state (such as keys) of this cipher object.
:: HasCallStack | |
=> Cipher | |
-> Nonce | nonce |
-> Bytes | input |
-> Bytes | associated data, ignored if not an AEAD or empty |
-> IO Bytes |
Do the encryption or decryption.
BE CAREFUL ON Nonce
handling! Some CipherMode
s will fail if Nonce
is reused or not randomly enough.
Stream Cipher
data StreamCipherType Source #
In contrast to block ciphers, stream ciphers operate on a plaintext stream instead of blocks. Thus encrypting data results in changing the internal state of the cipher and encryption of plaintext with arbitrary length is possible in one go (in byte amounts).
CTR_BE BlockCipherType | A cipher mode that converts a block cipher into a stream cipher. It offers parallel execution and can seek within the output stream, both useful properties. |
OFB BlockCipherType | Another stream cipher based on a block cipher. Unlike CTR mode, it does not allow parallel execution or seeking within the output stream. Prefer CTR. |
ChaCha8 | A very fast cipher, now widely deployed in TLS as part of the ChaCha20Poly1305 AEAD. Can be used with 8 (fast but dangerous), 12 (balance), or 20 rounds (conservative). Even with 20 rounds, ChaCha is very fast. Use 20 rounds. |
ChaCha12 | |
ChaCha20 | |
Salsa20 | An earlier iteration of the ChaCha design, this cipher is popular due to its use in the libsodium library. Prefer ChaCha. |
SHAKE128' | This is the SHAKE-128 XOF exposed as a stream cipher. It is slower than ChaCha and somewhat obscure. It does not support IVs or seeking within the cipher stream. |
RC4 | An old and very widely deployed stream cipher notable for its simplicity. It does not support IVs or seeking within the cipher stream. Warning: RC4 is now badly broken. Avoid in new code and use only if required for compatibility with existing systems. |
Instances
data StreamCipher Source #
A Botan stream cipher.
Instances
streamCipherName :: StreamCipher -> CBytes Source #
cipher algo name
streamCipherKeySpec :: StreamCipher -> KeySpec Source #
cipher keyspec
defaultIVLength :: StreamCipher -> Int Source #
a proper default IV length.
newStreamCipher :: HasCallStack => StreamCipherType -> IO StreamCipher Source #
Create a new stream cipher.
A stream cipher is a symmetric key cipher where plaintext digits are combined with a pseudorandom cipher digit stream (keystream). In a stream cipher, each plaintext digit is encrypted one at a time with the corresponding digit of the keystream, to give a digit of the ciphertext stream. Since encryption of each digit is dependent on the current state of the cipher, it is also known as state cipher. In practice, a digit is typically a bit and the combining operation is an exclusive-or (XOR).
setStreamCipherKey :: HasCallStack => StreamCipher -> Secret -> IO () Source #
Set the key for the StreamCipher
object
clearStreamCipher :: HasCallStack => StreamCipher -> IO () Source #
Clear the internal state (such as keys) of this cipher object.
setStreamCipherIV :: StreamCipher -> Nonce -> IO () Source #
Set the initail vector for a StreamCipher
.
seekStreamCipher :: StreamCipher -> Int -> IO () Source #
Seek StreamCipher
's state to given offset.
:: HasCallStack | |
=> StreamCipher | |
-> Bytes | |
-> IO Bytes | trailing input, output |
Update cipher with some data.
Since stream ciphers work by XOR data, encryption and decryption are the same process.
streamCipherKeyStream :: HasCallStack => StreamCipher -> Int -> IO Bytes Source #
Export StreamCipher
's key stream for other usage.
streamCipherBIO :: HasCallStack => StreamCipher -> BIO Bytes Bytes Source #
Wrap a StreamCipher
into a BIO
node(experimental).
The cipher should have already started by setting key, iv, etc, for example to encrypt a file in constant memory using AES with CTR mode:
import Z.Data.CBytes (CBytes) import Z.IO.BIO import Z.IO import Z.Crypto.Cipher -- | encryption and decryption are the same process. cipherFile :: CBytes -> CBytes -> IO () cipherFile origin target = do let demoKey = "12345678123456781234567812345678" iv = "demo only !!!!!!" cipher <- newStreamCipher (CTR_BE AES256) setStreamCipherKey cipher demoKey setStreamCipherIV cipher iv withResource (initSourceFromFile origin) $ \ src -> withResource (initSinkToFile target) $ \ sink -> runBIO_ $ src . streamCipherBIO cipher . sink
Note that many cipher modes have a maximum length limit on the plaintext under a security context, i.e. a key nonce combination. If you want to encrypt a large message, please consider divide it into smaller chunks, and re-key or change the iv.
:: HasCallStack | |
=> StreamCipher | |
-> Int | each chunk size |
-> Source Bytes |
Turn a StreamCipher
into a key stream source.
Internal helps
withBlockCipher :: BlockCipher -> (BotanStructT -> IO r) -> IO r Source #
Pass BlockCipher
to FFI as botan_block_cipher_t
.
withCipher :: Cipher -> (BotanStructT -> IO r) -> IO r Source #
Pass Cipher
to FFI as botan_cipher_t
.
withStreamCipher :: StreamCipher -> (BotanStructT -> IO r) -> IO r Source #
re-export
Available Hashs
BLAKE2b Int | A recently designed hash function. Very fast on 64-bit processors. Can output a hash of any length between 1 and 64 bytes, this is specified by passing desired byte length. |
BLAKE2b256 | Alias for |
BLAKE2b512 | Alias for |
Keccak1600_224 | An older (and incompatible) variant of SHA-3, but sometimes used. Prefer SHA-3 in new code. |
Keccak1600_256 | |
Keccak1600_384 | |
Keccak1600_512 | |
MD4 | An old hash function that is now known to be trivially breakable. It is very fast, and may still be suitable as a (non-cryptographic) checksum. |
MD5 | Widely used, now known to be broken. |
RIPEMD160 | A 160 bit hash function, quite old but still thought to be secure (up to the limit of 2**80 computation required for a collision which is possible with any 160 bit hash function). Somewhat deprecated these days. |
SHA160 | Widely adopted NSA designed hash function. Starting to show significant signs of weakness, and collisions can now be generated. Avoid in new designs. |
SHA256 | Relatively fast 256 bit hash function, thought to be secure. Also includes the variant SHA-224. There is no real reason to use SHA-224. |
SHA224 | |
SHA512 | SHA-512 is faster than SHA-256 on 64-bit processors. Also includes the truncated variants SHA-384 and SHA-512/256, which have the advantage of avoiding message extension attacks. |
SHA384 | |
SHA512_256 | |
SHA3_224 | The new NIST standard hash. Fairly slow. Supports 224, 256, 384 or 512 bit outputs. SHA-3 is faster with smaller outputs. Use as “SHA3_256” or “SHA3_512”. Plain “SHA-3” selects default 512 bit output. |
SHA3_256 | |
SHA3_384 | |
SHA3_512 | |
SHAKE128 Int | These are actually XOFs (extensible output functions) based on SHA-3, which can output a value of any byte length. For example “SHAKE128 @128” will produce 1024 bits of output. |
SHAKE256 Int | |
SM3 | Chinese national hash function, 256 bit output. Widely used in industry there. Fast and seemingly secure, but no reason to prefer it over SHA-2 or SHA-3 unless required. |
Skein512 Int CBytes | A contender for the NIST SHA-3 competition. Very fast on 64-bit systems. Can output a hash of any length between 1 and 64 bytes. It also accepts an optional “personalization string” which can create variants of the hash. This is useful for domain separation. |
Streebog256 | Newly designed Russian national hash function. Due to use of input-dependent table lookups, it is vulnerable to side channels. There is no reason to use it unless compatibility is needed. Warning: The Streebog Sbox has recently been revealed to have a hidden structure which interacts with its linear layer in a way which may provide a backdoor when used in certain ways. Avoid Streebog if at all possible. |
Streebog512 | |
Whirlpool | A 512-bit hash function standardized by ISO and NESSIE. Relatively slow, and due to the table based implementation it is potentially vulnerable to cache based side channels. |
Parallel HashType HashType | Parallel simply concatenates multiple hash functions. For example “Parallel SHA256 SHA512 outputs a 256+512 bit hash created by hashing the input with both SHA256 and SHA512 and concatenating the outputs. |
Comb4P HashType HashType | This combines two cryptographic hashes in such a way that preimage and collision attacks are provably at least as hard as a preimage or collision attack on the strongest hash. |
Adler32 | Checksums, not suitable for cryptographic use, but can be used for error checking purposes. |
CRC24 | |
CRC32 |
Instances
module Z.Crypto.SafeMem