triplesec-0.1.1.0: TripleSec is a simple, triple-paranoid, symmetric encryption library

LicenseBSD-style
MaintainerSam Protas <sam.protas@gmail.com>
Stabilityexperimental
Portabilityunknown
Safe HaskellNone
LanguageHaskell2010

Crypto.TripleSec

Contents

Description

TripleSec is a simple, triple-paranoid, symmetric encryption library.

https://keybase.io/triplesec/

Synopsis

Cipher Type

data TripleSec ba Source #

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.

Methods

encrypt :: ByteArray ba => ba -> ba -> m ba Source #

Encrypt a plaintext with a passphrase.

 encrypt passphrase plaintext

encryptWithCipher :: ByteArray ba => TripleSec ba -> ba -> m ba Source #

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.

newCipher :: ByteArray ba => ba -> m (TripleSec ba) Source #

Create a new TripleSec cipher.

Instances

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.

Methods

decrypt :: ByteArray ba => ba -> ba -> m ba Source #

Decrypt a ciphertext with a passphrase.

 decrypt passphrase ciphertext

decryptWithCipher :: ByteArray ba => TripleSec ba -> ba -> m ba Source #

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.

newCipherWithSalt :: ByteArray ba => ba -> ba -> m (TripleSec ba) Source #

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

Specialized IO API

encryptIO Source #

Arguments

:: ByteArray ba 
=> ba

Passphrase

-> ba

Plaintext

-> IO ba 

encrypt specialized to IO. Throws instead of returning a TripleSecException.

decryptIO Source #

Arguments

:: ByteArray ba 
=> ba

Passphrase

-> ba

Ciphertext

-> IO ba 

decrypt specialized to IO. Throws instead of returning a TripleSecException.

newCipherIO Source #

Arguments

:: ByteArray ba 
=> ba

Passphrase

-> IO (TripleSec ba) 

newCipher specialized to IO. Throws instead of returning a TripleSecException.

newCipherWithSaltIO Source #

Arguments

:: ByteArray ba 
=> ba

Passphrase

-> ba

Salt

-> IO (TripleSec ba) 

newCipherWithSalt specialized to IO. Throws instead of returning a TripleSecException.

encryptWithCipherIO Source #

Arguments

:: ByteArray ba 
=> TripleSec ba 
-> ba

Ciphertext

-> IO ba 

encryptWithCipher specialized to IO. Throws instead of returning a TripleSecException.

decryptWithCipherIO Source #

Arguments

:: ByteArray ba 
=> TripleSec ba 
-> ba

Ciphertext

-> IO ba 

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

MonadTrans TripleSecIOT Source # 

Methods

lift :: Monad m => m a -> TripleSecIOT m a #

Monad m => MonadError TripleSecException (TripleSecIOT m) Source # 
Monad m => Monad (TripleSecIOT m) Source # 

Methods

(>>=) :: TripleSecIOT m a -> (a -> TripleSecIOT m b) -> TripleSecIOT m b #

(>>) :: TripleSecIOT m a -> TripleSecIOT m b -> TripleSecIOT m b #

return :: a -> TripleSecIOT m a #

fail :: String -> TripleSecIOT m a #

Functor m => Functor (TripleSecIOT m) Source # 

Methods

fmap :: (a -> b) -> TripleSecIOT m a -> TripleSecIOT m b #

(<$) :: a -> TripleSecIOT m b -> TripleSecIOT m a #

Monad m => Applicative (TripleSecIOT m) Source # 

Methods

pure :: a -> TripleSecIOT m a #

(<*>) :: TripleSecIOT m (a -> b) -> TripleSecIOT m a -> TripleSecIOT m b #

(*>) :: TripleSecIOT m a -> TripleSecIOT m b -> TripleSecIOT m b #

(<*) :: TripleSecIOT m a -> TripleSecIOT m b -> TripleSecIOT m a #

MonadIO m => MonadIO (TripleSecIOT m) Source # 

Methods

liftIO :: IO a -> TripleSecIOT m a #

MonadIO m => MonadRandom (TripleSecIOT m) Source # 

Methods

getRandomBytes :: ByteArray byteArray => Int -> TripleSecIOT m byteArray #

MonadIO m => CanTripleSec (TripleSecIOT m) Source # 

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 #

Monad m => CanTripleSecDecrypt (TripleSecIOT m) Source # 

Methods

decrypt :: ByteArray ba => ba -> ba -> TripleSecIOT m ba Source #

decryptWithCipher :: ByteArray ba => TripleSec ba -> ba -> TripleSecIOT m ba Source #

newCipherWithSalt :: ByteArray ba => ba -> ba -> TripleSecIOT m (TripleSec ba) Source #

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

MonadTrans TripleSecT Source # 

Methods

lift :: Monad m => m a -> TripleSecT m a #

Monad m => MonadError TripleSecException (TripleSecT m) Source # 
Monad m => Monad (TripleSecT m) Source # 

Methods

(>>=) :: TripleSecT m a -> (a -> TripleSecT m b) -> TripleSecT m b #

(>>) :: TripleSecT m a -> TripleSecT m b -> TripleSecT m b #

return :: a -> TripleSecT m a #

fail :: String -> TripleSecT m a #

Functor m => Functor (TripleSecT m) Source # 

Methods

fmap :: (a -> b) -> TripleSecT m a -> TripleSecT m b #

(<$) :: a -> TripleSecT m b -> TripleSecT m a #

Monad m => Applicative (TripleSecT m) Source # 

Methods

pure :: a -> TripleSecT m a #

(<*>) :: TripleSecT m (a -> b) -> TripleSecT m a -> TripleSecT m b #

(*>) :: TripleSecT m a -> TripleSecT m b -> TripleSecT m b #

(<*) :: TripleSecT m a -> TripleSecT m b -> TripleSecT m a #

Monad m => MonadRandom (TripleSecT m) Source # 

Methods

getRandomBytes :: ByteArray byteArray => Int -> TripleSecT m byteArray #

Monad m => CanTripleSec (TripleSecT m) Source # 

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 #

Monad m => CanTripleSecDecrypt (TripleSecT m) Source # 

Methods

decrypt :: ByteArray ba => ba -> ba -> TripleSecT m ba Source #

decryptWithCipher :: ByteArray ba => TripleSec ba -> ba -> TripleSecT m ba Source #

newCipherWithSalt :: ByteArray ba => ba -> ba -> TripleSecT m (TripleSec ba) Source #

data SystemDRG :: * #

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 

Methods

randomBytesGenerate :: ByteArray byteArray => Int -> SystemDRG -> (byteArray, 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.

Low Level Utils

checkPrefix Source #

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.

checkSalt Source #

Arguments

:: (ByteArray ba, MonadError TripleSecException m) 
=> ba

Salt

-> m () 

Utility function to check salt length.

checkCipher Source #

Arguments

:: (ByteArray ba, MonadError TripleSecException m) 
=> TripleSec ba 
-> ba

Salt

-> m () 

Utility function to check that the provided TripleSec was built with the provided salt.

This function does not confirm anything about the passphrase provided when the TripleSec cipher was created or the passphrase used to encrypt a ciphertext where the salt came from.