jose-0.11: JSON Object Signing and Encryption (JOSE) and JSON Web Token (JWT) library
Safe HaskellSafe-Inferred
LanguageHaskell2010

Crypto.JWT

Description

JSON Web Token implementation (RFC 7519). A JWT is a JWS with a payload of claims to be transferred between two parties.

JWTs use the JWS compact serialisation. See Crypto.JOSE.Compact for details.

Synopsis

Overview / HOWTO

Basic usage

import Crypto.JWT

mkClaims :: IO ClaimsSet
mkClaims = do
  t <- currentTime
  pure $ emptyClaimsSet
    & claimIss ?~ "alice"
    & claimAud ?~ Audience ["bob"]
    & claimIat ?~ NumericDate t

doJwtSign :: JWK -> ClaimsSet -> IO (Either JWTError SignedJWT)
doJwtSign jwk claims = runJOSE $ do
  alg <- bestJWSAlg jwk
  signClaims jwk (newJWSHeader ((), alg)) claims

doJwtVerify :: JWK -> SignedJWT -> IO (Either JWTError ClaimsSet)
doJwtVerify jwk jwt = runJOSE $ do
  let config = defaultJWTValidationSettings (== "bob")
  verifyClaims config jwk jwt

Some JWT libraries have a function that takes two strings: the "secret" (a symmetric key) and the raw JWT. The following function achieves the same:

verify :: L.ByteString -> L.ByteString -> IO (Either JWTError ClaimsSet)
verify k s = runJOSE $ do
  let
    k' = fromOctets k      -- turn raw secret into symmetric JWK
    audCheck = const True  -- should be a proper audience check
  jwt <- decodeCompact s    -- decode JWT
  verifyClaims (defaultJWTValidationSettings audCheck) k' jwt

Supporting additional claims via subtypes

For applications that use additional claims, define a data type that wraps ClaimsSet and includes fields for the additional claims. You will also need to define FromJSON if verifying JWTs, and ToJSON if producing JWTs. The following example is taken from RFC 7519 §3.1.

import qualified Data.Aeson.KeyMap as M

data Super = Super { jwtClaims :: ClaimsSet, isRoot :: Bool }

instance HasClaimsSet Super where
  claimsSet f s = fmap (\a' -> s { jwtClaims = a' }) (f (jwtClaims s))

instance FromJSON Super where
  parseJSON = withObject "Super" $ \o -> Super
    <$> parseJSON (Object o)
    <*> o .: "http://example.com/is_root"

instance ToJSON Super where
  toJSON s =
    ins "http://example.com/is_root" (isRoot s) (toJSON (jwtClaims s))
    where
      ins k v (Object o) = Object $ M.insert k (toJSON v) o
      ins _ _ a = a

Use signJWT and verifyJWT when using custom payload types (instead of signClaims and verifyClaims which are specialised to ClaimsSet).

API

Creating a JWT

type SignedJWT = CompactJWS JWSHeader Source #

A digitally signed or MACed JWT

signClaims :: (MonadRandom m, MonadError e m, AsError e) => JWK -> JWSHeader () -> ClaimsSet -> m SignedJWT Source #

Create a JWS JWT. Specialisation of signJWT with payload type fixed at ClaimsSet.

Does not set any fields in the Claims Set, such as "iat" ("Issued At") Claim. The payload is encoded as-is.

signJWT :: (MonadRandom m, MonadError e m, AsError e, ToJSON payload) => JWK -> JWSHeader () -> payload -> m SignedJWT Source #

Create a JWS JWT. The payload can be any type with a ToJSON instance. See also signClaims which uses ClaimsSet as the payload type.

Does not set any fields in the Claims Set, such as "iat" ("Issued At") Claim. The payload is encoded as-is.

Validating a JWT and extracting claims

defaultJWTValidationSettings :: (StringOrURI -> Bool) -> JWTValidationSettings Source #

Acquire the default validation settings.

RFC 7519 §4.1.3. states that applications MUST identify itself with a value in the audience claim, therefore a predicate must be supplied.

The other defaults are:

  • defaultValidationSettings for JWS verification
  • Zero clock skew tolerance when validating nbf, exp and iat claims
  • iat claim is checked
  • issuer claim is not checked

