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 the 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.
- newtype CryptoID namespace a :: Symbol -> * -> * = CryptoID {
- ciphertext :: a
- type CryptoUUID namespace = CryptoID namespace UUID
- encrypt :: forall a m namespace. (KnownSymbol namespace, Binary a, MonadError CryptoIDError m) => CryptoIDKey -> a -> m (CryptoUUID namespace)
- decrypt :: forall a m namespace. (KnownSymbol namespace, Binary a, MonadError CryptoIDError m) => CryptoIDKey -> CryptoUUID namespace -> m a
- data CryptoIDError :: *
Documentation
newtype CryptoID namespace a :: Symbol -> * -> * #
CryptoID | |
|
Eq a => Eq (CryptoID namespace a) | |
(Data a, KnownSymbol namespace) => Data (CryptoID namespace a) | |
Ord a => Ord (CryptoID namespace a) | |
Read a => Read (CryptoID namespace a) | |
Show a => Show (CryptoID namespace a) | |
Generic (CryptoID namespace a) | |
Storable a => Storable (CryptoID namespace a) | |
Binary a => Binary (CryptoID namespace a) | |
ToHttpApiData a => ToHttpApiData (CryptoID namespace a) | |
FromHttpApiData a => FromHttpApiData (CryptoID namespace a) | |
PathPiece a => PathPiece (CryptoID namespace a) | |
type Rep (CryptoID namespace a) | |
type CryptoUUID namespace = CryptoID namespace UUID Source #
encrypt :: forall a m namespace. (KnownSymbol namespace, Binary a, MonadError CryptoIDError 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 one CryptoCipher
-block.
Larger values could likely not be contained wholly within 128 bits (the size
of an UUID
) in any case.
decrypt :: forall a m namespace. (KnownSymbol namespace, Binary a, MonadError CryptoIDError 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
.
data CryptoIDError :: * #
AlgorithmError CryptoError | One of the underlying cryptographic algorithms
( |
NamespaceHashIsWrongLength ByteString | The length of the digest produced by The offending digest is included. This error should not occur and is included primarily for sake of totality. |
CiphertextConversionFailed | The produced |
DeserializationError (ByteString, ByteOffset, String) | The plaintext obtained by decrypting a ciphertext with the given
This is expected behaviour if the |
InvalidNamespaceDetected | We have determined that, allthough deserializion succeded, the ciphertext was likely modified during transit or created using a different namespace. |