Fix padding
This commit is contained in:
parent
78a4b91032
commit
0cdc29fbf4
@ -34,7 +34,6 @@ import qualified Data.ByteString as ByteString
|
||||
import qualified Data.ByteString.Char8 as ByteString.Char
|
||||
|
||||
import qualified Data.ByteString.Lazy as Lazy (ByteString)
|
||||
import qualified Data.ByteString.Lazy as Lazy.ByteString
|
||||
|
||||
import Data.List (sortOn)
|
||||
import Data.Ord (Down(..))
|
||||
@ -142,6 +141,13 @@ genKey = CryptoIDKey <$> liftIO (getEntropy keySize)
|
||||
| KeySizeEnum ns <- keySize' = maximum ns
|
||||
| KeySizeRange _ max <- keySize' = max
|
||||
|
||||
|
||||
-- | @pad err size src@ appends null bytes to @src@ until it has length that is
|
||||
-- a multiple of @size@.
|
||||
pad :: ByteArrayAccess a => Int -> a -> ByteString
|
||||
pad n (ByteArray.unpack -> src) = ByteString.pack $ src ++ replicate (l `mod` n) 0
|
||||
where
|
||||
l = length src
|
||||
|
||||
-- | Use 'CryptoHash' to generate a 'Digest' of the Symbol passed as proxy type
|
||||
namespace' :: forall proxy namespace m.
|
||||
@ -159,18 +165,18 @@ cryptoFailable :: MonadError CryptoIDError m => CryptoFailable a -> m a
|
||||
cryptoFailable = either (throwError . AlgorithmError) return . eitherCryptoError
|
||||
|
||||
-- | Encrypt an arbitrary serializable value
|
||||
encrypt :: forall a m namespace.
|
||||
encrypt :: forall m namespace.
|
||||
( KnownSymbol namespace
|
||||
, MonadError CryptoIDError m
|
||||
) => CryptoIDKey -> ByteString -> m (CryptoID namespace ByteString)
|
||||
encrypt (keyMaterial -> key) plaintext = do
|
||||
cipher <- cryptoFailable (cipherInit key :: CryptoFailable CryptoCipher)
|
||||
namespace <- namespace' (Proxy :: Proxy namespace)
|
||||
return . CryptoID $ cbcEncrypt cipher namespace plaintext
|
||||
return . CryptoID . cbcEncrypt cipher namespace $ pad (blockSize cipher) plaintext
|
||||
|
||||
|
||||
-- | Decrypt an arbitrary serializable value
|
||||
decrypt :: forall a m namespace.
|
||||
decrypt :: forall m namespace.
|
||||
( KnownSymbol namespace
|
||||
, MonadError CryptoIDError m
|
||||
) => CryptoIDKey -> CryptoID namespace ByteString -> m ByteString
|
||||
|
||||
@ -43,8 +43,6 @@ import Control.Monad.Except
|
||||
|
||||
import GHC.TypeLits
|
||||
|
||||
import Crypto.Cipher.Types
|
||||
|
||||
|
||||
type CryptoUUID (namespace :: Symbol) = CryptoID namespace UUID
|
||||
|
||||
@ -76,13 +74,11 @@ encrypt :: forall a m namespace.
|
||||
, MonadError CryptoIDError m
|
||||
) => CryptoIDKey -> a -> m (CryptoUUID namespace)
|
||||
encrypt key val = do
|
||||
plaintext <- pad (blockSize cipher) . Lazy.ByteString.toStrict $ encode val
|
||||
plaintext <- pad 16 . Lazy.ByteString.toStrict $ encode val
|
||||
|
||||
mapCiphertext uuidConversion =<< Poly.encrypt key plaintext
|
||||
where
|
||||
uuidConversion = maybe (throwError CiphertextConversionFailed) return . fromByteString . Lazy.ByteString.fromStrict
|
||||
cipher :: CryptoCipher
|
||||
cipher = undefined
|
||||
|
||||
|
||||
-- | Decrypt an arbitrary serializable value
|
||||
|
||||
Loading…
Reference in New Issue
Block a user