webgear-core-1.0.4: Composable, type-safe library to build HTTP APIs
Safe HaskellSafe-Inferred
LanguageHaskell2010

WebGear.Core.Trait.Auth.JWT

Description

JWT authentication support.

Middlewares defined in this module add JWT authentication support to handlers. In most cases, you just need to use JWTAuth trait and jwtAuth middleware. The table below describes when to use other traits and middlewares.

TypeAuth SchemeTraitMiddleware
RequiredBearerJWTAuthjwtAuth
OptionalBearerJWTAuth' OptionaloptionalJWTAuth
RequiredAny schemeJWTAuth' RequiredjwtAuth'
OptionalAny schemeJWTAuth' OptionaloptionalJWTAuth'

For example, given this handler:

myHandler :: (Handler h IO, HasTrait (JWTAuth IO () ClaimsSet) req) => RequestHandler h req
myHandler = ....

and the following definitions:

authConfig :: JWTAuth IO () ClaimsSet
authConfig = JWTAuth'
  { jwtValidationSettings = defaultJWTValidationSettings (const True)
  , jwkSet = ....
  , toJWTAttribute = pure . Right
  }

type ErrorTraits = [Status, RequiredHeader "Content-Type" Text, RequiredHeader "WWW-Authenticate" Text, Body Text]

errorHandler :: (Handler h IO, Sets h ErrorTraits Response)
             => h (Linked req Request, JWTAuthError e) Response
errorHandler = respondUnauthorized "Bearer" "MyRealm"

we can add JWT authentication to myHandler:

myHandlerWithAuth :: (Handler h IO, Get h (JWTAuth IO () ClaimsSet) Request, Sets h ErrorTraits Response)
                  => RequestHandler h req
myHandlerWithAuth = jwtAuth authConfig errorHandler myHandler

The middlewares defined below take a JWTAuth' parameter which has settings for validating a JWT. It also contains a function of type ClaimsSet -> m (Either e a). This is used to convert the set of claims in the JWT to a value of type a or fail with an error of type e. In this case a is the type of the trait attribute and the next handler is invoked after this conversion.

Middlewares marked as Required take an additional error handling arrow as a parameter. This arrow is used when an error is encountered in authentication. This arrow receives the original request and a JWTAuthError as inputs and must produce a response as the output.

Middlewares marked as Optional do not have this additional error handling arrow. Instead, the trait attribute is of type Either (JWTAuthError e) a. The next handler will get the errors in this trait attribute and must handle it.

Synopsis

Documentation

data JWTAuth' (x :: Existence) (scheme :: Symbol) m e a Source #

Trait for JWT authentication with a bearer token: https://tools.ietf.org/html/rfc6750

This trait supports a custom scheme instead of the standard "Bearer" scheme.

Constructors

JWTAuth' 

Fields

Instances

Instances details
Trait (JWTAuth' 'Optional scheme m e a) Request Source # 
Instance details

Defined in WebGear.Core.Trait.Auth.JWT

Associated Types

type Attribute (JWTAuth' 'Optional scheme m e a) Request Source #

Trait (JWTAuth' 'Required scheme m e a) Request Source # 
Instance details

Defined in WebGear.Core.Trait.Auth.JWT

Associated Types

type Attribute (JWTAuth' 'Required scheme m e a) Request Source #

TraitAbsence (JWTAuth' 'Optional scheme m e a) Request Source # 
Instance details

Defined in WebGear.Core.Trait.Auth.JWT

Associated Types

type Absence (JWTAuth' 'Optional scheme m e a) Request Source #

TraitAbsence (JWTAuth' 'Required scheme m e a) Request Source # 
Instance details

Defined in WebGear.Core.Trait.Auth.JWT

Associated Types

type Absence (JWTAuth' 'Required scheme m e a) Request Source #

type Absence (JWTAuth' 'Optional scheme m e a) Request Source # 
Instance details

Defined in WebGear.Core.Trait.Auth.JWT

type Absence (JWTAuth' 'Optional scheme m e a) Request = Void
type Absence (JWTAuth' 'Required scheme m e a) Request Source # 
Instance details

Defined in WebGear.Core.Trait.Auth.JWT

type Absence (JWTAuth' 'Required scheme m e a) Request = JWTAuthError e
type Attribute (JWTAuth' 'Optional scheme m e a) Request Source # 
Instance details

Defined in WebGear.Core.Trait.Auth.JWT

type Attribute (JWTAuth' 'Optional scheme m e a) Request = Either (JWTAuthError e) a
type Attribute (JWTAuth' 'Required scheme m e a) Request Source # 
Instance details

