| License | BSD-style |
|---|---|
| Maintainer | Sam Protas <sam.protas@gmail.com> |
| Stability | experimental |
| Portability | unknown |
| Safe Haskell | None |
| Language | Haskell2010 |
Crypto.TripleSec
Contents
Description
TripleSec is a simple, triple-paranoid, symmetric encryption library.
A tutorial for how to use this library can be found in Crypto.TripleSec.Tutorial
Synopsis
- data TripleSec ba
- class (CanTripleSecDecrypt m, MonadRandom m) => CanTripleSec m where
- class MonadError TripleSecException m => CanTripleSecDecrypt m where
- decrypt :: ByteArray ba => ba -> ba -> m ba
- decryptWithCipher :: ByteArray ba => TripleSec ba -> ba -> m ba
- newCipherWithSalt :: ByteArray ba => ba -> ba -> m (TripleSec ba)
- data TripleSecException
- data CipherInitFailure
- data EncryptionFailure = ZeroLengthPlaintext
- data DecryptionFailure
- encryptIO :: ByteArray ba => ba -> ba -> IO ba
- decryptIO :: ByteArray ba => ba -> ba -> IO ba
- newCipherIO :: ByteArray ba => ba -> IO (TripleSec ba)
- newCipherWithSaltIO :: ByteArray ba => ba -> ba -> IO (TripleSec ba)
- encryptWithCipherIO :: ByteArray ba => TripleSec ba -> ba -> IO ba
- decryptWithCipherIO :: ByteArray ba => TripleSec ba -> ba -> IO ba
- type TripleSecIOM = TripleSecIOT IO
- data TripleSecIOT m a
- runTripleSecIO :: TripleSecIOT m a -> m (Either TripleSecException a)
- type TripleSecM = TripleSecT Identity
- data TripleSecT m a
- data SystemDRG
- getSystemDRG :: IO SystemDRG
- runTripleSecM :: TripleSecM a -> SystemDRG -> (Either TripleSecException a, SystemDRG)
- evalTripleSecM :: TripleSecM a -> SystemDRG -> Either TripleSecException a
- runTripleSecT :: TripleSecT m a -> SystemDRG -> m (Either TripleSecException a, SystemDRG)
- evalTripleSecT :: Functor m => TripleSecT m a -> SystemDRG -> m (Either TripleSecException a)
- type TripleSecDecryptM = TripleSecDecryptT Identity
- data TripleSecDecryptT m a
- runTripleSecDecryptM :: TripleSecDecryptM a -> Either TripleSecException a
- runTripleSecDecryptT :: TripleSecDecryptT m a -> m (Either TripleSecException a)
- checkPrefix :: (ByteArray ba, MonadError TripleSecException m) => ba -> m (ba, ba, ba)
- checkSalt :: (ByteArray ba, MonadError TripleSecException m) => ba -> m ()
- checkCipher :: (ByteArray ba, MonadError TripleSecException m) => TripleSec ba -> ba -> m ()
Cipher Type
TripleSec cipher used for encryption and decryption.
Dealing with this type is only necessary if you wish to use the somewhat lower-level API consisting of
encryptWithCipher and decryptWithCipher.
You can create a TripleSec cipher with newCipher or newCipherWithSalt.
Standard API
class (CanTripleSecDecrypt m, MonadRandom m) => CanTripleSec m where Source #
Represents the action of encrypting and decrypting with the TripleSec protocol.
Fully implemented with default functions. Any instances must provide a source of randomness and be an instance of
CanTripleSecDecrypt.
Minimal complete definition
Nothing
Methods
Arguments
| :: ByteArray ba | |
| => ba | Passphrase |
| -> ba | Plaintext |
| -> m ba | Ciphertext |
Encrypt a plaintext with a passphrase.
encrypt passphrase plaintext
Encrypt a plaintext with a TripleSec cipher.
This function allows encrypting multiple plaintexts without continually paying for the expensive key-derivation process. Please consider your use case and any risks that come from repeated usage of the same salt for encrypting different pieces of information.
For a simpler alternative, please see encrypt.
Create a new TripleSec cipher.
Instances
| Monad m => CanTripleSec (TripleSecT m) Source # | |
Defined in Crypto.TripleSec.Pure Methods encrypt :: ByteArray ba => ba -> ba -> TripleSecT m ba Source # encryptWithCipher :: ByteArray ba => TripleSec ba -> ba -> TripleSecT m ba Source # newCipher :: ByteArray ba => ba -> TripleSecT m (TripleSec ba) Source # | |
| MonadIO m => CanTripleSec (TripleSecIOT m) Source # | |
Defined in Crypto.TripleSec.IO Methods encrypt :: ByteArray ba => ba -> ba -> TripleSecIOT m ba Source # encryptWithCipher :: ByteArray ba => TripleSec ba -> ba -> TripleSecIOT m ba Source # newCipher :: ByteArray ba => ba -> TripleSecIOT m (TripleSec ba) Source # | |
class MonadError TripleSecException m => CanTripleSecDecrypt m where Source #
Represents the action of decrypting with the TripleSec protocol.
Fully implemented with default functions. Any instances must provide a way to represent failure with a
TripleSecException.
Minimal complete definition
Nothing
Methods
Arguments
| :: ByteArray ba | |
| => ba | Passphrase |
| -> ba | Ciphertext |
| -> m ba | Plaintext |
Decrypt a ciphertext with a passphrase.
decrypt passphrase ciphertext
Decrypt a ciphertext with a TripleSec cipher.
This function allows decrypting multiple ciphertexts without continually paying for the expensive key-derivation
process. This function will only work if the given cipher's salt matches that of the ciphertext, otherwise it
throws a MisMatchedCipherSalt.
For a simpler alternative, please see decrypt.
Create a new TripleSec cipher with a provided salt.
Creating a cipher with a specific salt is useful if you know you have several ciphertexts to decrypt, all of which were encrypted with the same cipher (salt + passphrase). Creating the cipher once up front allows you to save time, cpu, and memory by avoiding the expensive key-derivation on subsequent decryptions.
newCipherWithSalt passphrase salt
Instances
Exception Types
data TripleSecException Source #
Exceptions thrown by this library.
Constructors
| CipherInitException CipherInitFailure | |
| EncryptionException EncryptionFailure | |
| DecryptionException DecryptionFailure |
Instances
data CipherInitFailure Source #
Possible cipher initialization failures
Constructors
| ZeroLengthPassword | |
| InvalidSaltLength |
Instances
| Eq CipherInitFailure Source # | |
Defined in Crypto.TripleSec.Types Methods (==) :: CipherInitFailure -> CipherInitFailure -> Bool # (/=) :: CipherInitFailure -> CipherInitFailure -> Bool # | |
| Show CipherInitFailure Source # | |
Defined in Crypto.TripleSec.Types Methods showsPrec :: Int -> CipherInitFailure -> ShowS # show :: CipherInitFailure -> String # showList :: [CipherInitFailure] -> ShowS # | |
data EncryptionFailure Source #
Possible encryption failures
Constructors
| ZeroLengthPlaintext |
Instances
| Eq EncryptionFailure Source # | |
Defined in Crypto.TripleSec.Types Methods (==) :: EncryptionFailure -> EncryptionFailure -> Bool # (/=) :: EncryptionFailure -> EncryptionFailure -> Bool # | |
| Show EncryptionFailure Source # | |
Defined in Crypto.TripleSec.Types Methods showsPrec :: Int -> EncryptionFailure -> ShowS # show :: EncryptionFailure -> String # showList :: [EncryptionFailure] -> ShowS # | |
data DecryptionFailure Source #
Possible decryption Failures
Constructors
| InvalidCipherTextLength | |
| InvalidMagicBytes | |
| InvalidVersion | |
| InvalidSha512Hmac | |
| InvalidKeccakHmac | |
| MisMatchedCipherSalt |
Instances
| Eq DecryptionFailure Source # | |
Defined in Crypto.TripleSec.Types Methods (==) :: DecryptionFailure -> DecryptionFailure -> Bool # (/=) :: DecryptionFailure -> DecryptionFailure -> Bool # | |
| Show DecryptionFailure Source # | |
Defined in Crypto.TripleSec.Types Methods showsPrec :: Int -> DecryptionFailure -> ShowS # show :: DecryptionFailure -> String # showList :: [DecryptionFailure] -> ShowS # | |
Specialized IO API
encrypt specialized to IO. Throws instead of returning a TripleSecException.
decrypt specialized to IO. Throws instead of returning a TripleSecException.
newCipher specialized to IO. Throws instead of returning a TripleSecException.
newCipherWithSalt specialized to IO. Throws instead of returning a TripleSecException.
encryptWithCipher specialized to IO. Throws instead of returning a TripleSecException.
decryptWithCipher specialized to IO. Throws instead of returning a TripleSecException.
IO Based Monad API
type TripleSecIOM = TripleSecIOT IO Source #
Monad that works "out of the box" for encrypting/decrypting.
Does not throw exceptions (returns Either TripleSecException ba). Use with runTripleSecIO.
data TripleSecIOT m a Source #
Monad transformer for use with any IO based monad stack.
Does not throw exceptions (returns Either TripleSecException a). Use with runTripleSecIO.
Instances
runTripleSecIO :: TripleSecIOT m a -> m (Either TripleSecException a) Source #
Evaluate a TripleSecIOT computation.
Pure Monad API
type TripleSecM = TripleSecT Identity Source #
Monad that works "out of the box" for pure encrypting/decrypting.
Use with runTripleSecM or evalTripleSecM. SystemDRG can be obtained with getSystemDRG.
data TripleSecT m a Source #
Monad transformer for use with any non-IO based monad stack (See TripleSecIOT for IO based stacks).
Use with runTripleSecT or evalTripleSecT. SystemDRG can be obtained with getSystemDRG.
Instances
A referentially transparent System representation of the random evaluated out of the system.
Holding onto a specific DRG means that all the already evaluated bytes will be consistently replayed.
There's no need to reseed this DRG, as only pure entropy is represented here.
Instances
| DRG SystemDRG | |
Defined in Crypto.Random.SystemDRG | |
getSystemDRG :: IO SystemDRG #
Grab one instance of the System DRG
runTripleSecM :: TripleSecM a -> SystemDRG -> (Either TripleSecException a, SystemDRG) Source #
Evaluate a TripleSecM computation.
If you have no use for the output SystemDRG. See evalTripleSecM.
evalTripleSecM :: TripleSecM a -> SystemDRG -> Either TripleSecException a Source #
Evaluate a TripleSecM computation.
Do NOT re-use the input SystemDRG (very bad!). See runTripleSecM for an output SystemDRG that's safe to use
elsewhere.
runTripleSecT :: TripleSecT m a -> SystemDRG -> m (Either TripleSecException a, SystemDRG) Source #
Evaluate a TripleSecT computation.
If you have no use for the output SystemDRG. See evalTripleSecT.
evalTripleSecT :: Functor m => TripleSecT m a -> SystemDRG -> m (Either TripleSecException a) Source #
Evaluate a TripleSecT computation.
Do NOT re-use the input SystemDRG (very bad!). See runTripleSecT for an output SystemDRG that's safe to use
elsewhere.
Pure Decryption Only Monad API
type TripleSecDecryptM = TripleSecDecryptT Identity Source #
Monad that works "out of the box" for pure decrypting only.
Use with runTripleSecDecryptM. Useful as it does not require a source of randomness.
data TripleSecDecryptT m a Source #
Monad transformer for decryption only with any non-IO based monad stack (See TripleSecIOT for IO based stacks
as it's more powerful and just as easy to use).
Use with runTripleSecDecryptT. Useful as it does not require a source of randomness.
Instances
runTripleSecDecryptM :: TripleSecDecryptM a -> Either TripleSecException a Source #
Evaluate a TripleSecDecryptM computation.
runTripleSecDecryptT :: TripleSecDecryptT m a -> m (Either TripleSecException a) Source #
Evaluate a TripleSecDecryptT computation.
Low Level Utils
Arguments
| :: (ByteArray ba, MonadError TripleSecException m) | |
| => ba | Ciphertext |
| -> m (ba, ba, ba) | (TripleSec prefix, Salt, encrypted payload) |
Utility function to check that ciphertext is structurally valid and encrypted with a supported TripleSec version.
This function can be used for extracting the salt from a ciphertext to build a cipher with newCipherWithSalt. If
you know you've encrypted many things with the same cipher this lets you decrypt them all without continually paying
for the expensive key-derivation.
The only potentially useful output as a consumer of this library is the salt.
Arguments
| :: (ByteArray ba, MonadError TripleSecException m) | |
| => ba | Salt |
| -> m () |
Utility function to check salt length.
Arguments
| :: (ByteArray ba, MonadError TripleSecException m) | |
| => TripleSec ba | |
| -> ba | Salt |
| -> m () |