Copyright | (C) Hécate Moonlight 2022 |
---|---|
License | BSD-3-Clause |
Maintainer | The Haskell Cryptography Group |
Portability | GHC only |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Synopsis
- newKeyPair :: IO (PublicKey, SecretKey)
- newtype SecretKey = SecretKey (ForeignPtr CUChar)
- unsafeSecretKeyToHexByteString :: SecretKey -> StrictByteString
- newtype PublicKey = PublicKey (ForeignPtr CUChar)
- publicKeyToHexByteString :: PublicKey -> StrictByteString
- keyPairFromHexByteStrings :: StrictByteString -> StrictByteString -> Either Text (PublicKey, SecretKey)
- newtype Nonce = Nonce (ForeignPtr CUChar)
- nonceFromHexByteString :: StrictByteString -> Either Text Nonce
- nonceToHexByteString :: Nonce -> StrictByteString
- data CipherText = CipherText {}
- cipherTextFromHexByteString :: StrictByteString -> Either Text CipherText
- cipherTextToHexText :: CipherText -> Text
- cipherTextToHexByteString :: CipherText -> StrictByteString
- cipherTextToBinary :: CipherText -> StrictByteString
- encrypt :: StrictByteString -> PublicKey -> SecretKey -> IO (Nonce, CipherText)
- decrypt :: CipherText -> PublicKey -> SecretKey -> Nonce -> Maybe StrictByteString
- data KeyPairGenerationException = KeyPairGenerationException
- data EncryptionError = EncryptionError
Introduction
Public-key authenticated encryption allows a sender to encrypt a confidential message specifically for the recipient, using the recipient's public key.
Usage
import qualified Sel.PublicKey.Cipher as Cipher main = do -- We get the sender their pair of keys: (senderSecretKey, senderPublicKey) <- newKeyPair -- We get the nonce from the other party with the message, or with 'encrypt' and our own message. (nonce, encryptedMessage) <- Cipher.encrypt "hello hello" secretKey let result = Cipher.decrypt encryptedMessage secretKey nonce print result -- "Just \"hello hello\""
Key pair generation
newKeyPair :: IO (PublicKey, SecretKey) Source #
Generate a new random secret key.
May throw KeyPairGenerationException
if the generation fails.
Since: 0.0.1.0
A secret key of size cryptoBoxSecretKeyBytes
.
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.PublicKey.Cipher | |
Display SecretKey Source # | display secretKey == "[REDACTED]" Since: 0.0.1.0 |
Defined in Sel.PublicKey.Cipher displayBuilder :: SecretKey -> Builder # displayList :: [SecretKey] -> Builder # displayPrec :: Int -> SecretKey -> Builder # |
unsafeSecretKeyToHexByteString :: SecretKey -> StrictByteString Source #
Convert a SecretKey
to a hexadecimal-encoded StrictByteString
.
⚠️ Be prudent as to where you store it!
Since: 0.0.1.0
A public key of size cryptoBoxPublicKeyBytes
.
Since: 0.0.1.0
Instances
Show PublicKey Source # | Since: 0.0.1.0 |
Eq PublicKey Source # | Since: 0.0.1.0 |
Ord PublicKey Source # | Since: 0.0.1.0 |
Defined in Sel.PublicKey.Cipher | |
Display PublicKey Source # | Since: 0.0.1.0 |
Defined in Sel.PublicKey.Cipher displayBuilder :: PublicKey -> Builder # displayList :: [PublicKey] -> Builder # displayPrec :: Int -> PublicKey -> Builder # |
publicKeyToHexByteString :: PublicKey -> StrictByteString Source #
Convert a PublicKey
to a hexadecimal-encoded StrictByteString
.
Since: 0.0.1.0
keyPairFromHexByteStrings Source #
:: StrictByteString | Public key |
-> StrictByteString | Secret key |
-> Either Text (PublicKey, SecretKey) |
Create a pair of SecretKey
and PublicKey
from hexadecimal-encoded
StrictByteString
s that you have obtained on your own, usually from the network or disk.
The public and secret keys, once decoded from base16, must respectively
be at least of length cryptoBoxPublicKeyBytes
and 'cryptoBoxSecretKeyBytes.
Since: 0.0.1.0
Nonce
Convert a SecretKey
to a hexadecimal-encoded StrictByteString
.
⚠️ Be prudent as to where you store it!
A random number that must only be used once per exchanged message.
It does not have to be confidential.
It is of size cryptoBoxNonceBytes
.
Since: 0.0.1.0
nonceFromHexByteString :: StrictByteString -> Either Text Nonce Source #
Create a Nonce
from a hexadecimal-encoded StrictByteString
that you have obtained
on your own, usually from the network or disk.
Since: 0.0.1.0
nonceToHexByteString :: Nonce -> StrictByteString Source #
Convert a Nonce
to a hexadecimal-encoded StrictByteString
.
Since: 0.0.1.0
Cipher text
data CipherText Source #
A ciphertext consisting of an encrypted message and an authentication tag.
Since: 0.0.1.0
Instances
Show CipherText Source # | ⚠️ Be prudent as to what you do with it! Since: 0.0.1.0 |
Defined in Sel.PublicKey.Cipher showsPrec :: Int -> CipherText -> ShowS # show :: CipherText -> String # showList :: [CipherText] -> ShowS # | |
Eq CipherText Source # | Since: 0.0.1.0 |
Defined in Sel.PublicKey.Cipher (==) :: CipherText -> CipherText -> Bool # (/=) :: CipherText -> CipherText -> Bool # | |
Ord CipherText Source # | Since: 0.0.1.0 |
Defined in Sel.PublicKey.Cipher 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 # | ⚠️ Be prudent as to what you do with it! Since: 0.0.1.0 |
Defined in Sel.PublicKey.Cipher displayBuilder :: CipherText -> Builder # displayList :: [CipherText] -> Builder # displayPrec :: Int -> CipherText -> Builder # |
cipherTextFromHexByteString :: 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 cipherText built from the concatenation
of the encrypted message and the authentication tag.
The input cipher text, once decoded from base16, must be at least of length
cryptoBoxMACBytes
.
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
cipherTextToHexByteString :: CipherText -> StrictByteString Source #
Convert a CipherText
to a hexadecimal-encoded StrictByteString
.
⚠️ Be prudent as to where you store it!
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
Encryption and Decryption
:: StrictByteString | Message to encrypt. |
-> PublicKey | Public key of the recipient |
-> SecretKey | Secret key of the sender |
-> IO (Nonce, CipherText) |
Create an authenticated CipherText
from a message, a SecretKey
,
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
:: CipherText | Encrypted message you want to decrypt. |
-> PublicKey | Public key of the sender. |
-> SecretKey | Secret key of the recipient. |
-> Nonce | Nonce used for encrypting the original message. |
-> Maybe StrictByteString |
Decrypt a CipherText
and authenticated message with the shared
secret key and the one-time cryptographic nonce.
Since: 0.0.1.0
Errors
data KeyPairGenerationException Source #
Exception thrown upon error during the generation of
the key pair by newKeyPair
.
Since: 0.0.1.0
Instances
data EncryptionError Source #
Exception thrown upon error during the encryption
of the message by encrypt
.
Since: 0.0.1.0
Instances
Exception EncryptionError Source # | |
Defined in Sel.PublicKey.Cipher | |
Show EncryptionError Source # | |
Defined in Sel.PublicKey.Cipher showsPrec :: Int -> EncryptionError -> ShowS # show :: EncryptionError -> String # showList :: [EncryptionError] -> ShowS # | |
Eq EncryptionError Source # | |
Defined in Sel.PublicKey.Cipher (==) :: EncryptionError -> EncryptionError -> Bool # (/=) :: EncryptionError -> EncryptionError -> Bool # | |
Ord EncryptionError Source # | |
Defined in Sel.PublicKey.Cipher compare :: EncryptionError -> EncryptionError -> Ordering # (<) :: EncryptionError -> EncryptionError -> Bool # (<=) :: EncryptionError -> EncryptionError -> Bool # (>) :: EncryptionError -> EncryptionError -> Bool # (>=) :: EncryptionError -> EncryptionError -> Bool # max :: EncryptionError -> EncryptionError -> EncryptionError # min :: EncryptionError -> EncryptionError -> EncryptionError # |