paseto-0.1.0.0: Platform-Agnostic Security Tokens
Safe HaskellSafe-Inferred
LanguageHaskell2010

Crypto.Paseto

Description

This module is the recommended entry point for this library.

Synopsis

Mode

data Version Source #

PASETO protocol version.

Constructors

V3

Version 3. Modern NIST cryptography.

V4

Version 4. Modern Sodium (libsodium) cryptography.

Instances

Instances details
Show Version Source # 
Instance details

Defined in Crypto.Paseto.Mode

Eq Version Source # 
Instance details

Defined in Crypto.Paseto.Mode

Methods

(==) :: Version -> Version -> Bool #

(/=) :: Version -> Version -> Bool #

data Purpose Source #

PASETO token purpose.

Constructors

Local

Shared-key authenticated encryption.

Public

Public-key digital signatures (not encrypted).

Instances

Instances details
Show Purpose Source # 
Instance details

Defined in Crypto.Paseto.Mode

Eq Purpose Source # 
Instance details

Defined in Crypto.Paseto.Mode

Methods

(==) :: Purpose -> Purpose -> Bool #

(/=) :: Purpose -> Purpose -> Bool #

Keys

Symmetric keys

data SymmetricKey v where Source #

Symmetric key.

Note that this type's Eq instance performs a constant-time equality check.

Constructors

SymmetricKeyV3 :: !ScrubbedBytes32 -> SymmetricKey V3

Version 3 symmetric key.

SymmetricKeyV4 :: !ScrubbedBytes32 -> SymmetricKey V4

Version 4 symmetric key.

Instances

Instances details
Eq (SymmetricKey v) Source # 
Instance details

Defined in Crypto.Paseto.Keys

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.

Constructors

SigningKeyV3 :: !PrivateKeyP384 -> SigningKey V3

Version 3 signing key.

SigningKeyV4 :: !SecretKey -> SigningKey V4

Version 3 signing key.

Instances

Instances details
Eq (SigningKey v) Source # 
Instance details

Defined in Crypto.Paseto.Keys

Methods

(==) :: 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.

Constructors

ScalarDecodingInvalidLengthError

Invalid scalar length.

Fields

  • !Int

    Expected length

  • !Int

    Actual length

ScalarDecodingInvalidError

Decoded scalar is invalid for the curve.

Verification keys

data VerificationKey v where Source #

Verification key (also known as a public key).

Constructors

VerificationKeyV3 :: !PublicKeyP384 -> VerificationKey V3

Version 3 verification key.

VerificationKeyV4 :: !PublicKey -> VerificationKey V4

Version 4 verification key.

Instances

Instances details
Eq (VerificationKey v) Source # 
Instance details

Defined in Crypto.Paseto.Keys

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

Tokens

data Token v p where Source #

PASETO token parameterized by its protocol Version and Purpose.

Constructors

TokenV3Local

PASETO version 3 local token.

Fields

TokenV3Public

PASETO version 3 public token.

Fields

TokenV4Local

PASETO version 4 local token.

Fields

TokenV4Public

PASETO version 4 public token.

Fields

Instances

Instances details
Show (Token v p) Source # 
Instance details

Defined in Crypto.Paseto.Token

Methods

showsPrec :: Int -> Token v p -> ShowS #

show :: Token v p -> String #

showList :: [Token v p] -> ShowS #

Eq (Token v p) Source # 
Instance details

Defined in Crypto.Paseto.Token

Methods

(==) :: Token v p -> Token v p -> Bool #

(/=) :: Token v p -> Token v p -> Bool #

newtype Payload Source #

Raw PASETO token payload.

Note that this type's Eq instance performs a constant-time equality check.

Constructors

Payload 

Instances

Instances details
Show Payload Source # 
Instance details

Defined in Crypto.Paseto.Token

Eq Payload Source # 
Instance details

Defined in Crypto.Paseto.Token

Methods

(==) :: Payload -> Payload -> Bool #

(/=) :: Payload -> Payload -> Bool #

newtype Footer Source #

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.

Constructors

Footer 

Fields

Instances

Instances details
Show Footer Source # 
Instance details

Defined in Crypto.Paseto.Token

Eq Footer Source # 
Instance details

Defined in Crypto.Paseto.Token

Methods

(==) :: Footer -> Footer -> Bool #

(/=) :: Footer -> Footer -> Bool #

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.

Construction

getDefaultBuildTokenParams :: IO BuildTokenParams Source #

Get parameters for building a PASETO token which includes the recommended default claims.

This includes the following default claims:

The default Footer and ImplicitAssertion is Nothing.

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.

Constructors

V3LocalBuildEncryptionError EncryptionError

Encryption error.

newtype V3PublicBuildError Source #

