jwt-0.2.1: JSON Web Token (JWT) decoding and encoding

Stabilityexperimental
MaintainerStefan Saasen <stefan@saasen.me>
Safe HaskellNone

Web.JWT

Contents

Description

This implementation of JWT is based on http://self-issued.info/docs/draft-ietf-oauth-json-web-token.html (Version 16) but currently only implements the minimum required to work with the Atlassian Connect framework.

Known limitations:

  • Only HMAC SHA-256 algorithm is currently a supported signature algorithm
  • There is currently no verification of time related information (exp, nbf, iat).
  • Registered claims are not validated

Synopsis

Encoding & Decoding JWTs

Decoding

decode :: JSON -> Maybe (JWT UnverifiedJWT)Source

Decode a claims set without verifying the signature. This is useful if information from the claim set is required in order to verify the claim (e.g. the secret needs to be retrieved based on unverified information from the claims set).

>>> :{
 let
     input = "eyJ0eXAiOiJKV1QiLCJhbGciOiJIUzI1NiJ9.eyJzb21lIjoicGF5bG9hZCJ9.Joh1R2dYzkRvDkqv3sygm5YyK8Gi4ShZqbhK2gxcs2U" :: T.Text
     mJwt = decode input
 in fmap header mJwt
:}
Just (JWTHeader {typ = Just "JWT", cty = Nothing, alg = Just HS256})

and

>>> :{
 let
     input = "eyJ0eXAiOiJKV1QiLCJhbGciOiJIUzI1NiJ9.eyJzb21lIjoicGF5bG9hZCJ9.Joh1R2dYzkRvDkqv3sygm5YyK8Gi4ShZqbhK2gxcs2U" :: T.Text
     mJwt = decode input
 in fmap claims mJwt
:}
Just (JWTClaimsSet {iss = Nothing, sub = Nothing, aud = Nothing, exp = Nothing, nbf = Nothing, iat = Nothing, jti = Nothing, unregisteredClaims = fromList [("some",String "payload")]})

decodeAndVerifySignature :: Secret -> Text -> Maybe (JWT VerifiedJWT)Source

Decode a claims set and verify that the signature matches by using the supplied secret. The algorithm is based on the supplied header value.

This will return a VerifiedJWT if and only if the signature can be verified using the given secret.

>>> :{
 let
     input = "eyJ0eXAiOiJKV1QiLCJhbGciOiJIUzI1NiJ9.eyJzb21lIjoicGF5bG9hZCJ9.Joh1R2dYzkRvDkqv3sygm5YyK8Gi4ShZqbhK2gxcs2U" :: T.Text
     mJwt = decodeAndVerifySignature (secret "secret") input
 in join $ fmap signature mJwt
:}
Just (Signature "Joh1R2dYzkRvDkqv3sygm5YyK8Gi4ShZqbhK2gxcs2U")

Encoding

encodeSigned :: Algorithm -> Secret -> JWTClaimsSet -> JSONSource

Encode a claims set using the given secret

>>> :{
 let
     cs = def { -- def returns a default JWTClaimsSet
        iss = stringOrURI "Foo"
      , unregisteredClaims = Map.fromList [("http://example.com/is_root", (Bool True))]
     }
     key = secret "secret-key"
 in encodeSigned HS256 key cs
:}
"eyJ0eXAiOiJKV1QiLCJhbGciOiJIUzI1NiJ9.eyJodHRwOi8vZXhhbXBsZS5jb20vaXNfcm9vdCI6dHJ1ZSwiaXNzIjoiRm9vIn0.vHQHuG3ujbnBUmEp-fSUtYxk27rLiP2hrNhxpyWhb2E"

encodeUnsigned :: JWTClaimsSet -> JSONSource

Encode a claims set without signing it

