Safe Haskell | None |
---|---|
Language | Haskell2010 |
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.
Type | Auth Scheme | Trait | Middleware |
Required | Bearer | JWTAuth | jwtAuth |
Optional | Bearer | JWTAuth' Optional | optionalJWTAuth |
Required | Any scheme | JWTAuth' Required | jwtAuth' |
Optional | Any scheme | JWTAuth' Optional | optionalJWTAuth' |
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
. This is used to convert the set
of claims in the JWT to a value of type ClaimsSet
-> m (Either e a)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
(
. The next handler will get the errors in this
trait attribute and must handle it.JWTAuthError
e) a
Synopsis
- data JWTAuth' (x :: Existence) (scheme :: Symbol) m e a = JWTAuth' {
- jwtValidationSettings :: JWTValidationSettings
- jwkSet :: JWKSet
- toJWTAttribute :: ClaimsSet -> m (Either e a)
- type JWTAuth = JWTAuth' Required "Bearer"
- newtype Realm = Realm ByteString
- data JWTAuthError e
- jwtAuth :: (Get h (JWTAuth m e t) Request, ArrowChoice h) => JWTAuth m e t -> h (Linked req Request, JWTAuthError e) Response -> Middleware h req (JWTAuth m e t ': req)
- optionalJWTAuth :: (Get h (JWTAuth' Optional "Bearer" m e t) Request, ArrowChoice h) => JWTAuth' Optional "Bearer" m e t -> Middleware h req (JWTAuth' Optional "Bearer" m e t ': req)
- jwtAuth' :: forall s e t h m req. (Get h (JWTAuth' Required s m e t) Request, ArrowChoice h) => JWTAuth' Required s m e t -> h (Linked req Request, JWTAuthError e) Response -> Middleware h req (JWTAuth' Required s m e t ': req)
- optionalJWTAuth' :: forall s e t h m req. (Get h (JWTAuth' Optional s m e t) Request, ArrowChoice h) => JWTAuth' Optional s m e t -> Middleware h req (JWTAuth' Optional s m e t ': req)
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.
JWTAuth' | |
|
Instances
TraitAbsence (JWTAuth' 'Required scheme m e a) Request Source # | |
TraitAbsence (JWTAuth' 'Optional scheme m e a) Request Source # | |
Trait (JWTAuth' 'Required scheme m e a) Request Source # | |
Trait (JWTAuth' 'Optional scheme m e a) Request Source # | |
type Absence (JWTAuth' 'Required scheme m e a) Request Source # | |
Defined in WebGear.Core.Trait.Auth.JWT | |
type Absence (JWTAuth' 'Optional scheme m e a) Request Source # | |
type Attribute (JWTAuth' 'Required scheme m e a) Request Source # | |
Defined in WebGear.Core.Trait.Auth.JWT | |
type Attribute (JWTAuth' 'Optional scheme m e a) Request Source # | |
Defined in WebGear.Core.Trait.Auth.JWT |
type JWTAuth = JWTAuth' Required "Bearer" Source #
Trait for JWT authentication with the "Bearer" scheme
The protection space for authentication
data JWTAuthError e Source #
Error extracting a JWT from a request
Instances
Eq e => Eq (JWTAuthError e) Source # | |
Defined in WebGear.Core.Trait.Auth.JWT (==) :: JWTAuthError e -> JWTAuthError e -> Bool # (/=) :: JWTAuthError e -> JWTAuthError e -> Bool # | |
Show e => Show (JWTAuthError e) Source # | |
Defined in WebGear.Core.Trait.Auth.JWT showsPrec :: Int -> JWTAuthError e -> ShowS # show :: JWTAuthError e -> String # showList :: [JWTAuthError e] -> ShowS # |
:: (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.
:: (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
so that the handler can process the
authentication error appropriately.Either
(JWTAuthError
e) t
:: 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.
:: 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
so that the handler can process the
authentication error appropriately.Either
(JWTAuthError
e) t