yesod-auth-oidc-0.1.0: A yesod-auth plugin for multi-tenant SSO via OpenID Connect
Safe HaskellNone
LanguageHaskell2010

Yesod.Auth.OIDC

Description

A yesod-auth plugin for per-tenant SSO via OpenID Connect, using Authorization Code flow (AKA server flow) with client_secret_post client authentication.

Reserves "ya-oidc-*" as session keys.

Referenced standards: * OIDC Core: https://openid.net/specs/openid-connect-core-1_0.html * RFC 6749, OAuth 2.0: https://tools.ietf.org/html/rfc6749 * RFC 6750, OAuth 2.0 Bearer Token Usage: https://tools.ietf.org/html/rfc6750

Synopsis

Documentation

oidcPluginName :: Text Source #

The name used to render this plugin's routes, "oidc".

authOIDC :: YesodAuthOIDC site => AuthPlugin site Source #

Add this value to your YesodAuth instance's authPlugins list

newtype ClientId Source #

Constructors

ClientId 

Fields

Instances

Instances details
Eq ClientId Source # 
Instance details

Defined in Yesod.Auth.OIDC

Ord ClientId Source # 
Instance details

Defined in Yesod.Auth.OIDC

Show ClientId Source # 
Instance details

Defined in Yesod.Auth.OIDC

newtype ClientSecret Source #

Constructors

ClientSecret 

Fields

Instances

Instances details
Show ClientSecret Source # 
Instance details

Defined in Yesod.Auth.OIDC

type UserInfo = Object Source #

Response of call to the UserInfo Endpoint. This library does not currently support signed or encrypted responses to this particular request (unlike the ID Token response which must be signed). C.f. OIDC Core 5.3.2

data UserInfoPreference Source #

Constructors

GetUserInfoIfAvailable

Always requests the userinfo, as long as the Provider configuration has a userinfo endpoint.

GetUserInfoOnlyToSatisfyRequestedScopes

(Default). Only requests the user info if a) it's available and b) the token endpoint did not return all the scoped claims requested (cf getScopes). For example, many Identity Providers will return "email" in the token response, and thus there is no need to request the user info if that's all your app wants.

NeverGetUserInfo 

class YesodAuth site => YesodAuthOIDC site where Source #

Write an instance of this class for your Yesod App

Methods

enableLoginPage :: Bool Source #

(Optional). If this is False, there will be no 'authpageoidclogin' with its default form asking for an email. This can be used if you consolidate your various yesod auth plugins into one login page outside of this plugin. In that case, you would initialise OIDC login by POSTing to oidcForwardR with "email" and Yesod's defaultCsrfParamName from your own page. Defaut is True.

onBadLoginHint :: AuthHandler site TypedContent Source #

(Optional) A callback to your app in case oidcForwardR is called without the login_hint query parameter. Default implementation throws a BadLoginHint exception.

getProviderConfig :: LoginHint -> AuthHandler site (Either Provider IssuerLocation, ClientId) Source #

Looks up configuration. If none can be found, you should handle the fallback / error call yourself. Returns the ClientID for the given identity provider, and either the provider configuration itself, or otherwise just the Issuer URI. If the latter, this library will use OIDC discovery to retrieve the configuration.

The Issuer URI should only consist of the scheme (which must be "https:") and fully qualified host name (e.g. example.com), with no path etc.

The full configuration could be hard-coded or the cached result of a previous discovery. Cf onProviderConfigDiscovered.

Note that the Provider is both the configuration and the result of retrieving the keyset from jwks_uri.

onProviderConfigDiscovered :: Provider -> ClientId -> DiffTime -> AuthHandler site () Source #

(Optional). If the tenant is configured via a discovery URL, this function will be called with the discovered result and that result's retrieved keyset. This can be used to cache the configuration for the given duration. Since the oidc-client library combines discovery with key retrieval, the given time is the minimum of the two remaining cache lifetimes returned by both http requests.

onBadCallbackRequest Source #

Arguments

:: Maybe OAuthErrorResponse

The OAuth Error Response if present (See RFC6749 §5.2 and OIDC §3.1.2.6). This will only be Just if the "state" param (anti-CSRF token) is valid.

-> AuthHandler site a 

(Optional). Do something if the oidcCallbackR was called with incorrect parameters or the Identity Provider returned an error. This could happen if the request is not legitimate or if the identity provider doesn't provide the required state or code query or post parameters.

Defaults to a simple page showing the error (sans the error_uri).

getClientSecret :: ClientId -> Configuration -> AuthHandler site ClientSecret Source #

The printable-ASCII client_secret which you've set up with the provider ahead of time (this library does not support the dynamic registration spec).

getScopes :: ClientId -> Configuration -> AuthHandler site [ScopeValue] Source #

(Optional). The scopes that you are requesting. The "openid" scope will always be included in the eventual request whether or not you specify it here. Defaults to ["email"].

getUserInfoPreference :: LoginHint -> ClientId -> Configuration -> AuthHandler site UserInfoPreference Source #

(Optional). Configure the behaviour of when to request user information. The default behaviour is to only make this request if it's necessary satisfy the scopes in getScopes.

onSuccessfulAuthentication Source #

Arguments

:: LoginHint
  • Warning*: This is original login hint (typically an email), does *not* assert anything about the user's identity. The user could have logged in with an email different to this one, or their email at the Identity Provider could just be different to this hint. Use the information in the ID Token and UserInfo Response for authentic identity information.
-> ClientId 
-> Provider 
-> Tokens Object

The OIDC 'Token Response', including a fully validated ID Token. The otherClaims value is purposefully an unparsed JSON object to provide maximum flexibility.

