Stability | experimental |
---|---|
Maintainer | Stefan Saasen <[email protected]> |
Safe Haskell | None |
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:
- decode :: JSON -> Maybe (JWT UnverifiedJWT)
- decodeAndVerifySignature :: Secret -> Text -> Maybe (JWT VerifiedJWT)
- encodeSigned :: Algorithm -> Secret -> JWTClaimsSet -> JSON
- encodeUnsigned :: JWTClaimsSet -> JSON
- tokenIssuer :: JSON -> Maybe StringOrURI
- secret :: Text -> Secret
- claims :: JWT r -> JWTClaimsSet
- header :: JWT r -> JWTHeader
- signature :: JWT r -> Maybe Signature
- intDate :: NominalDiffTime -> Maybe IntDate
- stringOrURI :: Text -> Maybe StringOrURI
- typ :: JWTHeader -> Maybe Text
- cty :: JWTHeader -> Maybe Text
- alg :: JWTHeader -> Maybe Algorithm
- data UnverifiedJWT
- data VerifiedJWT
- data Signature
- data Secret
- data JWT r
- type JSON = Text
- data Algorithm = HS256
- data JWTClaimsSet = JWTClaimsSet {
- iss :: Maybe StringOrURI
- sub :: Maybe StringOrURI
- aud :: Maybe StringOrURI
- exp :: Maybe IntDate
- nbf :: Maybe IntDate
- iat :: Maybe IntDate
- jti :: Maybe StringOrURI
- unregisteredClaims :: ClaimsMap
- data IntDate
- data StringOrURI
- data JWTHeader
- module Data.Default
Encoding & Decoding JWTs
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).
import qualified Data.Text as T let input = "eyJ0eXAiOiJKV1QiLCJhbGciOiJIUzI1NiJ9.eyJzb21lIjoicGF5bG9hZCJ9.Joh1R2dYzkRvDkqv3sygm5YyK8Gi4ShZqbhK2gxcs2U" :: T.Text mJwt = decode input mHeader = fmap header mJwt mClaims = fmap claims mJwt mSignature = join $ fmap signature mJwt
This yields:
>>> mHeader Just (JWTHeader {typ = Just "JWT", cty = Nothing, alg = Just HS256})
and
>>> mClaims Just (JWTClaimsSet {iss = Nothing, sub = Nothing, aud = Nothing, exp = Nothing, nbf = Nothing, iat = Nothing, jti = Nothing, unregisteredClaims = fromList [("some",String "payload")]})
and
>>> mSignature Nothing
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.
import qualified Data.Text as T let input = "eyJ0eXAiOiJKV1QiLCJhbGciOiJIUzI1NiJ9.eyJzb21lIjoicGF5bG9hZCJ9.Joh1R2dYzkRvDkqv3sygm5YyK8Gi4ShZqbhK2gxcs2U" :: T.Text mJwt = decodeAndVerifySignature (secret "secret") input mSignature = join $ fmap signature mJwt
This yields:
>>> mJwt Just (Verified (JWTHeader {typ = Just "JWT", cty = Nothing, alg = Just HS256}) (JWTClaimsSet {iss = Nothing, sub = Nothing, aud = Nothing, exp = Nothing, nbf = Nothing, iat = Nothing, jti = Nothing, unregisteredClaims = fromList [("some",String "payload")]}) (Signature "Joh1R2dYzkRvDkqv3sygm5YyK8Gi4ShZqbhK2gxcs2U"))
and
>>> mSignature Just (Signature "Joh1R2dYzkRvDkqv3sygm5YyK8Gi4ShZqbhK2gxcs2U")
encodeSigned :: Algorithm -> Secret -> JWTClaimsSet -> JSONSource
Encode a claims set using the given secret
{-# LANGUAGE OverloadedStrings #-} import Data.Aeson import qualified Data.Map as Map 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" jwt = encodeSigned HS256 key cs
This yields:
>>> jwt "eyJ0eXAiOiJKV1QiLCJhbGciOiJIUzI1NiJ9.eyJodHRwOi8vZXhhbXBsZS5jb20vaXNfcm9vdCI6dHJ1ZSwiaXNzIjoiRm9vIn0.vHQHuG3ujbnBUmEp-fSUtYxk27rLiP2hrNhxpyWhb2E"
encodeUnsigned :: JWTClaimsSet -> JSONSource
Encode a claims set without signing it
{-# LANGUAGE OverloadedStrings #-} import Data.Aeson import qualified Data.Map as Map let cs = def { -- def returns a default JWTClaimsSet iss = stringOrURI "Foo" , unregisteredClaims = Map.fromList [("http://example.com/is_root", (Bool True))] } jwt = encodeUnsigned cs
This yields:
>>> jwt "eyJ0eXAiOiJKV1QiLCJhbGciOiJIUzI1NiJ9.eyJodHRwOi8vZXhhbXBsZS5jb20vaXNfcm9vdCI6dHJ1ZSwiaXNzIjoiRm9vIn0."
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
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).
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.
Types
data UnverifiedJWT Source
JSON Web Token without signature verification
data VerifiedJWT Source
JSON Web Token that has been successfully verified
The secret used for calculating the message signature
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
|
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.
Instances
JWT Header, describes the cryptographic operations applied to the JWT
module Data.Default