Safe Haskell | None |
---|---|
Language | Haskell2010 |
Internal functions for encrypting and signing / decrypting and verifying JWT content.
- hmacSign :: JwsAlg -> ByteString -> ByteString -> Either JwtError ByteString
- hmacVerify :: JwsAlg -> ByteString -> ByteString -> ByteString -> Bool
- rsaSign :: Maybe Blinder -> JwsAlg -> PrivateKey -> ByteString -> Either JwtError ByteString
- rsaVerify :: JwsAlg -> PublicKey -> ByteString -> ByteString -> Bool
- rsaEncrypt :: MonadRandom m => PublicKey -> JweAlg -> ByteString -> m (Either JwtError ByteString)
- rsaDecrypt :: Maybe Blinder -> PrivateKey -> JweAlg -> ByteString -> Either JwtError ByteString
- ecVerify :: JwsAlg -> PublicKey -> ByteString -> ByteString -> Bool
- encryptPayload :: Enc -> ByteString -> ByteString -> ByteString -> ByteString -> Maybe (AuthTag, ByteString)
- decryptPayload :: Enc -> ByteString -> ByteString -> ByteString -> AuthTag -> ByteString -> Maybe ByteString
- generateCmkAndIV :: MonadRandom m => Enc -> m (ByteString, ByteString)
- keyWrap :: JweAlg -> ByteString -> ByteString -> Either JwtError ByteString
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.
:: 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 | |
=> PublicKey | The encryption key |
-> JweAlg | The algorithm (either |
-> ByteString | The message to encrypt |
-> m (Either JwtError ByteString) | The encrypted message |
Encrypts a message (typically a symmetric key) using RSA.
:: Maybe Blinder | |
-> PrivateKey | The decryption key |
-> JweAlg | The RSA algorithm to use |
-> ByteString | The encrypted content |
-> Either JwtError ByteString | 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.
:: Enc | Encryption algorithm |
-> ByteString | Content management key |
-> ByteString | IV |
-> ByteString | Additional authenticated data |
-> ByteString | The message/JWT claims |
-> Maybe (AuthTag, ByteString) | Ciphertext claims and signature tag |
Encrypt a message using AES.
:: Enc | Encryption algorithm |
-> ByteString | Content management key |
-> ByteString | IV |
-> ByteString | Additional authentication data |
-> AuthTag | The integrity protection value to be checked |
-> ByteString | The encrypted JWT payload |
-> Maybe ByteString |
Decrypt an AES encrypted message.
:: MonadRandom m | |
=> Enc | The encryption algorithm to be used |
-> m (ByteString, ByteString) | The key, IV |
Generates the symmetric key (content management key) and IV
Used to encrypt a message.