Error building a version 3 public PASETO token.

Constructors

V3PublicBuildSigningError SigningError

Cryptographic signing error.

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.

Constructors

ValidatedToken 

Fields

Instances

Instances details
Show (ValidatedToken v p) Source # 
Instance details

Defined in Crypto.Paseto.Token.Encoding

Eq (ValidatedToken v p) Source # 
Instance details

Defined in Crypto.Paseto.Token.Encoding

decodeTokenV3Local Source #

Arguments

:: 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) 

Parse, decrypt, and validate a version 3 local PASETO token.

decodeTokenV3Public Source #

Arguments

:: 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) 

Parse, verify, and validate a version 3 public PASETO token.

decodeTokenV4Local Source #

Arguments

:: 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) 

Parse, decrypt, and validate a version 4 local PASETO token.

decodeTokenV4Public Source #

Arguments

:: 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) 

Parse, verify, and validate a version 4 public PASETO token.

Errors

data CommonDecodingError Source #

Common error decoding a PASETO token.

Constructors

CommonDecodingParseError !ParseError

Error parsing the token.

CommonDecodingClaimsValidationError !(NonEmpty ValidationError)

Token claims validation error.

data V3PublicDecodingError Source #

Error decoding a version 3 public PASETO token.

Constructors

V3PublicDecodingCommonError !CommonDecodingError

Common decoding error.

V3PublicDecodingVerificationError !VerificationError

Cryptographic signature verification error.

data V4PublicDecodingError Source #

Error decoding a version 4 public PASETO token.

Constructors

V4PublicDecodingCommonError !CommonDecodingError

Common decoding error.

V4PublicDecodingVerificationError !VerificationError

Cryptographic signature verification error.

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

data Claims Source #

Collection of Claims.

Instances

Instances details
FromJSON Claims Source # 
Instance details

Defined in Crypto.Paseto.Token.Claims

ToJSON Claims Source # 
Instance details

Defined in Crypto.Paseto.Token.Claims

Monoid Claims Source # 
Instance details

Defined in Crypto.Paseto.Token.Claims

Semigroup Claims Source # 
Instance details

Defined in Crypto.Paseto.Token.Claims

Show Claims Source # 
Instance details

Defined in Crypto.Paseto.Token.Claims

Eq Claims Source # 
Instance details

Defined in Crypto.Paseto.Token.Claims

Methods

(==) :: Claims -> Claims -> Bool #

(/=) :: Claims -> Claims -> Bool #

Claim types

data Claim Source #

Token claim.

Instances

Instances details
Show Claim Source # 
Instance details

Defined in Crypto.Paseto.Token.Claim

Methods

showsPrec :: Int -> Claim -> ShowS #

show :: Claim -> String #

showList :: [Claim] -> ShowS #

Eq Claim Source # 
Instance details

Defined in Crypto.Paseto.Token.Claim

Methods

(==) :: Claim -> Claim -> Bool #

(/=) :: Claim -> Claim -> Bool #

newtype Issuer Source #

Issuer of a token.

Constructors

Issuer 

Fields

Instances

Instances details
FromJSON Issuer Source # 
Instance details

Defined in Crypto.Paseto.Token.Claim

ToJSON Issuer Source # 
Instance details

Defined in Crypto.Paseto.Token.Claim

Show Issuer Source # 
Instance details

Defined in Crypto.Paseto.Token.Claim

Eq Issuer Source # 
Instance details

Defined in Crypto.Paseto.Token.Claim

Methods

(==) :: Issuer -> Issuer -> Bool #

(/=) :: Issuer -> Issuer -> Bool #

newtype Subject Source #

Subject of a token.

Constructors

Subject 

Fields

newtype Audience Source #

Recipient for which a token is intended.

Constructors

Audience 

Fields

newtype NotBefore Source #

Time from which a token should be considered valid.

Constructors

NotBefore 

Fields

newtype IssuedAt Source #

Time at which a token was issued.

Constructors

IssuedAt 

Fields

Custom claim keys

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.

Validation

Rules

newtype ValidationRule Source #

Token claim validation rule.

newtype ClaimMustExist Source #

Whether a claim must exist.

Constructors

ClaimMustExist Bool 

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):

customClaimEq Source #

Arguments

:: 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.

Constructors

ValidationClaimNotFoundError

Expected claim does not exist.

Fields

  • !ClaimKey

    Claim key which could not be found.

ValidationInvalidClaimError

Token claim is invalid.

Fields

ValidationExpirationError !Expiration

Token is expired.

ValidationIssuedAtError !IssuedAt

Token's IssuedAt time is in the future.

ValidationNotBeforeError !NotBefore

Token is not yet valid as its NotBefore time is in the future.

ValidationCustomError !Text

Custom validation error.

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.