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

Z.Crypto.MAC

Description

A Message Authentication Code algorithm computes a tag over a message utilizing a shared secret key. Thus a valid tag confirms the authenticity and integrity of the message. Only entities in possession of the shared secret key are able to verify the tag.

Synopsis

MAC 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

data MAC Source #

Instances

Instances details
Show MAC Source # 
Instance details

Defined in Z.Crypto.MAC

Methods

showsPrec :: Int -> MAC -> ShowS #

show :: MAC -> String #

showList :: [MAC] -> ShowS #

Generic MAC Source # 
Instance details

Defined in Z.Crypto.MAC

Associated Types

type Rep MAC :: Type -> Type #

Methods

from :: MAC -> Rep MAC x #

to :: Rep MAC x -> MAC #

Print MAC Source # 
Instance details

Defined in Z.Crypto.MAC

Methods

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

type Rep MAC Source # 
Instance details

Defined in Z.Crypto.MAC

type Rep MAC = D1 ('MetaData "MAC" "Z.Crypto.MAC" "Z-Botan-0.4.0.0-Cymuol1BxyD6d85e6LsrR5" 'False) (C1 ('MetaCons "MAC" 'PrefixI 'True) (S1 ('MetaSel ('Just "macStruct") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 BotanStruct) :*: (S1 ('MetaSel ('Just "macName") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 CBytes) :*: S1 ('MetaSel ('Just "macSize") 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Int))))

macName :: MAC -> CBytes Source #

mac algo name

macSize :: MAC -> Int Source #

mac output size in bytes

IUF interface

newMAC :: HasCallStack => MACType -> IO MAC Source #

Create a new MAC object.

setKeyMAC :: HasCallStack => MAC -> Secret -> IO () Source #

Set the random key.

updateMAC :: HasCallStack => MAC -> Bytes -> IO () Source #

Feed a chunk of input into a MAC object.

clearMAC :: HasCallStack => MAC -> IO () Source #

Reset the state of MAC object back to clean, as if no input has been supplied.

function interface

mac Source #

Arguments

:: HasCallStack 
=> MACType 
-> Secret

key

-> Bytes

input

-> CEBytes 

Directly compute a message's mac

macChunks :: HasCallStack => MACType -> Secret -> [Bytes] -> CEBytes Source #

Directly compute a chunked message's mac.

BIO interface

sinkToMAC :: HasCallStack => MAC -> Sink Bytes Source #

Trun MAC to a Bytes sink, update MAC by write bytes to the sink.

Internal helper

withMAC :: MAC -> (BotanStructT -> IO r) -> IO r Source #

Pass MAC to FFI as botan_mac_t.

re-export

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 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.

Constructors

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 details
Eq BlockCipherType Source # 
Instance details

Defined in Z.Crypto.Cipher

Ord BlockCipherType Source # 
Instance details

Defined in Z.Crypto.Cipher

Read BlockCipherType Source # 
Instance details

Defined in Z.Crypto.Cipher

Show BlockCipherType Source # 
Instance details

Defined in Z.Crypto.Cipher

Generic BlockCipherType Source # 
Instance details

Defined in Z.Crypto.Cipher

Associated Types

type Rep BlockCipherType :: Type -> Type #

JSON BlockCipherType Source # 
Instance details

Defined in Z.Crypto.Cipher

Print BlockCipherType Source # 
Instance details

Defined in Z.Crypto.Cipher

type Rep BlockCipherType Source # 
Instance details

Defined in Z.Crypto.Cipher

type Rep BlockCipherType = D1 ('MetaData "BlockCipherType" "Z.Crypto.Cipher" "Z-Botan-0.4.0.0-Cymuol1BxyD6d85e6LsrR5" 'False) ((((C1 ('MetaCons "AES128" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "AES192" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "AES256" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "ARIA128" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ARIA192" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "ARIA256" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Blowfish" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "Camellia128" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Camellia192" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Camellia256" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Cascade" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BlockCipherType) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BlockCipherType)) :+: C1 ('MetaCons "CAST128" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "CAST256" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DES" 'PrefixI 'False) (U1 :: Type -> Type))))) :+: (((C1 ('MetaCons "DESX" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "TripleDES" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "IDEA" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "KASUMI" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Lion" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 HashType) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 StreamCipherType) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)))) :+: (C1 ('MetaCons "MISTY1" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Noekeon" 'PrefixI 'False) (U1 :: Type -> Type)))) :+: ((C1 ('MetaCons "SEED" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Serpent" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SHACAL2" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "Twofish" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "SM4" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Threefish512" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "XTEA" 'PrefixI 'False) (U1 :: Type -> Type))))))