cryptoids-0.5.1.0: Reversable and secure encoding of object ids as a bytestring

LicenseBSD3
Safe HaskellNone
LanguageHaskell2010

Data.CryptoID.Poly

Contents

Description

Given a value of an arbitrary 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 serializedpayload is then encrypted using the symmetric cipher in CBC mode using the hashed namespace as an initialization vector (IV).

Since the serialized payload is padded such that its length is an integer multiple of the block size 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^{l text{mod} 64}) where \(l\) is the length of the serialized payload in bits.

Synopsis

Documentation

encrypt Source #

Arguments

:: (KnownSymbol namespace, MonadThrow m, Binary a) 
=> (ByteString -> m (Maybe Int))

Ensure the resulting ciphertext is of the provided length (needs to be a multiple of the block size of CryptoCipher in bytes, otherwise an exception will be thrown at runtime). The computation has access to the serialized plaintext

-> (ByteString -> m c) 
-> CryptoIDKey 
-> a 
-> m (CryptoID namespace c) 

Encrypt a serialized value

decrypt :: forall a m c namespace. (KnownSymbol namespace, MonadThrow m, Binary a) => (c -> m ByteString) -> CryptoIDKey -> CryptoID namespace c -> m a Source #

Decrypt a serialized value

newtype CryptoID (namespace :: Symbol) a #

Constructors

CryptoID 

Fields

Instances
Eq a => Eq (CryptoID namespace a) 
Instance details

Defined in Data.CryptoID

Methods

(==) :: CryptoID namespace a -> CryptoID namespace a -> Bool #

(/=) :: CryptoID namespace a -> CryptoID namespace a -> Bool #

(KnownSymbol namespace, Data a) => Data (CryptoID namespace a) 
Instance details

Defined in Data.CryptoID

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CryptoID namespace a -> c (CryptoID namespace a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (CryptoID namespace a) #

toConstr :: CryptoID namespace a -> Constr #

dataTypeOf :: CryptoID namespace a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (CryptoID namespace a)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (CryptoID namespace a)) #

gmapT :: (forall b. Data b => b -> b) -> CryptoID namespace a -> CryptoID namespace a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CryptoID namespace a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CryptoID namespace a -> r #

