sel-0.0.1.0: Cryptography for the casual user
Copyright(C) Hécate Moonlight 2024
LicenseBSD-3-Clause
MaintainerThe Haskell Cryptography Group
PortabilityGHC only
Safe HaskellSafe-Inferred
LanguageHaskell2010

Sel.SecretKey.Stream

Description

 
Synopsis

Introduction

This high-level API encrypts a sequence of messages, or a single message split into an arbitrary number of chunks, using a secret key, with the following properties:

  • Messages cannot be truncated, removed, reordered, duplicated or modified without this being detected by the decryption functions.
  • The same sequence encrypted twice will produce different ciphertexts.
  • An authentication tag is added to each encrypted message: stream corruption will be detected early, without having to read the stream until the end.
  • Each message can include additional data (ex: timestamp, protocol version) in the computation of the authentication tag.
  • Messages can have different sizes.
  • There are no practical limits to the total length of the stream, or to the total number of individual messages.

It uses the XChaCha20-Poly1305 algorithm.

Usage

>>> secretKey <- Stream.newSecretKey
>>> (header, cipherTexts) <- Stream.encryptStream secretKey $ \multipartState -> do -- we are in MonadIO
...   message1 <- getMessage -- This is your way to fetch a message from outside
...   encryptedChunk1 <- Stream.encryptChunk multipartState Stream.messag message1
...   message2 <- getMessage
...   encryptedChunk2 <- Stream.encryptChunk multipartState Stream.Final message2
...   pure [encryptedChunk1, encryptedChunk2]
>>> result <- Stream.decryptStream secretKey header $ \multipartState-> do
...    forM encryptedMessages $ \cipherText -> do
...      decryptChunk multipartState cipherText

Stream operations

Linked List operations

encryptList :: forall m. MonadIO m => SecretKey -> [StrictByteString] -> m (Header, [CipherText]) Source #

Perform streaming encryption of a finite list.

This function can throw StreamEncryptionException upon an error in the underlying implementation.

Since: 0.0.1.0

decryptList :: forall m. MonadIO m => SecretKey -> Header -> [CipherText] -> m (Maybe [StrictByteString]) Source #

Perform streaming decryption of a finite Linked List.

This function can throw StreamDecryptionException if the chunk is invalid, incomplete, or corrupted.

Since: 0.0.1.0

Chunk operations

data Multipart s Source #

Multipart is the cryptographic context for stream encryption.

Since: 0.0.1.0

encryptStream Source #

Arguments

:: forall (a :: Type) (m :: Type -> Type). MonadIO m 
=> SecretKey

Generated with newSecretKey.

-> (forall s. Multipart s -> m a)

Continuation that gives you access to a Multipart cryptographic context

-> m (Header, a) 

Perform streaming hashing with a Multipart cryptographic context.

Use encryptChunk within the continuation.

The context is safely allocated first, then the continuation is run and then it is deallocated after that.

Since: 0.0.1.0

encryptChunk Source #

Arguments

:: forall m s. MonadIO m 
=> Multipart s

Cryptographic context

-> MessageTag

Tag that will be associated with the message. See the documentation of MessageTag to know which to choose when.

-> StrictByteString

Message to encrypt.

-> m CipherText 

Add a message portion (chunk) to be encrypted.

Use it within encryptStream.

This function can throw StreamEncryptionException upon an error in the underlying implementation.

Since: 0.0.1.0

decryptStream Source #

Arguments

:: forall (a :: Type) (m :: Type -> Type). MonadIO m 
=> SecretKey 
-> Header

Header used by the encrypting party. See its documentation

-> (forall s. Multipart s -> m a)

Continuation that gives you access to a Multipart cryptographic context

-> m (Maybe a) 

Perform streaming decryption with a Multipart cryptographic context.

Use decryptChunk within the continuation.

The context is safely allocated first, then the continuation is run and then it is deallocated after that.

Since: 0.0.1.0

decryptChunk Source #

Arguments

:: forall m s. MonadIO m 
=> Multipart s

Cryptographic context

-> CipherText

Encrypted message portion to decrypt

-> m StrictByteString

Decrypted message portion

Add a message portion (chunk) to be decrypted.

Use this function within decryptStream.

This function can throw StreamDecryptionException if the chunk is invalid, incomplete, or corrupted.

Since: 0.0.1.0

Secret Key

data SecretKey Source #

A secret key of size cryptoSecretStreamXChaCha20Poly1305KeyBytes.

Since: 0.0.1.0

Instances

Instances details
Show SecretKey Source #
show secretKey == "[REDACTED]"

Since: 0.0.1.0

Instance details

Defined in Sel.SecretKey.Stream

Eq SecretKey Source #

Since: 0.0.1.0

Instance details

Defined in Sel.SecretKey.Stream