>>> :{
 let
     cs = def { -- def returns a default JWTClaimsSet
     iss = stringOrURI "Foo"
   , iat = intDate 1394700934
   , unregisteredClaims = Map.fromList [("http://example.com/is_root", (Bool True))]
 }
 in encodeUnsigned cs
:}
"eyJ0eXAiOiJKV1QiLCJhbGciOiJIUzI1NiJ9.eyJpYXQiOjEzOTQ3MDA5MzQsImh0dHA6Ly9leGFtcGxlLmNvbS9pc19yb290Ijp0cnVlLCJpc3MiOiJGb28ifQ."

Utility functions

Common

tokenIssuer :: JSON -> Maybe StringOrURISource

Try to extract the value for the issue claim field iss from the web token in JSON form

secret :: Text -> SecretSource

Create a Secret using the given key This will currently simply wrap the given key appropriately buy may return a Nothing in the future if the key needs to adhere to a specific format and the given key is invalid.

JWT structure

claims :: JWT r -> JWTClaimsSetSource

Extract the claims set from a JSON Web Token

header :: JWT r -> JWTHeaderSource

Extract the header from a JSON Web Token

signature :: JWT r -> Maybe SignatureSource

Extract the signature from a verified JSON Web Token

JWT claims set

intDate :: NominalDiffTime -> Maybe IntDateSource

Convert the NominalDiffTime into an IntDate. Returns a Nothing if the argument is invalid (e.g. the NominalDiffTime must be convertible into a positive Integer representing the seconds since epoch).

stringOrURI :: Text -> Maybe StringOrURISource

Convert a Text into a StringOrURI. Returns a Nothing if the String cannot be converted (e.g. if the String contains a : but is *not* a valid URI).

secondsSinceEpoch :: IntDate -> NominalDiffTimeSource

Return the seconds since 1970-01-01T0:0:0Z UTC for the given IntDate

JWT header

typ :: JWTHeader -> Maybe TextSource

The typ (type) Header Parameter defined by [JWS] and [JWE] is used to declare the MIME Media Type [IANA.MediaTypes] of this complete JWT in contexts where this is useful to the application. This parameter has no effect upon the JWT processing.

cty :: JWTHeader -> Maybe TextSource

The cty (content type) Header Parameter defined by [JWS] and [JWE] is used by this specification to convey structural information about the JWT.

alg :: JWTHeader -> Maybe AlgorithmSource

The alg (algorithm) used for signing the JWT. The HS256 (HMAC using SHA-256) is the only required algorithm and the only one supported in this implementation in addition to none which means that no signature will be used.

See http://tools.ietf.org/html/draft-ietf-jose-json-web-algorithms-23#page-6

Types

data UnverifiedJWT Source

JSON Web Token without signature verification

data VerifiedJWT Source

JSON Web Token that has been successfully verified

data Secret Source

The secret used for calculating the message signature

Instances

data JWT r Source

The JSON Web Token

Instances

Show (JWT r) 

data Algorithm Source

Constructors

HS256

HMAC using SHA-256 hash algorithm

data JWTClaimsSet Source

The JWT Claims Set represents a JSON object whose members are the claims conveyed by the JWT.

Constructors

JWTClaimsSet 

Fields

iss :: Maybe StringOrURI

The iss (issuer) claim identifies the principal that issued the JWT.

sub :: Maybe StringOrURI

The sub (subject) claim identifies the principal that is the subject of the JWT.

aud :: Maybe StringOrURI

The aud (audience) claim identifies the audiences that the JWT is intended for

exp :: Maybe IntDate

The exp (expiration time) claim identifies the expiration time on or after which the JWT MUST NOT be accepted for processing. Its value MUST be a number containing an IntDate value.

nbf :: Maybe IntDate

The nbf (not before) claim identifies the time before which the JWT MUST NOT be accepted for processing.

iat :: Maybe IntDate

The iat (issued at) claim identifies the time at which the JWT was issued.

jti :: Maybe StringOrURI

The jti (JWT ID) claim provides a unique identifier for the JWT.

unregisteredClaims :: ClaimsMap
 

data IntDate Source

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

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 [RFC3986]. StringOrURI values are compared as case-sensitive strings with no transformations or canonicalizations applied.

data JWTHeader Source

JWT Header, describes the cryptographic operations applied to the JWT