Safe Haskell | None |
---|---|
Language | Haskell2010 |
This is an implementation of the jwt-bearer authorization grant flow that is specified by the OAuth2 JWT profile in rfc7523.
This module includes everything you should need to implement an integration and obtain an access token.
{-# LANGUAGE OverloadedStrings #-} import Crypto.JWT (JWK) import Network.OAuth2.JWT.Client import Network.HTTP.Client (Manager)
The key function here is the grant
function which is what you call
to get your access token.
The grant
function obtains an access token, if we have already
aquired one (and it is still valid) we will re-use that token, if we
don't already have a token or the token has expired, we go and ask for
a new one.
example :: Manager -> JWK -> IO (Either GrantError AccessToken) example manager key = do let endpoint = TokenEndpoint "https://www.googleapis.com/oauth2/v4/token" iss = Issuer "example@example.org" scopes = [Scope "profile"] aud = Audience "https://www.googleapis.com/oauth2/v4/token" expiry = ExpiresIn 3600 claims = Claims iss Nothing aud scopes expiry [] store <- newStore manager endpoint claims key grant store
This operation is safe to call from multiple threads. If we are using a current token reads will happen concurrently, If we have to go to the network the request will be serialised so that only one request is made for a new token.
The access token can be used as a bearer token in an Authorization
header. See the specification for more details but it would be something
like:
Authorization: Bearer ${ACCESS_TOKEN}
Synopsis
- data GrantError
- newtype AccessToken = AccessToken {}
- grant :: Store -> IO (Either GrantError AccessToken)
- newtype Issuer = Issuer {}
- newtype Scope = Scope {}
- newtype Audience = Audience {
- getAudience :: Text
- newtype Subject = Subject {
- getSubject :: Text
- newtype ExpiresIn = ExpiresIn {}
- data Claims = Claims {
- claimsIssuer :: Issuer
- claimsSubject :: Maybe Subject
- claimsAudience :: Audience
- claimsScopes :: [Scope]
- claimsExpires :: ExpiresIn
- claimsCustom :: [(Text, Value)]
- newtype TokenEndpoint = TokenEndpoint {}
- data Store
- newStore :: Manager -> TokenEndpoint -> Claims -> JWK -> IO Store
Obtain an access token
data GrantError Source #
SerialisationGrantError Text | |
JWTGrantError JWTError | |
EndpointGrantError Text | |
StatusGrantError Int Text |
Instances
Eq GrantError Source # | |
Defined in Network.OAuth2.JWT.Client.AuthorizationGrant (==) :: GrantError -> GrantError -> Bool # (/=) :: GrantError -> GrantError -> Bool # | |
Show GrantError Source # | |
Defined in Network.OAuth2.JWT.Client.AuthorizationGrant showsPrec :: Int -> GrantError -> ShowS # show :: GrantError -> String # showList :: [GrantError] -> ShowS # |
newtype AccessToken Source #
Instances
Eq AccessToken Source # | |
Defined in Network.OAuth2.JWT.Client.Data (==) :: AccessToken -> AccessToken -> Bool # (/=) :: AccessToken -> AccessToken -> Bool # | |
Ord AccessToken Source # | |
Defined in Network.OAuth2.JWT.Client.Data compare :: AccessToken -> AccessToken -> Ordering # (<) :: AccessToken -> AccessToken -> Bool # (<=) :: AccessToken -> AccessToken -> Bool # (>) :: AccessToken -> AccessToken -> Bool # (>=) :: AccessToken -> AccessToken -> Bool # max :: AccessToken -> AccessToken -> AccessToken # min :: AccessToken -> AccessToken -> AccessToken # | |
Show AccessToken Source # | |
Defined in Network.OAuth2.JWT.Client.Data showsPrec :: Int -> AccessToken -> ShowS # show :: AccessToken -> String # showList :: [AccessToken] -> ShowS # |
grant :: Store -> IO (Either GrantError AccessToken) Source #
Obtain an access token, if we have already aquired one (and it is still valid) we will re-use that token, if we don't already have a token or the token has expired, we go and ask for a new one.
This operation is safe to call from multiple threads. If we are using a current token reads will happen concurrently, If we have to go to the network the request will be serialised so that only one request is made for a new token.
Claims
Claims | |
|
Configuration
newtype TokenEndpoint Source #
Instances
Eq TokenEndpoint Source # | |
Defined in Network.OAuth2.JWT.Client.Data (==) :: TokenEndpoint -> TokenEndpoint -> Bool # (/=) :: TokenEndpoint -> TokenEndpoint -> Bool # | |
Ord TokenEndpoint Source # | |
Defined in Network.OAuth2.JWT.Client.Data compare :: TokenEndpoint -> TokenEndpoint -> Ordering # (<) :: TokenEndpoint -> TokenEndpoint -> Bool # (<=) :: TokenEndpoint -> TokenEndpoint -> Bool # (>) :: TokenEndpoint -> TokenEndpoint -> Bool # (>=) :: TokenEndpoint -> TokenEndpoint -> Bool # max :: TokenEndpoint -> TokenEndpoint -> TokenEndpoint # min :: TokenEndpoint -> TokenEndpoint -> TokenEndpoint # | |
Show TokenEndpoint Source # | |
Defined in Network.OAuth2.JWT.Client.Data showsPrec :: Int -> TokenEndpoint -> ShowS # show :: TokenEndpoint -> String # showList :: [TokenEndpoint] -> ShowS # |