hoauth2-2.8.0: Haskell OAuth2 authentication client
Safe HaskellSafe-Inferred
LanguageHaskell2010

Network.OAuth2.Experiment

Description

This module contains a new way of doing OAuth2 authorization and authentication in order to obtain Access Token and maybe Refresh Token base on rfc6749.

This module will become default in future release. (TBD but likely 3.0).

The key concept/change is to introduce the GrantTypeFlow, which determines the entire work flow per spec. Each work flow will have slight different request parameters, which often time you'll see different configuration when creating OAuth2 application in the IdP developer application page.

Here are supported flows

  1. Authorization Code. This flow requires authorize call to obtain an authorize code, then exchange the code for tokens.
  2. Resource Owner Password. This flow only requires to hit token endpoint with, of course, username and password, to obtain tokens.
  3. Client Credentials. This flow also only requires to hit token endpoint but with different parameters. Client credentials flow does not involve an end user hence you won't be able to hit userinfo endpoint with access token obtained.
  4. PKCE (rfc7636). This is enhancement on top of authorization code flow.

Implicit flow is not supported because it is more for SPA (single page app) and more or less obsolete by Authorization Code flow with PKCE.

Here is quick sample for how to use vocabularies from this new module.

Firstly, initialize your IdP (use google as example) and the application.

