module Botan.BlockCipher.Blowfish
( Blowfish(..)
, BlowfishSecretKey(..)
, pattern BlowfishSecretKey
, getBlowfishSecretKey
, BlowfishCiphertext(..)
, blowfishEncrypt
, blowfishDecrypt
, blowfishEncryptLazy
, blowfishDecryptLazy
) where
import qualified Data.ByteString as ByteString
import qualified Data.ByteString.Lazy as Lazy
import qualified Data.Text as Text
import qualified Botan.BlockCipher as Botan
import qualified Botan.Utility as Botan
import Botan.Prelude hiding (Ciphertext, LazyCiphertext)
import Botan.BlockCipher.Class
import Botan.Types.Class
import Botan.RNG
data Blowfish
newtype instance SecretKey Blowfish = MkBlowfishSecretKey GSecretKey
deriving newtype (SecretKey Blowfish -> SecretKey Blowfish -> Bool
(SecretKey Blowfish -> SecretKey Blowfish -> Bool)
-> (SecretKey Blowfish -> SecretKey Blowfish -> Bool)
-> Eq (SecretKey Blowfish)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SecretKey Blowfish -> SecretKey Blowfish -> Bool
== :: SecretKey Blowfish -> SecretKey Blowfish -> Bool
$c/= :: SecretKey Blowfish -> SecretKey Blowfish -> Bool
/= :: SecretKey Blowfish -> SecretKey Blowfish -> Bool
Eq, Eq (SecretKey Blowfish)
Eq (SecretKey Blowfish) =>
(SecretKey Blowfish -> SecretKey Blowfish -> Ordering)
-> (SecretKey Blowfish -> SecretKey Blowfish -> Bool)
-> (SecretKey Blowfish -> SecretKey Blowfish -> Bool)
-> (SecretKey Blowfish -> SecretKey Blowfish -> Bool)
-> (SecretKey Blowfish -> SecretKey Blowfish -> Bool)
-> (SecretKey Blowfish -> SecretKey Blowfish -> SecretKey Blowfish)
-> (SecretKey Blowfish -> SecretKey Blowfish -> SecretKey Blowfish)
-> Ord (SecretKey Blowfish)
SecretKey Blowfish -> SecretKey Blowfish -> Bool
SecretKey Blowfish -> SecretKey Blowfish -> Ordering
SecretKey Blowfish -> SecretKey Blowfish -> SecretKey Blowfish
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 :: SecretKey Blowfish -> SecretKey Blowfish -> Ordering
compare :: SecretKey Blowfish -> SecretKey Blowfish -> Ordering
$c< :: SecretKey Blowfish -> SecretKey Blowfish -> Bool
< :: SecretKey Blowfish -> SecretKey Blowfish -> Bool
$c<= :: SecretKey Blowfish -> SecretKey Blowfish -> Bool
<= :: SecretKey Blowfish -> SecretKey Blowfish -> Bool
$c> :: SecretKey Blowfish -> SecretKey Blowfish -> Bool
> :: SecretKey Blowfish -> SecretKey Blowfish -> Bool
$c>= :: SecretKey Blowfish -> SecretKey Blowfish -> Bool
>= :: SecretKey Blowfish -> SecretKey Blowfish -> Bool
$cmax :: SecretKey Blowfish -> SecretKey Blowfish -> SecretKey Blowfish
max :: SecretKey Blowfish -> SecretKey Blowfish -> SecretKey Blowfish
$cmin :: SecretKey Blowfish -> SecretKey Blowfish -> SecretKey Blowfish
min :: SecretKey Blowfish -> SecretKey Blowfish -> SecretKey Blowfish
Ord, Int -> SecretKey Blowfish -> ShowS
[SecretKey Blowfish] -> ShowS
SecretKey Blowfish -> String
(Int -> SecretKey Blowfish -> ShowS)
-> (SecretKey Blowfish -> String)
-> ([SecretKey Blowfish] -> ShowS)
-> Show (SecretKey Blowfish)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SecretKey Blowfish -> ShowS
showsPrec :: Int -> SecretKey Blowfish -> ShowS
$cshow :: SecretKey Blowfish -> String
show :: SecretKey Blowfish -> String
$cshowList :: [SecretKey Blowfish] -> ShowS
showList :: [SecretKey Blowfish] -> ShowS
Show, ByteString -> Maybe (SecretKey Blowfish)
SecretKey Blowfish -> ByteString
(SecretKey Blowfish -> ByteString)
-> (ByteString -> Maybe (SecretKey Blowfish))
-> Encodable (SecretKey Blowfish)
forall a.
(a -> ByteString) -> (ByteString -> Maybe a) -> Encodable a
$cencode :: SecretKey Blowfish -> ByteString
encode :: SecretKey Blowfish -> ByteString
$cdecode :: ByteString -> Maybe (SecretKey Blowfish)
decode :: ByteString -> Maybe (SecretKey Blowfish)
Encodable)
pattern BlowfishSecretKey :: ByteString -> SecretKey Blowfish
pattern $mBlowfishSecretKey :: forall {r}.
SecretKey Blowfish -> (ByteString -> r) -> ((# #) -> r) -> r
$bBlowfishSecretKey :: ByteString -> SecretKey Blowfish
BlowfishSecretKey bytes = MkBlowfishSecretKey (MkGSecretKey bytes)
getBlowfishSecretKey :: SecretKey Blowfish -> ByteString
getBlowfishSecretKey :: SecretKey Blowfish -> ByteString
getBlowfishSecretKey (BlowfishSecretKey ByteString
bs) = ByteString
bs
type BlowfishSecretKey = SecretKey Blowfish
newtype instance Ciphertext Blowfish = MkBlowfishCiphertext GCiphertext
deriving newtype (Ciphertext Blowfish -> Ciphertext Blowfish -> Bool
(Ciphertext Blowfish -> Ciphertext Blowfish -> Bool)
-> (Ciphertext Blowfish -> Ciphertext Blowfish -> Bool)
-> Eq (Ciphertext Blowfish)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Ciphertext Blowfish -> Ciphertext Blowfish -> Bool
== :: Ciphertext Blowfish -> Ciphertext Blowfish -> Bool
$c/= :: Ciphertext Blowfish -> Ciphertext Blowfish -> Bool
/= :: Ciphertext Blowfish -> Ciphertext Blowfish -> Bool
Eq, Eq (Ciphertext Blowfish)
Eq (Ciphertext Blowfish) =>
(Ciphertext Blowfish -> Ciphertext Blowfish -> Ordering)
-> (Ciphertext Blowfish -> Ciphertext Blowfish -> Bool)
-> (Ciphertext Blowfish -> Ciphertext Blowfish -> Bool)
-> (Ciphertext Blowfish -> Ciphertext Blowfish -> Bool)
-> (Ciphertext Blowfish -> Ciphertext Blowfish -> Bool)
-> (Ciphertext Blowfish
-> Ciphertext Blowfish -> Ciphertext Blowfish)
-> (Ciphertext Blowfish
-> Ciphertext Blowfish -> Ciphertext Blowfish)
-> Ord (Ciphertext Blowfish)
Ciphertext Blowfish -> Ciphertext Blowfish -> Bool
Ciphertext Blowfish -> Ciphertext Blowfish -> Ordering
Ciphertext Blowfish -> Ciphertext Blowfish -> Ciphertext Blowfish
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 :: Ciphertext Blowfish -> Ciphertext Blowfish -> Ordering
compare :: Ciphertext Blowfish -> Ciphertext Blowfish -> Ordering
$c< :: Ciphertext Blowfish -> Ciphertext Blowfish -> Bool
< :: Ciphertext Blowfish -> Ciphertext Blowfish -> Bool
$c<= :: Ciphertext Blowfish -> Ciphertext Blowfish -> Bool
<= :: Ciphertext Blowfish -> Ciphertext Blowfish -> Bool
$c> :: Ciphertext Blowfish -> Ciphertext Blowfish -> Bool
> :: Ciphertext Blowfish -> Ciphertext Blowfish -> Bool
$c>= :: Ciphertext Blowfish -> Ciphertext Blowfish -> Bool
>= :: Ciphertext Blowfish -> Ciphertext Blowfish -> Bool
$cmax :: Ciphertext Blowfish -> Ciphertext Blowfish -> Ciphertext Blowfish
max :: Ciphertext Blowfish -> Ciphertext Blowfish -> Ciphertext Blowfish
$cmin :: Ciphertext Blowfish -> Ciphertext Blowfish -> Ciphertext Blowfish
min :: Ciphertext Blowfish -> Ciphertext Blowfish -> Ciphertext Blowfish
Ord, Int -> Ciphertext Blowfish -> ShowS
[Ciphertext Blowfish] -> ShowS
Ciphertext Blowfish -> String
(Int -> Ciphertext Blowfish -> ShowS)
-> (Ciphertext Blowfish -> String)
-> ([Ciphertext Blowfish] -> ShowS)
-> Show (Ciphertext Blowfish)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Ciphertext Blowfish -> ShowS
showsPrec :: Int -> Ciphertext Blowfish -> ShowS
$cshow :: Ciphertext Blowfish -> String
show :: Ciphertext Blowfish -> String
$cshowList :: [Ciphertext Blowfish] -> ShowS
showList :: [Ciphertext Blowfish] -> ShowS
Show, ByteString -> Maybe (Ciphertext Blowfish)
Ciphertext Blowfish -> ByteString
(Ciphertext Blowfish -> ByteString)
-> (ByteString -> Maybe (Ciphertext Blowfish))
-> Encodable (Ciphertext Blowfish)
forall a.
(a -> ByteString) -> (ByteString -> Maybe a) -> Encodable a
$cencode :: Ciphertext Blowfish -> ByteString
encode :: Ciphertext Blowfish -> ByteString
$cdecode :: ByteString -> Maybe (Ciphertext Blowfish)
decode :: ByteString -> Maybe (Ciphertext Blowfish)
Encodable)
pattern BlowfishCiphertext :: ByteString -> Ciphertext Blowfish
pattern $mBlowfishCiphertext :: forall {r}.
Ciphertext Blowfish -> (ByteString -> r) -> ((# #) -> r) -> r
$bBlowfishCiphertext :: ByteString -> Ciphertext Blowfish
BlowfishCiphertext bs = MkBlowfishCiphertext (MkGCiphertext bs)
getBlowfishCiphertext :: Ciphertext Blowfish -> ByteString
getBlowfishCiphertext :: Ciphertext Blowfish -> ByteString
getBlowfishCiphertext (BlowfishCiphertext ByteString
bs) = ByteString
bs
type BlowfishCiphertext = Ciphertext Blowfish
newtype instance LazyCiphertext Blowfish = MkBlowfishLazyCiphertext GLazyCiphertext
deriving newtype (LazyCiphertext Blowfish -> LazyCiphertext Blowfish -> Bool
(LazyCiphertext Blowfish -> LazyCiphertext Blowfish -> Bool)
-> (LazyCiphertext Blowfish -> LazyCiphertext Blowfish -> Bool)
-> Eq (LazyCiphertext Blowfish)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: LazyCiphertext Blowfish -> LazyCiphertext Blowfish -> Bool
== :: LazyCiphertext Blowfish -> LazyCiphertext Blowfish -> Bool
$c/= :: LazyCiphertext Blowfish -> LazyCiphertext Blowfish -> Bool
/= :: LazyCiphertext Blowfish -> LazyCiphertext Blowfish -> Bool
Eq, Eq (LazyCiphertext Blowfish)
Eq (LazyCiphertext Blowfish) =>
(LazyCiphertext Blowfish -> LazyCiphertext Blowfish -> Ordering)
-> (LazyCiphertext Blowfish -> LazyCiphertext Blowfish -> Bool)
-> (LazyCiphertext Blowfish -> LazyCiphertext Blowfish -> Bool)
-> (LazyCiphertext Blowfish -> LazyCiphertext Blowfish -> Bool)
-> (LazyCiphertext Blowfish -> LazyCiphertext Blowfish -> Bool)
-> (LazyCiphertext Blowfish
-> LazyCiphertext Blowfish -> LazyCiphertext Blowfish)
-> (LazyCiphertext Blowfish
-> LazyCiphertext Blowfish -> LazyCiphertext Blowfish)
-> Ord (LazyCiphertext Blowfish)
LazyCiphertext Blowfish -> LazyCiphertext Blowfish -> Bool
LazyCiphertext Blowfish -> LazyCiphertext Blowfish -> Ordering
LazyCiphertext Blowfish
-> LazyCiphertext Blowfish -> LazyCiphertext Blowfish
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 :: LazyCiphertext Blowfish -> LazyCiphertext Blowfish -> Ordering
compare :: LazyCiphertext Blowfish -> LazyCiphertext Blowfish -> Ordering
$c< :: LazyCiphertext Blowfish -> LazyCiphertext Blowfish -> Bool
< :: LazyCiphertext Blowfish -> LazyCiphertext Blowfish -> Bool
$c<= :: LazyCiphertext Blowfish -> LazyCiphertext Blowfish -> Bool
<= :: LazyCiphertext Blowfish -> LazyCiphertext Blowfish -> Bool
$c> :: LazyCiphertext Blowfish -> LazyCiphertext Blowfish -> Bool
> :: LazyCiphertext Blowfish -> LazyCiphertext Blowfish -> Bool
$c>= :: LazyCiphertext Blowfish -> LazyCiphertext Blowfish -> Bool
>= :: LazyCiphertext Blowfish -> LazyCiphertext Blowfish -> Bool
$cmax :: LazyCiphertext Blowfish
-> LazyCiphertext Blowfish -> LazyCiphertext Blowfish
max :: LazyCiphertext Blowfish
-> LazyCiphertext Blowfish -> LazyCiphertext Blowfish
$cmin :: LazyCiphertext Blowfish
-> LazyCiphertext Blowfish -> LazyCiphertext Blowfish
min :: LazyCiphertext Blowfish
-> LazyCiphertext Blowfish -> LazyCiphertext Blowfish
Ord, Int -> LazyCiphertext Blowfish -> ShowS
[LazyCiphertext Blowfish] -> ShowS
LazyCiphertext Blowfish -> String
(Int -> LazyCiphertext Blowfish -> ShowS)
-> (LazyCiphertext Blowfish -> String)
-> ([LazyCiphertext Blowfish] -> ShowS)
-> Show (LazyCiphertext Blowfish)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> LazyCiphertext Blowfish -> ShowS
showsPrec :: Int -> LazyCiphertext Blowfish -> ShowS
$cshow :: LazyCiphertext Blowfish -> String
show :: LazyCiphertext Blowfish -> String
$cshowList :: [LazyCiphertext Blowfish] -> ShowS
showList :: [LazyCiphertext Blowfish] -> ShowS
Show, ByteString -> Maybe (LazyCiphertext Blowfish)
LazyCiphertext Blowfish -> ByteString
(LazyCiphertext Blowfish -> ByteString)
-> (ByteString -> Maybe (LazyCiphertext Blowfish))
-> Encodable (LazyCiphertext Blowfish)
forall a.
(a -> ByteString) -> (ByteString -> Maybe a) -> Encodable a
$cencode :: LazyCiphertext Blowfish -> ByteString
encode :: LazyCiphertext Blowfish -> ByteString
$cdecode :: ByteString -> Maybe (LazyCiphertext Blowfish)
decode :: ByteString -> Maybe (LazyCiphertext Blowfish)
Encodable, Encodable (LazyCiphertext Blowfish)
ByteString -> Maybe (LazyCiphertext Blowfish)
LazyCiphertext Blowfish -> ByteString
Encodable (LazyCiphertext Blowfish) =>
(LazyCiphertext Blowfish -> ByteString)
-> (ByteString -> Maybe (LazyCiphertext Blowfish))
-> LazyEncodable (LazyCiphertext Blowfish)
forall a.
Encodable a =>
(a -> ByteString) -> (ByteString -> Maybe a) -> LazyEncodable a
$cencodeLazy :: LazyCiphertext Blowfish -> ByteString
encodeLazy :: LazyCiphertext Blowfish -> ByteString
$cdecodeLazy :: ByteString -> Maybe (LazyCiphertext Blowfish)
decodeLazy :: ByteString -> Maybe (LazyCiphertext Blowfish)
LazyEncodable)
pattern BlowfishLazyCiphertext :: Lazy.ByteString -> LazyCiphertext Blowfish
pattern $mBlowfishLazyCiphertext :: forall {r}.
LazyCiphertext Blowfish -> (ByteString -> r) -> ((# #) -> r) -> r
$bBlowfishLazyCiphertext :: ByteString -> LazyCiphertext Blowfish
BlowfishLazyCiphertext lbs = MkBlowfishLazyCiphertext (MkGLazyCiphertext lbs)
getBlowfishLazyCiphertext :: LazyCiphertext Blowfish -> Lazy.ByteString
getBlowfishLazyCiphertext :: LazyCiphertext Blowfish -> ByteString
getBlowfishLazyCiphertext (BlowfishLazyCiphertext ByteString
bs) = ByteString
bs
type BlowfishLazyCiphertext = LazyCiphertext Blowfish
instance HasSecretKey Blowfish where
secretKeySpec :: SizeSpecifier (SecretKey Blowfish)
secretKeySpec :: SizeSpecifier (SecretKey Blowfish)
secretKeySpec = SizeSpecifier () -> SizeSpecifier (SecretKey Blowfish)
forall a b. SizeSpecifier a -> SizeSpecifier b
coerceSizeSpec (SizeSpecifier () -> SizeSpecifier (SecretKey Blowfish))
-> SizeSpecifier () -> SizeSpecifier (SecretKey Blowfish)
forall a b. (a -> b) -> a -> b
$ BlockCipher -> SizeSpecifier ()
Botan.blockCipherKeySpec BlockCipher
Botan.blowfish
instance (MonadRandomIO m )=> SecretKeyGen Blowfish m where
newSecretKey :: MonadRandomIO m => m (SecretKey Blowfish)
newSecretKey :: MonadRandomIO m => m (SecretKey Blowfish)
newSecretKey = ByteString -> SecretKey Blowfish
BlowfishSecretKey (ByteString -> SecretKey Blowfish)
-> m ByteString -> m (SecretKey Blowfish)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> SizeSpecifier (SecretKey Blowfish) -> m ByteString
forall (m :: * -> *) a.
MonadRandomIO m =>
SizeSpecifier a -> m ByteString
newSized (forall alg. HasSecretKey alg => SizeSpecifier (SecretKey alg)
secretKeySpec @Blowfish)
newSecretKeyMaybe :: MonadRandomIO m => Int -> m (Maybe (SecretKey Blowfish))
newSecretKeyMaybe :: MonadRandomIO m => Int -> m (Maybe (SecretKey Blowfish))
newSecretKeyMaybe Int
i = (ByteString -> SecretKey Blowfish)
-> Maybe ByteString -> Maybe (SecretKey Blowfish)
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ByteString -> SecretKey Blowfish
BlowfishSecretKey (Maybe ByteString -> Maybe (SecretKey Blowfish))
-> m (Maybe ByteString) -> m (Maybe (SecretKey Blowfish))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> SizeSpecifier (SecretKey Blowfish) -> Int -> m (Maybe ByteString)
forall (m :: * -> *) a.
MonadRandomIO m =>
SizeSpecifier a -> Int -> m (Maybe ByteString)
newSizedMaybe (forall alg. HasSecretKey alg => SizeSpecifier (SecretKey alg)
secretKeySpec @Blowfish) Int
i
instance HasCiphertext Blowfish where
instance BlockCipher Blowfish where
blockCipherEncrypt :: SecretKey Blowfish -> ByteString -> Maybe (Ciphertext Blowfish)
blockCipherEncrypt :: SecretKey Blowfish -> ByteString -> Maybe (Ciphertext Blowfish)
blockCipherEncrypt (BlowfishSecretKey ByteString
k) = (ByteString -> Ciphertext Blowfish)
-> Maybe ByteString -> Maybe (Ciphertext Blowfish)
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ByteString -> Ciphertext Blowfish
BlowfishCiphertext (Maybe ByteString -> Maybe (Ciphertext Blowfish))
-> (ByteString -> Maybe ByteString)
-> ByteString
-> Maybe (Ciphertext Blowfish)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BlockCipher -> ByteString -> ByteString -> Maybe ByteString
Botan.blockCipherEncrypt BlockCipher
Botan.blowfish ByteString
k
blockCipherDecrypt :: SecretKey Blowfish -> Ciphertext Blowfish -> Maybe ByteString
blockCipherDecrypt :: SecretKey Blowfish -> Ciphertext Blowfish -> Maybe ByteString
blockCipherDecrypt (BlowfishSecretKey ByteString
k) (BlowfishCiphertext ByteString
ct) = BlockCipher -> ByteString -> ByteString -> Maybe ByteString
Botan.blockCipherDecrypt BlockCipher
Botan.blowfish ByteString
k ByteString
ct
instance HasLazyCiphertext Blowfish where
instance IncrementalBlockCipher Blowfish where
blockCipherEncryptLazy :: SecretKey Blowfish -> Lazy.ByteString -> Maybe (LazyCiphertext Blowfish)
blockCipherEncryptLazy :: SecretKey Blowfish -> ByteString -> Maybe (LazyCiphertext Blowfish)
blockCipherEncryptLazy (BlowfishSecretKey ByteString
k) = (ByteString -> LazyCiphertext Blowfish)
-> Maybe ByteString -> Maybe (LazyCiphertext Blowfish)
forall a b. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ByteString -> LazyCiphertext Blowfish
BlowfishLazyCiphertext (Maybe ByteString -> Maybe (LazyCiphertext Blowfish))
-> (ByteString -> Maybe ByteString)
-> ByteString
-> Maybe (LazyCiphertext Blowfish)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BlockCipher -> ByteString -> ByteString -> Maybe ByteString
Botan.blockCipherEncryptLazy BlockCipher
Botan.blowfish ByteString
k
blockCipherDecryptLazy :: SecretKey Blowfish -> LazyCiphertext Blowfish -> Maybe Lazy.ByteString
blockCipherDecryptLazy :: SecretKey Blowfish -> LazyCiphertext Blowfish -> Maybe ByteString
blockCipherDecryptLazy (BlowfishSecretKey ByteString
k) (BlowfishLazyCiphertext ByteString
ct) = BlockCipher -> ByteString -> ByteString -> Maybe ByteString
Botan.blockCipherDecryptLazy BlockCipher
Botan.blowfish ByteString
k ByteString
ct
blowfishEncrypt :: SecretKey Blowfish -> ByteString -> Maybe BlowfishCiphertext
blowfishEncrypt :: SecretKey Blowfish -> ByteString -> Maybe (Ciphertext Blowfish)
blowfishEncrypt = SecretKey Blowfish -> ByteString -> Maybe (Ciphertext Blowfish)
forall bc.
BlockCipher bc =>
SecretKey bc -> ByteString -> Maybe (Ciphertext bc)
blockCipherEncrypt
blowfishDecrypt :: SecretKey Blowfish -> BlowfishCiphertext -> Maybe ByteString
blowfishDecrypt :: SecretKey Blowfish -> Ciphertext Blowfish -> Maybe ByteString
blowfishDecrypt = SecretKey Blowfish -> Ciphertext Blowfish -> Maybe ByteString
forall bc.
BlockCipher bc =>
SecretKey bc -> Ciphertext bc -> Maybe ByteString
blockCipherDecrypt
blowfishEncryptLazy :: SecretKey Blowfish -> Lazy.ByteString -> Maybe BlowfishLazyCiphertext
blowfishEncryptLazy :: SecretKey Blowfish -> ByteString -> Maybe (LazyCiphertext Blowfish)
blowfishEncryptLazy = SecretKey Blowfish -> ByteString -> Maybe (LazyCiphertext Blowfish)
forall bc.
IncrementalBlockCipher bc =>
SecretKey bc -> ByteString -> Maybe (LazyCiphertext bc)
blockCipherEncryptLazy
blowfishDecryptLazy :: SecretKey Blowfish -> BlowfishLazyCiphertext -> Maybe Lazy.ByteString
blowfishDecryptLazy :: SecretKey Blowfish -> LazyCiphertext Blowfish -> Maybe ByteString
blowfishDecryptLazy = SecretKey Blowfish -> LazyCiphertext Blowfish -> Maybe ByteString
forall bc.
IncrementalBlockCipher bc =>
SecretKey bc -> LazyCiphertext bc -> Maybe ByteString
blockCipherDecryptLazy