filepath-crypto-0.0.0.3: Reversable and secure encoding of object ids as filepaths

LicenseBSD3
Safe HaskellNone
LanguageHaskell2010

System.FilePath.Cryptographic

Description

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 \left \lceil \frac{l}{b} \right \rceil - l}\) where \(l\) is the length of the serialized payload and \(b\) the length of a ciphertext block (both in bits).

Synopsis

Documentation

newtype CryptoID (namespace :: Symbol) a :: Symbol -> * -> * #

Constructors

CryptoID 

Fields

Instances

Eq a => Eq (CryptoID namespace a) 

Methods

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

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

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

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) 

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) 

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) 

Methods

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

show :: CryptoID namespace a -> String #

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

Generic (CryptoID namespace a) 

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) 

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) 

Methods

put :: CryptoID namespace a -> Put #

get :: Get (CryptoID namespace a) #

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

ToHttpApiData a => ToHttpApiData (CryptoID namespace a) 

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) 

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) 

Methods

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

toPathPiece :: CryptoID namespace a -> Text #

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

type CryptoFileName (namespace :: Symbol) = CryptoID namespace (CI FilePath) Source #

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).

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.

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.