module Botan.Cipher
(
Cipher(..)
, AEAD(..)
, aead
, unsafeAEAD
, isAEAD
, ciphers
, cbcPaddings
, aeads
, CipherKey(..)
, CipherNonce(..)
, CBCPadding(..)
, AEADAssociatedData(..)
, cipherName
, cipherKeySpec
, cipherDefaultNonceSize
, cipherNonceSizeIsValid
, cipherTagSize
, cipherUpdateGranularity
, cipherIdealUpdateGranularity
, cipherOutputLength
, cipherEncrypt
, cipherDecrypt
, cipherEncryptLazy
, cipherDecryptLazy
, aeadEncrypt
, aeadDecrypt
, MutableCipher(..)
, destroyCipher
, CipherDirection(..)
, CipherUpdate(..)
, newCipher
, getCipherName
, getCipherKeySpec
, getCipherDefaultNonceSize
, getCipherNonceSizeIsValid
, getCipherTagSize
, getCipherUpdateGranularity
, getCipherIdealUpdateGranularity
, getCipherEstimateOutputLength
, getCipherOutputLength
, setCipherKey
, setAEADAssociatedData
, clearCipher
, resetCipher
, startCipher
, updateCipher
, finalizeCipher
, finalizeResetCipher
, finalizeClearCipher
, cbc
, cbcWith
, cfb
, cfbWith
, xts
, chaCha20Poly1305
, gcm
, gcmWith
, ocb
, ocbWith
, eax
, eaxWith
, siv
, ccm
, ccmWith
) where
import qualified Botan.Low.Cipher as Low
import Botan.BlockCipher
import Botan.Error
import Botan.KeySpec
import Botan.Prelude
import qualified Data.ByteString as ByteString
import qualified Data.ByteString.Lazy as Lazy
import Botan.RNG
import Data.Maybe
data Cipher
= CBC BlockCipher CBCPadding
| CFB BlockCipher Int
| XTS BlockCipher
| ChaCha20Poly1305
| GCM BlockCipher128 Int
| OCB BlockCipher128 Int
| EAX BlockCipher Int
| SIV BlockCipher128
| CCM BlockCipher128 Int Int
deriving (Cipher -> Cipher -> Bool
(Cipher -> Cipher -> Bool)
-> (Cipher -> Cipher -> Bool) -> Eq Cipher
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Cipher -> Cipher -> Bool
== :: Cipher -> Cipher -> Bool
$c/= :: Cipher -> Cipher -> Bool
/= :: Cipher -> Cipher -> Bool
Eq, Eq Cipher
Eq Cipher =>
(Cipher -> Cipher -> Ordering)
-> (Cipher -> Cipher -> Bool)
-> (Cipher -> Cipher -> Bool)
-> (Cipher -> Cipher -> Bool)
-> (Cipher -> Cipher -> Bool)
-> (Cipher -> Cipher -> Cipher)
-> (Cipher -> Cipher -> Cipher)
-> Ord Cipher
Cipher -> Cipher -> Bool
Cipher -> Cipher -> Ordering
Cipher -> Cipher -> Cipher
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 :: Cipher -> Cipher -> Ordering
compare :: Cipher -> Cipher -> Ordering
$c< :: Cipher -> Cipher -> Bool
< :: Cipher -> Cipher -> Bool
$c<= :: Cipher -> Cipher -> Bool
<= :: Cipher -> Cipher -> Bool
$c> :: Cipher -> Cipher -> Bool
> :: Cipher -> Cipher -> Bool
$c>= :: Cipher -> Cipher -> Bool
>= :: Cipher -> Cipher -> Bool
$cmax :: Cipher -> Cipher -> Cipher
max :: Cipher -> Cipher -> Cipher
$cmin :: Cipher -> Cipher -> Cipher
min :: Cipher -> Cipher -> Cipher
Ord, Int -> Cipher -> ShowS
[Cipher] -> ShowS
Cipher -> String
(Int -> Cipher -> ShowS)
-> (Cipher -> String) -> ([Cipher] -> ShowS) -> Show Cipher
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Cipher -> ShowS
showsPrec :: Int -> Cipher -> ShowS
$cshow :: Cipher -> String
show :: Cipher -> String
$cshowList :: [Cipher] -> ShowS
showList :: [Cipher] -> ShowS
Show)
data CBCPadding
= PKCS7
| OneAndZeros
| X9_23
| ESP
| CTS
| NoPadding
deriving (CBCPadding -> CBCPadding -> Bool
(CBCPadding -> CBCPadding -> Bool)
-> (CBCPadding -> CBCPadding -> Bool) -> Eq CBCPadding
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CBCPadding -> CBCPadding -> Bool
== :: CBCPadding -> CBCPadding -> Bool
$c/= :: CBCPadding -> CBCPadding -> Bool
/= :: CBCPadding -> CBCPadding -> Bool
Eq, Eq CBCPadding
Eq CBCPadding =>
(CBCPadding -> CBCPadding -> Ordering)
-> (CBCPadding -> CBCPadding -> Bool)
-> (CBCPadding -> CBCPadding -> Bool)
-> (CBCPadding -> CBCPadding -> Bool)
-> (CBCPadding -> CBCPadding -> Bool)
-> (CBCPadding -> CBCPadding -> CBCPadding)
-> (CBCPadding -> CBCPadding -> CBCPadding)
-> Ord CBCPadding
CBCPadding -> CBCPadding -> Bool
CBCPadding -> CBCPadding -> Ordering
CBCPadding -> CBCPadding -> CBCPadding
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 :: CBCPadding -> CBCPadding -> Ordering
compare :: CBCPadding -> CBCPadding -> Ordering
$c< :: CBCPadding -> CBCPadding -> Bool
< :: CBCPadding -> CBCPadding -> Bool
$c<= :: CBCPadding -> CBCPadding -> Bool
<= :: CBCPadding -> CBCPadding -> Bool
$c> :: CBCPadding -> CBCPadding -> Bool
> :: CBCPadding -> CBCPadding -> Bool
$c>= :: CBCPadding -> CBCPadding -> Bool
>= :: CBCPadding -> CBCPadding -> Bool
$cmax :: CBCPadding -> CBCPadding -> CBCPadding
max :: CBCPadding -> CBCPadding -> CBCPadding
$cmin :: CBCPadding -> CBCPadding -> CBCPadding
min :: CBCPadding -> CBCPadding -> CBCPadding
Ord, Int -> CBCPadding -> ShowS
[CBCPadding] -> ShowS
CBCPadding -> String
(Int -> CBCPadding -> ShowS)
-> (CBCPadding -> String)
-> ([CBCPadding] -> ShowS)
-> Show CBCPadding
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CBCPadding -> ShowS
showsPrec :: Int -> CBCPadding -> ShowS
$cshow :: CBCPadding -> String
show :: CBCPadding -> String
$cshowList :: [CBCPadding] -> ShowS
showList :: [CBCPadding] -> ShowS
Show)
newtype AEAD = MkAEAD { AEAD -> Cipher
unAEAD :: Cipher }
deriving (AEAD -> AEAD -> Bool
(AEAD -> AEAD -> Bool) -> (AEAD -> AEAD -> Bool) -> Eq AEAD
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: AEAD -> AEAD -> Bool
== :: AEAD -> AEAD -> Bool
$c/= :: AEAD -> AEAD -> Bool
/= :: AEAD -> AEAD -> Bool
Eq, Eq AEAD
Eq AEAD =>
(AEAD -> AEAD -> Ordering)
-> (AEAD -> AEAD -> Bool)
-> (AEAD -> AEAD -> Bool)
-> (AEAD -> AEAD -> Bool)
-> (AEAD -> AEAD -> Bool)
-> (AEAD -> AEAD -> AEAD)
-> (AEAD -> AEAD -> AEAD)
-> Ord AEAD
AEAD -> AEAD -> Bool
AEAD -> AEAD -> Ordering
AEAD -> AEAD -> AEAD
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 :: AEAD -> AEAD -> Ordering
compare :: AEAD -> AEAD -> Ordering
$c< :: AEAD -> AEAD -> Bool
< :: AEAD -> AEAD -> Bool
$c<= :: AEAD -> AEAD -> Bool
<= :: AEAD -> AEAD -> Bool
$c> :: AEAD -> AEAD -> Bool
> :: AEAD -> AEAD -> Bool
$c>= :: AEAD -> AEAD -> Bool
>= :: AEAD -> AEAD -> Bool
$cmax :: AEAD -> AEAD -> AEAD
max :: AEAD -> AEAD -> AEAD
$cmin :: AEAD -> AEAD -> AEAD
min :: AEAD -> AEAD -> AEAD
Ord, Int -> AEAD -> ShowS
[AEAD] -> ShowS
AEAD -> String
(Int -> AEAD -> ShowS)
-> (AEAD -> String) -> ([AEAD] -> ShowS) -> Show AEAD
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> AEAD -> ShowS
showsPrec :: Int -> AEAD -> ShowS
$cshow :: AEAD -> String
show :: AEAD -> String
$cshowList :: [AEAD] -> ShowS
showList :: [AEAD] -> ShowS
Show)
aead :: Cipher -> Maybe AEAD
aead :: Cipher -> Maybe AEAD
aead c :: Cipher
c@(Cipher
ChaCha20Poly1305) = AEAD -> Maybe AEAD
forall a. a -> Maybe a
Just (AEAD -> Maybe AEAD) -> AEAD -> Maybe AEAD
forall a b. (a -> b) -> a -> b
$ Cipher -> AEAD
MkAEAD Cipher
c
aead c :: Cipher
c@(GCM BlockCipher128
_ Int
_) = AEAD -> Maybe AEAD
forall a. a -> Maybe a
Just (AEAD -> Maybe AEAD) -> AEAD -> Maybe AEAD
forall a b. (a -> b) -> a -> b
$ Cipher -> AEAD
MkAEAD Cipher
c
aead c :: Cipher
c@(OCB BlockCipher128
_ Int
_) = AEAD -> Maybe AEAD
forall a. a -> Maybe a
Just (AEAD -> Maybe AEAD) -> AEAD -> Maybe AEAD
forall a b. (a -> b) -> a -> b
$ Cipher -> AEAD
MkAEAD Cipher
c
aead c :: Cipher
c@(EAX BlockCipher
_ Int
_) = AEAD -> Maybe AEAD
forall a. a -> Maybe a
Just (AEAD -> Maybe AEAD) -> AEAD -> Maybe AEAD
forall a b. (a -> b) -> a -> b
$ Cipher -> AEAD
MkAEAD Cipher
c
aead c :: Cipher
c@(SIV BlockCipher128
_) = AEAD -> Maybe AEAD
forall a. a -> Maybe a
Just (AEAD -> Maybe AEAD) -> AEAD -> Maybe AEAD
forall a b. (a -> b) -> a -> b
$ Cipher -> AEAD
MkAEAD Cipher
c
aead c :: Cipher
c@(CCM BlockCipher128
_ Int
_ Int
_) = AEAD -> Maybe AEAD
forall a. a -> Maybe a
Just (AEAD -> Maybe AEAD) -> AEAD -> Maybe AEAD
forall a b. (a -> b) -> a -> b
$ Cipher -> AEAD
MkAEAD Cipher
c
aead Cipher
_ = Maybe AEAD
forall a. Maybe a
Nothing
unsafeAEAD :: Cipher -> AEAD
unsafeAEAD :: Cipher -> AEAD
unsafeAEAD = Cipher -> AEAD
MkAEAD
isAEAD :: Cipher -> Bool
isAEAD :: Cipher -> Bool
isAEAD = Maybe AEAD -> Bool
forall a. Maybe a -> Bool
isJust (Maybe AEAD -> Bool) -> (Cipher -> Maybe AEAD) -> Cipher -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Cipher -> Maybe AEAD
aead
ciphers :: [ Cipher ]
ciphers :: [Cipher]
ciphers = [[Cipher]] -> [Cipher]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
[ [ BlockCipher -> CBCPadding -> Cipher
CBC BlockCipher
bc CBCPadding
pd | BlockCipher
bc <- [BlockCipher]
blockCiphers, CBCPadding
pd <- [CBCPadding]
cbcPaddings ]
, [ BlockCipher -> Int -> Cipher
CFB BlockCipher
bc (Int
8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* BlockCipher -> Int
blockCipherBlockSize BlockCipher
bc) | BlockCipher
bc <- [BlockCipher]
blockCiphers ]
, [ BlockCipher -> Cipher
XTS BlockCipher
bc | BlockCipher
bc <- [BlockCipher]
blockCiphers ]
, (AEAD -> Cipher) -> [AEAD] -> [Cipher]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap AEAD -> Cipher
unAEAD [AEAD]
aeads
]
cbcPaddings :: [ CBCPadding ]
cbcPaddings :: [CBCPadding]
cbcPaddings =
[ CBCPadding
PKCS7
, CBCPadding
OneAndZeros
, CBCPadding
X9_23
, CBCPadding
ESP
, CBCPadding
CTS
, CBCPadding
NoPadding
]
aeads :: [ AEAD ]
aeads :: [AEAD]
aeads = (Cipher -> AEAD) -> [Cipher] -> [AEAD]
forall a b. (a -> b) -> [a] -> [b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Cipher -> AEAD
MkAEAD ([Cipher] -> [AEAD]) -> [Cipher] -> [AEAD]
forall a b. (a -> b) -> a -> b
$ [[Cipher]] -> [Cipher]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat
[ [ Cipher
ChaCha20Poly1305 ]
, [ BlockCipher128 -> Int -> Cipher
GCM BlockCipher128
bc Int
16 | BlockCipher128
bc <- [BlockCipher128]
blockCipher128s ]
, [ BlockCipher128 -> Int -> Cipher
OCB BlockCipher128
bc Int
16 | BlockCipher128
bc <- [BlockCipher128]
blockCipher128s ]
, [ BlockCipher -> Int -> Cipher
EAX BlockCipher
bc (BlockCipher -> Int
blockCipherBlockSize BlockCipher
bc) | BlockCipher
bc <- [BlockCipher]
blockCiphers ]
, [ BlockCipher128 -> Cipher
SIV BlockCipher128
bc | BlockCipher128
bc <- [BlockCipher128]
blockCipher128s ]
, [ BlockCipher128 -> Int -> Int -> Cipher
CCM BlockCipher128
bc Int
16 Int
3 | BlockCipher128
bc <- [BlockCipher128]
blockCipher128s ]
]
type CipherKeySpec = KeySpec
type CipherKey = Low.CipherKey
newCipherKey :: (MonadRandomIO m) => Cipher -> m CipherKey
newCipherKey :: forall (m :: * -> *). MonadRandomIO m => Cipher -> m CipherKey
newCipherKey = KeySpec -> m CipherKey
forall (m :: * -> *). MonadRandomIO m => KeySpec -> m CipherKey
newKey (KeySpec -> m CipherKey)
-> (Cipher -> KeySpec) -> Cipher -> m CipherKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Cipher -> KeySpec
cipherKeySpec
newCipherKeyMaybe :: (MonadRandomIO m) => Int -> Cipher -> m (Maybe CipherKey)
newCipherKeyMaybe :: forall (m :: * -> *).
MonadRandomIO m =>
Int -> Cipher -> m (Maybe CipherKey)
newCipherKeyMaybe Int
sz Cipher
bc = Int -> KeySpec -> m (Maybe CipherKey)
forall (m :: * -> *).
MonadRandomIO m =>
Int -> KeySpec -> m (Maybe CipherKey)
newKeyMaybe Int
sz (Cipher -> KeySpec
cipherKeySpec Cipher
bc)
type CipherNonce = ByteString
newCipherNonce :: (MonadRandomIO m) => Cipher -> m CipherNonce
newCipherNonce :: forall (m :: * -> *). MonadRandomIO m => Cipher -> m CipherKey
newCipherNonce = Int -> m CipherKey
forall (m :: * -> *). MonadRandomIO m => Int -> m CipherKey
getRandomBytes (Int -> m CipherKey) -> (Cipher -> Int) -> Cipher -> m CipherKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Cipher -> Int
cipherDefaultNonceSize
newCipherNonceMaybe :: (MonadRandomIO m) => Int -> Cipher -> m (Maybe CipherNonce)
newCipherNonceMaybe :: forall (m :: * -> *).
MonadRandomIO m =>
Int -> Cipher -> m (Maybe CipherKey)
newCipherNonceMaybe Int
sz Cipher
c = if Int -> Cipher -> Bool
cipherNonceSizeIsValid Int
sz Cipher
c
then CipherKey -> Maybe CipherKey
forall a. a -> Maybe a
Just (CipherKey -> Maybe CipherKey)
-> m CipherKey -> m (Maybe CipherKey)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> m CipherKey
forall (m :: * -> *). MonadRandomIO m => Int -> m CipherKey
getRandomBytes Int
sz
else Maybe CipherKey -> m (Maybe CipherKey)
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe CipherKey
forall a. Maybe a
Nothing
type AEADAssociatedData = ByteString
cipherName :: Cipher -> Low.CipherName
cipherName :: Cipher -> CipherKey
cipherName (CBC BlockCipher
bc CBCPadding
padding) = CipherKey -> CipherKey -> CipherKey
Low.cbcMode (BlockCipher -> CipherKey
blockCipherName BlockCipher
bc) (CBCPadding -> CipherKey
cbcPaddingName CBCPadding
padding)
cipherName (CFB BlockCipher
bc Int
fsz) = CipherKey -> Int -> CipherKey
Low.cfbModeWith (BlockCipher -> CipherKey
blockCipherName BlockCipher
bc) Int
fsz
cipherName (XTS BlockCipher
bc) = CipherKey -> CipherKey
Low.xtsMode (BlockCipher -> CipherKey
blockCipherName BlockCipher
bc)
cipherName Cipher
ChaCha20Poly1305 = CipherKey
Low.chaCha20Poly1305
cipherName (GCM BlockCipher128
bc128 Int
tsz) = CipherKey -> Int -> CipherKey
Low.gcmModeWith (BlockCipher128 -> CipherKey
blockCipher128Name BlockCipher128
bc128) Int
tsz
cipherName (OCB BlockCipher128
bc128 Int
tsz) = CipherKey -> Int -> CipherKey
Low.ocbModeWith (BlockCipher128 -> CipherKey
blockCipher128Name BlockCipher128
bc128) Int
tsz
cipherName (EAX BlockCipher
bc Int
tsz) = CipherKey -> Int -> CipherKey
Low.eaxModeWith (BlockCipher -> CipherKey
blockCipherName BlockCipher
bc) Int
tsz
cipherName (SIV BlockCipher128
bc128) = CipherKey -> CipherKey
Low.sivMode (BlockCipher128 -> CipherKey
blockCipher128Name BlockCipher128
bc128)
cipherName (CCM BlockCipher128
bc128 Int
tsz Int
l) = CipherKey -> Int -> Int -> CipherKey
Low.ccmModeWith (BlockCipher128 -> CipherKey
blockCipher128Name BlockCipher128
bc128) Int
tsz Int
l
cbcPaddingName :: CBCPadding -> ByteString
cbcPaddingName :: CBCPadding -> CipherKey
cbcPaddingName CBCPadding
PKCS7 = CipherKey
Low.PKCS7
cbcPaddingName CBCPadding
OneAndZeros = CipherKey
Low.OneAndZeros
cbcPaddingName CBCPadding
X9_23 = CipherKey
Low.X9_23
cbcPaddingName CBCPadding
ESP = CipherKey
Low.ESP
cbcPaddingName CBCPadding
CTS = CipherKey
Low.CTS
cbcPaddingName CBCPadding
NoPadding = CipherKey
Low.NoPadding
aeadName :: AEAD -> Low.CipherName
aeadName :: AEAD -> CipherKey
aeadName = Cipher -> CipherKey
cipherName (Cipher -> CipherKey) -> (AEAD -> Cipher) -> AEAD -> CipherKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AEAD -> Cipher
unAEAD
cipherKeySpec :: Cipher -> CipherKeySpec
cipherKeySpec :: Cipher -> KeySpec
cipherKeySpec (CBC BlockCipher
bc CBCPadding
_) = BlockCipher -> KeySpec
blockCipherKeySpec BlockCipher
bc
cipherKeySpec (CFB BlockCipher
bc Int
_) = BlockCipher -> KeySpec
blockCipherKeySpec BlockCipher
bc
cipherKeySpec (XTS BlockCipher
bc) = (Int -> Int) -> KeySpec -> KeySpec
monoMapKeySpec (Int -> Int -> Int
forall a. Num a => a -> a -> a
*Int
2) (KeySpec -> KeySpec) -> KeySpec -> KeySpec
forall a b. (a -> b) -> a -> b
$ BlockCipher -> KeySpec
blockCipherKeySpec BlockCipher
bc
cipherKeySpec Cipher
ChaCha20Poly1305 = Int -> Int -> Int -> KeySpec
keySpec Int
32 Int
32 Int
1
cipherKeySpec (GCM BlockCipher128
bc128 Int
_) = BlockCipher128 -> KeySpec
blockCipher128KeySpec BlockCipher128
bc128
cipherKeySpec (OCB BlockCipher128
bc128 Int
_) = BlockCipher128 -> KeySpec
blockCipher128KeySpec BlockCipher128
bc128
cipherKeySpec (EAX BlockCipher
bc Int
_) = BlockCipher -> KeySpec
blockCipherKeySpec BlockCipher
bc
cipherKeySpec (SIV BlockCipher128
bc128) = (Int -> Int) -> KeySpec -> KeySpec
monoMapKeySpec (Int -> Int -> Int
forall a. Num a => a -> a -> a
*Int
2) (KeySpec -> KeySpec) -> KeySpec -> KeySpec
forall a b. (a -> b) -> a -> b
$ BlockCipher128 -> KeySpec
blockCipher128KeySpec BlockCipher128
bc128
cipherKeySpec (CCM BlockCipher128
bc128 Int
_ Int
_) = BlockCipher128 -> KeySpec
blockCipher128KeySpec BlockCipher128
bc128
cipherDefaultNonceSize :: Cipher -> Int
cipherDefaultNonceSize :: Cipher -> Int
cipherDefaultNonceSize (CBC BlockCipher
bc CBCPadding
_) = BlockCipher -> Int
blockCipherBlockSize BlockCipher
bc
cipherDefaultNonceSize (CFB BlockCipher
bc Int
_) = BlockCipher -> Int
blockCipherBlockSize BlockCipher
bc
cipherDefaultNonceSize (XTS BlockCipher
bc) = BlockCipher -> Int
blockCipherBlockSize BlockCipher
bc
cipherDefaultNonceSize Cipher
_ = Int
12
internalMaximumCipherNonceSize :: Int
internalMaximumCipherNonceSize :: Int
internalMaximumCipherNonceSize = Int
1024
cipherNonceSizeIsValid :: Int -> Cipher -> Bool
cipherNonceSizeIsValid :: Int -> Cipher -> Bool
cipherNonceSizeIsValid Int
n (CBC BlockCipher
bc CBCPadding
_) = Int
n Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== BlockCipher -> Int
blockCipherBlockSize BlockCipher
bc
cipherNonceSizeIsValid Int
n (CFB BlockCipher
bc Int
_) = Int
n Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== BlockCipher -> Int
blockCipherBlockSize BlockCipher
bc
cipherNonceSizeIsValid Int
n (XTS BlockCipher
bc) = Int
1 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
n Bool -> Bool -> Bool
&& Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= BlockCipher -> Int
blockCipherBlockSize BlockCipher
bc
cipherNonceSizeIsValid Int
n Cipher
chaCha20Poly1305 = Int
n Int -> [Int] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [ Int
8, Int
12, Int
24 ]
cipherNonceSizeIsValid Int
n (GCM BlockCipher128
_ Int
_) = Int
1 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
n Bool -> Bool -> Bool
&& Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
internalMaximumCipherNonceSize
cipherNonceSizeIsValid Int
n (OCB BlockCipher128
bc128 Int
_) = Int
1 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
n Bool -> Bool -> Bool
&& Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= BlockCipher -> Int
blockCipherBlockSize (BlockCipher128 -> BlockCipher
unBlockCipher128 BlockCipher128
bc128) Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1
cipherNonceSizeIsValid Int
n (EAX BlockCipher
_ Int
_) = Int
1 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
n Bool -> Bool -> Bool
&& Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
internalMaximumCipherNonceSize
cipherNonceSizeIsValid Int
n (SIV BlockCipher128
_) = Int
1 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
n Bool -> Bool -> Bool
&& Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
internalMaximumCipherNonceSize
cipherNonceSizeIsValid Int
n (CCM BlockCipher128
_ Int
_ Int
_) = Int
n Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
12
cipherTagSize :: Cipher -> Maybe Int
cipherTagSize :: Cipher -> Maybe Int
cipherTagSize (CBC BlockCipher
bc CBCPadding
_) = Maybe Int
forall a. Maybe a
Nothing
cipherTagSize (CFB BlockCipher
bc Int
_) = Maybe Int
forall a. Maybe a
Nothing
cipherTagSize (XTS BlockCipher
bc) = Maybe Int
forall a. Maybe a
Nothing
cipherTagSize Cipher
chaCha20Poly1305 = Int -> Maybe Int
forall a. a -> Maybe a
Just Int
16
cipherTagSize (GCM BlockCipher128
_ Int
tsz) = Int -> Maybe Int
forall a. a -> Maybe a
Just Int
tsz
cipherTagSize (OCB BlockCipher128
_ Int
tsz) = Int -> Maybe Int
forall a. a -> Maybe a
Just Int
tsz
cipherTagSize (EAX BlockCipher
_ Int
tsz) = Int -> Maybe Int
forall a. a -> Maybe a
Just Int
tsz
cipherTagSize (SIV BlockCipher128
_) = Int -> Maybe Int
forall a. a -> Maybe a
Just Int
16
cipherTagSize (CCM BlockCipher128
_ Int
tsz Int
_) = Int -> Maybe Int
forall a. a -> Maybe a
Just Int
tsz
aeadTagSize :: AEAD -> Int
aeadTagSize :: AEAD -> Int
aeadTagSize = Maybe Int -> Int
forall a. HasCallStack => Maybe a -> a
fromJust (Maybe Int -> Int) -> (AEAD -> Maybe Int) -> AEAD -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Cipher -> Maybe Int
cipherTagSize (Cipher -> Maybe Int) -> (AEAD -> Cipher) -> AEAD -> Maybe Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AEAD -> Cipher
unAEAD
cipherUpdateGranularity :: Cipher -> Int
cipherUpdateGranularity :: Cipher -> Int
cipherUpdateGranularity (CBC BlockCipher
bc CBCPadding
CTS) = Int
2 Int -> Int -> Int
forall a. Num a => a -> a -> a
* BlockCipher -> Int
blockCipherBlockSize BlockCipher
bc
cipherUpdateGranularity (CBC BlockCipher
bc CBCPadding
_) = BlockCipher -> Int
blockCipherBlockSize BlockCipher
bc
cipherUpdateGranularity (CFB BlockCipher
bc Int
_) = BlockCipher -> Int
blockCipherBlockSize BlockCipher
bc
cipherUpdateGranularity (XTS BlockCipher
bc) = Int
2 Int -> Int -> Int
forall a. Num a => a -> a -> a
* BlockCipher -> Int
blockCipherBlockSize BlockCipher
bc
cipherUpdateGranularity Cipher
ChaCha20Poly1305 = Int
1
cipherUpdateGranularity (GCM BlockCipher128
bc128 Int
_) = BlockCipher -> Int
blockCipherBlockSize (BlockCipher128 -> BlockCipher
unBlockCipher128 BlockCipher128
bc128)
cipherUpdateGranularity (OCB BlockCipher128
bc128 Int
_) = BlockCipher -> Int
blockCipherBlockSize (BlockCipher128 -> BlockCipher
unBlockCipher128 BlockCipher128
bc128)
cipherUpdateGranularity (EAX BlockCipher
_ Int
_) = Int
1
cipherUpdateGranularity (SIV BlockCipher128
_) = Int
1
cipherUpdateGranularity (CCM BlockCipher128
_ Int
_ Int
_) = Int
1
cipherIdealUpdateGranularity :: Cipher -> Int
cipherIdealUpdateGranularity :: Cipher -> Int
cipherIdealUpdateGranularity Cipher
cipher = IO Int -> Int
forall a. IO a -> a
unsafePerformIO (IO Int -> Int) -> IO Int -> Int
forall a b. (a -> b) -> a -> b
$ do
Cipher
ctx <- CipherKey -> CipherInitFlags -> IO Cipher
Low.cipherInit (Cipher -> CipherKey
cipherName Cipher
cipher) CipherInitFlags
Low.Encrypt
Cipher -> IO Int
Low.cipherGetIdealUpdateGranularity Cipher
ctx
{-# NOINLINE cipherIdealUpdateGranularity #-}
cipherOutputLength :: Cipher -> CipherDirection -> Int -> Int
cipherOutputLength :: Cipher -> CipherDirection -> Int -> Int
cipherOutputLength Cipher
c CipherDirection
dir Int
n = IO Int -> Int
forall a. IO a -> a
unsafePerformIO (IO Int -> Int) -> IO Int -> Int
forall a b. (a -> b) -> a -> b
$ do
Cipher
ctx <- CipherKey -> CipherInitFlags -> IO Cipher
Low.cipherInit (Cipher -> CipherKey
cipherName Cipher
c) (CipherDirection -> CipherInitFlags
cipherDirectionFlags CipherDirection
dir)
Cipher -> Int -> IO Int
Low.cipherOutputLength Cipher
ctx Int
n
{-# NOINLINE cipherOutputLength #-}
cipherEncrypt :: Cipher -> CipherKey -> CipherNonce -> ByteString -> Ciphertext
cipherEncrypt :: Cipher -> CipherKey -> CipherKey -> CipherKey -> CipherKey
cipherEncrypt Cipher
c CipherKey
k CipherKey
n CipherKey
msg = IO CipherKey -> CipherKey
forall a. IO a -> a
unsafePerformIO (IO CipherKey -> CipherKey) -> IO CipherKey -> CipherKey
forall a b. (a -> b) -> a -> b
$ do
MutableCipher
ctx <- Cipher -> CipherDirection -> IO MutableCipher
forall (m :: * -> *).
MonadIO m =>
Cipher -> CipherDirection -> m MutableCipher
newCipher Cipher
c CipherDirection
CipherEncrypt
MutableCipher -> CipherKey -> IO ()
forall (m :: * -> *).
MonadIO m =>
MutableCipher -> CipherKey -> m ()
setCipherKey MutableCipher
ctx CipherKey
k
MutableCipher -> CipherKey -> IO ()
forall (m :: * -> *).
MonadIO m =>
MutableCipher -> CipherKey -> m ()
startCipher MutableCipher
ctx CipherKey
n
MutableCipher -> CipherKey -> IO CipherKey
forall (m :: * -> *).
MonadIO m =>
MutableCipher -> CipherKey -> m CipherKey
finalizeClearCipher MutableCipher
ctx CipherKey
msg
{-# NOINLINE cipherEncrypt #-}
cipherDecrypt :: Cipher -> CipherKey -> CipherNonce -> Ciphertext -> Maybe ByteString
cipherDecrypt :: Cipher -> CipherKey -> CipherKey -> CipherKey -> Maybe CipherKey
cipherDecrypt Cipher
c CipherKey
k CipherKey
n CipherKey
ct = IO (Maybe CipherKey) -> Maybe CipherKey
forall a. IO a -> a
unsafePerformIO (IO (Maybe CipherKey) -> Maybe CipherKey)
-> IO (Maybe CipherKey) -> Maybe CipherKey
forall a b. (a -> b) -> a -> b
$ do
MutableCipher
ctx <- Cipher -> CipherDirection -> IO MutableCipher
forall (m :: * -> *).
MonadIO m =>
Cipher -> CipherDirection -> m MutableCipher
newCipher Cipher
c CipherDirection
CipherDecrypt
MutableCipher -> CipherKey -> IO ()
forall (m :: * -> *).
MonadIO m =>
MutableCipher -> CipherKey -> m ()
setCipherKey MutableCipher
ctx CipherKey
k
MutableCipher -> CipherKey -> IO ()
forall (m :: * -> *).
MonadIO m =>
MutableCipher -> CipherKey -> m ()
startCipher MutableCipher
ctx CipherKey
n
CipherKey -> Maybe CipherKey
forall a. a -> Maybe a
Just (CipherKey -> Maybe CipherKey)
-> IO CipherKey -> IO (Maybe CipherKey)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> MutableCipher -> CipherKey -> IO CipherKey
forall (m :: * -> *).
MonadIO m =>
MutableCipher -> CipherKey -> m CipherKey
finalizeClearCipher MutableCipher
ctx CipherKey
ct
{-# NOINLINE cipherDecrypt #-}
cipherEncryptLazy :: Cipher -> CipherKey -> CipherNonce -> Lazy.ByteString -> LazyCiphertext
cipherEncryptLazy :: Cipher -> CipherKey -> CipherKey -> ByteString -> ByteString
cipherEncryptLazy = Cipher -> CipherKey -> CipherKey -> ByteString -> ByteString
forall a. HasCallStack => a
undefined
cipherDecryptLazy :: Cipher -> CipherKey -> CipherNonce -> LazyCiphertext -> Maybe Lazy.ByteString
cipherDecryptLazy :: Cipher -> CipherKey -> CipherKey -> ByteString -> Maybe ByteString
cipherDecryptLazy = Cipher -> CipherKey -> CipherKey -> ByteString -> Maybe ByteString
forall a. HasCallStack => a
undefined
aeadEncrypt :: AEAD -> CipherKey -> CipherNonce -> AEADAssociatedData -> ByteString -> Ciphertext
aeadEncrypt :: AEAD
-> CipherKey -> CipherKey -> CipherKey -> CipherKey -> CipherKey
aeadEncrypt AEAD
c CipherKey
k CipherKey
n CipherKey
ad CipherKey
msg = IO CipherKey -> CipherKey
forall a. IO a -> a
unsafePerformIO (IO CipherKey -> CipherKey) -> IO CipherKey -> CipherKey
forall a b. (a -> b) -> a -> b
$ do
MutableCipher
ctx <- Cipher -> CipherDirection -> IO MutableCipher
forall (m :: * -> *).
MonadIO m =>
Cipher -> CipherDirection -> m MutableCipher
newCipher (AEAD -> Cipher
unAEAD AEAD
c) CipherDirection
CipherEncrypt
MutableCipher -> CipherKey -> IO ()
forall (m :: * -> *).
MonadIO m =>
MutableCipher -> CipherKey -> m ()
setCipherKey MutableCipher
ctx CipherKey
k
MutableCipher -> CipherKey -> IO ()
forall (m :: * -> *).
MonadIO m =>
MutableCipher -> CipherKey -> m ()
setAEADAssociatedData MutableCipher
ctx CipherKey
ad
MutableCipher -> CipherKey -> IO ()
forall (m :: * -> *).
MonadIO m =>
MutableCipher -> CipherKey -> m ()
startCipher MutableCipher
ctx CipherKey
n
MutableCipher -> CipherKey -> IO CipherKey
forall (m :: * -> *).
MonadIO m =>
MutableCipher -> CipherKey -> m CipherKey
finalizeClearCipher MutableCipher
ctx CipherKey
msg
{-# NOINLINE aeadEncrypt #-}
aeadDecrypt :: AEAD -> CipherKey -> CipherNonce -> AEADAssociatedData -> Ciphertext -> Maybe ByteString
aeadDecrypt :: AEAD
-> CipherKey
-> CipherKey
-> CipherKey
-> CipherKey
-> Maybe CipherKey
aeadDecrypt AEAD
c CipherKey
k CipherKey
n CipherKey
ad CipherKey
ct = IO (Maybe CipherKey) -> Maybe CipherKey
forall a. IO a -> a
unsafePerformIO (IO (Maybe CipherKey) -> Maybe CipherKey)
-> IO (Maybe CipherKey) -> Maybe CipherKey
forall a b. (a -> b) -> a -> b
$ do
MutableCipher
ctx <- Cipher -> CipherDirection -> IO MutableCipher
forall (m :: * -> *).
MonadIO m =>
Cipher -> CipherDirection -> m MutableCipher
newCipher (AEAD -> Cipher
unAEAD AEAD
c) CipherDirection
CipherDecrypt
MutableCipher -> CipherKey -> IO ()
forall (m :: * -> *).
MonadIO m =>
MutableCipher -> CipherKey -> m ()
setCipherKey MutableCipher
ctx CipherKey
k
MutableCipher -> CipherKey -> IO ()
forall (m :: * -> *).
MonadIO m =>
MutableCipher -> CipherKey -> m ()
setAEADAssociatedData MutableCipher
ctx CipherKey
ad
MutableCipher -> CipherKey -> IO ()
forall (m :: * -> *).
MonadIO m =>
MutableCipher -> CipherKey -> m ()
startCipher MutableCipher
ctx CipherKey
n
CipherKey -> Maybe CipherKey
forall a. a -> Maybe a
Just (CipherKey -> Maybe CipherKey)
-> IO CipherKey -> IO (Maybe CipherKey)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> MutableCipher -> CipherKey -> IO CipherKey
forall (m :: * -> *).
MonadIO m =>
MutableCipher -> CipherKey -> m CipherKey
finalizeClearCipher MutableCipher
ctx CipherKey
ct
{-# NOINLINE aeadDecrypt #-}
data MutableCipher = MkMutableCipher
{ MutableCipher -> Cipher
mutableCipherType :: Cipher
, MutableCipher -> CipherDirection
mutableCipherDirection :: CipherDirection
, MutableCipher -> Cipher
mutableCipherCtx :: Low.Cipher
}
destroyCipher :: (MonadIO m) => MutableCipher -> m ()
destroyCipher :: forall (m :: * -> *). MonadIO m => MutableCipher -> m ()
destroyCipher = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ())
-> (MutableCipher -> IO ()) -> MutableCipher -> m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Cipher -> IO ()
Low.cipherDestroy (Cipher -> IO ())
-> (MutableCipher -> Cipher) -> MutableCipher -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MutableCipher -> Cipher
mutableCipherCtx
data CipherDirection
= CipherEncrypt
| CipherDecrypt
deriving (CipherDirection -> CipherDirection -> Bool
(CipherDirection -> CipherDirection -> Bool)
-> (CipherDirection -> CipherDirection -> Bool)
-> Eq CipherDirection
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CipherDirection -> CipherDirection -> Bool
== :: CipherDirection -> CipherDirection -> Bool
$c/= :: CipherDirection -> CipherDirection -> Bool
/= :: CipherDirection -> CipherDirection -> Bool
Eq, Eq CipherDirection
Eq CipherDirection =>
(CipherDirection -> CipherDirection -> Ordering)
-> (CipherDirection -> CipherDirection -> Bool)
-> (CipherDirection -> CipherDirection -> Bool)
-> (CipherDirection -> CipherDirection -> Bool)
-> (CipherDirection -> CipherDirection -> Bool)
-> (CipherDirection -> CipherDirection -> CipherDirection)
-> (CipherDirection -> CipherDirection -> CipherDirection)
-> Ord CipherDirection
CipherDirection -> CipherDirection -> Bool
CipherDirection -> CipherDirection -> Ordering
CipherDirection -> CipherDirection -> CipherDirection
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 :: CipherDirection -> CipherDirection -> Ordering
compare :: CipherDirection -> CipherDirection -> Ordering
$c< :: CipherDirection -> CipherDirection -> Bool
< :: CipherDirection -> CipherDirection -> Bool
$c<= :: CipherDirection -> CipherDirection -> Bool
<= :: CipherDirection -> CipherDirection -> Bool
$c> :: CipherDirection -> CipherDirection -> Bool
> :: CipherDirection -> CipherDirection -> Bool
$c>= :: CipherDirection -> CipherDirection -> Bool
>= :: CipherDirection -> CipherDirection -> Bool
$cmax :: CipherDirection -> CipherDirection -> CipherDirection
max :: CipherDirection -> CipherDirection -> CipherDirection
$cmin :: CipherDirection -> CipherDirection -> CipherDirection
min :: CipherDirection -> CipherDirection -> CipherDirection
Ord, Int -> CipherDirection -> ShowS
[CipherDirection] -> ShowS
CipherDirection -> String
(Int -> CipherDirection -> ShowS)
-> (CipherDirection -> String)
-> ([CipherDirection] -> ShowS)
-> Show CipherDirection
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CipherDirection -> ShowS
showsPrec :: Int -> CipherDirection -> ShowS
$cshow :: CipherDirection -> String
show :: CipherDirection -> String
$cshowList :: [CipherDirection] -> ShowS
showList :: [CipherDirection] -> ShowS
Show)
cipherDirectionFlags :: CipherDirection -> Low.CipherInitFlags
cipherDirectionFlags :: CipherDirection -> CipherInitFlags
cipherDirectionFlags CipherDirection
CipherEncrypt = CipherInitFlags
Low.Encrypt
cipherDirectionFlags CipherDirection
CipherDecrypt = CipherInitFlags
Low.Decrypt
data CipherUpdate
= CipherUpdate
| CipherFinal
deriving (CipherUpdate -> CipherUpdate -> Bool
(CipherUpdate -> CipherUpdate -> Bool)
-> (CipherUpdate -> CipherUpdate -> Bool) -> Eq CipherUpdate
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CipherUpdate -> CipherUpdate -> Bool
== :: CipherUpdate -> CipherUpdate -> Bool
$c/= :: CipherUpdate -> CipherUpdate -> Bool
/= :: CipherUpdate -> CipherUpdate -> Bool
Eq, Eq CipherUpdate
Eq CipherUpdate =>
(CipherUpdate -> CipherUpdate -> Ordering)
-> (CipherUpdate -> CipherUpdate -> Bool)
-> (CipherUpdate -> CipherUpdate -> Bool)
-> (CipherUpdate -> CipherUpdate -> Bool)
-> (CipherUpdate -> CipherUpdate -> Bool)
-> (CipherUpdate -> CipherUpdate -> CipherUpdate)
-> (CipherUpdate -> CipherUpdate -> CipherUpdate)
-> Ord CipherUpdate
CipherUpdate -> CipherUpdate -> Bool
CipherUpdate -> CipherUpdate -> Ordering
CipherUpdate -> CipherUpdate -> CipherUpdate
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 :: CipherUpdate -> CipherUpdate -> Ordering
compare :: CipherUpdate -> CipherUpdate -> Ordering
$c< :: CipherUpdate -> CipherUpdate -> Bool
< :: CipherUpdate -> CipherUpdate -> Bool
$c<= :: CipherUpdate -> CipherUpdate -> Bool
<= :: CipherUpdate -> CipherUpdate -> Bool
$c> :: CipherUpdate -> CipherUpdate -> Bool
> :: CipherUpdate -> CipherUpdate -> Bool
$c>= :: CipherUpdate -> CipherUpdate -> Bool
>= :: CipherUpdate -> CipherUpdate -> Bool
$cmax :: CipherUpdate -> CipherUpdate -> CipherUpdate
max :: CipherUpdate -> CipherUpdate -> CipherUpdate
$cmin :: CipherUpdate -> CipherUpdate -> CipherUpdate
min :: CipherUpdate -> CipherUpdate -> CipherUpdate
Ord, Int -> CipherUpdate -> ShowS
[CipherUpdate] -> ShowS
CipherUpdate -> String
(Int -> CipherUpdate -> ShowS)
-> (CipherUpdate -> String)
-> ([CipherUpdate] -> ShowS)
-> Show CipherUpdate
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CipherUpdate -> ShowS
showsPrec :: Int -> CipherUpdate -> ShowS
$cshow :: CipherUpdate -> String
show :: CipherUpdate -> String
$cshowList :: [CipherUpdate] -> ShowS
showList :: [CipherUpdate] -> ShowS
Show)
cipherUpdateFlags :: CipherUpdate -> Low.CipherUpdateFlags
cipherUpdateFlags :: CipherUpdate -> Int
cipherUpdateFlags CipherUpdate
CipherUpdate = Int
Low.CipherUpdate
cipherUpdateFlags CipherUpdate
CipherFinal = Int
Low.CipherFinal
newCipher
:: (MonadIO m)
=> Cipher
-> CipherDirection
-> m MutableCipher
newCipher :: forall (m :: * -> *).
MonadIO m =>
Cipher -> CipherDirection -> m MutableCipher
newCipher Cipher
c CipherDirection
dir = do
Cipher
ctx <- IO Cipher -> m Cipher
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Cipher -> m Cipher) -> IO Cipher -> m Cipher
forall a b. (a -> b) -> a -> b
$ CipherKey -> CipherInitFlags -> IO Cipher
Low.cipherInit (Cipher -> CipherKey
cipherName Cipher
c) (CipherDirection -> CipherInitFlags
cipherDirectionFlags CipherDirection
dir)
MutableCipher -> m MutableCipher
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (MutableCipher -> m MutableCipher)
-> MutableCipher -> m MutableCipher
forall a b. (a -> b) -> a -> b
$ Cipher -> CipherDirection -> Cipher -> MutableCipher
MkMutableCipher Cipher
c CipherDirection
dir Cipher
ctx
getCipherName :: (MonadIO m) => MutableCipher -> m ByteString
getCipherName :: forall (m :: * -> *). MonadIO m => MutableCipher -> m CipherKey
getCipherName = IO CipherKey -> m CipherKey
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO CipherKey -> m CipherKey)
-> (MutableCipher -> IO CipherKey) -> MutableCipher -> m CipherKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Cipher -> IO CipherKey
Low.cipherName (Cipher -> IO CipherKey)
-> (MutableCipher -> Cipher) -> MutableCipher -> IO CipherKey
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MutableCipher -> Cipher
mutableCipherCtx
getCipherKeySpec :: (MonadIO m) => MutableCipher -> m CipherKeySpec
getCipherKeySpec :: forall (m :: * -> *). MonadIO m => MutableCipher -> m KeySpec
getCipherKeySpec MutableCipher
c = 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
$ Cipher -> IO (Int, Int, Int)
Low.cipherGetKeyspec (MutableCipher -> Cipher
mutableCipherCtx MutableCipher
c)
KeySpec -> m KeySpec
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (KeySpec -> m KeySpec) -> KeySpec -> m KeySpec
forall a b. (a -> b) -> a -> b
$ Int -> Int -> Int -> KeySpec
keySpec Int
mn Int
mx Int
md
getCipherDefaultNonceSize :: (MonadIO m) => MutableCipher -> m Int
getCipherDefaultNonceSize :: forall (m :: * -> *). MonadIO m => MutableCipher -> m Int
getCipherDefaultNonceSize = IO Int -> m Int
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int -> m Int)
-> (MutableCipher -> IO Int) -> MutableCipher -> m Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Cipher -> IO Int
Low.cipherGetDefaultNonceLength (Cipher -> IO Int)
-> (MutableCipher -> Cipher) -> MutableCipher -> IO Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MutableCipher -> Cipher
mutableCipherCtx
getCipherNonceSizeIsValid :: (MonadIO m) => MutableCipher -> Int -> m Bool
getCipherNonceSizeIsValid :: forall (m :: * -> *). MonadIO m => MutableCipher -> Int -> m Bool
getCipherNonceSizeIsValid MutableCipher
c Int
n = IO Bool -> m Bool
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Bool -> m Bool) -> IO Bool -> m Bool
forall a b. (a -> b) -> a -> b
$ Cipher -> Int -> IO Bool
Low.cipherValidNonceLength (MutableCipher -> Cipher
mutableCipherCtx MutableCipher
c) Int
n
getCipherTagSize :: (MonadIO m) => MutableCipher -> m Int
getCipherTagSize :: forall (m :: * -> *). MonadIO m => MutableCipher -> m Int
getCipherTagSize = IO Int -> m Int
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int -> m Int)
-> (MutableCipher -> IO Int) -> MutableCipher -> m Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Cipher -> IO Int
Low.cipherGetTagLength (Cipher -> IO Int)
-> (MutableCipher -> Cipher) -> MutableCipher -> IO Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MutableCipher -> Cipher
mutableCipherCtx
getCipherUpdateGranularity :: (MonadIO m) => MutableCipher -> m Int
getCipherUpdateGranularity :: forall (m :: * -> *). MonadIO m => MutableCipher -> m Int
getCipherUpdateGranularity = IO Int -> m Int
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int -> m Int)
-> (MutableCipher -> IO Int) -> MutableCipher -> m Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Cipher -> IO Int
Low.cipherGetUpdateGranularity (Cipher -> IO Int)
-> (MutableCipher -> Cipher) -> MutableCipher -> IO Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MutableCipher -> Cipher
mutableCipherCtx
getCipherIdealUpdateGranularity :: (MonadIO m) => MutableCipher -> m Int
getCipherIdealUpdateGranularity :: forall (m :: * -> *). MonadIO m => MutableCipher -> m Int
getCipherIdealUpdateGranularity = IO Int -> m Int
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int -> m Int)
-> (MutableCipher -> IO Int) -> MutableCipher -> m Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Cipher -> IO Int
Low.cipherGetIdealUpdateGranularity (Cipher -> IO Int)
-> (MutableCipher -> Cipher) -> MutableCipher -> IO Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MutableCipher -> Cipher
mutableCipherCtx
getCipherEstimateOutputLength :: (MonadIO m) => MutableCipher -> Int -> m Int
getCipherEstimateOutputLength :: forall (m :: * -> *). MonadIO m => MutableCipher -> Int -> m Int
getCipherEstimateOutputLength MutableCipher
ctx Int
input = do
Int
o <- MutableCipher -> Int -> m Int
forall (m :: * -> *). MonadIO m => MutableCipher -> Int -> m Int
getCipherOutputLength MutableCipher
ctx Int
input
Int
u <- MutableCipher -> m Int
forall (m :: * -> *). MonadIO m => MutableCipher -> m Int
getCipherUpdateGranularity MutableCipher
ctx
Int
t <- MutableCipher -> m Int
forall (m :: * -> *). MonadIO m => MutableCipher -> m Int
getCipherTagSize MutableCipher
ctx
if MutableCipher -> CipherDirection
mutableCipherDirection MutableCipher
ctx CipherDirection -> CipherDirection -> Bool
forall a. Eq a => a -> a -> Bool
== CipherDirection
CipherEncrypt
then Int -> m Int
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Int
o Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
u Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
t)
else Int -> m Int
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Int
o Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
u Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
t)
{-# WARNING getCipherOutputLength "Needs to be confirmed accurate, use getCipherEstimateOutputLength" #-}
getCipherOutputLength :: (MonadIO m) => MutableCipher -> Int -> m Int
getCipherOutputLength :: forall (m :: * -> *). MonadIO m => MutableCipher -> Int -> m Int
getCipherOutputLength MutableCipher
c Int
n = IO Int -> m Int
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO Int -> m Int) -> IO Int -> m Int
forall a b. (a -> b) -> a -> b
$ Cipher -> Int -> IO Int
Low.cipherOutputLength (MutableCipher -> Cipher
mutableCipherCtx MutableCipher
c) Int
n
setCipherKey :: (MonadIO m) => MutableCipher -> CipherKey -> m ()
setCipherKey :: forall (m :: * -> *).
MonadIO m =>
MutableCipher -> CipherKey -> m ()
setCipherKey MutableCipher
c CipherKey
key = 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
$ Cipher -> CipherKey -> IO ()
Low.cipherSetKey (MutableCipher -> Cipher
mutableCipherCtx MutableCipher
c) CipherKey
key
setAEADAssociatedData :: (MonadIO m) => MutableCipher -> ByteString -> m ()
setAEADAssociatedData :: forall (m :: * -> *).
MonadIO m =>
MutableCipher -> CipherKey -> m ()
setAEADAssociatedData MutableCipher
c CipherKey
ad = 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
$ Cipher -> CipherKey -> IO ()
Low.cipherSetAssociatedData (MutableCipher -> Cipher
mutableCipherCtx MutableCipher
c) CipherKey
ad
clearCipher :: (MonadIO m) => MutableCipher -> m ()
clearCipher :: forall (m :: * -> *). MonadIO m => MutableCipher -> m ()
clearCipher = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ())
-> (MutableCipher -> IO ()) -> MutableCipher -> m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Cipher -> IO ()
Low.cipherClear (Cipher -> IO ())
-> (MutableCipher -> Cipher) -> MutableCipher -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MutableCipher -> Cipher
mutableCipherCtx
resetCipher :: (MonadIO m) => MutableCipher -> m ()
resetCipher :: forall (m :: * -> *). MonadIO m => MutableCipher -> m ()
resetCipher = IO () -> m ()
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ())
-> (MutableCipher -> IO ()) -> MutableCipher -> m ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Cipher -> IO ()
Low.cipherReset (Cipher -> IO ())
-> (MutableCipher -> Cipher) -> MutableCipher -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MutableCipher -> Cipher
mutableCipherCtx
startCipher :: (MonadIO m) => MutableCipher -> CipherNonce -> m ()
startCipher :: forall (m :: * -> *).
MonadIO m =>
MutableCipher -> CipherKey -> m ()
startCipher MutableCipher
c CipherKey
n = 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
$ Cipher -> CipherKey -> IO ()
Low.cipherStart (MutableCipher -> Cipher
mutableCipherCtx MutableCipher
c) CipherKey
n
updateCipher
:: (MonadIO m)
=> MutableCipher
-> ByteString
-> m (Int, ByteString)
updateCipher :: forall (m :: * -> *).
MonadIO m =>
MutableCipher -> CipherKey -> m (Int, CipherKey)
updateCipher MutableCipher
c CipherKey
msg = do
Int
o <- MutableCipher -> Int -> m Int
forall (m :: * -> *). MonadIO m => MutableCipher -> Int -> m Int
getCipherOutputLength MutableCipher
c (CipherKey -> Int
ByteString.length CipherKey
msg)
IO (Int, CipherKey) -> m (Int, CipherKey)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Int, CipherKey) -> m (Int, CipherKey))
-> IO (Int, CipherKey) -> m (Int, CipherKey)
forall a b. (a -> b) -> a -> b
$ Cipher -> Int -> Int -> CipherKey -> IO (Int, CipherKey)
Low.cipherUpdate (MutableCipher -> Cipher
mutableCipherCtx MutableCipher
c) (CipherUpdate -> Int
cipherUpdateFlags CipherUpdate
CipherUpdate) Int
o CipherKey
msg
finalizeCipher
:: (MonadIO m)
=> MutableCipher
-> ByteString
-> m ByteString
finalizeCipher :: forall (m :: * -> *).
MonadIO m =>
MutableCipher -> CipherKey -> m CipherKey
finalizeCipher MutableCipher
c CipherKey
msg = do
Int
o <- MutableCipher -> Int -> m Int
forall (m :: * -> *). MonadIO m => MutableCipher -> Int -> m Int
getCipherOutputLength MutableCipher
c (CipherKey -> Int
ByteString.length CipherKey
msg)
(Int
_,CipherKey
out) <- IO (Int, CipherKey) -> m (Int, CipherKey)
forall a. IO a -> m a
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (Int, CipherKey) -> m (Int, CipherKey))
-> IO (Int, CipherKey) -> m (Int, CipherKey)
forall a b. (a -> b) -> a -> b
$ Cipher -> Int -> Int -> CipherKey -> IO (Int, CipherKey)
Low.cipherUpdate (MutableCipher -> Cipher
mutableCipherCtx MutableCipher
c) (CipherUpdate -> Int
cipherUpdateFlags CipherUpdate
CipherFinal) Int
o CipherKey
msg
CipherKey -> m CipherKey
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return CipherKey
out
finalizeResetCipher
:: (MonadIO m)
=> MutableCipher
-> ByteString
-> m ByteString
finalizeResetCipher :: forall (m :: * -> *).
MonadIO m =>
MutableCipher -> CipherKey -> m CipherKey
finalizeResetCipher MutableCipher
c CipherKey
msg = MutableCipher -> CipherKey -> m CipherKey
forall (m :: * -> *).
MonadIO m =>
MutableCipher -> CipherKey -> m CipherKey
finalizeCipher MutableCipher
c CipherKey
msg m CipherKey -> m () -> m CipherKey
forall a b. m a -> m b -> m a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* MutableCipher -> m ()
forall (m :: * -> *). MonadIO m => MutableCipher -> m ()
resetCipher MutableCipher
c
finalizeClearCipher
:: (MonadIO m)
=> MutableCipher
-> ByteString
-> m ByteString
finalizeClearCipher :: forall (m :: * -> *).
MonadIO m =>
MutableCipher -> CipherKey -> m CipherKey
finalizeClearCipher MutableCipher
c CipherKey
msg = MutableCipher -> CipherKey -> m CipherKey
forall (m :: * -> *).
MonadIO m =>
MutableCipher -> CipherKey -> m CipherKey
finalizeCipher MutableCipher
c CipherKey
msg m CipherKey -> m () -> m CipherKey
forall a b. m a -> m b -> m a
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* MutableCipher -> m ()
forall (m :: * -> *). MonadIO m => MutableCipher -> m ()
clearCipher MutableCipher
c
cbc :: BlockCipher -> Cipher
cbc :: BlockCipher -> Cipher
cbc BlockCipher
bc = BlockCipher -> CBCPadding -> Cipher
cbcWith BlockCipher
bc CBCPadding
PKCS7
cbcWith :: BlockCipher -> CBCPadding -> Cipher
cbcWith :: BlockCipher -> CBCPadding -> Cipher
cbcWith = BlockCipher -> CBCPadding -> Cipher
CBC
cfb :: BlockCipher -> Cipher
cfb :: BlockCipher -> Cipher
cfb BlockCipher
bc = BlockCipher -> Int -> Cipher
cfbWith BlockCipher
bc (Int
8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* BlockCipher -> Int
blockCipherBlockSize BlockCipher
bc)
cfbWith :: BlockCipher -> Int -> Cipher
cfbWith :: BlockCipher -> Int -> Cipher
cfbWith = BlockCipher -> Int -> Cipher
CFB
xts :: BlockCipher -> Cipher
xts :: BlockCipher -> Cipher
xts = BlockCipher -> Cipher
XTS
chaCha20Poly1305 :: Cipher
chaCha20Poly1305 :: Cipher
chaCha20Poly1305 = Cipher
ChaCha20Poly1305
gcm :: BlockCipher128 -> Cipher
gcm :: BlockCipher128 -> Cipher
gcm BlockCipher128
bc = BlockCipher128 -> Int -> Cipher
gcmWith BlockCipher128
bc Int
16
gcmWith :: BlockCipher128 -> Int -> Cipher
gcmWith :: BlockCipher128 -> Int -> Cipher
gcmWith = BlockCipher128 -> Int -> Cipher
GCM
ocb :: BlockCipher128 -> Cipher
ocb :: BlockCipher128 -> Cipher
ocb BlockCipher128
bc = BlockCipher128 -> Int -> Cipher
ocbWith BlockCipher128
bc Int
16
ocbWith :: BlockCipher128 -> Int -> Cipher
ocbWith :: BlockCipher128 -> Int -> Cipher
ocbWith = BlockCipher128 -> Int -> Cipher
OCB
eax :: BlockCipher -> Cipher
eax :: BlockCipher -> Cipher
eax BlockCipher
bc = BlockCipher -> Int -> Cipher
eaxWith BlockCipher
bc (BlockCipher -> Int
blockCipherBlockSize BlockCipher
bc)
eaxWith :: BlockCipher -> Int -> Cipher
eaxWith :: BlockCipher -> Int -> Cipher
eaxWith = BlockCipher -> Int -> Cipher
EAX
siv :: BlockCipher128 -> Cipher
siv :: BlockCipher128 -> Cipher
siv = BlockCipher128 -> Cipher
SIV
ccm :: BlockCipher128 -> Cipher
ccm :: BlockCipher128 -> Cipher
ccm BlockCipher128
bc = BlockCipher128 -> Int -> Int -> Cipher
ccmWith BlockCipher128
bc Int
16 Int
3
ccmWith :: BlockCipher128 -> Int -> Int -> Cipher
ccmWith :: BlockCipher128 -> Int -> Int -> Cipher
ccmWith = BlockCipher128 -> Int -> Int -> Cipher
CCM