sel
Copyright(C) Hécate Moonlight 2022
LicenseBSD-3-Clause
MaintainerThe Haskell Cryptography Group
PortabilityGHC only
Safe HaskellNone
LanguageHaskell2010

Sel.SecretKey.Cipher

Description

 
Synopsis

Introduction

"Authenticated Encryption" uses a secret key along with a single-use number called a "nonce" to encrypt a message. The resulting ciphertext is accompanied by an authentication tag.

Encryption is done with the XSalsa20 stream cipher and authentication is done with the Poly1305 MAC hash.

Usage

import qualified Sel.SecretKey.Cipher as Cipher
import Sel (secureMain)

main = secureMain $ do
  -- We get the secretKey from the other party or with 'newSecretKey'.
  -- We get the nonce from the other party with the message, or with 'encrypt' and our own message.
  -- Do not reuse a nonce with the same secret key!
  (nonce, encryptedMessage) <- Cipher.encrypt "hello hello" secretKey
  let result = Cipher.decrypt encryptedMessage secretKey nonce
  print result
  -- "Just \"hello hello\""

Encryption and Decryption

encrypt Source #

Arguments

:: StrictByteString

Message to encrypt.

-> SecretKey

Secret key generated with newSecretKey.

-> IO (Nonce, Ciphertext) 

Create an authenticated ciphertext from a message, a secret key, and a one-time cryptographic nonce that must never be re-used with the same secret key to encrypt another message.

Since: 0.0.1.0

decrypt Source #

Arguments

:: Ciphertext

Encrypted message you want to decrypt.

-> SecretKey

Secret key used for encrypting the original message.

-> Nonce

Nonce used for encrypting the original message.

-> Maybe StrictByteString 

Decrypt an encrypted and authenticated message with the shared secret key and the one-time cryptographic nonce.

Since: 0.0.1.0

Secret Key

data SecretKey Source #

A secret key of size cryptoSecretboxKeyBytes.

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

Eq SecretKey Source #

Since: 0.0.1.0

Instance details

Defined in Sel.SecretKey.Cipher

Ord SecretKey Source #

Since: 0.0.1.0

Instance details

Defined in Sel.SecretKey.Cipher

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

Since: 0.0.1.0

Instance details

Defined in Sel.SecretKey.Cipher

newSecretKey :: IO SecretKey Source #

Generate a new random secret key.

Since: 0.0.1.0

secretKeyFromHexByteString :: 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 cryptoSecretboxKeyBytes.

Since: 0.0.1.0

unsafeSecretKeyToHexByteString :: SecretKey -> StrictByteString Source #

Convert a SecretKey to a hexadecimal-encoded StrictByteString in constant time.

⚠️ Be prudent as to where you store it!

Since: 0.0.1.0

Nonce

data Nonce Source #

A random number that must only be used once per exchanged message. It does not have to be confidential. It is of size cryptoSecretboxNonceBytes.

Since: 0.0.1.0

Instances

Instances details
Show Nonce Source #

Since: 0.0.1.0

Instance details

Defined in Sel.SecretKey.Cipher

Methods

showsPrec :: Int -> Nonce -> ShowS #

show :: Nonce -> String #

showList :: [Nonce] -> ShowS #

Eq Nonce Source #

Since: 0.0.1.0

Instance details

Defined in Sel.SecretKey.Cipher

Methods

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

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

Ord Nonce Source #

Since: 0.0.1.0

Instance details

Defined in Sel.SecretKey.Cipher

Methods

compare :: Nonce -> Nonce -> Ordering #

(<) :: Nonce -> Nonce -> Bool #

(<=) :: Nonce -> Nonce -> Bool #

(>) :: Nonce -> Nonce -> Bool #

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

max :: Nonce -> Nonce -> Nonce #

min :: Nonce -> Nonce -> Nonce #

Display Nonce Source #

Since: 0.0.1.0

Instance details

Defined in Sel.SecretKey.Cipher

nonceFromHexByteString :: StrictByteString -> Either Text Nonce Source #

Create a Nonce from a binary StrictByteString that you have obtained on your own, usually from the network or disk. Once decoded from hexadecimal, it must be of length cryptoSecretboxNonceBytes.

Since: 0.0.1.0

nonceToHexByteString :: Nonce -> StrictByteString Source #

Convert a Nonce to a hexadecimal-encoded StrictByteString in constant time.

Since: 0.0.1.0

Ciphertext

data Ciphertext Source #

A ciphertext consisting of an encrypted message and an authentication tag.

Since: 0.0.1.0

Instances

Instances details
Show Ciphertext Source #

⚠️ Be prudent as to what you do with it!

Since: 0.0.1.0

Instance details

Defined in Sel.SecretKey.Cipher

Eq Ciphertext Source #

Since: 0.0.1.0

Instance details

Defined in Sel.SecretKey.Cipher

Ord Ciphertext Source #

Since: 0.0.1.0

Instance details

Defined in Sel.SecretKey.Cipher

Display Ciphertext Source #

⚠️ Be prudent as to what you do with it!

Since: 0.0.1.0

Instance details

Defined in Sel.SecretKey.Cipher

ciphertextFromHexByteString :: StrictByteString -> Either Text Ciphertext Source #

Create a Ciphertext from a hexadecimal-encoded StrictByteString that you have obtained on your own, usually from the network or disk. It must be a valid ciphertext built from the concatenation of the encrypted message and the authentication tag.

The input ciphertext must at least of length cryptoSecretboxMACBytes.

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 -> StrictByteString Source #

Convert a Ciphertext to a hexadecimal-encoded StrictByteString in constant time.

⚠️ Be prudent as to where you store it!

Since: 0.0.1.0

ciphertextToHexText :: Ciphertext -> Text Source #

Convert a Ciphertext to a hexadecimal-encoded Text.

⚠️ Be prudent as to where you store it!

Since: 0.0.1.0