Copyright | (c) Leo D 2023 |
---|---|
License | BSD-3-Clause |
Maintainer | leo@apotheca.io |
Stability | experimental |
Portability | POSIX |
Safe Haskell | None |
Language | Haskell2010 |
This is a ‘raw’ interface to ECB mode block ciphers. Most applications want the higher level cipher API which provides authenticated encryption. This API exists as an escape hatch for applications which need to implement custom primitives using a PRP.
Synopsis
- data BlockCipher
- = Blowfish
- | CAST128
- | DES
- | TripleDES
- | GOST_28147_89
- | IDEA
- | AES128
- | AES192
- | AES256
- | ARIA128
- | ARIA192
- | ARIA256
- | Camellia128
- | Camellia192
- | Camellia256
- | Noekeon
- | SEED
- | Serpent
- | SM4
- | Twofish
- | SHACAL2
- | Threefish512
- newtype BlockCipher128 = MkBlockCipher128 {}
- blockCiphers :: [BlockCipher]
- blockCipher128s :: [BlockCipher128]
- type BlockCipherKeySpec = KeySpec
- type BlockCipherKey = ByteString
- newBlockCipherKey :: MonadRandomIO m => BlockCipher -> m BlockCipherKey
- newBlockCipherKeyMaybe :: MonadRandomIO m => Int -> BlockCipher -> m (Maybe BlockCipherKey)
- type BlockCipherText = ByteString
- type BlockCipher128Key = BlockCipherKey
- blockCipher128Name :: BlockCipher128 -> BlockCipherName
- blockCipher128KeySpec :: BlockCipher128 -> BlockCipherKeySpec
- isBlockCipher128 :: BlockCipher -> Bool
- blockCipherName :: BlockCipher -> BlockCipherName
- blockCipherBlockSize :: BlockCipher -> Int
- blockCipherKeySpec :: BlockCipher -> BlockCipherKeySpec
- blockCipherEncrypt :: BlockCipher -> BlockCipherKey -> ByteString -> Maybe ByteString
- blockCipherDecrypt :: BlockCipher -> BlockCipherKey -> ByteString -> Maybe ByteString
- blockCipherEncryptLazy :: BlockCipher -> BlockCipherKey -> ByteString -> Maybe ByteString
- blockCipherDecryptLazy :: BlockCipher -> BlockCipherKey -> ByteString -> Maybe ByteString
- data MutableBlockCipher = MkMutableBlockCipher {
- mutableBlockCipherType :: BlockCipher
- mutableBlockCipherCtx :: BlockCipher
- destroyBlockCipher :: MonadIO m => MutableBlockCipher -> m ()
- newBlockCipher :: MonadIO m => BlockCipher -> m MutableBlockCipher
- getBlockCipherName :: MonadIO m => MutableBlockCipher -> m BlockCipherName
- getBlockCipherBlockSize :: MonadIO m => MutableBlockCipher -> m Int
- getBlockCipherKeySpec :: MonadIO m => MutableBlockCipher -> m BlockCipherKeySpec
- setBlockCipherKey :: MonadIO m => BlockCipherKey -> MutableBlockCipher -> m Bool
- clearBlockCipher :: MonadIO m => MutableBlockCipher -> m ()
- encryptBlockCipherBlocks :: MonadIO m => MutableBlockCipher -> ByteString -> m BlockCipherText
- decryptBlockCipherBlocks :: MonadIO m => MutableBlockCipher -> BlockCipherText -> m ByteString
- autoEncryptBlockCipherBlocks :: MonadIO m => MutableBlockCipher -> BlockCipherKey -> ByteString -> m (Maybe BlockCipherText)
- autoDecryptBlockCipherBlocks :: MonadIO m => MutableBlockCipher -> BlockCipherKey -> BlockCipherText -> m (Maybe ByteString)
- blowfish :: BlockCipher
- cast128 :: BlockCipher
- des :: BlockCipher
- tripleDES :: BlockCipher
- gost_28147_89 :: BlockCipher
- idea :: BlockCipher
- aes128 :: BlockCipher
- aes192 :: BlockCipher
- aes256 :: BlockCipher
- aria128 :: BlockCipher
- aria192 :: BlockCipher
- aria256 :: BlockCipher
- camellia128 :: BlockCipher
- camellia192 :: BlockCipher
- camellia256 :: BlockCipher
- noekeon :: BlockCipher
- seed :: BlockCipher
- sm4 :: BlockCipher
- serpent :: BlockCipher
- twofish :: BlockCipher
- shalcal2 :: BlockCipher
- threefish512 :: BlockCipher
Block ciphers
Usage
Idiomatic interface
Data type
data BlockCipher Source #
Blowfish | |
CAST128 | |
DES | |
TripleDES | |
GOST_28147_89 | |
IDEA | |
AES128 | |
AES192 | |
AES256 | |
ARIA128 | |
ARIA192 | |
ARIA256 | |
Camellia128 | |
Camellia192 | |
Camellia256 | |
Noekeon | |
SEED | |
Serpent | |
SM4 | |
Twofish | |
SHACAL2 | |
Threefish512 |
Instances
Show BlockCipher Source # | |
Defined in Botan.BlockCipher showsPrec :: Int -> BlockCipher -> ShowS # show :: BlockCipher -> String # showList :: [BlockCipher] -> ShowS # | |
Eq BlockCipher Source # | Cascade BlockCipher BlockCipher | Lion HashSpec StreamCipher Int |
Defined in Botan.BlockCipher (==) :: BlockCipher -> BlockCipher -> Bool # (/=) :: BlockCipher -> BlockCipher -> Bool # | |
Ord BlockCipher Source # | |
Defined in Botan.BlockCipher compare :: BlockCipher -> BlockCipher -> Ordering # (<) :: BlockCipher -> BlockCipher -> Bool # (<=) :: BlockCipher -> BlockCipher -> Bool # (>) :: BlockCipher -> BlockCipher -> Bool # (>=) :: BlockCipher -> BlockCipher -> Bool # max :: BlockCipher -> BlockCipher -> BlockCipher # min :: BlockCipher -> BlockCipher -> BlockCipher # |
newtype BlockCipher128 Source #
Instances
Show BlockCipher128 Source # | |
Defined in Botan.BlockCipher showsPrec :: Int -> BlockCipher128 -> ShowS # show :: BlockCipher128 -> String # showList :: [BlockCipher128] -> ShowS # | |
Eq BlockCipher128 Source # | |
Defined in Botan.BlockCipher (==) :: BlockCipher128 -> BlockCipher128 -> Bool # (/=) :: BlockCipher128 -> BlockCipher128 -> Bool # | |
Ord BlockCipher128 Source # | |
Defined in Botan.BlockCipher compare :: BlockCipher128 -> BlockCipher128 -> Ordering # (<) :: BlockCipher128 -> BlockCipher128 -> Bool # (<=) :: BlockCipher128 -> BlockCipher128 -> Bool # (>) :: BlockCipher128 -> BlockCipher128 -> Bool # (>=) :: BlockCipher128 -> BlockCipher128 -> Bool # max :: BlockCipher128 -> BlockCipher128 -> BlockCipher128 # min :: BlockCipher128 -> BlockCipher128 -> BlockCipher128 # |
Enumerations
blockCiphers :: [BlockCipher] Source #
Associated types
type BlockCipherKeySpec = KeySpec Source #
type BlockCipherKey = ByteString Source #
newBlockCipherKey :: MonadRandomIO m => BlockCipher -> m BlockCipherKey Source #
newBlockCipherKeyMaybe :: MonadRandomIO m => Int -> BlockCipher -> m (Maybe BlockCipherKey) Source #
type BlockCipherText = ByteString Source #
Convenience
type BlockCipher128Key = BlockCipherKey Source #
blockCipher128Name :: BlockCipher128 -> BlockCipherName Source #
isBlockCipher128 :: BlockCipher -> Bool Source #
Accessors
blockCipherName :: BlockCipher -> BlockCipherName Source #
Idiomatic algorithm
blockCipherEncrypt :: BlockCipher -> BlockCipherKey -> ByteString -> Maybe ByteString Source #
blockCipherDecrypt :: BlockCipher -> BlockCipherKey -> ByteString -> Maybe ByteString Source #
Mutable interface
Tagged mutable context
data MutableBlockCipher Source #
MkMutableBlockCipher | |
|
Destructor
destroyBlockCipher :: MonadIO m => MutableBlockCipher -> m () Source #
Initializers
newBlockCipher :: MonadIO m => BlockCipher -> m MutableBlockCipher Source #
Accessors
:: MonadIO m | |
=> MutableBlockCipher | The cipher object |
-> m BlockCipherName | The cipher name |
getBlockCipherBlockSize Source #
:: MonadIO m | |
=> MutableBlockCipher | The cipher object |
-> m Int |
getBlockCipherKeySpec Source #
:: MonadIO m | |
=> MutableBlockCipher | The cipher object |
-> m BlockCipherKeySpec |
setBlockCipherKey :: MonadIO m => BlockCipherKey -> MutableBlockCipher -> m Bool Source #
Accessory functions
clearBlockCipher :: MonadIO m => MutableBlockCipher -> m () Source #
Mutable algorithm
encryptBlockCipherBlocks :: MonadIO m => MutableBlockCipher -> ByteString -> m BlockCipherText Source #
decryptBlockCipherBlocks :: MonadIO m => MutableBlockCipher -> BlockCipherText -> m ByteString Source #
autoEncryptBlockCipherBlocks :: MonadIO m => MutableBlockCipher -> BlockCipherKey -> ByteString -> m (Maybe BlockCipherText) Source #
autoDecryptBlockCipherBlocks :: MonadIO m => MutableBlockCipher -> BlockCipherKey -> BlockCipherText -> m (Maybe ByteString) Source #
des :: BlockCipher Source #
idea :: BlockCipher Source #
aes128 :: BlockCipher Source #
aes192 :: BlockCipher Source #
aes256 :: BlockCipher Source #
seed :: BlockCipher Source #
sm4 :: BlockCipher Source #