Minor cleanup
This commit is contained in:
parent
0cdc29fbf4
commit
03d67910e2
@ -1,14 +1,14 @@
|
||||
{-# LANGUAGE ScopedTypeVariables #-}
|
||||
|
||||
{-|
|
||||
Description: Reversably generate variable length bytestrings from arbitrary serializable types in a secure fashion
|
||||
Description: Encryption of bytestrings using a type level nonce for determinism
|
||||
License: BSD3
|
||||
|
||||
Given a value of a serializable type (like 'Int') we perform serialization and
|
||||
compute a cryptographic hash of the associated namespace (carried as a phantom
|
||||
type of kind 'Symbol').
|
||||
The serialized payload is then encrypted using the a symmetric cipher in CBC
|
||||
mode using the hashed namespace as an initialization vector (IV).
|
||||
The serialized payload is then encrypted using the symmetric cipher in CBC mode
|
||||
using the hashed namespace as an initialization vector (IV).
|
||||
|
||||
The probability of detecting a namespace mismatch is thus \(1 - 2^{128-l}\)
|
||||
where \(l\) is the length of the serialized payload.
|
||||
|
||||
@ -47,8 +47,8 @@ import GHC.TypeLits
|
||||
type CryptoUUID (namespace :: Symbol) = CryptoID namespace UUID
|
||||
|
||||
|
||||
mapCiphertext :: Functor m => (a -> m b) -> CryptoID n a -> m (CryptoID n b)
|
||||
mapCiphertext f (CryptoID x) = CryptoID <$> f x
|
||||
_ciphertext :: Functor m => (a -> m b) -> CryptoID n a -> m (CryptoID n b)
|
||||
_ciphertext f (CryptoID x) = CryptoID <$> f x
|
||||
|
||||
|
||||
-- | @pad err size src@ appends null bytes to @src@ until it has length @size@.
|
||||
@ -76,7 +76,7 @@ encrypt :: forall a m namespace.
|
||||
encrypt key val = do
|
||||
plaintext <- pad 16 . Lazy.ByteString.toStrict $ encode val
|
||||
|
||||
mapCiphertext uuidConversion =<< Poly.encrypt key plaintext
|
||||
_ciphertext uuidConversion =<< Poly.encrypt key plaintext
|
||||
where
|
||||
uuidConversion = maybe (throwError CiphertextConversionFailed) return . fromByteString . Lazy.ByteString.fromStrict
|
||||
|
||||
@ -91,9 +91,9 @@ decrypt :: forall a m namespace.
|
||||
, Binary a
|
||||
, MonadError CryptoIDError m
|
||||
) => CryptoIDKey -> CryptoUUID namespace -> m a
|
||||
decrypt key id = do
|
||||
id' <- (return . Lazy.ByteString.toStrict . toByteString) `mapCiphertext` id
|
||||
plaintext <- Lazy.ByteString.fromStrict <$> Poly.decrypt key id'
|
||||
decrypt key cId = do
|
||||
cId' <- _ciphertext (return . Lazy.ByteString.toStrict . toByteString) cId
|
||||
plaintext <- Lazy.ByteString.fromStrict <$> Poly.decrypt key cId'
|
||||
|
||||
case decodeOrFail plaintext of
|
||||
Left err -> throwError $ DeserializationError err
|
||||
|
||||
Loading…
Reference in New Issue
Block a user