Z-Botan-0.3.1.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.3.1.0-GbapUVQUdq6A2uFR3TMVx6" '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 -> Bytes -> 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 
-> Bytes

key

-> Bytes

input

-> Bytes 

Directly compute a message's mac

macChunks :: HasCallStack => MACType -> Bytes -> [Bytes] -> Bytes 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.