libjwt-typed-0.1: A Haskell implementation of JSON Web Token (JWT)
Safe HaskellNone
LanguageHaskell2010
Extensions
  • UndecidableInstances
  • ScopedTypeVariables
  • OverloadedStrings
  • RecordPuns
  • StandaloneDeriving
  • DerivingStrategies
  • FlexibleContexts
  • ExplicitForAll

Libjwt.Jwt

Description

JWT representation, signing and decoding.

Synopsis

Documentation

data Jwt pc ns Source #

JSON Web Token representation

Constructors

Jwt 

Fields

Instances

Instances details
Eq (PrivateClaims pc ns) => Eq (Jwt pc ns) Source # 
Instance details

Defined in Libjwt.Jwt

Methods

(==) :: Jwt pc ns -> Jwt pc ns -> Bool #

(/=) :: Jwt pc ns -> Jwt pc ns -> Bool #

Show (PrivateClaims pc ns) => Show (Jwt pc ns) Source # 
Instance details

Defined in Libjwt.Jwt

Methods

showsPrec :: Int -> Jwt pc ns -> ShowS #

show :: Jwt pc ns -> String #

showList :: [Jwt pc ns] -> ShowS #

Encode (PrivateClaims pc ns) => Encode (Jwt pc ns) Source # 
Instance details

Defined in Libjwt.Jwt

Methods

encode :: Jwt pc ns -> JwtT -> EncodeResult Source #

data Encoded t Source #

base64url-encoded value of type t

Instances

Instances details
Eq (Encoded t) Source # 
Instance details

Defined in Libjwt.Jwt

Methods

(==) :: Encoded t -> Encoded t -> Bool #

(/=) :: Encoded t -> Encoded t -> Bool #

Show (Encoded t) Source # 
Instance details

Defined in Libjwt.Jwt

Methods

showsPrec :: Int -> Encoded t -> ShowS #

show :: Encoded t -> String #

showList :: [Encoded t] -> ShowS #

getToken :: Encoded t -> ByteString Source #

octets of the UTF-8 representation

sign :: Encode (PrivateClaims pc ns) => Alg -> Payload pc ns -> Encoded (Jwt pc ns) Source #

Compute the encoded JWT value with the JWS Signature in the manner defined for the algorithm alg . typ of the JWT Header is set to JWT

Creates the serialized ouput, that is: BASE64URL(UTF8(JWT Header)) || . || BASE64URL(JWT Payload) || . || BASE64URL(JWT Signature)

signJwt :: Encode (PrivateClaims pc ns) => Jwt pc ns -> Encoded (Jwt pc ns) Source #

Compute the encoded JWT value with the JWS Signature in the manner defined for the algorithm alg present in the JWT's header .

Creates the serialized ouput, that is: BASE64URL(UTF8(JWT Header)) || . || BASE64URL(JWT Payload) || . || BASE64URL(JWT Signature)

data Decoded t Source #

Decoded value of type t

Instances

Instances details
Eq t => Eq (Decoded t) Source # 
Instance details

Defined in Libjwt.Jwt

Methods

(==) :: Decoded t -> Decoded t -> Bool #

(/=) :: Decoded t -> Decoded t -> Bool #

Show t => Show (Decoded t) Source # 
Instance details

Defined in Libjwt.Jwt

Methods

showsPrec :: Int -> Decoded t -> ShowS #

show :: Decoded t -> String #

showList :: [Decoded t] -> ShowS #

decodeByteString :: forall ns pc m. (MonadThrow m, Decode (PrivateClaims pc ns)) => Alg -> ByteString -> m (Decoded (Jwt pc ns)) Source #

Parse the base64url-encoded representation to extract the serialized values for the components of the JWT. Verify that:

  1. token is a valid UTF-8 encoded representation of a completely valid JSON object,
  2. input JWT signature matches,
  3. the correct algorithm was used,
  4. all required fields are present.

If steps 1-2 are unuccessful, DecodeException will be thrown. If step 3 fails, AlgorithmMismatch will be thrown. If the last step fails, MissingClaim will be thrown.

data Validated t Source #

Successfully validated value of type t

Instances

Instances details
Eq t => Eq (Validated t) Source # 
Instance details

Defined in Libjwt.Jwt

Methods

(==) :: Validated t -> Validated t -> Bool #

(/=) :: Validated t -> Validated t -> Bool #

Show t => Show (Validated t) Source # 
Instance details

Defined in Libjwt.Jwt

validateJwt Source #

Arguments

:: MonadTime m 
=> ValidationSettings

leeway and appName

-> JwtValidation pc ns

additional validation rules

-> Decoded (Jwt pc ns)

decoded token

-> m (ValidationNEL ValidationFailure (Validated (Jwt pc ns))) 

Accept or reject successfully decoded JWT value. In addition to the default rules mandated by the RFC, the application can add its own rules.

The default rules are:

  • check exp claim to see if the current time is before the expiration time,
  • check nbf claim to see if the current time is after or equal the not-before time,
  • check aud claim if the application identifies itself with a value in the aud list (if present)

You may allow a little leeway when checking time-based claims.

aud claim is checked against appName.

jwtFromByteString Source #

Arguments

:: (Decode (PrivateClaims pc ns), MonadTime m, MonadThrow m) 
=> ValidationSettings

leeway and appName

-> JwtValidation pc ns

additional validation rules

-> Alg

algorithm used to verify the signature

-> ByteString

base64url-encoded representation (a token)

-> m (ValidationNEL ValidationFailure (Validated (Jwt pc ns))) 
jwtFromByteString = validateJwt settings v <=< decodeByteString alg

In other words, it:

Parses the base64url-encoded representation to extract the serialized values for the components of the JWT. Verifies that:

  1. token is a valid UTF-8 encoded representation of a completely valid JSON object,
  2. input JWT signature matches,
  3. the correct algorithm was used,
  4. all required fields are present.

If steps 1-2 are unuccessful, DecodeException will be thrown. If step 3 fails, AlgorithmMismatch will be thrown. If the last step fails, MissingClaim will be thrown.

Once the token has been successfully decoded, it is validated.

In addition to the default rules mandated by the RFC, the application can add its own rules.

The default rules are:

  • check exp claim to see if the current time is before the expiration time,
  • check nbf claim to see if the current time is after or equal the not-before time,
  • check aud claim if the application identifies itself with a value in the aud list (if present)

You may allow a little leeway when checking time-based claims.

aud claim is checked against appName.