verifyJWT :: (MonadTime m, HasAllowedSkew a, HasAudiencePredicate a, HasIssuerPredicate a, HasCheckIssuedAt a, HasValidationSettings a, AsError e, AsJWTError e, MonadError e m, VerificationKeyStore m (JWSHeader ()) payload k, HasClaimsSet payload, FromJSON payload) => a -> k -> SignedJWT -> m payload Source #

Cryptographically verify a JWS JWT, then validate the Claims Set, returning it if valid. The claims are validated at the current system time.

This is the only way to get at the claims of a JWS JWT, enforcing that the claims are cryptographically and semantically valid before the application can use them.

This function is abstracted over any payload type with HasClaimsSet and FromJSON instances. The verifyClaims variant uses ClaimsSet as the payload type.

See also verifyClaimsAt which allows you to explicitly specify the time of validation (against which time-related claims will be validated).

class HasAllowedSkew s where Source #

Maximum allowed skew when validating the nbf, exp and iat claims.

Instances

Instances details
HasJWTValidationSettings a => HasAllowedSkew a Source # 
Instance details

Defined in Crypto.JWT

class HasAudiencePredicate s where Source #

Predicate for checking values in the aud claim.

Instances

Instances details
HasJWTValidationSettings a => HasAudiencePredicate a Source # 
Instance details

Defined in Crypto.JWT

class HasIssuerPredicate s where Source #

Predicate for checking the iss claim.

Instances

Instances details
HasJWTValidationSettings a => HasIssuerPredicate a Source # 
Instance details

Defined in Crypto.JWT

class HasCheckIssuedAt s where Source #

Whether to check that the iat claim is not in the future.

Instances

Instances details
HasJWTValidationSettings a => HasCheckIssuedAt a Source # 
Instance details

Defined in Crypto.JWT

Specifying the verification time

newtype WrappedUTCTime Source #

Constructors

WrappedUTCTime 

Fields

Instances

Instances details
Monad m => MonadTime (ReaderT WrappedUTCTime m) Source #

monotonicTime = pure 0. jose doesn't use this so we fake it

Instance details

Defined in Crypto.JWT

verifyClaimsAt :: (HasAllowedSkew a, HasAudiencePredicate a, HasIssuerPredicate a, HasCheckIssuedAt a, HasValidationSettings a, AsError e, AsJWTError e, MonadError e m, VerificationKeyStore (ReaderT WrappedUTCTime m) (JWSHeader ()) ClaimsSet k) => a -> k -> UTCTime -> SignedJWT -> m ClaimsSet Source #

Variant of verifyJWT that uses ClaimsSet as the payload type and where validation time is provided by caller.

verifyJWTAt :: (HasAllowedSkew a, HasAudiencePredicate a, HasIssuerPredicate a, HasCheckIssuedAt a, HasValidationSettings a, AsError e, AsJWTError e, MonadError e m, VerificationKeyStore (ReaderT WrappedUTCTime m) (JWSHeader ()) payload k, HasClaimsSet payload, FromJSON payload) => a -> k -> UTCTime -> SignedJWT -> m payload Source #

Variant of verifyJWT where the validation time is provided by caller. If you process many tokens per second this lets you avoid unnecessary repeat system calls.

Claims Set

data ClaimsSet Source #

The JWT Claims Set represents a JSON object whose members are the registered claims defined by RFC 7519. To construct a ClaimsSet use emptyClaimsSet then use the lenses defined in HasClaimsSet to set relevant claims.

For applications that use additional claims beyond those defined by RFC 7519, define a subtype and instance HasClaimsSet.

emptyClaimsSet :: ClaimsSet Source #

Return an empty claims set.

class HasClaimsSet a where Source #

Minimal complete definition

claimsSet

Methods

claimsSet :: Lens' a ClaimsSet Source #

claimIss :: Lens' a (Maybe StringOrURI) Source #

The issuer claim identifies the principal that issued the JWT. The processing of this claim is generally application specific.

claimSub :: Lens' a (Maybe StringOrURI) Source #

The subject claim identifies the principal that is the subject of the JWT. The Claims in a JWT are normally statements about the subject. The subject value MAY be scoped to be locally unique in the context of the issuer or MAY be globally unique. The processing of this claim is generally application specific.

claimAud :: Lens' a (Maybe Audience) Source #

The audience claim identifies the recipients that the JWT is intended for. Each principal intended to process the JWT MUST identify itself with a value in the audience claim. If the principal processing the claim does not identify itself with a value in the aud claim when this claim is present, then the JWT MUST be rejected.

claimExp :: Lens' a (Maybe NumericDate) Source #

