| License | BSD3 |
|---|---|
| Safe Haskell | None |
| Language | Haskell2010 |
Data.CryptoID.ByteString
Contents
Description
Given a strict ByteString we compute a cryptographic hash of the associated
namespace (carried as a phantom type of kind Symbol).
The 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 the density of valid
payloads within all ByteStrings of the correct length.
Synopsis
- type CryptoByteString (namespace :: Symbol) = CryptoID namespace ByteString
- type HasCryptoByteString (namespace :: Symbol) = HasCryptoID namespace ByteString
- data CryptoIDKey
- genKey :: MonadIO m => m CryptoIDKey
- readKeyFile :: MonadIO m => FilePath -> m CryptoIDKey
- encrypt :: forall m namespace. (KnownSymbol namespace, MonadThrow m) => CryptoIDKey -> ByteString -> m (CryptoID namespace ByteString)
- decrypt :: forall m namespace. (KnownSymbol namespace, MonadThrow m) => CryptoIDKey -> CryptoID namespace ByteString -> m ByteString
- data CryptoIDError
- type CryptoCipher = Blowfish
- type CryptoHash = SHAKE128 64
- cipherBlockSize :: Int
- module Data.CryptoID
- class MonadThrow m => MonadCrypto (m :: * -> *) where
- type MonadCryptoKey (m :: * -> *) :: *
- class MonadCrypto m => HasCryptoID (namespace :: Symbol) ciphertext plaintext (m :: * -> *)
Documentation
type CryptoByteString (namespace :: Symbol) = CryptoID namespace ByteString Source #
type HasCryptoByteString (namespace :: Symbol) = HasCryptoID namespace ByteString Source #
data CryptoIDKey Source #
This newtype ensures only keys of the correct length can be created
Use genKey to securely generate keys.
Use the Binary instance to save and restore values of CryptoIDKey across
executions.
Instances
| Show CryptoIDKey Source # | Does not actually show any key material |
Defined in Data.CryptoID.ByteString Methods showsPrec :: Int -> CryptoIDKey -> ShowS # show :: CryptoIDKey -> String # showList :: [CryptoIDKey] -> ShowS # | |
| Binary CryptoIDKey Source # | |
Defined in Data.CryptoID.ByteString | |
| ByteArrayAccess CryptoIDKey Source # | |
Defined in Data.CryptoID.ByteString Methods length :: CryptoIDKey -> Int # withByteArray :: CryptoIDKey -> (Ptr p -> IO a) -> IO a # copyByteArrayToPtr :: CryptoIDKey -> Ptr p -> IO () # | |
genKey :: MonadIO m => m CryptoIDKey Source #
Securely generate a new key using system entropy
When CryptoCipher accepts keys of varying lengths this function generates a
key of the largest accepted size.
readKeyFile :: MonadIO m => FilePath -> m CryptoIDKey Source #
Try to read a CryptoIDKey from a file.
If the file does not exist, securely generate a key (using genKey) and
save it to the file.
encrypt :: forall m namespace. (KnownSymbol namespace, MonadThrow m) => CryptoIDKey -> ByteString -> m (CryptoID namespace ByteString) Source #
Encrypt a serialized value
decrypt :: forall m namespace. (KnownSymbol namespace, MonadThrow m) => CryptoIDKey -> CryptoID namespace ByteString -> m ByteString Source #
Decrypt a serialized value
data CryptoIDError Source #
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).
Constructors
| 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. |
| CiphertextIsWrongLength ByteString | The length of the ciphertext is not a multiple of the block size of
The offending ciphertext 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. |
Instances
| Eq CryptoIDError Source # | |
Defined in Data.CryptoID.ByteString Methods (==) :: CryptoIDError -> CryptoIDError -> Bool # (/=) :: CryptoIDError -> CryptoIDError -> Bool # | |
| Show CryptoIDError Source # | |
Defined in Data.CryptoID.ByteString Methods showsPrec :: Int -> CryptoIDError -> ShowS # show :: CryptoIDError -> String # showList :: [CryptoIDError] -> ShowS # | |
| Exception CryptoIDError Source # | |
Defined in Data.CryptoID.ByteString Methods toException :: CryptoIDError -> SomeException # fromException :: SomeException -> Maybe CryptoIDError # displayException :: CryptoIDError -> String # | |
type CryptoCipher = Blowfish Source #
The symmetric cipher BlockCipher this module uses
type CryptoHash = SHAKE128 64 Source #
The cryptographic HashAlgorithm this module uses
We expect the block size of CryptoCipher to be exactly the size of the
Digest generated by CryptoHash (since a Digest is used as an IV).
Violation of this expectation causes runtime errors.
module Data.CryptoID
class MonadThrow m => MonadCrypto (m :: * -> *) where #
Class of monads granting reader access to a key and allowing for failure during cryptographic operations
This formulation is weaker than MonadReader key (from mtl) in that it does not require local.
Minimal complete definition
Associated Types
type MonadCryptoKey (m :: * -> *) :: * #
Methods
cryptoIDKey :: (MonadCryptoKey m -> m a) -> m a #
class MonadCrypto m => HasCryptoID (namespace :: Symbol) ciphertext plaintext (m :: * -> *) #
Multiparameter typeclass of (namespace, ciphertext, plaintext, monad) tuples which allow for cryptographic operations on CryptoIDs with appropriate namespace, plaintext, and ciphertext, utilising the state of monad
Instances of this typeclass are usually universally quantified over (at least) namespace, and m
Instances
| (MonadCrypto m, MonadCryptoKey m ~ CryptoIDKey, KnownSymbol namespace) => HasCryptoID namespace ByteString ByteString m # | This instance is somewhat improper in that it works only for plain- and
ciphertexts whose length is a multiple of Improper plaintext lengths throw Improper ciphertext lengths throw |
Defined in Data.CryptoID.ByteString Methods encrypt :: ByteString -> m (CryptoID namespace ByteString) # decrypt :: CryptoID namespace ByteString -> m ByteString # | |
| (MonadCrypto m, MonadCryptoKey m ~ CryptoIDKey, KnownSymbol namespace, Binary a) => HasCryptoID namespace ByteString a m # | |
Defined in Data.CryptoID.Poly Methods encrypt :: a -> m (CryptoID namespace ByteString) # decrypt :: CryptoID namespace ByteString -> m a # | |
Orphan instances
| (MonadCrypto m, MonadCryptoKey m ~ CryptoIDKey, KnownSymbol namespace) => HasCryptoID namespace ByteString ByteString m Source # | This instance is somewhat improper in that it works only for plain- and
ciphertexts whose length is a multiple of Improper plaintext lengths throw Improper ciphertext lengths throw |
Methods encrypt :: ByteString -> m (CryptoID namespace ByteString) # decrypt :: CryptoID namespace ByteString -> m ByteString # | |