Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
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.
import Crypto.JWT mkClaims :: IOClaimsSet
mkClaims = do t <-currentTime
pure $emptyClaimsSet
&claimIss
?~ "alice" &claimAud
?~Audience
["bob"] &claimIat
?~NumericDate
t doJwtSign ::JWK
->ClaimsSet
-> IO (EitherJWTError
SignedJWT
) doJwtSign jwk claims =runJOSE
$ do alg <-bestJWSAlg
jwksignClaims
jwk (newJWSHeader
((), alg)) claims doJwtVerify ::JWK
->SignedJWT
-> IO (EitherJWTError
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 (EitherJWTError
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 JWTverifyClaims
(defaultJWTValidationSettings
audCheck) k' jwt
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 } instanceHasClaimsSet
Super whereclaimsSet
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
).
Synopsis
- type SignedJWT = CompactJWS JWSHeader
- signClaims :: (MonadRandom m, MonadError e m, AsError e) => JWK -> JWSHeader () -> ClaimsSet -> m SignedJWT
- signJWT :: (MonadRandom m, MonadError e m, AsError e, ToJSON payload) => JWK -> JWSHeader () -> payload -> m SignedJWT
- defaultJWTValidationSettings :: (StringOrURI -> Bool) -> JWTValidationSettings
- verifyClaims :: (MonadTime m, HasAllowedSkew a, HasAudiencePredicate a, HasIssuerPredicate a, HasCheckIssuedAt a, HasValidationSettings a, AsError e, AsJWTError e, MonadError e m, VerificationKeyStore m (JWSHeader ()) ClaimsSet k) => a -> k -> SignedJWT -> m ClaimsSet
- 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
- class HasAllowedSkew s where
- class HasAudiencePredicate s where
- audiencePredicate :: Lens' s (StringOrURI -> Bool)
- class HasIssuerPredicate s where
- issuerPredicate :: Lens' s (StringOrURI -> Bool)
- class HasCheckIssuedAt s where
- checkIssuedAt :: Lens' s Bool
- data JWTValidationSettings
- class HasJWTValidationSettings c where
- jWTValidationSettings :: Lens' c JWTValidationSettings
- jwtValidationSettingsAllowedSkew :: Lens' c NominalDiffTime
- jwtValidationSettingsAudiencePredicate :: Lens' c (StringOrURI -> Bool)
- jwtValidationSettingsCheckIssuedAt :: Lens' c Bool
- jwtValidationSettingsIssuerPredicate :: Lens' c (StringOrURI -> Bool)
- jwtValidationSettingsValidationSettings :: Lens' c ValidationSettings
- newtype WrappedUTCTime = WrappedUTCTime {}
- 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
- 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
- class HasClaimsSet a where
- data ClaimsSet
- emptyClaimsSet :: ClaimsSet
- addClaim :: Text -> Value -> ClaimsSet -> ClaimsSet
- unregisteredClaims :: Lens' ClaimsSet (Map Text Value)
- validateClaimsSet :: (MonadTime m, HasAllowedSkew a, HasAudiencePredicate a, HasIssuerPredicate a, HasCheckIssuedAt a, AsJWTError e, MonadError e m) => a -> ClaimsSet -> m ClaimsSet
- data JWTError
- class AsJWTError r where
- _JWTError :: Prism' r JWTError
- _JWSError :: Prism' r Error
- _JWTClaimsSetDecodeError :: Prism' r String
- _JWTExpired :: Prism' r ()
- _JWTNotYetValid :: Prism' r ()
- _JWTNotInIssuer :: Prism' r ()
- _JWTNotInAudience :: Prism' r ()
- _JWTIssuedAtFuture :: Prism' r ()
- newtype Audience = Audience [StringOrURI]
- data StringOrURI
- stringOrUri :: (Cons s s Char Char, AsEmpty s) => Prism' s StringOrURI
- string :: Prism' StringOrURI Text
- uri :: Prism' StringOrURI URI
- newtype NumericDate = NumericDate UTCTime
- module Crypto.JOSE
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 #
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
verifyClaims :: (MonadTime m, HasAllowedSkew a, HasAudiencePredicate a, HasIssuerPredicate a, HasCheckIssuedAt a, HasValidationSettings a, AsError e, AsJWTError e, MonadError e m, VerificationKeyStore m (JWSHeader ()) ClaimsSet k) => a -> k -> SignedJWT -> m ClaimsSet Source #
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
HasJWTValidationSettings a => HasAllowedSkew a Source # | |
Defined in Crypto.JWT |
class HasAudiencePredicate s where Source #
Predicate for checking values in the aud claim.
audiencePredicate :: Lens' s (StringOrURI -> Bool) Source #
Instances
HasJWTValidationSettings a => HasAudiencePredicate a Source # | |
Defined in Crypto.JWT audiencePredicate :: Lens' a (StringOrURI -> Bool) Source # |
class HasIssuerPredicate s where Source #
Predicate for checking the iss claim.
issuerPredicate :: Lens' s (StringOrURI -> Bool) Source #
Instances
HasJWTValidationSettings a => HasIssuerPredicate a Source # | |
Defined in Crypto.JWT issuerPredicate :: Lens' a (StringOrURI -> Bool) Source # |
class HasCheckIssuedAt s where Source #
Whether to check that the iat claim is not in the future.
checkIssuedAt :: Lens' s Bool Source #
Instances
HasJWTValidationSettings a => HasCheckIssuedAt a Source # | |
Defined in Crypto.JWT checkIssuedAt :: Lens' a Bool Source # |
data JWTValidationSettings Source #
Instances
class HasJWTValidationSettings c where Source #
jWTValidationSettings :: Lens' c JWTValidationSettings Source #
jwtValidationSettingsAllowedSkew :: Lens' c NominalDiffTime Source #
jwtValidationSettingsAudiencePredicate :: Lens' c (StringOrURI -> Bool) Source #
jwtValidationSettingsCheckIssuedAt :: Lens' c Bool Source #
jwtValidationSettingsIssuerPredicate :: Lens' c (StringOrURI -> Bool) Source #
jwtValidationSettingsValidationSettings :: Lens' c ValidationSettings Source #
Instances
Specifying the verification time
newtype WrappedUTCTime Source #
Instances
Monad m => MonadTime (ReaderT WrappedUTCTime m) Source # | |
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 #
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
class HasClaimsSet a where Source #
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.
Instances
HasClaimsSet ClaimsSet Source # | |
Defined in Crypto.JWT claimsSet :: Lens' ClaimsSet ClaimsSet Source # claimIss :: Lens' ClaimsSet (Maybe StringOrURI) Source # claimSub :: Lens' ClaimsSet (Maybe StringOrURI) Source # claimAud :: Lens' ClaimsSet (Maybe Audience) Source # claimExp :: Lens' ClaimsSet (Maybe NumericDate) Source # claimNbf :: Lens' ClaimsSet (Maybe NumericDate) 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 from this
class to set relevant claims.
For applications that use additional claims beyond those defined
by RFC 7519, define a new data type and instance HasClaimsSet
.
See the module synopsis for more details and an example.
Instances
FromJSON ClaimsSet Source # | |
ToJSON ClaimsSet Source # | |
Defined in Crypto.JWT | |
Show ClaimsSet Source # | |
Eq ClaimsSet Source # | |
HasClaimsSet ClaimsSet Source # | |
Defined in Crypto.JWT claimsSet :: Lens' ClaimsSet ClaimsSet Source # claimIss :: Lens' ClaimsSet (Maybe StringOrURI) Source # claimSub :: Lens' ClaimsSet (Maybe StringOrURI) Source # claimAud :: Lens' ClaimsSet (Maybe Audience) Source # claimExp :: Lens' ClaimsSet (Maybe NumericDate) Source # claimNbf :: Lens' ClaimsSet (Maybe NumericDate) Source # |
emptyClaimsSet :: ClaimsSet Source #
Return an empty claims set.
addClaim :: Text -> Value -> ClaimsSet -> ClaimsSet Source #
Deprecated: unregisteredClaims
is deprecated; use a sub-type
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 sub-type
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.
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.
JWT errors
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
class AsJWTError r where Source #
_JWTError :: Prism' r JWTError Source #
_JWSError :: Prism' r Error Source #
_JWTClaimsSetDecodeError :: Prism' r String Source #
_JWTExpired :: Prism' r () Source #
_JWTNotYetValid :: Prism' r () Source #
_JWTNotInIssuer :: Prism' r () Source #
_JWTNotInAudience :: Prism' r () Source #
_JWTIssuedAtFuture :: Prism' r () Source #
Instances
AsJWTError JWTError Source # | |
Defined in Crypto.JWT _JWTError :: Prism' JWTError JWTError Source # _JWSError :: Prism' JWTError Error Source # _JWTClaimsSetDecodeError :: Prism' JWTError String Source # _JWTExpired :: Prism' JWTError () Source # _JWTNotYetValid :: Prism' JWTError () Source # _JWTNotInIssuer :: Prism' JWTError () Source # _JWTNotInAudience :: Prism' JWTError () Source # _JWTIssuedAtFuture :: Prism' JWTError () Source # |
Miscellaneous
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.)
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
FromJSON StringOrURI Source # | |
Defined in Crypto.JWT parseJSON :: Value -> Parser StringOrURI # parseJSONList :: Value -> Parser [StringOrURI] # | |
ToJSON StringOrURI Source # | |
Defined in Crypto.JWT toJSON :: StringOrURI -> Value # toEncoding :: StringOrURI -> Encoding # toJSONList :: [StringOrURI] -> Value # toEncodingList :: [StringOrURI] -> Encoding # | |
IsString StringOrURI Source # | Non-total. A string with a |
Defined in Crypto.JWT fromString :: String -> StringOrURI # | |
Show StringOrURI Source # | |
Defined in Crypto.JWT showsPrec :: Int -> StringOrURI -> ShowS # show :: StringOrURI -> String # showList :: [StringOrURI] -> ShowS # | |
Eq StringOrURI Source # | |
Defined in Crypto.JWT (==) :: StringOrURI -> StringOrURI -> Bool # (/=) :: StringOrURI -> StringOrURI -> Bool # |
stringOrUri :: (Cons s s Char Char, AsEmpty s) => Prism' s StringOrURI Source #
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.
Instances
module Crypto.JOSE