Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
This module is the recommended entry point for this library.
Synopsis
- data Version
- data Purpose
- data SymmetricKey v where
- symmetricKeyToBytes :: SymmetricKey v -> ScrubbedBytes
- bytesToSymmetricKeyV3 :: ScrubbedBytes -> Maybe (SymmetricKey V3)
- bytesToSymmetricKeyV4 :: ScrubbedBytes -> Maybe (SymmetricKey V4)
- generateSymmetricKeyV3 :: IO (SymmetricKey V3)
- generateSymmetricKeyV4 :: IO (SymmetricKey V4)
- data SigningKey v where
- SigningKeyV3 :: !PrivateKeyP384 -> SigningKey V3
- SigningKeyV4 :: !SecretKey -> SigningKey V4
- signingKeyToBytes :: SigningKey v -> ScrubbedBytes
- bytesToSigningKeyV3 :: ScrubbedBytes -> Either ScalarDecodingError (SigningKey V3)
- bytesToSigningKeyV4 :: ScrubbedBytes -> Maybe (SigningKey V4)
- generateSigningKeyV3 :: IO (SigningKey V3)
- generateSigningKeyV4 :: IO (SigningKey V4)
- data ScalarDecodingError
- renderScalarDecodingError :: ScalarDecodingError -> Text
- data VerificationKey v where
- verificationKeyToBytes :: VerificationKey v -> ByteString
- bytesToVerificationKeyV3 :: ByteString -> Either PublicKeyP384DecodingError (VerificationKey V3)
- bytesToVerificationKeyV4 :: ByteString -> Maybe (VerificationKey V4)
- fromSigningKey :: SigningKey v -> VerificationKey v
- data PublicKeyP384DecodingError
- renderPublicKeyP384DecodingError :: PublicKeyP384DecodingError -> Text
- data Token v p where
- newtype Payload = Payload {}
- newtype Footer = Footer {}
- newtype ImplicitAssertion = ImplicitAssertion {}
- data BuildTokenParams = BuildTokenParams {
- btpClaims :: !Claims
- btpFooter :: !(Maybe Footer)
- btpImplicitAssertion :: !(Maybe ImplicitAssertion)
- getDefaultBuildTokenParams :: IO BuildTokenParams
- buildTokenV3Local :: BuildTokenParams -> SymmetricKey V3 -> ExceptT V3LocalBuildError IO (Token V3 Local)
- buildTokenV3Public :: BuildTokenParams -> SigningKey V3 -> ExceptT V3PublicBuildError IO (Token V3 Public)
- buildTokenV4Local :: BuildTokenParams -> SymmetricKey V4 -> IO (Token V4 Local)
- buildTokenV4Public :: BuildTokenParams -> SigningKey V4 -> Token V4 Public
- newtype V3LocalBuildError = V3LocalBuildEncryptionError EncryptionError
- renderV3LocalBuildError :: V3LocalBuildError -> Text
- newtype V3PublicBuildError = V3PublicBuildSigningError SigningError
- renderV3PublicBuildError :: V3PublicBuildError -> Text
- encode :: Token v p -> Text
- data ValidatedToken v p = ValidatedToken {}
- decodeTokenV3Local :: SymmetricKey V3 -> [ValidationRule] -> Maybe Footer -> Maybe ImplicitAssertion -> Text -> Either V3LocalDecodingError (ValidatedToken V3 Local)
- decodeTokenV3Public :: VerificationKey V3 -> [ValidationRule] -> Maybe Footer -> Maybe ImplicitAssertion -> Text -> Either V3PublicDecodingError (ValidatedToken V3 Public)
- decodeTokenV4Local :: SymmetricKey V4 -> [ValidationRule] -> Maybe Footer -> Maybe ImplicitAssertion -> Text -> Either V4LocalDecodingError (ValidatedToken V4 Local)
- decodeTokenV4Public :: VerificationKey V4 -> [ValidationRule] -> Maybe Footer -> Maybe ImplicitAssertion -> Text -> Either V4PublicDecodingError (ValidatedToken V4 Public)
- data CommonDecodingError
- renderCommonDecodingError :: CommonDecodingError -> Text
- data V3LocalDecodingError
- renderV3LocalDecodingError :: V3LocalDecodingError -> Text
- data V3PublicDecodingError
- renderV3PublicDecodingError :: V3PublicDecodingError -> Text
- data V4LocalDecodingError
- renderV4LocalDecodingError :: V4LocalDecodingError -> Text
- data V4PublicDecodingError
- renderV4PublicDecodingError :: V4PublicDecodingError -> Text
- data Claims
- data Claim
- newtype Issuer = Issuer {}
- newtype Subject = Subject {}
- newtype Audience = Audience {
- unAudience :: Text
- newtype Expiration = Expiration {}
- renderExpiration :: Expiration -> Text
- newtype NotBefore = NotBefore {}
- renderNotBefore :: NotBefore -> Text
- newtype IssuedAt = IssuedAt {}
- renderIssuedAt :: IssuedAt -> Text
- newtype TokenIdentifier = TokenIdentifier {}
- data UnregisteredClaimKey
- mkUnregisteredClaimKey :: Text -> Maybe UnregisteredClaimKey
- renderUnregisteredClaimKey :: UnregisteredClaimKey -> Text
- newtype ValidationRule = ValidationRule {
- unValidationRule :: Claims -> Either ValidationError ()
- newtype ClaimMustExist = ClaimMustExist Bool
- getDefaultValidationRules :: IO [ValidationRule]
- forAudience :: Audience -> ValidationRule
- identifiedBy :: TokenIdentifier -> ValidationRule
- issuedBy :: Issuer -> ValidationRule
- notExpired :: UTCTime -> ValidationRule
- subject :: Subject -> ValidationRule
- validAt :: UTCTime -> ValidationRule
- customClaimEq :: ClaimMustExist -> UnregisteredClaimKey -> Value -> ValidationRule
- data ValidationError
- renderValidationError :: ValidationError -> Text
- renderValidationErrors :: NonEmpty ValidationError -> Text
- parseTokenV3Local :: Text -> Either ParseError (Token V3 Local)
- parseTokenV3Public :: Text -> Either ParseError (Token V3 Public)
- parseTokenV4Local :: Text -> Either ParseError (Token V4 Local)
- parseTokenV4Public :: Text -> Either ParseError (Token V4 Public)
Mode
PASETO protocol version.
V3 | Version 3. Modern NIST cryptography. |
V4 | Version 4. Modern Sodium ( |
PASETO token purpose.
Keys
Symmetric keys
data SymmetricKey v where Source #
Symmetric key.
Note that this type's Eq
instance performs a constant-time equality
check.
SymmetricKeyV3 :: !ScrubbedBytes32 -> SymmetricKey V3 | Version 3 symmetric key. |
SymmetricKeyV4 :: !ScrubbedBytes32 -> SymmetricKey V4 | Version 4 symmetric key. |
Instances
Eq (SymmetricKey v) Source # | |
Defined in Crypto.Paseto.Keys (==) :: SymmetricKey v -> SymmetricKey v -> Bool # (/=) :: SymmetricKey v -> SymmetricKey v -> Bool # |
symmetricKeyToBytes :: SymmetricKey v -> ScrubbedBytes Source #
Get the raw bytes associated with a symmetric key.
bytesToSymmetricKeyV3 :: ScrubbedBytes -> Maybe (SymmetricKey V3) Source #
Construct a version 3 symmetric key from bytes.
If the provided byte string does not have a length of 32
(256
bits),
Nothing
is returned.
bytesToSymmetricKeyV4 :: ScrubbedBytes -> Maybe (SymmetricKey V4) Source #
Construct a version 4 symmetric key from bytes.
If the provided byte string does not have a length of 32
(256
bits),
Nothing
is returned.
generateSymmetricKeyV3 :: IO (SymmetricKey V3) Source #
Randomly generate a version 3 symmetric key.
generateSymmetricKeyV4 :: IO (SymmetricKey V4) Source #
Randomly generate a version 4 symmetric key.
Asymmetric keys
Signing keys
data SigningKey v where Source #
Signing key (also known as a private/secret key).
Note that this type's Eq
instance performs a constant-time equality
check.
SigningKeyV3 :: !PrivateKeyP384 -> SigningKey V3 | Version 3 signing key. |
SigningKeyV4 :: !SecretKey -> SigningKey V4 | Version 3 signing key. |
Instances
Eq (SigningKey v) Source # | |
Defined in Crypto.Paseto.Keys (==) :: SigningKey v -> SigningKey v -> Bool # (/=) :: SigningKey v -> SigningKey v -> Bool # |
signingKeyToBytes :: SigningKey v -> ScrubbedBytes Source #
Get the raw bytes associated with a signing key.
bytesToSigningKeyV3 :: ScrubbedBytes -> Either ScalarDecodingError (SigningKey V3) Source #
Construct a version 3 signing key from bytes.
bytesToSigningKeyV4 :: ScrubbedBytes -> Maybe (SigningKey V4) Source #
Construct a version 4 signing key from bytes.
generateSigningKeyV3 :: IO (SigningKey V3) Source #
Randomly generate a version 3 signing key.
generateSigningKeyV4 :: IO (SigningKey V4) Source #
Randomly generate a version 4 signing key.
Errors
data ScalarDecodingError Source #
Error decoding a scalar value.
ScalarDecodingInvalidLengthError | Invalid scalar length. |
ScalarDecodingInvalidError | Decoded scalar is invalid for the curve. |
Instances
Show ScalarDecodingError Source # | |
Defined in Crypto.Paseto.Keys.V3.Internal showsPrec :: Int -> ScalarDecodingError -> ShowS # show :: ScalarDecodingError -> String # showList :: [ScalarDecodingError] -> ShowS # | |
Eq ScalarDecodingError Source # | |
Defined in Crypto.Paseto.Keys.V3.Internal (==) :: ScalarDecodingError -> ScalarDecodingError -> Bool # (/=) :: ScalarDecodingError -> ScalarDecodingError -> Bool # |
renderScalarDecodingError :: ScalarDecodingError -> Text Source #
Render a ScalarDecodingError
as Text
.
Verification keys
data VerificationKey v where Source #
Verification key (also known as a public key).
VerificationKeyV3 :: !PublicKeyP384 -> VerificationKey V3 | Version 3 verification key. |
VerificationKeyV4 :: !PublicKey -> VerificationKey V4 | Version 4 verification key. |
Instances
Eq (VerificationKey v) Source # | |
Defined in Crypto.Paseto.Keys (==) :: VerificationKey v -> VerificationKey v -> Bool # (/=) :: VerificationKey v -> VerificationKey v -> Bool # |
verificationKeyToBytes :: VerificationKey v -> ByteString Source #
Get the raw bytes associated with a verification key.
bytesToVerificationKeyV3 :: ByteString -> Either PublicKeyP384DecodingError (VerificationKey V3) Source #
Construct a version 3 verification key from bytes.
The input ByteString
is expected to be formatted as either a compressed
or uncompressed elliptic curve public key as defined by
SEC 1 and
RFC 5480 section 2.2.
bytesToVerificationKeyV4 :: ByteString -> Maybe (VerificationKey V4) Source #
Construct a version 4 verification key from bytes.
fromSigningKey :: SigningKey v -> VerificationKey v Source #
Get the VerificationKey
which corresponds to a given SigningKey
.
Errors
data PublicKeyP384DecodingError Source #
Error decoding a public key for curve SEC_p384r1
.
PublicKeyP384DecodingCompressedError !CompressedPointDecodingError | Error decoding a compressed public key. |
PublicKeyP384DecodingUncompressedError !UncompressedPointDecodingError | Error decoding an uncompressed public key. |
Instances
Show PublicKeyP384DecodingError Source # | |
Defined in Crypto.Paseto.Keys.V3 showsPrec :: Int -> PublicKeyP384DecodingError -> ShowS # show :: PublicKeyP384DecodingError -> String # showList :: [PublicKeyP384DecodingError] -> ShowS # | |
Eq PublicKeyP384DecodingError Source # | |
Defined in Crypto.Paseto.Keys.V3 |
renderPublicKeyP384DecodingError :: PublicKeyP384DecodingError -> Text Source #
Render a PublicKeyP384DecodingError
as Text
.
Tokens
TokenV3Local | PASETO version 3 local token. |
TokenV3Public | PASETO version 3 public token. |
TokenV4Local | PASETO version 4 local token. |
TokenV4Public | PASETO version 4 public token. |
Instances
Raw PASETO token payload.
Note that this type's Eq
instance performs a constant-time equality
check.
Footer consisting of unencrypted free-form data.
The footer's contents may be JSON or some other structured data, but it doesn't have to be.
When a PASETO token is constructed, the footer is authenticated, but not encrypted (i.e. its integrity is protected, but it is not made confidential). In authenticated encryption schemes, this is referred to as "associated data".
Note that this type's Eq
instance performs a constant-time equality
check.
Instances
newtype ImplicitAssertion Source #
Unencrypted authenticated data which is not stored in the PASETO token.
When a PASETO token is constructed, the implicit assertion is authenticated, but it is not stored in the token. This is useful if one wants to associate some data that should remain confidential.
Note that this type's Eq
instance performs a constant-time equality
check.
Instances
Show ImplicitAssertion Source # | |
Defined in Crypto.Paseto.Token showsPrec :: Int -> ImplicitAssertion -> ShowS # show :: ImplicitAssertion -> String # showList :: [ImplicitAssertion] -> ShowS # | |
Eq ImplicitAssertion Source # | |
Defined in Crypto.Paseto.Token (==) :: ImplicitAssertion -> ImplicitAssertion -> Bool # (/=) :: ImplicitAssertion -> ImplicitAssertion -> Bool # |
Construction
data BuildTokenParams Source #
Parameters for building a PASETO token.
BuildTokenParams | |
|
Instances
Show BuildTokenParams Source # | |
Defined in Crypto.Paseto.Token.Build showsPrec :: Int -> BuildTokenParams -> ShowS # show :: BuildTokenParams -> String # showList :: [BuildTokenParams] -> ShowS # | |
Eq BuildTokenParams Source # | |
Defined in Crypto.Paseto.Token.Build (==) :: BuildTokenParams -> BuildTokenParams -> Bool # (/=) :: BuildTokenParams -> BuildTokenParams -> Bool # |
getDefaultBuildTokenParams :: IO BuildTokenParams Source #
Get parameters for building a PASETO token which includes the recommended default claims.
This includes the following default claims:
- An
ExpirationClaim
of 1 hour from the current system time. - An
IssuedAtClaim
of the current system time. - A
NotBeforeClaim
of the current system time.
The default Footer
and ImplicitAssertion
is Nothing
.
buildTokenV3Local :: BuildTokenParams -> SymmetricKey V3 -> ExceptT V3LocalBuildError IO (Token V3 Local) Source #
Build a version 3 local token.
buildTokenV3Public :: BuildTokenParams -> SigningKey V3 -> ExceptT V3PublicBuildError IO (Token V3 Public) Source #
Build a version 3 public token.
buildTokenV4Local :: BuildTokenParams -> SymmetricKey V4 -> IO (Token V4 Local) Source #
Build a version 4 local token.
buildTokenV4Public :: BuildTokenParams -> SigningKey V4 -> Token V4 Public Source #
Build a version 4 public token.
Errors
newtype V3LocalBuildError Source #
Error building a version 3 local PASETO token.
V3LocalBuildEncryptionError EncryptionError | Encryption error. |
Instances
Show V3LocalBuildError Source # | |
Defined in Crypto.Paseto.Token.Build showsPrec :: Int -> V3LocalBuildError -> ShowS # show :: V3LocalBuildError -> String # showList :: [V3LocalBuildError] -> ShowS # | |
Eq V3LocalBuildError Source # | |
Defined in Crypto.Paseto.Token.Build (==) :: V3LocalBuildError -> V3LocalBuildError -> Bool # (/=) :: V3LocalBuildError -> V3LocalBuildError -> Bool # |
renderV3LocalBuildError :: V3LocalBuildError -> Text Source #
Render a V3LocalBuildError
as Text
.
newtype V3PublicBuildError Source #
Error building a version 3 public PASETO token.
V3PublicBuildSigningError SigningError | Cryptographic signing error. |
Instances
Show V3PublicBuildError Source # | |
Defined in Crypto.Paseto.Token.Build showsPrec :: Int -> V3PublicBuildError -> ShowS # show :: V3PublicBuildError -> String # showList :: [V3PublicBuildError] -> ShowS # | |
Eq V3PublicBuildError Source # | |
Defined in Crypto.Paseto.Token.Build (==) :: V3PublicBuildError -> V3PublicBuildError -> Bool # (/=) :: V3PublicBuildError -> V3PublicBuildError -> Bool # |
renderV3PublicBuildError :: V3PublicBuildError -> Text Source #
Render a V3PublicBuildError
as Text
.
Encoding and decoding
encode :: Token v p -> Text Source #
Encode a PASETO token as human-readable text according to the message format defined in the specification.
data ValidatedToken v p Source #
PASETO token which has been decoded and validated.
Instances
Show (ValidatedToken v p) Source # | |
Defined in Crypto.Paseto.Token.Encoding showsPrec :: Int -> ValidatedToken v p -> ShowS # show :: ValidatedToken v p -> String # showList :: [ValidatedToken v p] -> ShowS # | |
Eq (ValidatedToken v p) Source # | |
Defined in Crypto.Paseto.Token.Encoding (==) :: ValidatedToken v p -> ValidatedToken v p -> Bool # (/=) :: ValidatedToken v p -> ValidatedToken v p -> Bool # |
:: SymmetricKey V3 | Symmetric key. |
-> [ValidationRule] | Validation rules. |
-> Maybe Footer | Optional footer to authenticate. |
-> Maybe ImplicitAssertion | Optional implicit assertion to authenticate. |
-> Text | Encoded PASETO token. |
-> Either V3LocalDecodingError (ValidatedToken V3 Local) |
:: VerificationKey V3 | Verification key. |
-> [ValidationRule] | Validation rules. |
-> Maybe Footer | Optional footer to authenticate. |
-> Maybe ImplicitAssertion | Optional implicit assertion to authenticate. |
-> Text | Encoded PASETO token. |
-> Either V3PublicDecodingError (ValidatedToken V3 Public) |
:: SymmetricKey V4 | Symmetric key. |
-> [ValidationRule] | Validation rules. |
-> Maybe Footer | Optional footer to authenticate. |
-> Maybe ImplicitAssertion | Optional implicit assertion to authenticate. |
-> Text | Encoded PASETO token. |
-> Either V4LocalDecodingError (ValidatedToken V4 Local) |
:: VerificationKey V4 | Verification key. |
-> [ValidationRule] | Validation rules. |
-> Maybe Footer | Optional footer to authenticate. |
-> Maybe ImplicitAssertion | Optional implicit assertion to authenticate. |
-> Text | Encoded PASETO token. |
-> Either V4PublicDecodingError (ValidatedToken V4 Public) |
Errors
data CommonDecodingError Source #
Common error decoding a PASETO token.
CommonDecodingParseError !ParseError | Error parsing the token. |
CommonDecodingClaimsValidationError !(NonEmpty ValidationError) | Token claims validation error. |
Instances
Show CommonDecodingError Source # | |
Defined in Crypto.Paseto.Token.Encoding showsPrec :: Int -> CommonDecodingError -> ShowS # show :: CommonDecodingError -> String # showList :: [CommonDecodingError] -> ShowS # | |
Eq CommonDecodingError Source # | |
Defined in Crypto.Paseto.Token.Encoding (==) :: CommonDecodingError -> CommonDecodingError -> Bool # (/=) :: CommonDecodingError -> CommonDecodingError -> Bool # |
renderCommonDecodingError :: CommonDecodingError -> Text Source #
Render a CommonDecodingError
as Text
.
data V3LocalDecodingError Source #
Error decoding a version 3 local PASETO token.
V3LocalDecodingCommonError !CommonDecodingError | Common decoding error. |
V3LocalDecodingDecryptionError !DecryptionError | Decryption error. |
Instances
Show V3LocalDecodingError Source # | |
Defined in Crypto.Paseto.Token.Encoding showsPrec :: Int -> V3LocalDecodingError -> ShowS # show :: V3LocalDecodingError -> String # showList :: [V3LocalDecodingError] -> ShowS # | |
Eq V3LocalDecodingError Source # | |
Defined in Crypto.Paseto.Token.Encoding (==) :: V3LocalDecodingError -> V3LocalDecodingError -> Bool # (/=) :: V3LocalDecodingError -> V3LocalDecodingError -> Bool # |
renderV3LocalDecodingError :: V3LocalDecodingError -> Text Source #
Render a V3LocalDecodingError
as Text
.
data V3PublicDecodingError Source #
Error decoding a version 3 public PASETO token.
V3PublicDecodingCommonError !CommonDecodingError | Common decoding error. |
V3PublicDecodingVerificationError !VerificationError | Cryptographic signature verification error. |
Instances
Show V3PublicDecodingError Source # | |
Defined in Crypto.Paseto.Token.Encoding showsPrec :: Int -> V3PublicDecodingError -> ShowS # show :: V3PublicDecodingError -> String # showList :: [V3PublicDecodingError] -> ShowS # | |
Eq V3PublicDecodingError Source # | |
Defined in Crypto.Paseto.Token.Encoding (==) :: V3PublicDecodingError -> V3PublicDecodingError -> Bool # (/=) :: V3PublicDecodingError -> V3PublicDecodingError -> Bool # |
renderV3PublicDecodingError :: V3PublicDecodingError -> Text Source #
Render a V3PublicDecodingError
as Text
.
data V4LocalDecodingError Source #
Error decoding a version 4 local PASETO token.
V4LocalDecodingCommonError !CommonDecodingError | Common decoding error. |
V4LocalDecodingDecryptionError !DecryptionError | Decryption error. |
Instances
Show V4LocalDecodingError Source # | |
Defined in Crypto.Paseto.Token.Encoding showsPrec :: Int -> V4LocalDecodingError -> ShowS # show :: V4LocalDecodingError -> String # showList :: [V4LocalDecodingError] -> ShowS # | |
Eq V4LocalDecodingError Source # | |
Defined in Crypto.Paseto.Token.Encoding (==) :: V4LocalDecodingError -> V4LocalDecodingError -> Bool # (/=) :: V4LocalDecodingError -> V4LocalDecodingError -> Bool # |
renderV4LocalDecodingError :: V4LocalDecodingError -> Text Source #
Render a V4LocalDecodingError
as Text
.
data V4PublicDecodingError Source #
Error decoding a version 4 public PASETO token.
V4PublicDecodingCommonError !CommonDecodingError | Common decoding error. |
V4PublicDecodingVerificationError !VerificationError | Cryptographic signature verification error. |
Instances
Show V4PublicDecodingError Source # | |
Defined in Crypto.Paseto.Token.Encoding showsPrec :: Int -> V4PublicDecodingError -> ShowS # show :: V4PublicDecodingError -> String # showList :: [V4PublicDecodingError] -> ShowS # | |
Eq V4PublicDecodingError Source # | |
Defined in Crypto.Paseto.Token.Encoding (==) :: V4PublicDecodingError -> V4PublicDecodingError -> Bool # (/=) :: V4PublicDecodingError -> V4PublicDecodingError -> Bool # |
renderV4PublicDecodingError :: V4PublicDecodingError -> Text Source #
Render a V4PublicDecodingError
as Text
.
Claims
Container type
Collection of PASETO token claims.
Note that we only re-export the Claims
type from this module as the rest
of the API contains functions which may conflict with those in Prelude
and other container implementations such as Data.Map.
If you need access to those other functions, it's recommended to import Crypto.Paseto.Token.Claims qualified. For example:
import qualified Crypto.Paseto.Token.Claims as Claims
Collection of Claim
s.
Claim types
Token claim.
Issuer of a token.
Subject of a token.
Recipient for which a token is intended.
newtype Expiration Source #
Time after which a token expires.
Instances
FromJSON Expiration Source # | |
Defined in Crypto.Paseto.Token.Claim parseJSON :: Value -> Parser Expiration # parseJSONList :: Value -> Parser [Expiration] # | |
ToJSON Expiration Source # | |
Defined in Crypto.Paseto.Token.Claim toJSON :: Expiration -> Value # toEncoding :: Expiration -> Encoding # toJSONList :: [Expiration] -> Value # toEncodingList :: [Expiration] -> Encoding # omitField :: Expiration -> Bool # | |
Show Expiration Source # | |
Defined in Crypto.Paseto.Token.Claim showsPrec :: Int -> Expiration -> ShowS # show :: Expiration -> String # showList :: [Expiration] -> ShowS # | |
Eq Expiration Source # | |
Defined in Crypto.Paseto.Token.Claim (==) :: Expiration -> Expiration -> Bool # (/=) :: Expiration -> Expiration -> Bool # |
renderExpiration :: Expiration -> Text Source #
Render an Expiration
as Text
.
Time from which a token should be considered valid.
Time at which a token was issued.
newtype TokenIdentifier Source #
Token identifier.
Instances
FromJSON TokenIdentifier Source # | |
Defined in Crypto.Paseto.Token.Claim parseJSON :: Value -> Parser TokenIdentifier # parseJSONList :: Value -> Parser [TokenIdentifier] # | |
ToJSON TokenIdentifier Source # | |
Defined in Crypto.Paseto.Token.Claim toJSON :: TokenIdentifier -> Value # toEncoding :: TokenIdentifier -> Encoding # toJSONList :: [TokenIdentifier] -> Value # toEncodingList :: [TokenIdentifier] -> Encoding # omitField :: TokenIdentifier -> Bool # | |
Show TokenIdentifier Source # | |
Defined in Crypto.Paseto.Token.Claim showsPrec :: Int -> TokenIdentifier -> ShowS # show :: TokenIdentifier -> String # showList :: [TokenIdentifier] -> ShowS # | |
Eq TokenIdentifier Source # | |
Defined in Crypto.Paseto.Token.Claim (==) :: TokenIdentifier -> TokenIdentifier -> Bool # (/=) :: TokenIdentifier -> TokenIdentifier -> Bool # |
Custom claim keys
data UnregisteredClaimKey Source #
Unregistered claim key.
Instances
Show UnregisteredClaimKey Source # | |
Defined in Crypto.Paseto.Token.Claim showsPrec :: Int -> UnregisteredClaimKey -> ShowS # show :: UnregisteredClaimKey -> String # showList :: [UnregisteredClaimKey] -> ShowS # | |
Eq UnregisteredClaimKey Source # | |
Defined in Crypto.Paseto.Token.Claim (==) :: UnregisteredClaimKey -> UnregisteredClaimKey -> Bool # (/=) :: UnregisteredClaimKey -> UnregisteredClaimKey -> Bool # |
mkUnregisteredClaimKey :: Text -> Maybe UnregisteredClaimKey Source #
Construct an unregistered claim key.
If the provided Text
key matches that of a registered claim
(registeredClaimKeys
), this function will return Nothing
.
renderUnregisteredClaimKey :: UnregisteredClaimKey -> Text Source #
Render an UnregisteredClaimKey
as Text
.
Validation
Rules
newtype ValidationRule Source #
Token claim validation rule.
Default rules
getDefaultValidationRules :: IO [ValidationRule] Source #
Get a list of recommended default validation rules.
At the moment, the only default rule is checking validAt
for the current
system time (getCurrentTime
).
Simple rules
forAudience :: Audience -> ValidationRule Source #
Validate that a token is intended for a given audience.
identifiedBy :: TokenIdentifier -> ValidationRule Source #
Validate a token's identifier.
issuedBy :: Issuer -> ValidationRule Source #
Validate a token's issuer.
notExpired :: UTCTime -> ValidationRule Source #
Validate that a token is not expired at the given time.
That is, if the ExpirationClaim
is present,
check that it isn't in the past (relative to the given time).
subject :: Subject -> ValidationRule Source #
Validate the subject of a token.
validAt :: UTCTime -> ValidationRule Source #
Validate that a token is valid at the given time.
This involves the following checks (relative to the given time):
- If the
ExpirationClaim
is present, check that it isn't in the past. - If the
IssuedAtClaim
is present, check that it isn't in the future. - If the
NotBeforeClaim
is present, check that it isn't in the future.
:: ClaimMustExist | Whether the custom claim must exist. |
-> UnregisteredClaimKey | Custom claim key to lookup. |
-> Value | Custom claim value to validate (i.e. the expected value). |
-> ValidationRule |
Validate that a custom claim is equal to the given value.
Errors
data ValidationError Source #
Validation error.
ValidationClaimNotFoundError | Expected claim does not exist. |
| |
ValidationInvalidClaimError | Token claim is invalid. |
ValidationExpirationError !Expiration | Token is expired. |
ValidationIssuedAtError !IssuedAt | Token's |
ValidationNotBeforeError !NotBefore | Token is not yet valid as its |
ValidationCustomError !Text | Custom validation error. |
Instances
Show ValidationError Source # | |
Defined in Crypto.Paseto.Token.Validation showsPrec :: Int -> ValidationError -> ShowS # show :: ValidationError -> String # showList :: [ValidationError] -> ShowS # | |
Eq ValidationError Source # | |
Defined in Crypto.Paseto.Token.Validation (==) :: ValidationError -> ValidationError -> Bool # (/=) :: ValidationError -> ValidationError -> Bool # |
renderValidationError :: ValidationError -> Text Source #
Render a ValidationError
as Text
.
renderValidationErrors :: NonEmpty ValidationError -> Text Source #
Render a non-empty list of ValidationError
s as Text
.
Unsafe parsers
Note that these parsers are considered unsafe as they do not perform any kind of token validation, cryptographic or otherwise. They simply ensure that the input looks like a well-formed token.
For typical usage, one should use the decoding functions that perform parsing, cryptographic verification, and validation from the encoding and decoding section.
As a result, you should only use these unsafe parsers in specific situations where you really know what you're doing. For example, they can be useful in situations where one wants to parse some information out of a token's footer without first needing to decrypt or verify the token. For more information on this particular scenario, see Key-ID Support in the PASETO specification.
parseTokenV3Local :: Text -> Either ParseError (Token V3 Local) Source #
Parse a version 3 local PASETO token from human-readable text according to the message format defined in the specification.
Note that this function does not perform any kind of token validation, cryptographic or otherwise. It simply parses the token and ensures that it is well-formed.
parseTokenV3Public :: Text -> Either ParseError (Token V3 Public) Source #
Parse a version 3 public PASETO token from human-readable text according to the message format defined in the specification.
Note that this function does not perform any kind of token validation, cryptographic or otherwise. It simply parses the token and ensures that it is well-formed.
parseTokenV4Local :: Text -> Either ParseError (Token V4 Local) Source #
Parse a version 4 local PASETO token from human-readable text according to the message format defined in the specification.
Note that this function does not perform any kind of token validation, cryptographic or otherwise. It simply parses the token and ensures that it is well-formed.
parseTokenV4Public :: Text -> Either ParseError (Token V4 Public) Source #
Parse a version 4 public PASETO token from human-readable text according to the message format defined in the specification.
Note that this function does not perform any kind of token validation, cryptographic or otherwise. It simply parses the token and ensures that it is well-formed.