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 encrypted using a symmetric cipher in CBC mode using
the hashed namespace as an initialization vector (IV).
The ciphertext is then base32-encoded and padding stripped.
Rather than being indicated by the amount of padding, the length of the
serialized plaintext is instead carried at the type level within
CryptoFileName
(analogously to the namespace).
Mismatches in serialized plaintext length are checked for but are not
guaranteed to cause runtime errors in all cases.
Since the serialized payload is padded to the length of the next cipher block 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^{b cdot left lceil frac{l}{b} right rceil-l}]) where \(l\) is the length of the serialized payload.
- newtype CryptoID namespace a :: Symbol -> * -> * = CryptoID {
- ciphertext :: a
- type CryptoFileName namespace = CryptoID namespace (CI FilePath)
- module Data.Binary.SerializationLength
- encrypt :: forall a m namespace. (KnownSymbol namespace, Binary a, MonadThrow m, HasFixedSerializationLength a) => CryptoIDKey -> a -> m (CryptoFileName namespace)
- decrypt :: forall a m namespace. (KnownSymbol namespace, Binary a, MonadThrow m, HasFixedSerializationLength a) => CryptoIDKey -> CryptoFileName 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) | |
encrypt :: forall a m namespace. (KnownSymbol namespace, Binary a, MonadThrow m, HasFixedSerializationLength a) => CryptoIDKey -> a -> m (CryptoFileName 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 meets the expected length given at type level.
decrypt :: forall a m namespace. (KnownSymbol namespace, Binary a, MonadThrow m, HasFixedSerializationLength a) => CryptoIDKey -> CryptoFileName 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 :: * #
Error cases that can be encountered during encrypt
and decrypt
Care has been taken to ensure that presenting values of CryptoIDError
to an
attacker leaks no plaintext (it does leak information about the length of the
plaintext).
AlgorithmError CryptoError | One of the underlying cryptographic algorithms
( |
PlaintextIsWrongLength Int | The length of the plaintext is not a multiple of the block size of
The length of the offending plaintext is included. |
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 ByteString | The produced The offending |
DeserializationError | 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. |