Z-Botan-0.4.0.0: Crypto for Haskell
CopyrightDong Han 2021
AnJie Dong 2021
LicenseBSD
Maintainerwinterland1989@gmail.com
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Z.Crypto.KDF

Description

KDF(Key Derivation Function) and PBKDF(Password Based Key Derivation Function).

Synopsis

KDF

data KDFType Source #

Key derivation functions are used to turn some amount of shared secret material into uniform random keys suitable for use with symmetric algorithms. An example of an input which is useful for a KDF is a shared secret created using Diffie-Hellman key agreement.

Constructors

HKDF MACType 
HKDF_Extract MACType 
HKDF_Expand MACType

Defined in RFC 5869, HKDF uses HMAC to process inputs. Also available are variants HKDF-Extract and HKDF-Expand. HKDF is the combined Extract+Expand operation. Use the combined HKDF unless you need compatibility with some other system.

KDF2 HashType

KDF2 comes from IEEE 1363. It uses a hash function.

KDF1_18033 HashType

KDF1 from ISO 18033-2. Very similar to (but incompatible with) KDF2.

KDF1 HashType

KDF1 from IEEE 1363. It can only produce an output at most the length of the hash function used.

TLS_PRF

A KDF from ANSI X9.42. Sometimes used for Diffie-Hellman.

TLS_12_PRF MACType 
SP800_108_Counter MACType

KDFs from NIST SP 800-108. Variants include “SP800-108-Counter”, “SP800-108-Feedback” and “SP800-108-Pipeline”.

SP800_108_Feedback MACType 
SP800_108_Pipeline MACType 
SP800_56AHash HashType

NIST SP 800-56A KDF using hash function

SP800_56AMAC MACType

NIST SP 800-56A KDF using HMAC

SP800_56C MACType

NIST SP 800-56C KDF using HMAC

Instances

Instances details
Eq KDFType Source # 
Instance details

Defined in Z.Crypto.KDF

Methods

(==) :: KDFType -> KDFType -> Bool #

(/=) :: KDFType -> KDFType -> Bool #

Ord KDFType Source # 
Instance details

Defined in Z.Crypto.KDF

Read KDFType Source # 
Instance details

Defined in Z.Crypto.KDF

Show KDFType Source # 
Instance details

Defined in Z.Crypto.KDF

Generic KDFType Source # 
Instance details

Defined in Z.Crypto.KDF

Associated Types

type Rep KDFType :: Type -> Type #

Methods

from :: KDFType -> Rep KDFType x #

to :: Rep KDFType x -> KDFType #

JSON KDFType Source # 
Instance details

Defined in Z.Crypto.KDF

Print KDFType Source # 
Instance details

Defined in Z.Crypto.KDF

Methods

toUTF8BuilderP :: Int -> KDFType -> Builder () #

type Rep KDFType Source # 
Instance details

Defined in Z.Crypto.KDF

