Copyright | (C) Hécate Moonlight 2024 |
---|---|
License | BSD-3-Clause |
Maintainer | The Haskell Cryptography Group |
Portability | GHC only |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Synopsis
- encryptList :: forall m. MonadIO m => SecretKey -> [StrictByteString] -> m (Header, [CipherText])
- decryptList :: forall m. MonadIO m => SecretKey -> Header -> [CipherText] -> m (Maybe [StrictByteString])
- data Multipart s
- encryptStream :: forall (a :: Type) (m :: Type -> Type). MonadIO m => SecretKey -> (forall s. Multipart s -> m a) -> m (Header, a)
- encryptChunk :: forall m s. MonadIO m => Multipart s -> MessageTag -> StrictByteString -> m CipherText
- decryptStream :: forall (a :: Type) (m :: Type -> Type). MonadIO m => SecretKey -> Header -> (forall s. Multipart s -> m a) -> m (Maybe a)
- decryptChunk :: forall m s. MonadIO m => Multipart s -> CipherText -> m StrictByteString
- data SecretKey
- newSecretKey :: IO SecretKey
- secretKeyFromHexByteString :: Base16 StrictByteString -> Either Text SecretKey
- unsafeSecretKeyToHexByteString :: SecretKey -> Base16 StrictByteString
- data Header
- headerToHexByteString :: Header -> Base16 StrictByteString
- headerFromHexByteString :: Base16 StrictByteString -> Either Text Header
- data MessageTag
- data CipherText
- ciphertextFromHexByteString :: Base16 StrictByteString -> Either Text CipherText
- ciphertextToBinary :: CipherText -> StrictByteString
- ciphertextToHexByteString :: CipherText -> Base16 StrictByteString
- ciphertextToHexText :: CipherText -> Base16 Text
- data StreamInitEncryptionException
- data StreamEncryptionException
- data StreamDecryptionException
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
Multipart
is the cryptographic context for stream encryption.
Since: 0.0.1.0
:: forall (a :: Type) (m :: Type -> Type). MonadIO m | |
=> SecretKey | Generated with |
-> (forall s. Multipart s -> m a) | Continuation that gives you access to a |
-> 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
:: forall m s. MonadIO m | |
=> Multipart s | Cryptographic context |
-> MessageTag | Tag that will be associated with the message. See the documentation of |
-> 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
:: 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 |
-> 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
:: 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
A secret key of size cryptoSecretStreamXChaCha20Poly1305KeyBytes
.
Since: 0.0.1.0
Instances
Show SecretKey Source # | show secretKey == "[REDACTED]" Since: 0.0.1.0 |
Eq SecretKey Source # | Since: 0.0.1.0 |
Ord SecretKey Source # | Since: 0.0.1.0 |
Defined in Sel.SecretKey.Stream | |
Display SecretKey Source # | display secretKey == "[REDACTED]" Since: 0.0.1.0 |
Defined in Sel.SecretKey.Stream displayBuilder :: SecretKey -> Builder # displayList :: [SecretKey] -> Builder # displayPrec :: Int -> SecretKey -> Builder # |
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
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
headerToHexByteString :: Header -> Base16 StrictByteString Source #
Convert a Header
to a hexadecimal-encoded StrictByteString
Since: 0.0.1.0
headerFromHexByteString :: Base16 StrictByteString -> Either Text Header Source #
Build a Header
from a base16-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
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
Show CipherText Source # | Since: 0.0.1.0 |
Defined in Sel.SecretKey.Stream showsPrec :: Int -> CipherText -> ShowS # show :: CipherText -> String # showList :: [CipherText] -> ShowS # | |
Eq CipherText Source # | Since: 0.0.1.0 |
Defined in Sel.SecretKey.Stream (==) :: CipherText -> CipherText -> Bool # (/=) :: CipherText -> CipherText -> Bool # | |
Ord CipherText Source # | Since: 0.0.1.0 |
Defined in Sel.SecretKey.Stream compare :: CipherText -> CipherText -> Ordering # (<) :: CipherText -> CipherText -> Bool # (<=) :: CipherText -> CipherText -> Bool # (>) :: CipherText -> CipherText -> Bool # (>=) :: CipherText -> CipherText -> Bool # max :: CipherText -> CipherText -> CipherText # min :: CipherText -> CipherText -> CipherText # | |
Display CipherText Source # | Since: 0.0.1.0 |
Defined in Sel.SecretKey.Stream displayBuilder :: CipherText -> Builder # displayList :: [CipherText] -> Builder # displayPrec :: Int -> CipherText -> Builder # |
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
data StreamEncryptionException Source #
Since: 0.0.1.0
Instances
data StreamDecryptionException Source #
Since: 0.0.1.0