-> Maybe UserInfo

The response of the userinfo endpoint is given depending on the getUserInfoPreference and whether the request was actually successful. For flexibility, any exceptions in the course of getting the UserInfo are caught by this library; such errors only manifest as an unexpected Nothing here.

-> AuthHandler site Text 

(Required). Should return a unique identifier for this user to use as the key in the yesod app's session backend. Sent after the user has successfully authenticated and right before telling Yesod that the user is authenticated. This function can still cancel authentication if it throws an error or short-circuits.

If you are using the underlying OAuth spec for non-OIDC reasons, you can do extra work here, such as storing the access and refresh tokens.

onSessionExpiry :: HandlerFor site () Source #

Defaults to clearing the credentials from the session and redirecting to the site's logoutDest (if not currently there already or out loginDest)

getHttpManagerForOidc :: AuthHandler site (Either MockOidcProvider Manager) Source #

Should return your app's HttpManager or a mock for testing. Allows high-level mocking of the 3 functions that use the HttpManager (as opposed to a lower-level mock of the 3 HTTP responses themselves).

data OAuthErrorResponse Source #

As defined in RFC6749 §5.2

Instances

Instances details
Show OAuthErrorResponse Source # 
Instance details

Defined in Yesod.Auth.OIDC

oidcSessionExpiryMiddleware :: YesodAuthOIDC site => HandlerFor site a -> HandlerFor site a Source #

Checks if the user has authenticated via `yesod-auth-oidc`. If so, checks for the session expiry time as returned by the original ID Token. If expired, it removes the sessionExpiryKey from the session, then calls onSessionExpired. We can greatly improve this by following the specs that can request re-authentication via the OIDC-defined "prompt" parameter, but this is not implemented yet.

You should add this to your app's middleware. This library cannot include it automatically.

Routes

oidcLoginR :: AuthRoute Source #

Optional route that reads in the "login hint" (commonly an email address). Your app can use this for its main login screen, or it could have a separate login screen not managed by this plugin but which redirects to oidcForwardR with the login_hint when appropriate.

authpageoidclogin

oidcForwardR :: AuthRoute Source #

This accepts an email post param. Looks up or discovers the OIDC provider associated with this login_hint, and redirects the user to the provider's Authorization Endpoint.

authpageoidcforward

oidcCallbackR :: AuthRoute Source #

This route is given to the provider so that the provider can redirect the user here with the appropriate Authorisation Code, at which point the library continues the authentication process.

authpageoidccallback

Re-exported from oidc-client

data Provider #

An OpenID Provider information

Constructors

Provider 

data Tokens a #

Instances

Instances details
Eq a => Eq (Tokens a) 
Instance details

Defined in Web.OIDC.Client.Tokens

Methods

(==) :: Tokens a -> Tokens a -> Bool #

(/=) :: Tokens a -> Tokens a -> Bool #

Show a => Show (Tokens a) 
Instance details

Defined in Web.OIDC.Client.Tokens

Methods

showsPrec :: Int -> Tokens a -> ShowS #

show :: Tokens a -> String #

showList :: [Tokens a] -> ShowS #

data IdTokenClaims a #

Claims required for an ID Token, plus recommended claims (nonce) and other custom claims.

Constructors

IdTokenClaims 

Fields

Instances

Instances details
Eq a => Eq (IdTokenClaims a) 
Instance details

Defined in Web.OIDC.Client.Tokens

Show a => Show (IdTokenClaims a) 
Instance details

Defined in Web.OIDC.Client.Tokens

Generic (IdTokenClaims a) 
Instance details

Defined in Web.OIDC.Client.Tokens

Associated Types

type Rep (IdTokenClaims a) :: Type -> Type #

FromJSON a => FromJSON (IdTokenClaims a) 
Instance details

Defined in Web.OIDC.Client.Tokens

type Rep (IdTokenClaims a) 
Instance details

Defined in Web.OIDC.Client.Tokens

Exposed or re-exported for testing and mocking

data SessionStore (m :: Type -> Type) #

Manages state and nonce. (Maybe OIDC should have them)

Constructors

SessionStore 

Fields

data OIDC #

This data type represents information needed in the OpenID flow.

data JwsAlg #

A subset of the signature algorithms from the JWA Spec.

Instances

Instances details
Eq JwsAlg 
Instance details

Defined in Jose.Jwa

Methods

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

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

Read JwsAlg 
Instance details

Defined in Jose.Jwa

Show JwsAlg 
Instance details

Defined in Jose.Jwa

ToJSON JwsAlg 
Instance details

Defined in Jose.Jwa

FromJSON JwsAlg 
Instance details

Defined in Jose.Jwa

newtype Jwt #

An encoded JWT.

Constructors

Jwt 

Fields

Instances

Instances details
Eq Jwt 
Instance details

Defined in Jose.Types

Methods

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

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

Show Jwt 
Instance details

Defined in Jose.Types

Methods

showsPrec :: Int -> Jwt -> ShowS #

show :: Jwt -> String #

showList :: [Jwt] -> ShowS #

ToJSON Jwt 
Instance details

Defined in Jose.Types

FromJSON Jwt 
Instance details

Defined in Jose.Types

newtype IntDate #

Constructors

IntDate POSIXTime 

Instances

Instances details
Eq IntDate 
Instance details

Defined in Jose.Types

Methods

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

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

Ord IntDate 
Instance details

Defined in Jose.Types

Show IntDate 
Instance details

Defined in Jose.Types

ToJSON IntDate 
Instance details

Defined in Jose.Types

FromJSON IntDate 
Instance details

Defined in Jose.Types

data CallbackInput Source #

Constructors

CallbackInput 

Fields