oauth2-jwt-bearer-0.0.1: OAuth2 jwt-bearer client flow as per rfc7523

Safe HaskellNone
LanguageHaskell2010

Network.OAuth2.JWT.Client

Contents

Description

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

Obtain an access token

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

newtype Issuer Source #

Constructors

Issuer 

Fields

Instances
Eq Issuer Source # 
Instance details

Defined in Network.OAuth2.JWT.Client.Data

Methods

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

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

Ord Issuer Source # 
Instance details

Defined in Network.OAuth2.JWT.Client.Data

Show Issuer Source # 
Instance details

Defined in Network.OAuth2.JWT.Client.Data

newtype Scope Source #

Constructors

Scope 

Fields

Instances
Eq Scope Source # 
Instance details

Defined in Network.OAuth2.JWT.Client.Data

Methods

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

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

Ord Scope Source # 
Instance details

Defined in Network.OAuth2.JWT.Client.Data

Methods

compare :: Scope -> Scope -> Ordering #

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

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

(>) :: Scope -> Scope -> Bool #

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

max :: Scope -> Scope -> Scope #

min :: Scope -> Scope -> Scope #

Show Scope Source # 
Instance details

Defined in Network.OAuth2.JWT.Client.Data

Methods

showsPrec :: Int -> Scope -> ShowS #

show :: Scope -> String #

showList :: [Scope] -> ShowS #

newtype Subject Source #

Constructors

Subject 

Fields

Instances
Eq Subject Source # 
Instance details

Defined in Network.OAuth2.JWT.Client.Data

Methods

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

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

Ord Subject Source # 
Instance details

Defined in Network.OAuth2.JWT.Client.Data

Show Subject Source # 
Instance details

Defined in Network.OAuth2.JWT.Client.Data

Configuration