Defined in WebGear.Core.Trait.Auth.JWT

type Attribute (JWTAuth' 'Required scheme m e a) Request = a

type JWTAuth = JWTAuth' Required "Bearer" Source #

Trait for JWT authentication with the "Bearer" scheme

newtype Realm Source #

The protection space for authentication

Constructors

Realm ByteString 

Instances

Instances details
IsString Realm Source # 
Instance details

Defined in WebGear.Core.Trait.Auth.Common

Methods

fromString :: String -> Realm #

Read Realm Source # 
Instance details

Defined in WebGear.Core.Trait.Auth.Common

Show Realm Source # 
Instance details

Defined in WebGear.Core.Trait.Auth.Common

Methods

showsPrec :: Int -> Realm -> ShowS #

show :: Realm -> String #

showList :: [Realm] -> ShowS #

Eq Realm Source # 
Instance details

Defined in WebGear.Core.Trait.Auth.Common

Methods

(==) :: Realm -> Realm -> Bool #

(/=) :: Realm -> Realm -> Bool #

Ord Realm Source # 
Instance details

Defined in WebGear.Core.Trait.Auth.Common

Methods

compare :: Realm -> Realm -> Ordering #

(<) :: Realm -> Realm -> Bool #

(<=) :: Realm -> Realm -> Bool #

(>) :: Realm -> Realm -> Bool #

(>=) :: Realm -> Realm -> Bool #

max :: Realm -> Realm -> Realm #

min :: Realm -> Realm -> Realm #

data JWTAuthError e Source #

Error extracting a JWT from a request

Instances

Instances details
Show e => Show (JWTAuthError e) Source # 
Instance details

Defined in WebGear.Core.Trait.Auth.JWT

Eq e => Eq (JWTAuthError e) Source # 
Instance details

Defined in WebGear.Core.Trait.Auth.JWT

jwtAuth Source #

Arguments

:: (Get h (JWTAuth m e t) Request, ArrowChoice h) 
=> JWTAuth m e t

Authentication configuration

-> h (Linked req Request, JWTAuthError e) Response

Error handler

-> Middleware h req (JWTAuth m e t ': req) 

Middleware to add JWT authentication protection for a handler. Expects the JWT to be available via a standard bearer authorization header in the format:

Authorization: Bearer <jwt>

Example usage:

jwtAuth cfg errorHandler nextHandler

The errorHandler is invoked if the credentials are invalid or missing. The nextHandler is invoked if the credentials were retrieved successfully.

optionalJWTAuth Source #

Arguments

:: (Get h (JWTAuth' Optional "Bearer" m e t) Request, ArrowChoice h) 
=> JWTAuth' Optional "Bearer" m e t

Authentication configuration

-> Middleware h req (JWTAuth' Optional "Bearer" m e t ': req) 

Middleware to add optional JWT authentication protection for a handler. Expects the JWT to be available via a standard bearer authorization header in the format:

Authorization: Bearer <jwt>

Example usage:

optionalJWTAuth cfg handler

This middleware will not fail if authorization credentials are invalid or missing. Instead the trait attribute is of type Either (JWTAuthError e) t so that the handler can process the authentication error appropriately.

jwtAuth' Source #

Arguments

:: forall s e t h m req. (Get h (JWTAuth' Required s m e t) Request, ArrowChoice h) 
=> JWTAuth' Required s m e t

Authentication configuration

-> h (Linked req Request, JWTAuthError e) Response

Error handler

-> Middleware h req (JWTAuth' Required s m e t ': req) 

Middleware to add JWT authentication protection for a handler. Expects the JWT to be available via an authorization header in the format:

Authorization: <scheme> <jwt>

Example usage:

jwtAuth' @"<scheme>" cfg errorHandler nextHandler

The errorHandler is invoked if the credentials are invalid or missing. The nextHandler is invoked if the credentials were retrieved successfully.

optionalJWTAuth' Source #

Arguments

:: forall s e t h m req. (Get h (JWTAuth' Optional s m e t) Request, ArrowChoice h) 
=> JWTAuth' Optional s m e t

Authentication configuration

-> Middleware h req (JWTAuth' Optional s m e t ': req) 

Middleware to add JWT authentication protection for a handler. Expects the JWT to be available via an authorization header in the format:

Authorization: <scheme> <jwt>

Example usage:

optionalJWTAuth' @"<scheme>" cfg nextHandler

This middleware will not fail if authorization credentials are invalid or missing. Instead the trait attribute is of type Either (JWTAuthError e) t so that the handler can process the authentication error appropriately.