type Rep KDFType = D1 ('MetaData "KDFType" "Z.Crypto.KDF" "Z-Botan-0.4.0.0-Cymuol1BxyD6d85e6LsrR5" 'False) (((C1 ('MetaCons "HKDF" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 MACType)) :+: (C1 ('MetaCons "HKDF_Extract" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 MACType)) :+: C1 ('MetaCons "HKDF_Expand" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 MACType)))) :+: ((C1 ('MetaCons "KDF2" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 HashType)) :+: C1 ('MetaCons "KDF1_18033" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 HashType))) :+: (C1 ('MetaCons "KDF1" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 HashType)) :+: C1 ('MetaCons "TLS_PRF" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "TLS_12_PRF" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 MACType)) :+: (C1 ('MetaCons "SP800_108_Counter" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 MACType)) :+: C1 ('MetaCons "SP800_108_Feedback" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 MACType)))) :+: ((C1 ('MetaCons "SP800_108_Pipeline" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 MACType)) :+: C1 ('MetaCons "SP800_56AHash" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 HashType))) :+: (C1 ('MetaCons "SP800_56AMAC" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 MACType)) :+: C1 ('MetaCons "SP800_56C" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 MACType))))))

data HashType Source #

Available Hashs

Constructors

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 Blake2b 32

BLAKE2b512

Alias for Blake2b 64

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

Instances details
Eq HashType Source # 
Instance details

Defined in Z.Crypto.Hash

Ord HashType Source # 
Instance details

Defined in Z.Crypto.Hash

Read HashType Source # 
Instance details

Defined in Z.Crypto.Hash

Show HashType Source # 
Instance details

Defined in Z.Crypto.Hash

Generic HashType Source # 
Instance details

Defined in Z.Crypto.Hash

Associated Types

type Rep HashType :: Type -> Type #

Methods

from :: HashType -> Rep HashType x #

to :: Rep HashType x -> HashType #

JSON HashType Source # 
Instance details

Defined in Z.Crypto.Hash

Print HashType Source # 
Instance details

Defined in Z.Crypto.Hash

Methods

toUTF8BuilderP :: Int -> HashType -> Builder () #

type Rep HashType Source # 
Instance details

Defined in Z.Crypto.Hash

type Rep HashType = D1 ('MetaData "HashType" "Z.Crypto.Hash" "Z-Botan-0.4.0.0-Cymuol1BxyD6d85e6LsrR5" 'False) (((((C1 ('MetaCons "BLAKE2b" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)) :+: C1 ('MetaCons "BLAKE2b256" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "BLAKE2b512" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Keccak1600_224" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Keccak1600_256" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Keccak1600_384" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Keccak1600_512" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "MD4" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: (((C1 ('MetaCons "MD5" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "RIPEMD160" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "SHA160" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SHA256" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "SHA224" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SHA512" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "SHA384" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SHA512_256" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: ((((C1 ('MetaCons "SHA3_224" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SHA3_256" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "SHA3_384" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SHA3_512" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "SHAKE128" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)) :+: C1 ('MetaCons "SHAKE256" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int))) :+: (C1 ('MetaCons "SM3" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Skein512" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CBytes))))) :+: (((C1 ('MetaCons "Streebog256" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Streebog512" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Whirlpool" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Parallel" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 HashType) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 HashType)))) :+: ((C1 ('MetaCons "Comb4P" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 HashType) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 HashType)) :+: C1 ('MetaCons "Adler32" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "CRC24" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CRC32" 'PrefixI 'False) (U1 :: Type -> Type))))))

data MACType Source #

Constructors

CMAC BlockCipherType

A modern CBC-MAC variant that avoids the security problems of plain CBC-MAC. Approved by NIST. Also sometimes called OMAC.

GMAC BlockCipherType

GMAC is related to the GCM authenticated cipher mode. It is quite slow unless hardware support for carryless multiplications is available. A new nonce must be used with each message authenticated, or otherwise all security is lost.

CBC_MAC BlockCipherType

An older authentication code based on a block cipher. Serious security problems, in particular insecure if messages of several different lengths are authenticated. Avoid unless required for compatibility.

HMAC HashType

A message authentication code based on a hash function. Very commonly used.

Poly1305

A polynomial mac (similar to GMAC). Very fast, but tricky to use safely. Forms part of the ChaCha20Poly1305 AEAD mode. A new key must be used for each message, or all security is lost.

SipHash Int Int

A modern and very fast PRF. Produces only a 64-bit output. Defaults to “SipHash(2,4)” which is the recommended configuration, using 2 rounds for each input block and 4 rounds for finalization.

X9'19_MAC

A CBC-MAC variant sometimes used in finance. Always uses DES. Sometimes called the “DES retail MAC”, also standardized in ISO 9797-1. It is slow and has known attacks. Avoid unless required.

Instances

Instances details
Eq MACType Source # 
Instance details

Defined in Z.Crypto.MAC

Methods

(==) :: MACType -> MACType -> Bool #

(/=) :: MACType -> MACType -> Bool #

Ord MACType Source # 
Instance details

Defined in Z.Crypto.MAC

Read MACType Source # 
Instance details

Defined in Z.Crypto.MAC

Show MACType Source # 
Instance details

Defined in Z.Crypto.MAC

Generic MACType Source # 
Instance details

Defined in Z.Crypto.MAC

Associated Types

type Rep MACType :: Type -> Type #

Methods

from :: MACType -> Rep MACType x #

to :: Rep MACType x -> MACType #

JSON MACType Source # 
Instance details

Defined in Z.Crypto.MAC

Print MACType Source # 
Instance details

Defined in Z.Crypto.MAC

Methods

toUTF8BuilderP :: Int -> MACType -> Builder () #

type Rep MACType Source # 
Instance details

Defined in Z.Crypto.MAC

kdf Source #

Arguments

:: HasCallStack 
=> KDFType

the name of the given PBKDF algorithm

-> Int

length of output key

-> Secret

secret

-> Bytes

salt

-> Bytes

label

-> IO Secret 

Derive a key using the given KDF algorithm.

kdf' Source #

Arguments

:: HasCallStack 
=> KDFType

the name of the given PBKDF algorithm

-> Int

length of output key

-> Secret

secret

-> IO Secret 

Derive a key using the given KDF algorithm, with default empty salt and label.

PBKDF

data PBKDFType Source #

Often one needs to convert a human readable password into a cryptographic key. It is useful to slow down the computation of these computations in order to reduce the speed of brute force search, thus they are parameterized in some way which allows their required computation to be tuned.

Constructors

PBKDF2 MACType Int

iterations ^ PBKDF2 is the “standard” password derivation scheme, widely implemented in many different libraries.

Scrypt Int Int Int

N, r, p ^ Scrypt is a relatively newer design which is “memory hard”, in addition to requiring large amounts of CPU power it uses a large block of memory to compute the hash. This makes brute force attacks using ASICs substantially more expensive.

Argon2d Int Int Int

iterations, memory, parallelism ^ Argon2 is the winner of the PHC (Password Hashing Competition) and provides a tunable memory hard PBKDF.

Argon2i Int Int Int

iterations, memory, parallelism

Argon2id Int Int Int

iterations, memory, parallelism

Bcrypt Int

iterations

OpenPGP_S2K HashType Int

iterations ^ The OpenPGP algorithm is weak and strange, and should be avoided unless implementing OpenPGP.

pbkdf Source #

Arguments

:: HasCallStack 
=> PBKDFType

PBKDF algorithm type

-> Int

length of output key

-> Password

passphrase

-> Bytes

salt

-> IO Secret 

Derive a key from a passphrase for a number of iterations using the given PBKDF algorithm and params.

pbkdfTimed Source #

Arguments

:: HasCallStack 
=> PBKDFType

the name of the given PBKDF algorithm

-> Int

run until milliseconds have passwd

-> Int

length of output key

-> CBytes

passphrase

-> Bytes

salt

-> IO Secret 

Derive a key from a passphrase using the given PBKDF algorithm, the iteration params are ignored and PBKDF is run until given milliseconds have passed.

Internal helps

re-export