Copyright | (c) simplex.chat |
---|---|
License | AGPL-3 |
Maintainer | chat@simplex.chat |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
This module provides cryptography implementation for SMP protocols based on cryptonite package.
Synopsis
- class PrivateKey k where
- rsaPrivateKey :: k -> PrivateKey
- data SafePrivateKey
- newtype FullPrivateKey = FullPrivateKey {}
- newtype PublicKey = PublicKey {}
- type SafeKeyPair = (PublicKey, SafePrivateKey)
- type FullKeyPair = (PublicKey, FullPrivateKey)
- newtype KeyHash = KeyHash {}
- generateKeyPair :: PrivateKey k => Int -> IO (KeyPair k)
- publicKey :: FullPrivateKey -> PublicKey
- publicKeySize :: PublicKey -> Int
- validKeySize :: Int -> Bool
- safePrivateKey :: (Int, Integer, Integer) -> SafePrivateKey
- encrypt :: PublicKey -> Int -> ByteString -> ExceptT CryptoError IO ByteString
- decrypt :: PrivateKey k => k -> ByteString -> ExceptT CryptoError IO ByteString
- encryptOAEP :: PublicKey -> ByteString -> ExceptT CryptoError IO ByteString
- decryptOAEP :: PrivateKey k => k -> ByteString -> ExceptT CryptoError IO ByteString
- newtype Signature = Signature {}
- sign :: PrivateKey k => k -> ByteString -> ExceptT CryptoError IO Signature
- verify :: PublicKey -> Signature -> ByteString -> Bool
- newtype Key = Key {
- unKey :: ByteString
- newtype IV = IV {
- unIV :: ByteString
- encryptAES :: Key -> IV -> Int -> ByteString -> ExceptT CryptoError IO (AuthTag, ByteString)
- decryptAES :: Key -> IV -> ByteString -> AuthTag -> ExceptT CryptoError IO ByteString
- authTagSize :: Int
- authTagToBS :: AuthTag -> ByteString
- bsToAuthTag :: ByteString -> AuthTag
- randomAesKey :: IO Key
- randomIV :: IO IV
- aesKeyP :: Parser Key
- ivP :: Parser IV
- serializePrivKey :: PrivateKey k => k -> ByteString
- serializePubKey :: PublicKey -> ByteString
- encodePubKey :: PublicKey -> ByteString
- publicKeyHash :: PublicKey -> KeyHash
- privKeyP :: PrivateKey k => Parser k
- pubKeyP :: Parser PublicKey
- binaryPubKeyP :: Parser PublicKey
- sha256Hash :: ByteString -> ByteString
- data CryptoError
RSA keys
class PrivateKey k where Source #
Type-class used for both private key types: SafePrivateKey and FullPrivateKey.
rsaPrivateKey, _privateKey, mkPrivateKey
rsaPrivateKey :: k -> PrivateKey Source #
Instances
PrivateKey FullPrivateKey Source # | |
Defined in Simplex.Messaging.Crypto | |
PrivateKey SafePrivateKey Source # | |
Defined in Simplex.Messaging.Crypto |
data SafePrivateKey Source #
A newtype of PrivateKey
, with PublicKey removed.
It is not possible to recover PublicKey from SafePrivateKey. The constructor of this type is not exported.
Instances
Eq SafePrivateKey Source # | |
Defined in Simplex.Messaging.Crypto (==) :: SafePrivateKey -> SafePrivateKey -> Bool # (/=) :: SafePrivateKey -> SafePrivateKey -> Bool # | |
Show SafePrivateKey Source # | |
Defined in Simplex.Messaging.Crypto showsPrec :: Int -> SafePrivateKey -> ShowS # show :: SafePrivateKey -> String # showList :: [SafePrivateKey] -> ShowS # | |
FromField SafePrivateKey Source # | |
Defined in Simplex.Messaging.Crypto | |
ToField SafePrivateKey Source # | |
Defined in Simplex.Messaging.Crypto toField :: SafePrivateKey -> SQLData # | |
PrivateKey SafePrivateKey Source # | |
Defined in Simplex.Messaging.Crypto |
newtype FullPrivateKey Source #
A newtype of PrivateKey
(with PublicKey inside).
Instances
Eq FullPrivateKey Source # | |
Defined in Simplex.Messaging.Crypto (==) :: FullPrivateKey -> FullPrivateKey -> Bool # (/=) :: FullPrivateKey -> FullPrivateKey -> Bool # | |
Show FullPrivateKey Source # | |
Defined in Simplex.Messaging.Crypto showsPrec :: Int -> FullPrivateKey -> ShowS # show :: FullPrivateKey -> String # showList :: [FullPrivateKey] -> ShowS # | |
IsString FullPrivateKey Source # | |
Defined in Simplex.Messaging.Crypto fromString :: String -> FullPrivateKey # | |
PrivateKey FullPrivateKey Source # | |
Defined in Simplex.Messaging.Crypto |
A newtype of PublicKey
.
type SafeKeyPair = (PublicKey, SafePrivateKey) Source #
Tuple of RSA PublicKey
and SafePrivateKey
.
type FullKeyPair = (PublicKey, FullPrivateKey) Source #
Tuple of RSA PublicKey
and FullPrivateKey
.
Key hash newtype.
generateKeyPair :: PrivateKey k => Int -> IO (KeyPair k) Source #
Generate RSA key pair with either SafePrivateKey or FullPrivateKey.
publicKey :: FullPrivateKey -> PublicKey Source #
publicKeySize :: PublicKey -> Int Source #
validKeySize :: Int -> Bool Source #
safePrivateKey :: (Int, Integer, Integer) -> SafePrivateKey Source #
Construct SafePrivateKey
from three numbers - used internally and in the tests.
E2E hybrid encryption scheme
encrypt :: PublicKey -> Int -> ByteString -> ExceptT CryptoError IO ByteString Source #
E2E encrypt SMP agent messages.
https://github.com/simplex-chat/simplexmq/blob/master/rfcs/2021-01-26-crypto.md#e2e-encryption
decrypt :: PrivateKey k => k -> ByteString -> ExceptT CryptoError IO ByteString Source #
E2E decrypt SMP agent messages.
https://github.com/simplex-chat/simplexmq/blob/master/rfcs/2021-01-26-crypto.md#e2e-encryption
RSA OAEP encryption
encryptOAEP :: PublicKey -> ByteString -> ExceptT CryptoError IO ByteString Source #
RSA OAEP encryption.
Used as part of hybrid E2E encryption scheme and for SMP transport handshake.
decryptOAEP :: PrivateKey k => k -> ByteString -> ExceptT CryptoError IO ByteString Source #
RSA OAEP decryption.
Used as part of hybrid E2E encryption scheme and for SMP transport handshake.
RSA PSS signing
RSA signature newtype.
sign :: PrivateKey k => k -> ByteString -> ExceptT CryptoError IO Signature Source #
RSA PSS message signing.
Used by SMP clients to sign SMP commands and by SMP agents to sign messages.
verify :: PublicKey -> Signature -> ByteString -> Bool Source #
RSA PSS signature verification.
Used by SMP servers to authorize SMP commands and by SMP agents to verify messages.
AES256 AEAD-GCM scheme
encryptAES :: Key -> IV -> Int -> ByteString -> ExceptT CryptoError IO (AuthTag, ByteString) Source #
AEAD-GCM encryption.
Used as part of hybrid E2E encryption scheme and for SMP transport blocks encryption.
decryptAES :: Key -> IV -> ByteString -> AuthTag -> ExceptT CryptoError IO ByteString Source #
AEAD-GCM decryption.
Used as part of hybrid E2E encryption scheme and for SMP transport blocks decryption.
authTagSize :: Int Source #
authTagToBS :: AuthTag -> ByteString Source #
Convert AEAD AuthTag
to ByteString.
bsToAuthTag :: ByteString -> AuthTag Source #
Convert ByteString to AEAD AuthTag
.
randomAesKey :: IO Key Source #
Random AES256 key.
Encoding of RSA keys
serializePrivKey :: PrivateKey k => k -> ByteString Source #
Base-64 PKCS8 encoding of PSA private key.
Not used as part of SMP protocols.
serializePubKey :: PublicKey -> ByteString Source #
Base-64 X509 encoding of RSA public key.
Used as part of SMP queue information (out-of-band message).
encodePubKey :: PublicKey -> ByteString Source #
publicKeyHash :: PublicKey -> KeyHash Source #
Digest (hash) of binary X509 encoding of RSA public key.
privKeyP :: PrivateKey k => Parser k Source #
SHA256 hash
sha256Hash :: ByteString -> ByteString Source #
SHA256 digest.
Cryptography error type
data CryptoError Source #
Various cryptographic or related errors.
RSAEncryptError Error | RSA OAEP encryption error |
RSADecryptError Error | RSA OAEP decryption error |
RSASignError Error | RSA PSS signature error |
AESCipherError CryptoError | AES initialization error |
CryptoIVError | IV generation error |
AESDecryptError | AES decryption error |
CryptoLargeMsgError | message does not fit in SMP block |
CryptoHeaderError String | failure parsing RSA-encrypted message header |
Instances
Eq CryptoError Source # | |
Defined in Simplex.Messaging.Crypto (==) :: CryptoError -> CryptoError -> Bool # (/=) :: CryptoError -> CryptoError -> Bool # | |
Show CryptoError Source # | |
Defined in Simplex.Messaging.Crypto showsPrec :: Int -> CryptoError -> ShowS # show :: CryptoError -> String # showList :: [CryptoError] -> ShowS # | |
Exception CryptoError Source # | |
Defined in Simplex.Messaging.Crypto |