module Botan.BlockCipher
(
BlockCipher(..)
, BlockCipher128(..)
, blockCiphers
, blockCipher128s
, BlockCipherKeySpec(..)
, BlockCipherKey(..)
, newBlockCipherKey
, newBlockCipherKeyMaybe
, BlockCipherText(..)
, BlockCipher128Key(..)
, blockCipher128Name
, blockCipher128KeySpec
, isBlockCipher128
, blockCipherName
, blockCipherBlockSize
, blockCipherKeySpec
, blockCipherEncrypt
, blockCipherDecrypt
, blockCipherEncryptLazy
, blockCipherDecryptLazy
, MutableBlockCipher(..)
, destroyBlockCipher
, newBlockCipher
, getBlockCipherName
, getBlockCipherBlockSize
, getBlockCipherKeySpec
, setBlockCipherKey
, clearBlockCipher
, encryptBlockCipherBlocks
, decryptBlockCipherBlocks
, autoEncryptBlockCipherBlocks
, autoDecryptBlockCipherBlocks
, blowfish
, cast128
, des
, tripleDES
, gost_28147_89
, idea
, aes128
, aes192
, aes256
, aria128
, aria192
, aria256
, camellia128
, camellia192
, camellia256
, noekeon
, seed
, sm4
, serpent
, twofish
, shalcal2
, threefish512
) where
import qualified Botan.Low.BlockCipher as Low
import Botan.Prelude
import qualified Data.ByteString as ByteString
import qualified Data.ByteString.Lazy as Lazy
import Data.Maybe
import Botan.KeySpec
import Botan.RNG
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
deriving (BlockCipher -> BlockCipher -> Bool
(BlockCipher -> BlockCipher -> Bool)
-> (BlockCipher -> BlockCipher -> Bool) -> Eq BlockCipher
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: BlockCipher -> BlockCipher -> Bool
== :: BlockCipher -> BlockCipher -> Bool
$c/= :: BlockCipher -> BlockCipher -> Bool
/= :: BlockCipher -> BlockCipher -> Bool
Eq, Eq BlockCipher
Eq BlockCipher =>
(BlockCipher -> BlockCipher -> Ordering)
-> (BlockCipher -> BlockCipher -> Bool)
-> (BlockCipher -> BlockCipher -> Bool)
-> (BlockCipher -> BlockCipher -> Bool)
-> (BlockCipher -> BlockCipher -> Bool)
-> (BlockCipher -> BlockCipher -> BlockCipher)
-> (BlockCipher -> BlockCipher -> BlockCipher)
-> Ord BlockCipher
BlockCipher -> BlockCipher -> Bool
BlockCipher -> BlockCipher -> Ordering
BlockCipher -> BlockCipher -> BlockCipher
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: BlockCipher -> BlockCipher -> Ordering
compare :: BlockCipher -> BlockCipher -> Ordering
$c< :: BlockCipher -> BlockCipher -> Bool
< :: BlockCipher -> BlockCipher -> Bool
$c<= :: BlockCipher -> BlockCipher -> Bool
<= :: BlockCipher -> BlockCipher -> Bool
$c> :: BlockCipher -> BlockCipher -> Bool
> :: BlockCipher -> BlockCipher -> Bool
$c>= :: BlockCipher -> BlockCipher -> Bool
>= :: BlockCipher -> BlockCipher -> Bool
$cmax :: BlockCipher -> BlockCipher -> BlockCipher
max :: BlockCipher -> BlockCipher -> BlockCipher
$cmin :: BlockCipher -> BlockCipher -> BlockCipher
min :: BlockCipher -> BlockCipher -> BlockCipher
Ord, Int -> BlockCipher -> ShowS
[BlockCipher] -> ShowS
BlockCipher -> String
(Int -> BlockCipher -> ShowS)
-> (BlockCipher -> String)
-> ([BlockCipher] -> ShowS)
-> Show BlockCipher
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> BlockCipher -> ShowS
showsPrec :: Int -> BlockCipher -> ShowS
$cshow :: BlockCipher -> String
show :: BlockCipher -> String
$cshowList :: [BlockCipher] -> ShowS
showList :: [BlockCipher] -> ShowS
Show)
blockCiphers :: [ BlockCipher ]
blockCiphers :: [BlockCipher]
blockCiphers =
[ BlockCipher
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
Serpent
, BlockCipher
SM4
, BlockCipher
Twofish
, BlockCipher
SHACAL2
, BlockCipher
Threefish512
]
newtype BlockCipher128 = MkBlockCipher128 { BlockCipher128 -> BlockCipher
unBlockCipher128 :: BlockCipher }
deriving (BlockCipher128 -> BlockCipher128 -> Bool
(BlockCipher128 -> BlockCipher128 -> Bool)
-> (BlockCipher128 -> BlockCipher128 -> Bool) -> Eq BlockCipher128
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: BlockCipher128 -> BlockCipher128 -> Bool
== :: BlockCipher128 -> BlockCipher128 -> Bool
$c/= :: BlockCipher128 -> BlockCipher128 -> Bool
/= :: BlockCipher128 -> BlockCipher128 -> Bool
Eq, Eq BlockCipher128
Eq BlockCipher128 =>
(BlockCipher128 -> BlockCipher128 -> Ordering)
-> (BlockCipher128 -> BlockCipher128 -> Bool)
-> (BlockCipher128 -> BlockCipher128 -> Bool)
-> (BlockCipher128 -> BlockCipher128 -> Bool)
-> (BlockCipher128 -> BlockCipher128 -> Bool)
-> (BlockCipher128 -> BlockCipher128 -> BlockCipher128)
-> (BlockCipher128 -> BlockCipher128 -> BlockCipher128)
-> Ord BlockCipher128
BlockCipher128 -> BlockCipher128 -> Bool
BlockCipher128 -> BlockCipher128 -> Ordering
BlockCipher128 -> BlockCipher128 -> BlockCipher128
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: BlockCipher128 -> BlockCipher128 -> Ordering
compare :: BlockCipher128 -> BlockCipher128 -> Ordering
$c< :: BlockCipher128 -> BlockCipher128 -> Bool
< :: BlockCipher128 -> BlockCipher128 -> Bool
$c<= :: BlockCipher128 -> BlockCipher128 -> Bool
<= :: BlockCipher128 -> BlockCipher128 -> Bool
$c> :: BlockCipher128 -> BlockCipher128 -> Bool
> :: BlockCipher128 -> BlockCipher128 -> Bool
$c>= :: BlockCipher128 -> BlockCipher128 -> Bool
>= :: BlockCipher128 -> BlockCipher128 -> Bool
$cmax :: BlockCipher128 -> BlockCipher128 -> BlockCipher128
max :: BlockCipher128 -> BlockCipher128 -> BlockCipher128
$cmin :: BlockCipher128 -> BlockCipher128 -> BlockCipher128
min :: BlockCipher128 -> BlockCipher128 -> BlockCipher128
Ord, Int -> BlockCipher128 -> ShowS
[BlockCipher128] -> ShowS
BlockCipher128 -> String
(Int -> BlockCipher128 -> ShowS)
-> (BlockCipher128 -> String)
-> ([BlockCipher128] -> ShowS)
-> Show BlockCipher128
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> BlockCipher128 -> ShowS
showsPrec :: Int -> BlockCipher128 -> ShowS
$cshow :: BlockCipher128 -> String
show :: BlockCipher128 -> String
$cshowList :: [BlockCipher128] -> ShowS
showList :: [BlockCipher128] -> ShowS
Show)
blockCipher128 :: BlockCipher -> Maybe BlockCipher128
blockCipher128 :: BlockCipher -> Maybe BlockCipher128
blockCipher128 bc :: BlockCipher
bc@BlockCipher
AES128 = BlockCipher128 -> Maybe BlockCipher128
forall a. a -> Maybe a
Just (BlockCipher128 -> Maybe BlockCipher128)
-> BlockCipher128 -> Maybe BlockCipher128
forall a b. (a -> b) -> a -> b
$ BlockCipher -> BlockCipher128
MkBlockCipher128 BlockCipher
bc
blockCipher128 bc :: BlockCipher
bc@BlockCipher
AES192 = BlockCipher128 -> Maybe BlockCipher128
forall a. a -> Maybe a
Just (BlockCipher128 -> Maybe BlockCipher128)
-> BlockCipher128 -> Maybe BlockCipher128
forall a b. (a -> b) -> a -> b
$ BlockCipher -> BlockCipher128
MkBlockCipher128 BlockCipher
bc
blockCipher128 bc :: BlockCipher
bc@BlockCipher
AES256 = BlockCipher128 -> Maybe BlockCipher128
forall a. a -> Maybe a
Just (BlockCipher128 -> Maybe BlockCipher128)
-> BlockCipher128 -> Maybe BlockCipher128
forall a b. (a -> b) -> a -> b
$ BlockCipher -> BlockCipher128
MkBlockCipher128 BlockCipher
bc
blockCipher128 bc :: BlockCipher
bc@BlockCipher
ARIA128 = BlockCipher128 -> Maybe BlockCipher128
forall a. a -> Maybe a
Just (BlockCipher128 -> Maybe BlockCipher128)
-> BlockCipher128 -> Maybe BlockCipher128
forall a b. (a -> b) -> a -> b
$ BlockCipher -> BlockCipher128
MkBlockCipher128 BlockCipher
bc
blockCipher128 bc :: BlockCipher
bc@BlockCipher
ARIA192 = BlockCipher128 -> Maybe BlockCipher128
forall a. a -> Maybe a
Just (BlockCipher128 -> Maybe BlockCipher128)
-> BlockCipher128 -> Maybe BlockCipher128
forall a b. (a -> b) -> a -> b
$ BlockCipher -> BlockCipher128
MkBlockCipher128 BlockCipher
bc
blockCipher128 bc :: BlockCipher
bc@BlockCipher
ARIA256 = BlockCipher128 -> Maybe BlockCipher128
forall a. a -> Maybe a
Just (BlockCipher128 -> Maybe BlockCipher128)
-> BlockCipher128 -> Maybe BlockCipher128
forall a b. (a -> b) -> a -> b
$ BlockCipher -> BlockCipher128
MkBlockCipher128 BlockCipher
bc
blockCipher128 bc :: BlockCipher
bc@BlockCipher
Camellia128 = BlockCipher128 -> Maybe BlockCipher128
forall a. a -> Maybe a
Just (BlockCipher128 -> Maybe BlockCipher128)
-> BlockCipher128 -> Maybe BlockCipher128
forall a b. (a -> b) -> a -> b
$ BlockCipher -> BlockCipher128
MkBlockCipher128 BlockCipher
bc
blockCipher128 bc :: BlockCipher
bc@BlockCipher
Camellia192 = BlockCipher128 -> Maybe BlockCipher128
forall a. a -> Maybe a
Just (BlockCipher128 -> Maybe BlockCipher128)
-> BlockCipher128 -> Maybe BlockCipher128
forall a b. (a -> b) -> a -> b
$ BlockCipher -> BlockCipher128
MkBlockCipher128 BlockCipher
bc
blockCipher128 bc :: BlockCipher
bc@BlockCipher
Camellia256 = BlockCipher128 -> Maybe BlockCipher128
forall a. a -> Maybe a
Just (BlockCipher128 -> Maybe BlockCipher128)
-> BlockCipher128 -> Maybe BlockCipher128
forall a b. (a -> b) -> a -> b
$ BlockCipher -> BlockCipher128
MkBlockCipher128 BlockCipher
bc
blockCipher128 bc :: BlockCipher
bc@BlockCipher
Noekeon = BlockCipher128 -> Maybe BlockCipher128
forall a. a -> Maybe a
Just (BlockCipher128 -> Maybe BlockCipher128)
-> BlockCipher128 -> Maybe BlockCipher128
forall a b. (a -> b) -> a -> b
$ BlockCipher -> BlockCipher128
MkBlockCipher128 BlockCipher
bc
blockCipher128 bc :: BlockCipher
bc@BlockCipher
SEED = BlockCipher128 -> Maybe BlockCipher128
forall a. a -> Maybe a
Just (BlockCipher128 -> Maybe BlockCipher128)
-> BlockCipher128 -> Maybe BlockCipher128
forall a b. (a -> b) -> a -> b
$ BlockCipher -> BlockCipher128
MkBlockCipher128 BlockCipher
bc
blockCipher128 bc :: BlockCipher
bc@BlockCipher
Serpent = BlockCipher128 -> Maybe BlockCipher128
forall a. a -> Maybe a
Just (BlockCipher128 -> Maybe BlockCipher128)
-> BlockCipher128 -> Maybe BlockCipher128
forall a b. (a -> b) -> a -> b
$ BlockCipher -> BlockCipher128
MkBlockCipher128 BlockCipher
bc
blockCipher128 bc :: BlockCipher
bc@BlockCipher
SM4 = BlockCipher128 -> Maybe BlockCipher128
forall a. a -> Maybe a
Just (BlockCipher128 -> Maybe BlockCipher128)
-> BlockCipher128 -> Maybe BlockCipher128
forall a b. (a -> b) -> a -> b
$ BlockCipher -> BlockCipher128
MkBlockCipher128 BlockCipher
bc
blockCipher128 bc :: BlockCipher
bc@BlockCipher
Twofish = BlockCipher128 -> Maybe BlockCipher128
forall a. a -> Maybe a
Just (BlockCipher128 -> Maybe BlockCipher128)
-> BlockCipher128 -> Maybe BlockCipher128
forall a b. (a -> b) -> a -> b
$ BlockCipher -> BlockCipher128
MkBlockCipher128 BlockCipher
bc
blockCipher128 BlockCipher
_ = Maybe BlockCipher128
forall a. Maybe a
Nothing
unsafeBlockCipher128 :: BlockCipher -> BlockCipher128
unsafeBlockCipher128 :: BlockCipher -> BlockCipher128
unsafeBlockCipher128 = BlockCipher -> BlockCipher128
MkBlockCipher128
blockCipher128s :: [ BlockCipher128 ]
blockCipher128s :: [BlockCipher128]
blockCipher128s = (BlockCipher -> BlockCipher128)
-> [BlockCipher] -> [BlockCipher128]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap BlockCipher -> BlockCipher128
MkBlockCipher128
[ BlockCipher
AES128
, BlockCipher
AES192
, BlockCipher
AES256
, BlockCipher
ARIA128
, BlockCipher
ARIA192
, BlockCipher
ARIA256
, BlockCipher
Camellia128
, BlockCipher
Camellia192
, BlockCipher
Camellia256
, BlockCipher
Noekeon
, BlockCipher
SEED
, BlockCipher
Serpent
, BlockCipher
SM4
, BlockCipher
Twofish
]
isBlockCipher128 :: BlockCipher -> Bool
isBlockCipher128 :: BlockCipher -> Bool
isBlockCipher128 = Maybe BlockCipher128 -> Bool
forall a. Maybe a -> Bool
isJust (Maybe BlockCipher128 -> Bool)
-> (BlockCipher -> Maybe BlockCipher128) -> BlockCipher -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BlockCipher -> Maybe BlockCipher128
blockCipher128
blockCipher128Name :: BlockCipher128 -> Low.BlockCipherName
blockCipher128Name :: BlockCipher128 -> BlockCipherName
blockCipher128Name = BlockCipher -> BlockCipherName
blockCipherName (BlockCipher -> BlockCipherName)
-> (BlockCipher128 -> BlockCipher)
-> BlockCipher128
-> BlockCipherName
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BlockCipher128 -> BlockCipher
unBlockCipher128
blockCipher128KeySpec :: BlockCipher128 -> BlockCipherKeySpec
blockCipher128KeySpec :: BlockCipher128 -> BlockCipherKeySpec
blockCipher128KeySpec = BlockCipher -> BlockCipherKeySpec
blockCipherKeySpec (BlockCipher -> BlockCipherKeySpec)
-> (BlockCipher128 -> BlockCipher)
-> BlockCipher128
-> BlockCipherKeySpec
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BlockCipher128 -> BlockCipher
unBlockCipher128
type BlockCipherKeySpec = KeySpec
type BlockCipherKey = ByteString
type BlockCipher128Key = BlockCipherKey
newBlockCipherKey :: (MonadRandomIO m) => BlockCipher -> m BlockCipherKey
newBlockCipherKey :: forall (m :: * -> *).
MonadRandomIO m =>
BlockCipher -> m BlockCipherName
newBlockCipherKey = BlockCipherKeySpec -> m BlockCipherName
forall (m :: * -> *).
MonadRandomIO m =>
BlockCipherKeySpec -> m BlockCipherName
newKey (BlockCipherKeySpec -> m BlockCipherName)
-> (BlockCipher -> BlockCipherKeySpec)
-> BlockCipher
-> m BlockCipherName
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BlockCipher -> BlockCipherKeySpec
blockCipherKeySpec
newBlockCipherKeyMaybe :: (MonadRandomIO m) => Int -> BlockCipher -> m (Maybe BlockCipherKey)
newBlockCipherKeyMaybe :: forall (m :: * -> *).
MonadRandomIO m =>
Int -> BlockCipher -> m (Maybe BlockCipherName)
newBlockCipherKeyMaybe Int
sz BlockCipher
bc = Int -> BlockCipherKeySpec -> m (Maybe BlockCipherName)
forall (m :: * -> *).
MonadRandomIO m =>
Int -> BlockCipherKeySpec -> m (Maybe BlockCipherName)
newKeyMaybe Int
sz (BlockCipher -> BlockCipherKeySpec
blockCipherKeySpec BlockCipher
bc)
type BlockCipherText = ByteString
blockCipherName :: BlockCipher -> Low.BlockCipherName
blockCipherName :: BlockCipher -> BlockCipherName
blockCipherName BlockCipher
spec = case BlockCipher
spec of
BlockCipher
Blowfish -> BlockCipherName
Low.Blowfish
BlockCipher
CAST128 -> BlockCipherName
Low.CAST128
BlockCipher
DES -> BlockCipherName
Low.DES
BlockCipher
TripleDES -> BlockCipherName
Low.TripleDES
BlockCipher
GOST_28147_89 -> BlockCipherName
Low.GOST_28147_89
BlockCipher
IDEA -> BlockCipherName
Low.IDEA
BlockCipher
AES128 -> BlockCipherName
Low.AES128
BlockCipher
AES192 -> BlockCipherName
Low.AES192
BlockCipher
AES256 -> BlockCipherName
Low.AES256
BlockCipher
ARIA128 -> BlockCipherName
Low.ARIA128
BlockCipher
ARIA192 -> BlockCipherName
Low.ARIA192
BlockCipher
ARIA256 -> BlockCipherName
Low.ARIA256
BlockCipher
Camellia128 -> BlockCipherName
Low.Camellia128
BlockCipher
Camellia192 -> BlockCipherName
Low.Camellia192
BlockCipher
Camellia256 -> BlockCipherName
Low.Camellia256
BlockCipher
Noekeon -> BlockCipherName
Low.Noekeon
BlockCipher
SEED -> BlockCipherName
Low.SEED
BlockCipher
Serpent -> BlockCipherName
Low.Serpent
BlockCipher
SM4 -> BlockCipherName
Low.SM4
BlockCipher
Twofish -> BlockCipherName
Low.Twofish
BlockCipher
SHACAL2 -> BlockCipherName
Low.SHACAL2
BlockCipher
Threefish512 -> BlockCipherName
Low.Threefish512
blockCipherBlockSize :: BlockCipher -> Int
blockCipherBlockSize :: BlockCipher -> Int
blockCipherBlockSize BlockCipher
Blowfish = Int
8
blockCipherBlockSize BlockCipher
CAST128 = Int
8
blockCipherBlockSize BlockCipher
DES = Int
8
blockCipherBlockSize BlockCipher
TripleDES = Int
8
blockCipherBlockSize BlockCipher
GOST_28147_89 = Int
8
blockCipherBlockSize BlockCipher
IDEA = Int
8
blockCipherBlockSize BlockCipher
AES128 = Int
16
blockCipherBlockSize BlockCipher
AES192 = Int
16
blockCipherBlockSize BlockCipher
AES256 = Int
16
blockCipherBlockSize BlockCipher
ARIA128 = Int
16
blockCipherBlockSize BlockCipher
ARIA192 = Int
16
blockCipherBlockSize BlockCipher
ARIA256 = Int
16
blockCipherBlockSize BlockCipher
Camellia128 = Int
16
blockCipherBlockSize BlockCipher
Camellia192 = Int
16
blockCipherBlockSize BlockCipher
Camellia256 = Int
16
blockCipherBlockSize BlockCipher
Noekeon = Int
16
blockCipherBlockSize BlockCipher
SEED = Int
16
blockCipherBlockSize BlockCipher
Serpent = Int
16
blockCipherBlockSize BlockCipher
SM4 = Int
16
blockCipherBlockSize BlockCipher
Twofish = Int
16
blockCipherBlockSize BlockCipher
SHACAL2 = Int
32
blockCipherBlockSize BlockCipher
Threefish512 = Int
64
blockCipherKeySpec :: BlockCipher -> BlockCipherKeySpec
blockCipherKeySpec :: BlockCipher -> BlockCipherKeySpec
blockCipherKeySpec BlockCipher
Blowfish = Int -> Int -> Int -> BlockCipherKeySpec
keySpec Int
1 Int
56 Int
1
blockCipherKeySpec BlockCipher
CAST128 = Int -> Int -> Int -> BlockCipherKeySpec
keySpec Int
11 Int
16 Int
1
blockCipherKeySpec BlockCipher
DES = Int -> Int -> Int -> BlockCipherKeySpec
keySpec Int
8 Int
8 Int
1
blockCipherKeySpec BlockCipher
TripleDES = Int -> Int -> Int -> BlockCipherKeySpec
keySpec Int
16 Int
24 Int
8
blockCipherKeySpec BlockCipher
GOST_28147_89 = Int -> Int -> Int -> BlockCipherKeySpec
keySpec Int
32 Int
32 Int
1
blockCipherKeySpec BlockCipher
IDEA = Int -> Int -> Int -> BlockCipherKeySpec
keySpec Int
16 Int
16 Int
1
blockCipherKeySpec BlockCipher
AES128 = Int -> Int -> Int -> BlockCipherKeySpec
keySpec Int
16 Int
16 Int
1
blockCipherKeySpec BlockCipher
AES192 = Int -> Int -> Int -> BlockCipherKeySpec
keySpec Int
24 Int
24 Int
1
blockCipherKeySpec BlockCipher
AES256 = Int -> Int -> Int -> BlockCipherKeySpec
keySpec Int
32 Int
32 Int
1
blockCipherKeySpec BlockCipher
ARIA128 = Int -> Int -> Int -> BlockCipherKeySpec
keySpec Int
16 Int
16 Int
1
blockCipherKeySpec BlockCipher
ARIA192 = Int -> Int -> Int -> BlockCipherKeySpec
keySpec Int
24 Int
24 Int
1
blockCipherKeySpec BlockCipher
ARIA256 = Int -> Int -> Int -> BlockCipherKeySpec
keySpec Int
32 Int
32 Int
1
blockCipherKeySpec BlockCipher
Camellia128 = Int -> Int -> Int -> BlockCipherKeySpec
keySpec Int
16 Int
16 Int
1
blockCipherKeySpec BlockCipher
Camellia192 = Int -> Int -> Int -> BlockCipherKeySpec
keySpec Int
24 Int
24 Int
1
blockCipherKeySpec BlockCipher
Camellia256 = Int -> Int -> Int -> BlockCipherKeySpec
keySpec Int
32 Int
32 Int
1
blockCipherKeySpec BlockCipher
Noekeon = Int -> Int -> Int -> BlockCipherKeySpec
keySpec Int
16 Int
16 Int
1
blockCipherKeySpec BlockCipher
SEED = Int -> Int -> Int -> BlockCipherKeySpec
keySpec Int
16 Int
16 Int
1
blockCipherKeySpec BlockCipher
Serpent = Int -> Int -> Int -> BlockCipherKeySpec
keySpec Int
16 Int
32 Int
8
blockCipherKeySpec BlockCipher
SM4 = Int -> Int -> Int -> BlockCipherKeySpec
keySpec Int
16 Int
16 Int
1
blockCipherKeySpec BlockCipher
Twofish = Int -> Int -> Int -> BlockCipherKeySpec
keySpec Int
16 Int
32 Int
8
blockCipherKeySpec BlockCipher
SHACAL2 = Int -> Int -> Int -> BlockCipherKeySpec
keySpec Int
16 Int
64 Int
4
blockCipherKeySpec BlockCipher
Threefish512 = Int -> Int -> Int -> BlockCipherKeySpec
keySpec Int
64 Int
64 Int
1
blockCipherEncrypt
:: BlockCipher
-> BlockCipherKey
-> ByteString
-> Maybe ByteString
blockCipherEncrypt :: BlockCipher
-> BlockCipherName -> BlockCipherName -> Maybe BlockCipherName
blockCipherEncrypt BlockCipher
bc BlockCipherName
k BlockCipherName
pt = IO (Maybe BlockCipherName) -> Maybe BlockCipherName
forall a. IO a -> a
unsafePerformIO (IO (Maybe BlockCipherName) -> Maybe BlockCipherName)
-> IO (Maybe BlockCipherName) -> Maybe BlockCipherName
forall a b. (a -> b) -> a -> b
$ do
MutableBlockCipher
mc <- BlockCipher -> IO MutableBlockCipher
forall (m :: * -> *).
MonadIO m =>
BlockCipher -> m MutableBlockCipher
newBlockCipher BlockCipher
bc
MutableBlockCipher
-> BlockCipherName -> BlockCipherName -> IO (Maybe BlockCipherName)
forall (m :: * -> *).
MonadIO m =>
MutableBlockCipher
-> BlockCipherName -> BlockCipherName -> m (Maybe BlockCipherName)
autoEncryptBlockCipherBlocks MutableBlockCipher
mc BlockCipherName
k BlockCipherName
pt
{-# NOINLINE blockCipherEncrypt #-}
blockCipherDecrypt
:: BlockCipher
-> BlockCipherKey
-> ByteString
-> Maybe ByteString
blockCipherDecrypt :: BlockCipher
-> BlockCipherName -> BlockCipherName -> Maybe BlockCipherName
blockCipherDecrypt BlockCipher
bc BlockCipherName
k BlockCipherName
ct = IO (Maybe BlockCipherName) -> Maybe BlockCipherName
forall a. IO a -> a
unsafePerformIO (IO (Maybe BlockCipherName) -> Maybe BlockCipherName)
-> IO (Maybe BlockCipherName) -> Maybe BlockCipherName
forall a b. (a -> b) -> a -> b
$ do
MutableBlockCipher
mc <- BlockCipher -> IO MutableBlockCipher
forall (m :: * -> *).
MonadIO m =>
BlockCipher -> m MutableBlockCipher
newBlockCipher BlockCipher
bc
MutableBlockCipher
-> BlockCipherName -> BlockCipherName -> IO (Maybe BlockCipherName)
forall (m :: * -> *).
MonadIO m =>
MutableBlockCipher
-> BlockCipherName -> BlockCipherName -> m (Maybe BlockCipherName)
autoDecryptBlockCipherBlocks MutableBlockCipher
mc BlockCipherName
k BlockCipherName
ct
{-# NOINLINE blockCipherDecrypt #-}
blockCipherEncryptLazy
:: BlockCipher
-> BlockCipherKey
-> Lazy.ByteString
-> Maybe Lazy.ByteString
blockCipherEncryptLazy :: BlockCipher -> BlockCipherName -> ByteString -> Maybe ByteString
blockCipherEncryptLazy = BlockCipher -> BlockCipherName -> ByteString -> Maybe ByteString
forall a. HasCallStack => a
undefined
blockCipherDecryptLazy
:: BlockCipher
-> BlockCipherKey
-> Lazy.ByteString
-> Maybe Lazy.ByteString
blockCipherDecryptLazy :: BlockCipher -> BlockCipherName -> ByteString -> Maybe ByteString
blockCipherDecryptLazy = BlockCipher -> BlockCipherName -> ByteString -> Maybe ByteString
forall a. HasCallStack => a
undefined
data MutableBlockCipher = MkMutableBlockCipher
{ MutableBlockCipher -> BlockCipher
mutableBlockCipherType :: BlockCipher
, MutableBlockCipher -> BlockCipher
mutableBlockCipherCtx :: Low.BlockCipher
}
destroyBlockCipher :: (MonadIO m) => MutableBlockCipher -> m ()
destroyBlockCipher :: forall (m :: * -> *). MonadIO m => MutableBlockCipher -> m ()
destroyBlockCipher = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ())
-> (MutableBlockCipher -> IO ()) -> MutableBlockCipher -> m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BlockCipher -> IO ()
Low.blockCipherDestroy (BlockCipher -> IO ())
-> (MutableBlockCipher -> BlockCipher)
-> MutableBlockCipher
-> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MutableBlockCipher -> BlockCipher
mutableBlockCipherCtx
newBlockCipher :: (MonadIO m) => BlockCipher -> m MutableBlockCipher
newBlockCipher :: forall (m :: * -> *).
MonadIO m =>
BlockCipher -> m MutableBlockCipher
newBlockCipher BlockCipher
c = do
BlockCipher
ctx <- IO BlockCipher -> m BlockCipher
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO BlockCipher -> m BlockCipher)
-> IO BlockCipher -> m BlockCipher
forall a b. (a -> b) -> a -> b
$ BlockCipherName -> IO BlockCipher
Low.blockCipherInit (BlockCipherName -> IO BlockCipher)
-> BlockCipherName -> IO BlockCipher
forall a b. (a -> b) -> a -> b
$ BlockCipher -> BlockCipherName
blockCipherName BlockCipher
c
MutableBlockCipher -> m MutableBlockCipher
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (MutableBlockCipher -> m MutableBlockCipher)
-> MutableBlockCipher -> m MutableBlockCipher
forall a b. (a -> b) -> a -> b
$ BlockCipher -> BlockCipher -> MutableBlockCipher
MkMutableBlockCipher BlockCipher
c BlockCipher
ctx
getBlockCipherName
:: (MonadIO m)
=> MutableBlockCipher
-> m (Low.BlockCipherName)
getBlockCipherName :: forall (m :: * -> *).
MonadIO m =>
MutableBlockCipher -> m BlockCipherName
getBlockCipherName = IO BlockCipherName -> m BlockCipherName
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO BlockCipherName -> m BlockCipherName)
-> (MutableBlockCipher -> IO BlockCipherName)
-> MutableBlockCipher
-> m BlockCipherName
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BlockCipher -> IO BlockCipherName
Low.blockCipherName (BlockCipher -> IO BlockCipherName)
-> (MutableBlockCipher -> BlockCipher)
-> MutableBlockCipher
-> IO BlockCipherName
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MutableBlockCipher -> BlockCipher
mutableBlockCipherCtx
getBlockCipherBlockSize
:: (MonadIO m)
=> MutableBlockCipher
-> m Int
getBlockCipherBlockSize :: forall (m :: * -> *). MonadIO m => MutableBlockCipher -> m Int
getBlockCipherBlockSize = IO Int -> m Int
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int -> m Int)
-> (MutableBlockCipher -> IO Int) -> MutableBlockCipher -> m Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BlockCipher -> IO Int
Low.blockCipherBlockSize (BlockCipher -> IO Int)
-> (MutableBlockCipher -> BlockCipher)
-> MutableBlockCipher
-> IO Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MutableBlockCipher -> BlockCipher
mutableBlockCipherCtx
getBlockCipherKeySpec
:: (MonadIO m)
=> MutableBlockCipher
-> m BlockCipherKeySpec
getBlockCipherKeySpec :: forall (m :: * -> *).
MonadIO m =>
MutableBlockCipher -> m BlockCipherKeySpec
getBlockCipherKeySpec MutableBlockCipher
mc = do
(Int
mn,Int
mx,Int
md) <- IO (Int, Int, Int) -> m (Int, Int, Int)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Int, Int, Int) -> m (Int, Int, Int))
-> IO (Int, Int, Int) -> m (Int, Int, Int)
forall a b. (a -> b) -> a -> b
$ BlockCipher -> IO (Int, Int, Int)
Low.blockCipherGetKeyspec (MutableBlockCipher -> BlockCipher
mutableBlockCipherCtx MutableBlockCipher
mc)
BlockCipherKeySpec -> m BlockCipherKeySpec
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (BlockCipherKeySpec -> m BlockCipherKeySpec)
-> BlockCipherKeySpec -> m BlockCipherKeySpec
forall a b. (a -> b) -> a -> b
$ Int -> Int -> Int -> BlockCipherKeySpec
keySpec Int
mn Int
mx Int
md
setBlockCipherKey
:: (MonadIO m)
=> BlockCipherKey
-> MutableBlockCipher
-> m Bool
setBlockCipherKey :: forall (m :: * -> *).
MonadIO m =>
BlockCipherName -> MutableBlockCipher -> m Bool
setBlockCipherKey BlockCipherName
k MutableBlockCipher
mc = do
Bool
valid <- Int -> BlockCipherKeySpec -> Bool
keySizeIsValid (BlockCipherName -> Int
ByteString.length BlockCipherName
k) (BlockCipherKeySpec -> Bool) -> m BlockCipherKeySpec -> m Bool
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> MutableBlockCipher -> m BlockCipherKeySpec
forall (m :: * -> *).
MonadIO m =>
MutableBlockCipher -> m BlockCipherKeySpec
getBlockCipherKeySpec MutableBlockCipher
mc
if Bool
valid
then do
IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ BlockCipher -> BlockCipherName -> IO ()
Low.blockCipherSetKey (MutableBlockCipher -> BlockCipher
mutableBlockCipherCtx MutableBlockCipher
mc) BlockCipherName
k
Bool -> m Bool
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True
else Bool -> m Bool
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False
clearBlockCipher :: (MonadIO m) => MutableBlockCipher -> m ()
clearBlockCipher :: forall (m :: * -> *). MonadIO m => MutableBlockCipher -> m ()
clearBlockCipher = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ())
-> (MutableBlockCipher -> IO ()) -> MutableBlockCipher -> m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BlockCipher -> IO ()
Low.blockCipherClear (BlockCipher -> IO ())
-> (MutableBlockCipher -> BlockCipher)
-> MutableBlockCipher
-> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MutableBlockCipher -> BlockCipher
mutableBlockCipherCtx
encryptBlockCipherBlocks
:: (MonadIO m)
=> MutableBlockCipher
-> ByteString
-> m BlockCipherText
encryptBlockCipherBlocks :: forall (m :: * -> *).
MonadIO m =>
MutableBlockCipher -> BlockCipherName -> m BlockCipherName
encryptBlockCipherBlocks MutableBlockCipher
mc BlockCipherName
pt = IO BlockCipherName -> m BlockCipherName
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO BlockCipherName -> m BlockCipherName)
-> IO BlockCipherName -> m BlockCipherName
forall a b. (a -> b) -> a -> b
$ BlockCipher -> BlockCipherName -> IO BlockCipherName
Low.blockCipherEncryptBlocks (MutableBlockCipher -> BlockCipher
mutableBlockCipherCtx MutableBlockCipher
mc) BlockCipherName
pt
decryptBlockCipherBlocks
:: (MonadIO m)
=> MutableBlockCipher
-> BlockCipherText
-> m ByteString
decryptBlockCipherBlocks :: forall (m :: * -> *).
MonadIO m =>
MutableBlockCipher -> BlockCipherName -> m BlockCipherName
decryptBlockCipherBlocks MutableBlockCipher
mc BlockCipherName
ct = IO BlockCipherName -> m BlockCipherName
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO BlockCipherName -> m BlockCipherName)
-> IO BlockCipherName -> m BlockCipherName
forall a b. (a -> b) -> a -> b
$ BlockCipher -> BlockCipherName -> IO BlockCipherName
Low.blockCipherDecryptBlocks (MutableBlockCipher -> BlockCipher
mutableBlockCipherCtx MutableBlockCipher
mc) BlockCipherName
ct
autoEncryptBlockCipherBlocks
:: (MonadIO m)
=> MutableBlockCipher
-> BlockCipherKey
-> ByteString
-> m (Maybe BlockCipherText)
autoEncryptBlockCipherBlocks :: forall (m :: * -> *).
MonadIO m =>
MutableBlockCipher
-> BlockCipherName -> BlockCipherName -> m (Maybe BlockCipherName)
autoEncryptBlockCipherBlocks MutableBlockCipher
mc BlockCipherName
k BlockCipherName
pt = do
Bool
wasSet <- BlockCipherName -> MutableBlockCipher -> m Bool
forall (m :: * -> *).
MonadIO m =>
BlockCipherName -> MutableBlockCipher -> m Bool
setBlockCipherKey BlockCipherName
k MutableBlockCipher
mc
if Bool
wasSet
then do
BlockCipherName
bct <- MutableBlockCipher -> BlockCipherName -> m BlockCipherName
forall (m :: * -> *).
MonadIO m =>
MutableBlockCipher -> BlockCipherName -> m BlockCipherName
encryptBlockCipherBlocks MutableBlockCipher
mc BlockCipherName
pt
MutableBlockCipher -> m ()
forall (m :: * -> *). MonadIO m => MutableBlockCipher -> m ()
clearBlockCipher MutableBlockCipher
mc
Maybe BlockCipherName -> m (Maybe BlockCipherName)
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe BlockCipherName -> m (Maybe BlockCipherName))
-> Maybe BlockCipherName -> m (Maybe BlockCipherName)
forall a b. (a -> b) -> a -> b
$ BlockCipherName -> Maybe BlockCipherName
forall a. a -> Maybe a
Just BlockCipherName
bct
else Maybe BlockCipherName -> m (Maybe BlockCipherName)
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe BlockCipherName
forall a. Maybe a
Nothing
autoDecryptBlockCipherBlocks
:: (MonadIO m)
=> MutableBlockCipher
-> BlockCipherKey
-> BlockCipherText
-> m (Maybe ByteString)
autoDecryptBlockCipherBlocks :: forall (m :: * -> *).
MonadIO m =>
MutableBlockCipher
-> BlockCipherName -> BlockCipherName -> m (Maybe BlockCipherName)
autoDecryptBlockCipherBlocks MutableBlockCipher
mc BlockCipherName
k BlockCipherName
ct = do
Bool
wasSet <- BlockCipherName -> MutableBlockCipher -> m Bool
forall (m :: * -> *).
MonadIO m =>
BlockCipherName -> MutableBlockCipher -> m Bool
setBlockCipherKey BlockCipherName
k MutableBlockCipher
mc
if Bool
wasSet
then do
BlockCipherName
pt <- MutableBlockCipher -> BlockCipherName -> m BlockCipherName
forall (m :: * -> *).
MonadIO m =>
MutableBlockCipher -> BlockCipherName -> m BlockCipherName
decryptBlockCipherBlocks MutableBlockCipher
mc BlockCipherName
ct
MutableBlockCipher -> m ()
forall (m :: * -> *). MonadIO m => MutableBlockCipher -> m ()
clearBlockCipher MutableBlockCipher
mc
Maybe BlockCipherName -> m (Maybe BlockCipherName)
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe BlockCipherName -> m (Maybe BlockCipherName))
-> Maybe BlockCipherName -> m (Maybe BlockCipherName)
forall a b. (a -> b) -> a -> b
$ BlockCipherName -> Maybe BlockCipherName
forall a. a -> Maybe a
Just BlockCipherName
pt
else Maybe BlockCipherName -> m (Maybe BlockCipherName)
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe BlockCipherName
forall a. Maybe a
Nothing
blowfish :: BlockCipher
blowfish :: BlockCipher
blowfish = BlockCipher
Blowfish
cast128 :: BlockCipher
cast128 :: BlockCipher
cast128 = BlockCipher
CAST128
des :: BlockCipher
des :: BlockCipher
des = BlockCipher
DES
tripleDES :: BlockCipher
tripleDES :: BlockCipher
tripleDES = BlockCipher
TripleDES
gost_28147_89 :: BlockCipher
gost_28147_89 :: BlockCipher
gost_28147_89 = BlockCipher
GOST_28147_89
idea :: BlockCipher
idea :: BlockCipher
idea = BlockCipher
IDEA
aes128 :: BlockCipher
aes128 :: BlockCipher
aes128 = BlockCipher
AES128
aes192 :: BlockCipher
aes192 :: BlockCipher
aes192 = BlockCipher
AES192
aes256 :: BlockCipher
aes256 :: BlockCipher
aes256 = BlockCipher
AES256
aria128 :: BlockCipher
aria128 :: BlockCipher
aria128 = BlockCipher
ARIA128
aria192 :: BlockCipher
aria192 :: BlockCipher
aria192 = BlockCipher
ARIA192
aria256 :: BlockCipher
aria256 :: BlockCipher
aria256 = BlockCipher
ARIA256
camellia128 :: BlockCipher
camellia128 :: BlockCipher
camellia128 = BlockCipher
Camellia128
camellia192 :: BlockCipher
camellia192 :: BlockCipher
camellia192 = BlockCipher
Camellia192
camellia256 :: BlockCipher
camellia256 :: BlockCipher
camellia256 = BlockCipher
Camellia256
noekeon :: BlockCipher
noekeon :: BlockCipher
noekeon = BlockCipher
Noekeon
seed :: BlockCipher
seed :: BlockCipher
seed = BlockCipher
SEED
sm4 :: BlockCipher
sm4 :: BlockCipher
sm4 = BlockCipher
SM4
serpent :: BlockCipher
serpent :: BlockCipher
serpent = BlockCipher
Serpent
twofish :: BlockCipher
twofish :: BlockCipher
twofish = BlockCipher
Twofish
shalcal2 :: BlockCipher
shalcal2 :: BlockCipher
shalcal2 = BlockCipher
SHACAL2
threefish512 :: BlockCipher
threefish512 :: BlockCipher
threefish512 = BlockCipher
Threefish512