Safe Haskell | None |
---|---|
Language | Haskell98 |
Crypto.JWT
Description
JSON Web Token implementation.
- data JWT = JWT {}
- data JWTCrypto = JWTJWS (JWS JWSHeader)
- data JWTError
- class AsJWTError r where
- data JWTValidationSettings
- defaultJWTValidationSettings :: JWTValidationSettings
- class HasJWTValidationSettings c where
- class HasAllowedSkew s where
- class HasAudiencePredicate s where
- class HasIssuerPredicate s where
- class HasCheckIssuedAt s where
- createJWSJWT :: (MonadRandom m, MonadError e m, AsError e) => JWK -> JWSHeader -> ClaimsSet -> m JWT
- validateJWSJWT :: (MonadTime m, HasAllowedSkew a, HasAudiencePredicate a, HasIssuerPredicate a, HasCheckIssuedAt a, HasValidationSettings a, AsError e, AsJWTError e, MonadError e m) => a -> JWK -> JWT -> m ()
- data ClaimsSet = ClaimsSet {}
- claimAud :: Lens' ClaimsSet (Maybe Audience)
- claimExp :: Lens' ClaimsSet (Maybe NumericDate)
- claimIat :: Lens' ClaimsSet (Maybe NumericDate)
- claimIss :: Lens' ClaimsSet (Maybe StringOrURI)
- claimJti :: Lens' ClaimsSet (Maybe Text)
- claimNbf :: Lens' ClaimsSet (Maybe NumericDate)
- claimSub :: Lens' ClaimsSet (Maybe StringOrURI)
- unregisteredClaims :: Lens' ClaimsSet (HashMap Text Value)
- addClaim :: Text -> Value -> ClaimsSet -> ClaimsSet
- emptyClaimsSet :: ClaimsSet
- validateClaimsSet :: (MonadTime m, HasAllowedSkew a, HasAudiencePredicate a, HasIssuerPredicate a, HasCheckIssuedAt a, AsJWTError e, MonadError e m) => a -> ClaimsSet -> m ()
- newtype Audience = Audience [StringOrURI]
- data StringOrURI
- fromString :: Text -> StringOrURI
- fromURI :: URI -> StringOrURI
- getString :: StringOrURI -> Maybe Text
- getURI :: StringOrURI -> Maybe URI
- newtype NumericDate = NumericDate UTCTime
Documentation
JSON Web Token data.
Constructors
JWT | |
Fields
|
Data representing the JOSE aspects of a JWT.
class AsJWTError r where Source #
Methods
_JWTError :: Prism' r JWTError Source #
_JWSError :: Prism' r Error Source #
_JWTExpired :: Prism' r () Source #
_JWTNotYetValid :: Prism' r () Source #
_JWTNotInIssuer :: Prism' r () Source #
_JWTNotInAudience :: Prism' r () Source #
_JWTIssuedAtFuture :: Prism' r () Source #
Instances
data JWTValidationSettings Source #
class HasJWTValidationSettings c where Source #
Minimal complete definition
Methods
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
class HasAudiencePredicate s where Source #
Minimal complete definition
Methods
audiencePredicate :: Lens' s (StringOrURI -> Bool) Source #
Instances
class HasIssuerPredicate s where Source #
Minimal complete definition
Methods
issuerPredicate :: Lens' s (StringOrURI -> Bool) Source #
Instances
class HasCheckIssuedAt s where Source #
Minimal complete definition
Methods
checkIssuedAt :: Lens' s Bool Source #
Instances
createJWSJWT :: (MonadRandom m, MonadError e m, AsError e) => JWK -> JWSHeader -> ClaimsSet -> m JWT Source #
Create a JWT that is a JWS.
validateJWSJWT :: (MonadTime m, HasAllowedSkew a, HasAudiencePredicate a, HasIssuerPredicate a, HasCheckIssuedAt a, HasValidationSettings a, AsError e, AsJWTError e, MonadError e m) => a -> JWK -> JWT -> m () Source #
Validate a JWT as a JWS (JSON Web Signature), then as a Claims Set.
The JWT Claims Set represents a JSON object whose members are the claims conveyed by the JWT.
Constructors
ClaimsSet | |
Fields
|
emptyClaimsSet :: ClaimsSet Source #
Return an empty claims set.
validateClaimsSet :: (MonadTime m, HasAllowedSkew a, HasAudiencePredicate a, HasIssuerPredicate a, HasCheckIssuedAt a, AsJWTError e, MonadError e m) => a -> ClaimsSet -> m () Source #
Validate the claims made by a ClaimsSet. Currently only inspects
the exp and nbf claims. N.B. These checks are also performed by
validateJWSJWT
, which also validates any signatures, so you
shouldn’t need to use this directly in the normal course of things.
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.
Constructors
Audience [StringOrURI] |
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.
fromString :: Text -> StringOrURI Source #
Construct a StringOrURI
from text
fromURI :: URI -> StringOrURI Source #
Construct a StringOrURI
from a URI
getURI :: StringOrURI -> Maybe URI Source #
Get the uri from a StringOrURI
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 |
Instances