The expiration time claim identifies the expiration time on or after which the JWT MUST NOT be accepted for processing. The processing of exp claim requires that the current date/time MUST be before expiration date/time listed in the exp claim. Implementers MAY provide for some small leeway, usually no more than a few minutes, to account for clock skew.

claimNbf :: Lens' a (Maybe NumericDate) Source #

The not before claim identifies the time before which the JWT MUST NOT be accepted for processing. The processing of the nbf claim requires that the current date/time MUST be after or equal to the not-before date/time listed in the nbf claim. Implementers MAY provide for some small leeway, usually no more than a few minutes, to account for clock skew.

claimIat :: Lens' a (Maybe NumericDate) Source #

The issued at claim identifies the time at which the JWT was issued. This claim can be used to determine the age of the JWT.

claimJti :: Lens' a (Maybe Text) Source #

The JWT ID claim provides a unique identifier for the JWT. The identifier value MUST be assigned in a manner that ensures that there is a negligible probability that the same value will be accidentally assigned to a different data object. The jti claim can be used to prevent the JWT from being replayed. The jti value is a case-sensitive string.

validateClaimsSet :: (MonadTime m, HasAllowedSkew a, HasAudiencePredicate a, HasIssuerPredicate a, HasCheckIssuedAt a, AsJWTError e, MonadError e m) => a -> ClaimsSet -> m ClaimsSet Source #

Validate the claims made by a ClaimsSet.

You should never need to use this function directly. These checks are always performed by verifyClaims and verifyJWT. The function is exported mainly for testing purposes.

Unregistered claims (deprecated)

addClaim :: Text -> Value -> ClaimsSet -> ClaimsSet Source #

Deprecated: use a subtype to define additional claims

Add a non-RFC 7519 claim. Use the lenses from the HasClaimsSet class for setting registered claims.

unregisteredClaims :: Lens' ClaimsSet (Map Text Value) Source #

Deprecated: use a subtype to define additional claims

Claim Names can be defined at will by those using JWTs. Use this lens to access a map non-RFC 7519 claims in the Claims Set object.

JWT errors

data JWTError Source #

Constructors

JWSError Error

A JOSE error occurred while processing the JWT

JWTClaimsSetDecodeError String

The JWT payload is not a JWT Claims Set

JWTExpired 
JWTNotYetValid 
JWTNotInIssuer 
JWTNotInAudience 
JWTIssuedAtFuture 

Instances

Instances details
Show JWTError Source # 
Instance details

Defined in Crypto.JWT

Eq JWTError Source # 
Instance details

Defined in Crypto.JWT

AsError JWTError Source # 
Instance details

Defined in Crypto.JWT

AsJWTError JWTError Source # 
Instance details

Defined in Crypto.JWT

Miscellaneous types

newtype Audience Source #

Audience data. In the general case, the aud value is an array of case-sensitive strings, each containing a StringOrURI value. In the special case when the JWT has one audience, the aud value MAY be a single case-sensitive string containing a StringOrURI value.

The ToJSON instance formats an Audience with one value as a string (some non-compliant implementations require this.)

Constructors

Audience [StringOrURI] 

Instances

Instances details
FromJSON Audience Source # 
Instance details

Defined in Crypto.JWT

ToJSON Audience Source # 
Instance details

Defined in Crypto.JWT

Show Audience Source # 
Instance details

Defined in Crypto.JWT

Eq Audience Source # 
Instance details

Defined in Crypto.JWT

data StringOrURI Source #

A JSON string value, with the additional requirement that while arbitrary string values MAY be used, any value containing a : character MUST be a URI.

Note: the IsString instance will fail if the string contains a : but does not parse as a URI. Use stringOrUri directly in this situation.

Instances

Instances details
FromJSON StringOrURI Source # 
Instance details

Defined in Crypto.JWT

ToJSON StringOrURI Source # 
Instance details

Defined in Crypto.JWT

IsString StringOrURI Source #

Non-total. A string with a : in it MUST parse as a URI

Instance details

Defined in Crypto.JWT

Show StringOrURI Source # 
Instance details

Defined in Crypto.JWT

Eq StringOrURI Source # 
Instance details

Defined in Crypto.JWT

newtype NumericDate Source #

A JSON numeric value representing the number of seconds from 1970-01-01T0:0:0Z UTC until the specified UTC date/time.

Constructors

NumericDate UTCTime 

Re-exports

Orphan instances