License | BSD3 |
---|---|
Safe Haskell | None |
Language | Haskell2010 |
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 a symmetric cipher in CBC mode
using the hashed namespace as an initialization vector (IV).
Since the serialized payload is padded to the length of an UUID we can detect namespace mismatches by checking that all bytes expected to have been inserted during padding are nil. The probability of detecting a namespace mismatch is thus \(1 - 2^{128-l}\) where \(l\) is the length of the serialized payload.
- type CryptoUUID (namespace :: Symbol) = CryptoID namespace UUID
- type HasCryptoUUID (namespace :: Symbol) = HasCryptoID namespace UUID
- encrypt :: forall a m namespace. (KnownSymbol namespace, Binary a, MonadThrow m) => CryptoIDKey -> a -> m (CryptoUUID namespace)
- decrypt :: forall a m namespace. (KnownSymbol namespace, Binary a, MonadThrow m) => CryptoIDKey -> CryptoUUID namespace -> m a
- module Data.CryptoID.Poly
Documentation
type HasCryptoUUID (namespace :: Symbol) = HasCryptoID namespace UUID Source #
encrypt :: forall a m namespace. (KnownSymbol namespace, Binary a, MonadThrow m) => CryptoIDKey -> a -> m (CryptoUUID namespace) Source #
Encrypt an arbitrary serializable value
We only expect to fail if the given value is not serialized in such a fashion
that it fits within 128 bits (the length of an UUID
).
decrypt :: forall a m namespace. (KnownSymbol namespace, Binary a, MonadThrow m) => CryptoIDKey -> CryptoUUID namespace -> m a Source #
Decrypt an arbitrary serializable value
Since no integrity guarantees can be made (we do not sign the values we
encrypt
) it is likely that deserialization will fail emitting
DeserializationError
or InvalidNamespaceDetected
.
module Data.CryptoID.Poly
Orphan instances
(MonadCrypto m, (~) * (MonadCryptoKey m) CryptoIDKey, KnownSymbol namespace, Binary a) => HasCryptoID namespace UUID a m Source # | |