gmapQ :: (forall d. Data d => d -> u) -> CryptoID namespace a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CryptoID namespace a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CryptoID namespace a -> m (CryptoID namespace a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CryptoID namespace a -> m (CryptoID namespace a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CryptoID namespace a -> m (CryptoID namespace a) #

Ord a => Ord (CryptoID namespace a) 
Instance details

Defined in Data.CryptoID

Methods

compare :: CryptoID namespace a -> CryptoID namespace a -> Ordering #

(<) :: CryptoID namespace a -> CryptoID namespace a -> Bool #

(<=) :: CryptoID namespace a -> CryptoID namespace a -> Bool #

(>) :: CryptoID namespace a -> CryptoID namespace a -> Bool #

(>=) :: CryptoID namespace a -> CryptoID namespace a -> Bool #

max :: CryptoID namespace a -> CryptoID namespace a -> CryptoID namespace a #

min :: CryptoID namespace a -> CryptoID namespace a -> CryptoID namespace a #

Read a => Read (CryptoID namespace a) 
Instance details

Defined in Data.CryptoID

Methods

readsPrec :: Int -> ReadS (CryptoID namespace a) #

readList :: ReadS [CryptoID namespace a] #

readPrec :: ReadPrec (CryptoID namespace a) #

readListPrec :: ReadPrec [CryptoID namespace a] #

Show a => Show (CryptoID namespace a) 
Instance details

Defined in Data.CryptoID

Methods

showsPrec :: Int -> CryptoID namespace a -> ShowS #

show :: CryptoID namespace a -> String #

showList :: [CryptoID namespace a] -> ShowS #

Generic (CryptoID namespace a) 
Instance details

Defined in Data.CryptoID

Associated Types

type Rep (CryptoID namespace a) :: * -> * #

Methods

from :: CryptoID namespace a -> Rep (CryptoID namespace a) x #

to :: Rep (CryptoID namespace a) x -> CryptoID namespace a #

Storable a => Storable (CryptoID namespace a) 
Instance details

Defined in Data.CryptoID

Methods

sizeOf :: CryptoID namespace a -> Int #

alignment :: CryptoID namespace a -> Int #

peekElemOff :: Ptr (CryptoID namespace a) -> Int -> IO (CryptoID namespace a) #

pokeElemOff :: Ptr (CryptoID namespace a) -> Int -> CryptoID namespace a -> IO () #

peekByteOff :: Ptr b -> Int -> IO (CryptoID namespace a) #

pokeByteOff :: Ptr b -> Int -> CryptoID namespace a -> IO () #

peek :: Ptr (CryptoID namespace a) -> IO (CryptoID namespace a) #

poke :: Ptr (CryptoID namespace a) -> CryptoID namespace a -> IO () #

Binary a => Binary (CryptoID namespace a) 
Instance details

Defined in Data.CryptoID

Methods

put :: CryptoID namespace a -> Put #

get :: Get (CryptoID namespace a) #

putList :: [CryptoID namespace a] -> Put #

ToHttpApiData a => ToHttpApiData (CryptoID namespace a) 
Instance details

Defined in Data.CryptoID

Methods

toUrlPiece :: CryptoID namespace a -> Text #

toEncodedUrlPiece :: CryptoID namespace a -> Builder #

toHeader :: CryptoID namespace a -> ByteString #

toQueryParam :: CryptoID namespace a -> Text #

FromHttpApiData a => FromHttpApiData (CryptoID namespace a) 
Instance details

Defined in Data.CryptoID

Methods

parseUrlPiece :: Text -> Either Text (CryptoID namespace a) #

parseHeader :: ByteString -> Either Text (CryptoID namespace a) #

parseQueryParam :: Text -> Either Text (CryptoID namespace a) #

PathPiece a => PathPiece (CryptoID namespace a) 
Instance details

Defined in Data.CryptoID

Methods

fromPathPiece :: Text -> Maybe (CryptoID namespace a) #

toPathPiece :: CryptoID namespace a -> Text #

type Rep (CryptoID namespace a) 
Instance details

Defined in Data.CryptoID

type Rep (CryptoID namespace a) = D1 (MetaData "CryptoID" "Data.CryptoID" "cryptoids-types-0.0.0-A24B5NambBzDVKCx18tpGq" True) (C1 (MetaCons "CryptoID" PrefixI True) (S1 (MetaSel (Just "ciphertext") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))

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

cryptoIDKey

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

Minimal complete definition

encrypt, decrypt

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 cipherBlockSize

Improper plaintext lengths throw PlaintextIsWrongLength

Improper ciphertext lengths throw CiphertextIsWrongLength

Instance details

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 # 
Instance details

Defined in Data.CryptoID.Poly

Methods

encrypt :: a -> m (CryptoID namespace ByteString) #

decrypt :: CryptoID namespace ByteString -> m a #

type HasCryptoByteString (namespace :: Symbol) = HasCryptoID namespace ByteString Source #

type CryptoByteString (namespace :: Symbol) = CryptoID namespace ByteString Source #

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 (CryptoHash or CryptoCipher) failed.

PlaintextIsWrongLength Int

The length of the plaintext is not a multiple of the block size of CryptoCipher

The length of the offending plaintext is included.

CiphertextIsWrongLength ByteString

The length of the ciphertext is not a multiple of the block size of CryptoCipher

The offending ciphertext is included.

NamespaceHashIsWrongLength ByteString

The length of the digest produced by CryptoHash does not match the block size of CryptoCipher.

The offending digest is included.

This error should not occur and is included primarily for sake of totality.

CiphertextConversionFailed ByteString

The produced ByteString is the wrong length for deserialization into a ciphertext.

The offending ByteString is included.

DeserializationError

The plaintext obtained by decrypting a ciphertext with the given CryptoIDKey in the context of the namespace could not be deserialized into a value of the expected payload-type.

This is expected behaviour if the namespace or payload-type does not match the ones used during encryption or if the ciphertext was tempered with.

InvalidNamespaceDetected

We have determined that, allthough deserializion succeded, the ciphertext was likely modified during transit or created using a different namespace.

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

Instance details

Defined in Data.CryptoID.ByteString

Binary CryptoIDKey Source # 
Instance details

Defined in Data.CryptoID.ByteString

ByteArrayAccess CryptoIDKey Source # 
Instance details

Defined in Data.CryptoID.ByteString

Methods

length :: CryptoIDKey -> Int #

withByteArray :: CryptoIDKey -> (Ptr p -> IO a) -> IO a #

copyByteArrayToPtr :: CryptoIDKey -> Ptr p -> IO () #

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.

type CryptoCipher = Blowfish Source #

The symmetric cipher BlockCipher this module uses

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.

Orphan instances

(MonadCrypto m, MonadCryptoKey m ~ CryptoIDKey, KnownSymbol namespace, Binary a) => HasCryptoID namespace ByteString a m Source # 
Instance details

Methods

encrypt :: a -> m (CryptoID namespace ByteString) #

decrypt :: CryptoID namespace ByteString -> m a #