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

Z.Crypto.Cipher

Description

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

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.

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.1.1.1-6owjsCiiiOqL08hsGvk7Pd" '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))))))

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

Instances details
Show BlockCipher Source # 
Instance details

Defined in Z.Crypto.Cipher

Generic BlockCipher Source # 
Instance details

Defined in Z.Crypto.Cipher

Associated Types

type Rep BlockCipher :: Type -> Type #

Print BlockCipher Source # 
Instance details

Defined in Z.Crypto.Cipher

type Rep BlockCipher Source # 
Instance details

Defined in Z.Crypto.Cipher

newBlockCipher :: HasCallStack => BlockCipherType -> IO BlockCipher Source #

Create a new block cipher.

setBlockCipherKey :: HasCallStack => BlockCipher -> Bytes -> 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.

encryptBlocks Source #

Arguments

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

decryptBlocks Source #

Arguments

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

Stream Cipher & Cipher Mode

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

Constructors

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

Instances details
Eq StreamCipherType Source # 
Instance details

Defined in Z.Crypto.Cipher

Ord StreamCipherType Source # 
Instance details

Defined in Z.Crypto.Cipher

Read StreamCipherType Source # 
Instance details

Defined in Z.Crypto.Cipher

Show StreamCipherType Source # 
Instance details

Defined in Z.Crypto.Cipher

Generic StreamCipherType Source # 
Instance details

Defined in Z.Crypto.Cipher

Associated Types

type Rep StreamCipherType :: Type -> Type #

JSON StreamCipherType Source # 
Instance details

Defined in Z.Crypto.Cipher

Print StreamCipherType Source # 
Instance details

Defined in Z.Crypto.Cipher

type Rep StreamCipherType Source # 
Instance details

Defined in Z.Crypto.Cipher

