Safe Haskell | None |
---|---|
Language | Haskell2010 |
Internal functions for encrypting and signing / decrypting and verifying JWT content.
Synopsis
- hmacSign :: JwsAlg -> ByteString -> ByteString -> Either JwtError ByteString
- hmacVerify :: JwsAlg -> ByteString -> ByteString -> ByteString -> Bool
- ed25519Verify :: JwsAlg -> PublicKey -> ByteString -> ByteString -> Bool
- ed448Verify :: JwsAlg -> PublicKey -> ByteString -> ByteString -> Bool
- rsaSign :: Maybe Blinder -> JwsAlg -> PrivateKey -> ByteString -> Either JwtError ByteString
- rsaVerify :: JwsAlg -> PublicKey -> ByteString -> ByteString -> Bool
- rsaEncrypt :: (MonadRandom m, ByteArray msg, ByteArray out) => PublicKey -> JweAlg -> msg -> m (Either JwtError out)
- rsaDecrypt :: ByteArray ct => Maybe Blinder -> PrivateKey -> JweAlg -> ct -> Either JwtError ScrubbedBytes
- ecVerify :: JwsAlg -> PublicKey -> ByteString -> ByteString -> Bool
- encryptPayload :: forall ba iv. (ByteArray ba, ByteArray iv) => Enc -> ScrubbedBytes -> iv -> ba -> ba -> Maybe (AuthTag, ba)
- decryptPayload :: forall ba. ByteArray ba => Enc -> ScrubbedBytes -> IV -> ba -> Tag -> ba -> Maybe ba
- generateCmkAndIV :: MonadRandom m => Enc -> m (ScrubbedBytes, ScrubbedBytes)
- keyWrap :: ByteArray ba => JweAlg -> ScrubbedBytes -> ScrubbedBytes -> Either JwtError ba
Documentation
:: JwsAlg | HMAC algorithm to use |
-> ByteString | Key |
-> ByteString | The message/content |
-> Either JwtError ByteString | HMAC output |
Sign a message with an HMAC key.
:: JwsAlg | HMAC Algorithm to use |
-> ByteString | Key |
-> ByteString | The message/content |
-> ByteString | The signature to check |
-> Bool | Whether the signature is correct |
Verify the HMAC for a given message.
Returns false if the MAC is incorrect or the Alg
is not an HMAC.
:: JwsAlg | |
-> PublicKey | |
-> ByteString | The message/content |
-> ByteString | The signature to check |
-> Bool | Whether the signature is correct |
Verify an Ed25519 signed message
:: JwsAlg | |
-> PublicKey | |
-> ByteString | The message/content |
-> ByteString | The signature to check |
-> Bool | Whether the signature is correct |
Verify an Ed448 signed message
:: Maybe Blinder | RSA blinder |
-> JwsAlg | Algorithm to use. Must be one of |
-> PrivateKey | Private key to sign with |
-> ByteString | Message to sign |
-> Either JwtError ByteString | The signature |
Sign a message using an RSA private key.
The failure condition should only occur if the algorithm is not an RSA algorithm, or the RSA key is too small, causing the padding of the signature to fail. With real-world RSA keys this shouldn't happen in practice.
:: JwsAlg | The signature algorithm. Used to obtain the hash function. |
-> PublicKey | The key to check the signature with |
-> ByteString | The message/content |
-> ByteString | The signature to check |
-> Bool | Whether the signature is correct |
Verify the signature for a message using an RSA public key.
Returns false if the check fails or if the Alg
value is not
an RSA signature algorithm.
:: (MonadRandom m, ByteArray msg, ByteArray out) | |
=> PublicKey | The encryption key |
-> JweAlg | The algorithm ( |
-> msg | The message to encrypt |
-> m (Either JwtError out) | The encrypted message |
Encrypts a message (typically a symmetric key) using RSA.
:: ByteArray ct | |
=> Maybe Blinder | |
-> PrivateKey | The decryption key |
-> JweAlg | The RSA algorithm to use |
-> ct | The encrypted content |
-> Either JwtError ScrubbedBytes | The decrypted key |
Decrypts an RSA encrypted message.
:: JwsAlg | The signature algorithm. Used to obtain the hash function. |
-> PublicKey | The key to check the signature with |
-> ByteString | The message/content |
-> ByteString | The signature to check |
-> Bool | Whether the signature is correct |
Verify the signature for a message using an EC public key.
Returns false if the check fails or if the Alg
value is not
an EC signature algorithm.
:: forall ba iv. (ByteArray ba, ByteArray iv) | |
=> Enc | Encryption algorithm |
-> ScrubbedBytes | Content management key |
-> iv | IV |
-> ba | Additional authenticated data |
-> ba | The message/JWT claims |
-> Maybe (AuthTag, ba) | Ciphertext claims and signature tag |
Encrypt a message using AES.
:: forall ba. ByteArray ba | |
=> Enc | Encryption algorithm |
-> ScrubbedBytes | Content encryption key |
-> IV | IV |
-> ba | Additional authentication data |
-> Tag | The integrity protection value to be checked |
-> ba | The encrypted JWT payload |
-> Maybe ba |
Decrypt an AES encrypted message.
:: MonadRandom m | |
=> Enc | The encryption algorithm to be used |
-> m (ScrubbedBytes, ScrubbedBytes) | The key, IV |
Generates the symmetric key (content management key) and IV
Used to encrypt a message.