Ord SecretKey Source #

Since: 0.0.1.0

Instance details

Defined in Sel.SecretKey.Stream

Display SecretKey Source #
display secretKey == "[REDACTED]"

Since: 0.0.1.0

Instance details

Defined in Sel.SecretKey.Stream

newSecretKey :: IO SecretKey Source #

Generate a new random secret key.

Since: 0.0.1.0

secretKeyFromHexByteString :: Base16 StrictByteString -> Either Text SecretKey Source #

Create a SecretKey from a binary StrictByteString that you have obtained on your own, usually from the network or disk.

The input secret key, once decoded from base16, must be of length cryptoSecretStreamXChaCha20Poly1305KeyBytes.

Since: 0.0.1.0

unsafeSecretKeyToHexByteString :: SecretKey -> Base16 StrictByteString Source #

Convert a SecretKey to a hexadecimal-encoded StrictByteString.

⚠️ Be prudent as to where you store it!

Since: 0.0.1.0

Header

data Header Source #

An encrypted stream starts with a Header of size cryptoSecretStreamXChaCha20Poly1305HeaderBytes.

That header must be sent/stored before the sequence of encrypted messages, as it is required to decrypt the stream.

The header content doesn’t have to be secret and decryption with a different header will fail.

Since: 0.0.1.0

Instances

Instances details
Show Header Source #

Since: 0.0.1.0

Instance details

Defined in Sel.SecretKey.Stream

Eq Header Source #

Since: 0.0.1.0

Instance details

Defined in Sel.SecretKey.Stream

Methods

(==) :: Header -> Header -> Bool #

(/=) :: Header -> Header -> Bool #

Ord Header Source #

Since: 0.0.1.0

Instance details

Defined in Sel.SecretKey.Stream

Display Header Source #

Since: 0.0.1.0

Instance details

Defined in Sel.SecretKey.Stream

headerToHexByteString :: Header -> Base16 StrictByteString Source #

Convert a Header to a hexadecimal-encoded StrictByteString

Since: 0.0.1.0

Message Tags

data MessageTag Source #

Each encrypted message is associated with a tag.

A typical encrypted stream simply attaches Message as a tag to all messages, except the last one which is tagged as Final.

Since: 0.0.1.0

Constructors

Message

The most common tag, that doesn’t add any information about the nature of the message.

Final

Indicates that the message marks the end of the stream, and erases the secret key used to encrypt the previous sequence.

Push

Indicates that the message marks the end of a set of messages, but not the end of the stream.

Rekey

“Forget” the key used to encrypt this message and the previous ones, and derive a new secret key.

CipherText

data CipherText Source #

An encrypted message. It is guaranteed to be of size: original_message_length + cryptoSecretStreamXChaCha20Poly1305ABytes

Since: 0.0.1.0

Instances

Instances details
Show CipherText Source #

Since: 0.0.1.0

Instance details

Defined in Sel.SecretKey.Stream

Eq CipherText Source #

Since: 0.0.1.0

Instance details

Defined in Sel.SecretKey.Stream

Ord CipherText Source #

Since: 0.0.1.0

Instance details

Defined in Sel.SecretKey.Stream

Display CipherText Source #

Since: 0.0.1.0

Instance details

Defined in Sel.SecretKey.Stream

ciphertextFromHexByteString :: Base16 StrictByteString -> Either Text CipherText Source #

Create a CipherText from a binary StrictByteString that you have obtained on your own, usually from the network or disk. It must be a valid hash built from the concatenation of the encrypted message and the authentication tag.

The input hash must at least of length cryptoSecretStreamXChaCha20Poly1305ABytes

Since: 0.0.1.0

ciphertextToBinary :: CipherText -> StrictByteString Source #

Convert a CipherText to a binary StrictByteString.

⚠️ Be prudent as to where you store it!

Since: 0.0.1.0

ciphertextToHexByteString :: CipherText -> Base16 StrictByteString Source #

Convert a CipherText to a hexadecimal-encoded StrictByteString.

⚠️ Be prudent as to where you store it!

Since: 0.0.1.0

ciphertextToHexText :: CipherText -> Base16 Text Source #

Convert a CipherText to a hexadecimal-encoded Text.

⚠️ Be prudent as to where you store it!

Since: 0.0.1.0

Exceptions

data StreamInitEncryptionException Source #

Since: 0.0.1.0

Instances

Instances details
Exception StreamInitEncryptionException Source # 
Instance details

Defined in Sel.SecretKey.Stream

Show StreamInitEncryptionException Source # 
Instance details

Defined in Sel.SecretKey.Stream

Eq StreamInitEncryptionException Source # 
Instance details

Defined in Sel.SecretKey.Stream

Ord StreamInitEncryptionException Source # 
Instance details

Defined in Sel.SecretKey.Stream