type Rep StreamCipherType = D1 ('MetaData "StreamCipherType" "Z.Crypto.Cipher" "Z-Botan-0.1.1.1-6owjsCiiiOqL08hsGvk7Pd" 'False) (((C1 ('MetaCons "CTR_BE" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BlockCipherType)) :+: C1 ('MetaCons "OFB" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BlockCipherType))) :+: (C1 ('MetaCons "ChaCha8" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "ChaCha12" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "ChaCha20" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Salsa20" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "SHAKE128'" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "RC4" 'PrefixI 'False) (U1 :: Type -> Type))))

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

Constructors

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.

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.

EAX BlockCipherType

EAX A secure composition of CTR mode and CMAC. Supports 128-bit, 256-bit and 512-bit block ciphers.

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.

CFB BlockCipherType Int

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.

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

  • PKCS#7 (RFC5652) The last byte in the padded block defines the padding length p, the remaining padding bytes are set to p as well.
CBC_OneAndZeros BlockCipherType

CBC

  • OneAndZeros (ISO/IEC 7816-4) The first padding byte is set to 0x80, the remaining padding bytes are set to 0x00.
CBC_X9'23 BlockCipherType

CBC

  • ANSI X9.23 The last byte in the padded block defines the padding length, the remaining padding is filled with 0x00.
CBC_ESP BlockCipherType

CBC

  • ESP (RFC4303) Padding with 0x01, 0x02, 0x03...
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

Instances details
Eq CipherMode Source # 
Instance details

Defined in Z.Crypto.Cipher

Ord CipherMode Source # 
Instance details

Defined in Z.Crypto.Cipher

Read CipherMode Source # 
Instance details

Defined in Z.Crypto.Cipher

Show CipherMode Source # 
Instance details

Defined in Z.Crypto.Cipher

Generic CipherMode Source # 
Instance details

Defined in Z.Crypto.Cipher

Associated Types

type Rep CipherMode :: Type -> Type #

JSON CipherMode Source # 
Instance details

Defined in Z.Crypto.Cipher

Print CipherMode Source # 
Instance details

Defined in Z.Crypto.Cipher

type Rep CipherMode Source # 
Instance details

Defined in Z.Crypto.Cipher

type Rep CipherMode = D1 ('MetaData "CipherMode" "Z.Crypto.Cipher" "Z-Botan-0.1.1.1-6owjsCiiiOqL08hsGvk7Pd" 'False) (((C1 ('MetaCons "ChaCha20Poly1305" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "GCM" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BlockCipherType)) :+: C1 ('MetaCons "OCB" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BlockCipherType)))) :+: ((C1 ('MetaCons "EAX" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BlockCipherType)) :+: C1 ('MetaCons "SIV" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BlockCipherType))) :+: (C1 ('MetaCons "CCM" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BlockCipherType)) :+: C1 ('MetaCons "CFB" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BlockCipherType) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int))))) :+: ((C1 ('MetaCons "XTS" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BlockCipherType)) :+: (C1 ('MetaCons "CBC_PKCS7" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BlockCipherType)) :+: C1 ('MetaCons "CBC_OneAndZeros" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BlockCipherType)))) :+: ((C1 ('MetaCons "CBC_X9'23" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BlockCipherType)) :+: C1 ('MetaCons "CBC_ESP" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BlockCipherType))) :+: (C1 ('MetaCons "CBC_CTS" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BlockCipherType)) :+: C1 ('MetaCons "CBC_NoPadding" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 BlockCipherType))))))

data CipherDirection Source #

Instances

Instances details
Eq CipherDirection Source # 
Instance details

Defined in Z.Botan.FFI

Ord CipherDirection Source # 
Instance details

Defined in Z.Botan.FFI

Show CipherDirection Source # 
Instance details

Defined in Z.Botan.FFI

Generic CipherDirection Source # 
Instance details

Defined in Z.Botan.FFI

Associated Types

type Rep CipherDirection :: Type -> Type #

JSON CipherDirection Source # 
Instance details

Defined in Z.Botan.FFI

Print CipherDirection Source # 
Instance details

Defined in Z.Botan.FFI

type Rep CipherDirection Source # 
Instance details

Defined in Z.Botan.FFI

type Rep CipherDirection = D1 ('MetaData "CipherDirection" "Z.Botan.FFI" "Z-Botan-0.1.1.1-6owjsCiiiOqL08hsGvk7Pd" 'False) (C1 ('MetaCons "CipherEncrypt" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "CipherDecrypt" 'PrefixI 'False) (U1 :: Type -> Type))

data Cipher Source #

A Botan cipher.

Instances

Instances details
Show Cipher Source # 
Instance details

Defined in Z.Crypto.Cipher

Generic Cipher Source # 
Instance details

Defined in Z.Crypto.Cipher

Associated Types

type Rep Cipher :: Type -> Type #

Methods

from :: Cipher -> Rep Cipher x #

to :: Rep Cipher x -> Cipher #

Print Cipher Source # 
Instance details

Defined in Z.Crypto.Cipher

Methods

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

type Rep Cipher Source # 
Instance details

Defined in Z.Crypto.Cipher

type Rep Cipher

cipherTagLength :: Cipher -> Int Source #

This will be zero for non-authenticated ciphers.

Cipher operations

setCipherKey :: HasCallStack => Cipher -> Bytes -> 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.

resetCipher :: HasCallStack => Cipher -> IO () Source #

Reset the message specific state for this cipher. Without resetting the keys, this resets the nonce, and any state associated with any message bits that have been processed so far.

It is conceptually equivalent to calling botan_cipher_clear followed by botan_cipher_set_key with the original key.

setAssociatedData :: HasCallStack => Cipher -> Bytes -> IO () Source #

Set the associated data. Will fail if cipher is not an AEAD.

startCipher Source #

Arguments

:: HasCallStack 
=> Cipher 
-> Bytes

nonce

-> IO () 

Begin processing a new message using the provided nonce.

updateCipher Source #

Arguments

:: HasCallStack 
=> Cipher 
-> Bytes 
-> IO (Bytes, Bytes)

trailing input, output

Update cipher with some data.

If the input size is not a multiplier of cipherUpdateGranularity, there'll be some trailing input.

finishCipher :: HasCallStack => Cipher -> Bytes -> IO Bytes Source #

Finish cipher with some data.

You can directly call this function to encrypt a whole message, Note some cipher modes have a minimal input length requirement for last chunk(CTS, XTS, etc.).

cipherBIO :: HasCallStack => Cipher -> IO (BIO Bytes Bytes) Source #

Wrap a cipher into a BIO node(experimental).

The cipher should have already started by setting key, nounce, etc.

Note some cipher modes have a minimal input length requirement for last chunk(CBC_CTS, XTS, etc.), which may not be suitable for arbitrary bytes streams.

Internal helps

withBlockCipher :: HasCallStack => BlockCipher -> (BotanStructT -> IO r) -> IO r Source #

Pass BlockCipher to FFI as botan_block_cipher_t.

withCipher :: HasCallStack => Cipher -> (BotanStructT -> IO r) -> IO r Source #

Pass Cipher to FFI as botan_cipher_t.