{-# LANGUAGE DataKinds #-}

data Google = Google deriving (Eq, Show)
googleIdp :: Idp Google
googleIdp =
  Idp
    { idpFetchUserInfo = authGetJSON @(IdpUserInfo Google),
      idpAuthorizeEndpoint = [uri|https://accounts.google.com/o/oauth2/v2/auth|],
      idpTokenEndpoint = [uri|https://oauth2.googleapis.com/token|],
      idpUserInfoEndpoint = [uri|https://www.googleapis.com/oauth2/v2/userinfo|]
    }

fooApp :: IdpApplication 'AuthorizationCode Google
fooApp =
  AuthorizationCodeIdpApplication
    { idpAppClientId = "xxxxx",
      idpAppClientSecret = "xxxxx",
      idpAppScope =
        Set.fromList
          [ "https://www.googleapis.com/auth/userinfo.email",
            "https://www.googleapis.com/auth/userinfo.profile"
          ],
      idpAppAuthorizeState = "CHANGE_ME",
      idpAppAuthorizeExtraParams = Map.empty,
      idpAppRedirectUri = [uri|http://localhost/oauth2/callback|],
      idpAppName = "default-google-App",
      idpAppTokenRequestAuthenticationMethod = ClientSecretBasic,
      idp = googleIdp
    }

Secondly, construct the authorize URL.

authorizeUrl = mkAuthorizeRequest fooApp

Thirdly, after a successful redirect with authorize code, you could exchange for access token

mgr <- liftIO $ newManager tlsManagerSettings
tokenResp <- conduitTokenRequest fooApp mgr authorizeCode

Lastly, you probably like to fetch user info

conduitUserInfoRequest fooApp mgr (accessToken tokenResp)

Also you could find example from hoauth2-providers-tutorials module.

Synopsis

Grant Type

Response Type value

class ToResponseTypeValue (a :: GrantTypeFlow) where Source #

Instances

Instances details
ToResponseTypeValue 'AuthorizationCode Source # 
Instance details

Defined in Network.OAuth2.Experiment.Types

toResponseTypeParam :: forall a b req. (ToResponseTypeValue a, IsString b) => req a -> Map b b Source #

Grant Type value

newtype UrnOAuthParam a Source #

Constructors

UrnOAuthParam a 

data GrantTypeValue Source #

Grant type query parameter has association with GrantTypeFlow but not completely strict.

e.g. Both AuthorizationCode and ResourceOwnerPassword flow could support refresh token flow.

Scope

newtype Scope Source #

Constructors

Scope 

Fields

Instances

Instances details
IsString Scope Source # 
Instance details

Defined in Network.OAuth2.Experiment.Types

Methods

fromString :: String -> Scope #

Show Scope Source # 
Instance details

Defined in Network.OAuth2.Experiment.Types

Methods

showsPrec :: Int -> Scope -> ShowS #

show :: Scope -> String #

showList :: [Scope] -> ShowS #

Eq Scope Source # 
Instance details

Defined in Network.OAuth2.Experiment.Types

Methods

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

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

Ord Scope Source # 
Instance details

Defined in Network.OAuth2.Experiment.Types

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 #

ToQueryParam (Set Scope) Source # 
Instance details

Defined in Network.OAuth2.Experiment.Types

Credentials

newtype ClientId Source #

Constructors

ClientId 

Fields

Instances

Instances details
IsString ClientId Source # 
Instance details

Defined in Network.OAuth2.Experiment.Types

Show ClientId Source # 
Instance details

Defined in Network.OAuth2.Experiment.Types

Eq ClientId Source # 
Instance details

Defined in Network.OAuth2.Experiment.Types

ToQueryParam ClientId Source # 
Instance details

Defined in Network.OAuth2.Experiment.Types

newtype ClientSecret Source #

Can be either "Client Secret" or JWT base on client authentication method

Constructors

ClientSecret 

Fields

toOAuth2Key :: ClientId -> ClientSecret -> OAuth2 Source #

In order to reuse some methods from legacy Network.OAuth.OAuth2. Will be removed when Experiment module becomes default.

newtype RedirectUri Source #

Constructors

RedirectUri 

Fields

Instances

Instances details
Eq RedirectUri Source # 
Instance details

Defined in Network.OAuth2.Experiment.Types

ToQueryParam RedirectUri Source # 
Instance details

Defined in Network.OAuth2.Experiment.Types

newtype Username Source #

Constructors

Username 

Fields

Instances

Instances details
IsString Username Source # 
Instance details

Defined in Network.OAuth2.Experiment.Types

Eq Username Source # 
Instance details

Defined in Network.OAuth2.Experiment.Types

ToQueryParam Username Source # 
Instance details

Defined in Network.OAuth2.Experiment.Types

newtype Password Source #

Constructors

Password 

Fields

Instances

Instances details
IsString Password Source # 
Instance details

Defined in Network.OAuth2.Experiment.Types

Eq Password Source # 
Instance details

Defined in Network.OAuth2.Experiment.Types

ToQueryParam Password Source # 
Instance details

Defined in Network.OAuth2.Experiment.Types

Query parameters

class ToQueryParam a where Source #

Methods

toQueryParam :: a -> Map Text Text Source #

Instances

Instances details
ToQueryParam ExchangeToken Source # 
Instance details

Defined in Network.OAuth2.Experiment.Types

ToQueryParam RefreshToken Source # 
Instance details

Defined in Network.OAuth2.Experiment.Types

ToQueryParam CodeChallenge Source # 
Instance details

Defined in Network.OAuth2.Experiment.Types

ToQueryParam CodeChallengeMethod Source # 
Instance details

Defined in Network.OAuth2.Experiment.Types

ToQueryParam CodeVerifier Source # 
Instance details

Defined in Network.OAuth2.Experiment.Types

ToQueryParam AuthorizeState Source # 
Instance details

Defined in Network.OAuth2.Experiment.Types

ToQueryParam ClientId Source # 
Instance details

Defined in Network.OAuth2.Experiment.Types

ToQueryParam ClientSecret Source # 
Instance details

Defined in Network.OAuth2.Experiment.Types

ToQueryParam GrantTypeValue Source # 
Instance details

Defined in Network.OAuth2.Experiment.Types

ToQueryParam Password Source # 
Instance details

Defined in Network.OAuth2.Experiment.Types

ToQueryParam RedirectUri Source # 
Instance details

Defined in Network.OAuth2.Experiment.Types

ToQueryParam Username Source # 
Instance details

Defined in Network.OAuth2.Experiment.Types

ToQueryParam (Set Scope) Source # 
Instance details

Defined in Network.OAuth2.Experiment.Types

ToQueryParam (AuthorizationRequest 'AuthorizationCode) Source # 
Instance details

Defined in Network.OAuth2.Experiment.Types

ToQueryParam (RefreshTokenRequest 'AuthorizationCode) Source # 
Instance details

Defined in Network.OAuth2.Experiment.Types

ToQueryParam (TokenRequest 'AuthorizationCode) Source # 
Instance details

Defined in Network.OAuth2.Experiment.Types

ToQueryParam (TokenRequest 'ClientCredentials) Source # 
Instance details

Defined in Network.OAuth2.Experiment.Types

ToQueryParam (TokenRequest 'JwtBearer) Source # 
Instance details

Defined in Network.OAuth2.Experiment.Types

ToQueryParam (TokenRequest 'ResourceOwnerPassword) Source # 
Instance details

Defined in Network.OAuth2.Experiment.Types

ToQueryParam a => ToQueryParam (Maybe a) Source # 
Instance details

Defined in Network.OAuth2.Experiment.Types

Authorization and Token Requests types

class HasTokenRequest (a :: GrantTypeFlow) where Source #

Associated Types

data TokenRequest a Source #

Each GrantTypeFlow has slightly different request parameter to /token endpoint.

type WithExchangeToken a b Source #

Only 'AuthorizationCode flow (but not resource owner password nor client credentials) will use ExchangeToken in the token request create type family to be explicit on it. with 'type instance WithExchangeToken a b = b' implies no exchange token v.s. 'type instance WithExchangeToken a b = ExchangeToken -> b' implies needing an exchange token

Instances

Instances details
HasTokenRequest 'AuthorizationCode Source # 
Instance details

Defined in Network.OAuth2.Experiment.Types

HasTokenRequest 'ClientCredentials Source # 
Instance details

Defined in Network.OAuth2.Experiment.Types

HasTokenRequest 'JwtBearer Source # 
Instance details

Defined in Network.OAuth2.Experiment.Types

HasTokenRequest 'ResourceOwnerPassword Source # 
Instance details

Defined in Network.OAuth2.Experiment.Types

User Info types

type family IdpUserInfo a Source #

Idp App

data Idp a Source #

Shall IdpApplication has a field of 'Idp a'??

Idp App Config

data family IdpApplication (a :: GrantTypeFlow) (i :: Type) Source #

Instances

Instances details
data IdpApplication 'AuthorizationCode i Source #

An Application that supports "Authorization code" flow

Instance details

Defined in Network.OAuth2.Experiment.Types

data IdpApplication 'ClientCredentials i Source # 
Instance details

Defined in Network.OAuth2.Experiment.Types

data IdpApplication 'JwtBearer i Source #

An Application that supports "Authorization code" flow

Instance details

Defined in Network.OAuth2.Experiment.Types

data IdpApplication 'ResourceOwnerPassword i Source # 
Instance details

Defined in Network.OAuth2.Experiment.Types

Authorization Code flow

JWTBearer

Password flow

Client Credentials flow

newtype CodeChallenge Source #

Constructors

CodeChallenge 

Instances

Instances details
ToQueryParam CodeChallenge Source # 
Instance details

Defined in Network.OAuth2.Experiment.Types