-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | Auto-generated ory-hydra API Client -- -- Client library for calling the ORY Hydra API based on http-client. -- -- host: localhost -- -- base path: http://localhost -- -- ORY Hydra API version: 2.1.2 -- -- OpenAPI version: 6.6.0 @package ory-hydra-client @version 2.1.2.1 -- | Logging functions module ORYHydra.Logging -- | Runs a Katip logging block with the Log environment type LogExecWithContext = forall m a. MonadIO m => LogContext -> LogExec m a -- | A Katip logging block type LogExec m a = KatipT m a -> m a -- | A Katip Log environment type LogContext = LogEnv -- | A Katip Log severity type LogLevel = Severity -- | the default log environment initLogContext :: IO LogContext -- | Runs a Katip logging block with the Log environment runDefaultLogExecWithContext :: LogExecWithContext -- | Runs a Katip logging block with the Log environment stdoutLoggingExec :: LogExecWithContext -- | A Katip Log environment which targets stdout stdoutLoggingContext :: LogContext -> IO LogContext -- | Runs a Katip logging block with the Log environment stderrLoggingExec :: LogExecWithContext -- | A Katip Log environment which targets stderr stderrLoggingContext :: LogContext -> IO LogContext -- | Disables Katip logging runNullLogExec :: LogExecWithContext -- | Log a katip message _log :: (Applicative m, Katip m) => Text -> LogLevel -> Text -> m () -- | re-throws exceptions after logging them logExceptions :: (Katip m, MonadCatch m, Applicative m) => Text -> m a -> m a levelInfo :: LogLevel levelError :: LogLevel levelDebug :: LogLevel module ORYHydra.MimeTypes data ContentType a ContentType :: a -> ContentType a [unContentType] :: ContentType a -> a data Accept a Accept :: a -> Accept a [unAccept] :: Accept a -> a class MimeType mtype => Consumes req mtype class MimeType mtype => Produces req mtype data MimeJSON MimeJSON :: MimeJSON data MimeXML MimeXML :: MimeXML data MimePlainText MimePlainText :: MimePlainText data MimeFormUrlEncoded MimeFormUrlEncoded :: MimeFormUrlEncoded data MimeMultipartFormData MimeMultipartFormData :: MimeMultipartFormData data MimeOctetStream MimeOctetStream :: MimeOctetStream data MimeNoContent MimeNoContent :: MimeNoContent data MimeAny MimeAny :: MimeAny -- | A type for responses without content-body. data NoContent NoContent :: NoContent class Typeable mtype => MimeType mtype mimeTypes :: MimeType mtype => Proxy mtype -> [MediaType] mimeType :: MimeType mtype => Proxy mtype -> Maybe MediaType mimeType' :: MimeType mtype => mtype -> Maybe MediaType mimeTypes' :: MimeType mtype => mtype -> [MediaType] class MimeType mtype => MimeRender mtype x mimeRender :: MimeRender mtype x => Proxy mtype -> x -> ByteString mimeRender' :: MimeRender mtype x => mtype -> x -> ByteString mimeRenderDefaultMultipartFormData :: ToHttpApiData a => a -> ByteString class MimeType mtype => MimeUnrender mtype o mimeUnrender :: MimeUnrender mtype o => Proxy mtype -> ByteString -> Either String o mimeUnrender' :: MimeUnrender mtype o => mtype -> ByteString -> Either String o instance GHC.Classes.Eq ORYHydra.MimeTypes.NoContent instance GHC.Show.Show ORYHydra.MimeTypes.NoContent instance Data.Aeson.Types.FromJSON.FromJSON a => ORYHydra.MimeTypes.MimeUnrender ORYHydra.MimeTypes.MimeJSON a instance Web.Internal.FormUrlEncoded.FromForm a => ORYHydra.MimeTypes.MimeUnrender ORYHydra.MimeTypes.MimeFormUrlEncoded a instance ORYHydra.MimeTypes.MimeUnrender ORYHydra.MimeTypes.MimePlainText Data.ByteString.Lazy.Internal.ByteString instance ORYHydra.MimeTypes.MimeUnrender ORYHydra.MimeTypes.MimePlainText Data.Text.Internal.Text instance ORYHydra.MimeTypes.MimeUnrender ORYHydra.MimeTypes.MimePlainText GHC.Base.String instance ORYHydra.MimeTypes.MimeUnrender ORYHydra.MimeTypes.MimeOctetStream Data.ByteString.Lazy.Internal.ByteString instance ORYHydra.MimeTypes.MimeUnrender ORYHydra.MimeTypes.MimeOctetStream Data.Text.Internal.Text instance ORYHydra.MimeTypes.MimeUnrender ORYHydra.MimeTypes.MimeOctetStream GHC.Base.String instance ORYHydra.MimeTypes.MimeUnrender ORYHydra.MimeTypes.MimeNoContent ORYHydra.MimeTypes.NoContent instance Data.Aeson.Types.ToJSON.ToJSON a => ORYHydra.MimeTypes.MimeRender ORYHydra.MimeTypes.MimeJSON a instance Web.Internal.FormUrlEncoded.ToForm a => ORYHydra.MimeTypes.MimeRender ORYHydra.MimeTypes.MimeFormUrlEncoded a instance ORYHydra.MimeTypes.MimeRender ORYHydra.MimeTypes.MimePlainText Data.ByteString.Lazy.Internal.ByteString instance ORYHydra.MimeTypes.MimeRender ORYHydra.MimeTypes.MimePlainText Data.Text.Internal.Text instance ORYHydra.MimeTypes.MimeRender ORYHydra.MimeTypes.MimePlainText GHC.Base.String instance ORYHydra.MimeTypes.MimeRender ORYHydra.MimeTypes.MimeOctetStream Data.ByteString.Lazy.Internal.ByteString instance ORYHydra.MimeTypes.MimeRender ORYHydra.MimeTypes.MimeOctetStream Data.Text.Internal.Text instance ORYHydra.MimeTypes.MimeRender ORYHydra.MimeTypes.MimeOctetStream GHC.Base.String instance ORYHydra.MimeTypes.MimeRender ORYHydra.MimeTypes.MimeMultipartFormData Data.ByteString.Lazy.Internal.ByteString instance ORYHydra.MimeTypes.MimeRender ORYHydra.MimeTypes.MimeMultipartFormData GHC.Types.Bool instance ORYHydra.MimeTypes.MimeRender ORYHydra.MimeTypes.MimeMultipartFormData GHC.Types.Char instance ORYHydra.MimeTypes.MimeRender ORYHydra.MimeTypes.MimeMultipartFormData GHC.Types.Double instance ORYHydra.MimeTypes.MimeRender ORYHydra.MimeTypes.MimeMultipartFormData GHC.Types.Float instance ORYHydra.MimeTypes.MimeRender ORYHydra.MimeTypes.MimeMultipartFormData GHC.Types.Int instance ORYHydra.MimeTypes.MimeRender ORYHydra.MimeTypes.MimeMultipartFormData GHC.Num.Integer.Integer instance ORYHydra.MimeTypes.MimeRender ORYHydra.MimeTypes.MimeMultipartFormData GHC.Base.String instance ORYHydra.MimeTypes.MimeRender ORYHydra.MimeTypes.MimeMultipartFormData Data.Text.Internal.Text instance ORYHydra.MimeTypes.MimeRender ORYHydra.MimeTypes.MimeNoContent ORYHydra.MimeTypes.NoContent instance ORYHydra.MimeTypes.MimeType ORYHydra.MimeTypes.MimeJSON instance ORYHydra.MimeTypes.MimeType ORYHydra.MimeTypes.MimeXML instance ORYHydra.MimeTypes.MimeType ORYHydra.MimeTypes.MimeFormUrlEncoded instance ORYHydra.MimeTypes.MimeType ORYHydra.MimeTypes.MimeMultipartFormData instance ORYHydra.MimeTypes.MimeType ORYHydra.MimeTypes.MimePlainText instance ORYHydra.MimeTypes.MimeType ORYHydra.MimeTypes.MimeOctetStream instance ORYHydra.MimeTypes.MimeType ORYHydra.MimeTypes.MimeAny instance ORYHydra.MimeTypes.MimeType ORYHydra.MimeTypes.MimeNoContent module ORYHydra.Core data ORYHydraConfig ORYHydraConfig :: ByteString -> Text -> LogExecWithContext -> LogContext -> [AnyAuthMethod] -> Bool -> ByteString -> ORYHydraConfig -- | host supplied in the Request [configHost] :: ORYHydraConfig -> ByteString -- | user-agent supplied in the Request [configUserAgent] :: ORYHydraConfig -> Text -- | Run a block using a Logger instance [configLogExecWithContext] :: ORYHydraConfig -> LogExecWithContext -- | Configures the logger [configLogContext] :: ORYHydraConfig -> LogContext -- | List of configured auth methods [configAuthMethods] :: ORYHydraConfig -> [AnyAuthMethod] -- | throw exceptions if auth methods are not configured [configValidateAuthMethods] :: ORYHydraConfig -> Bool -- | Configures additional querystring characters which must not be URI -- encoded, e.g. + or : [configQueryExtraUnreserved] :: ORYHydraConfig -> ByteString -- | constructs a default ORYHydraConfig -- -- configHost: -- --
-- http://localhost ---- -- configUserAgent: -- --
-- "ory-hydra-client/0.1.0.0" --newConfig :: IO ORYHydraConfig -- | updates config use AuthMethod on matching requests addAuthMethod :: AuthMethod auth => ORYHydraConfig -> auth -> ORYHydraConfig -- | updates the config to use stdout logging withStdoutLogging :: ORYHydraConfig -> IO ORYHydraConfig -- | updates the config to use stderr logging withStderrLogging :: ORYHydraConfig -> IO ORYHydraConfig -- | updates the config to disable logging withNoLogging :: ORYHydraConfig -> ORYHydraConfig -- | Represents a request. -- -- Type Variables: -- --
-- _parseISO8601 --_readDateTime :: (MonadFail m, Alternative m) => String -> m DateTime -- |
-- TI.formatISO8601Millis --_showDateTime :: (t ~ UTCTime, FormatTime t) => t -> String -- | parse an ISO8601 date-time string _parseISO8601 :: (ParseTime t, MonadFail m, Alternative m) => String -> m t newtype Date Date :: Day -> Date [unDate] :: Date -> Day -- |
-- TI.parseTimeM True TI.defaultTimeLocale "%Y-%m-%d" --_readDate :: MonadFail m => String -> m Date -- |
-- TI.formatTime TI.defaultTimeLocale "%Y-%m-%d" --_showDate :: FormatTime t => t -> String -- | base64 encoded characters newtype ByteArray ByteArray :: ByteString -> ByteArray [unByteArray] :: ByteArray -> ByteString -- | read base64 encoded characters _readByteArray :: MonadFail m => Text -> m ByteArray -- | show base64 encoded characters _showByteArray :: ByteArray -> Text -- | any sequence of octets newtype Binary Binary :: ByteString -> Binary [unBinary] :: Binary -> ByteString _readBinaryBase64 :: MonadFail m => Text -> m Binary _showBinaryBase64 :: Binary -> Text type Lens_' s a = Lens_ s s a a type Lens_ s t a b = forall (f :: Type -> Type). Functor f => (a -> f b) -> s -> f t instance GHC.Show.Show ORYHydra.Core.ParamBody instance GHC.Show.Show ORYHydra.Core.Params instance GHC.Show.Show (ORYHydra.Core.ORYHydraRequest req contentType res accept) instance GHC.Show.Show ORYHydra.Core.AuthMethodException instance Control.DeepSeq.NFData ORYHydra.Core.DateTime instance GHC.Classes.Ord ORYHydra.Core.DateTime instance Data.Data.Data ORYHydra.Core.DateTime instance GHC.Classes.Eq ORYHydra.Core.DateTime instance Control.DeepSeq.NFData ORYHydra.Core.Date instance GHC.Ix.Ix ORYHydra.Core.Date instance GHC.Classes.Ord ORYHydra.Core.Date instance Data.Data.Data ORYHydra.Core.Date instance GHC.Classes.Eq ORYHydra.Core.Date instance GHC.Enum.Enum ORYHydra.Core.Date instance Control.DeepSeq.NFData ORYHydra.Core.ByteArray instance GHC.Classes.Ord ORYHydra.Core.ByteArray instance Data.Data.Data ORYHydra.Core.ByteArray instance GHC.Classes.Eq ORYHydra.Core.ByteArray instance Control.DeepSeq.NFData ORYHydra.Core.Binary instance GHC.Classes.Ord ORYHydra.Core.Binary instance Data.Data.Data ORYHydra.Core.Binary instance GHC.Classes.Eq ORYHydra.Core.Binary instance Data.Aeson.Types.FromJSON.FromJSON ORYHydra.Core.Binary instance Data.Aeson.Types.ToJSON.ToJSON ORYHydra.Core.Binary instance Web.Internal.HttpApiData.FromHttpApiData ORYHydra.Core.Binary instance Web.Internal.HttpApiData.ToHttpApiData ORYHydra.Core.Binary instance GHC.Show.Show ORYHydra.Core.Binary instance ORYHydra.MimeTypes.MimeRender ORYHydra.MimeTypes.MimeMultipartFormData ORYHydra.Core.Binary instance Data.Aeson.Types.FromJSON.FromJSON ORYHydra.Core.ByteArray instance Data.Aeson.Types.ToJSON.ToJSON ORYHydra.Core.ByteArray instance Web.Internal.HttpApiData.FromHttpApiData ORYHydra.Core.ByteArray instance Web.Internal.HttpApiData.ToHttpApiData ORYHydra.Core.ByteArray instance GHC.Show.Show ORYHydra.Core.ByteArray instance ORYHydra.MimeTypes.MimeRender ORYHydra.MimeTypes.MimeMultipartFormData ORYHydra.Core.ByteArray instance Data.Aeson.Types.FromJSON.FromJSON ORYHydra.Core.Date instance Data.Aeson.Types.ToJSON.ToJSON ORYHydra.Core.Date instance Web.Internal.HttpApiData.FromHttpApiData ORYHydra.Core.Date instance Web.Internal.HttpApiData.ToHttpApiData ORYHydra.Core.Date instance GHC.Show.Show ORYHydra.Core.Date instance ORYHydra.MimeTypes.MimeRender ORYHydra.MimeTypes.MimeMultipartFormData ORYHydra.Core.Date instance Data.Aeson.Types.FromJSON.FromJSON ORYHydra.Core.DateTime instance Data.Aeson.Types.ToJSON.ToJSON ORYHydra.Core.DateTime instance Web.Internal.HttpApiData.FromHttpApiData ORYHydra.Core.DateTime instance Web.Internal.HttpApiData.ToHttpApiData ORYHydra.Core.DateTime instance GHC.Show.Show ORYHydra.Core.DateTime instance ORYHydra.MimeTypes.MimeRender ORYHydra.MimeTypes.MimeMultipartFormData ORYHydra.Core.DateTime instance GHC.Exception.Type.Exception ORYHydra.Core.AuthMethodException instance GHC.Show.Show ORYHydra.Core.ORYHydraConfig instance ORYHydra.Core.AuthMethod ORYHydra.Core.AnyAuthMethod module ORYHydra.Client -- | send a request returning the raw http response dispatchLbs :: (Produces req accept, MimeType contentType) => Manager -> ORYHydraConfig -> ORYHydraRequest req contentType res accept -> IO (Response ByteString) -- | pair of decoded http body and http response data MimeResult res MimeResult :: Either MimeError res -> Response ByteString -> MimeResult res -- | decoded http body [mimeResult] :: MimeResult res -> Either MimeError res -- | http response [mimeResultResponse] :: MimeResult res -> Response ByteString -- | pair of unrender/parser error and http response data MimeError MimeError :: String -> Response ByteString -> MimeError -- | unrender/parser error [mimeError] :: MimeError -> String -- | http response [mimeErrorResponse] :: MimeError -> Response ByteString -- | send a request returning the MimeResult dispatchMime :: forall req contentType res accept. (Produces req accept, MimeUnrender accept res, MimeType contentType) => Manager -> ORYHydraConfig -> ORYHydraRequest req contentType res accept -> IO (MimeResult res) -- | like dispatchMime, but only returns the decoded http body dispatchMime' :: (Produces req accept, MimeUnrender accept res, MimeType contentType) => Manager -> ORYHydraConfig -> ORYHydraRequest req contentType res accept -> IO (Either MimeError res) -- | like dispatchReqLbs, but does not validate the operation is a -- Producer of the "accept" MimeType. (Useful if the -- server's response is undocumented) dispatchLbsUnsafe :: (MimeType accept, MimeType contentType) => Manager -> ORYHydraConfig -> ORYHydraRequest req contentType res accept -> IO (Response ByteString) -- | dispatch an InitRequest dispatchInitUnsafe :: Manager -> ORYHydraConfig -> InitRequest req contentType res accept -> IO (Response ByteString) -- | wraps an http-client Request with request/response type -- parameters newtype InitRequest req contentType res accept InitRequest :: Request -> InitRequest req contentType res accept [unInitRequest] :: InitRequest req contentType res accept -> Request -- | Build an http-client Request record from the supplied config -- and request _toInitRequest :: (MimeType accept, MimeType contentType) => ORYHydraConfig -> ORYHydraRequest req contentType res accept -> IO (InitRequest req contentType res accept) -- | modify the underlying Request modifyInitRequest :: InitRequest req contentType res accept -> (Request -> Request) -> InitRequest req contentType res accept -- | modify the underlying Request (monadic) modifyInitRequestM :: Monad m => InitRequest req contentType res accept -> (Request -> m Request) -> m (InitRequest req contentType res accept) -- | Run a block using the configured logger instance runConfigLog :: MonadIO m => ORYHydraConfig -> LogExec m a -- | Run a block using the configured logger instance (logs exceptions) runConfigLogWithExceptions :: (MonadCatch m, MonadIO m) => Text -> ORYHydraConfig -> LogExec m a instance GHC.Show.Show ORYHydra.Client.MimeError instance Data.Traversable.Traversable ORYHydra.Client.MimeResult instance Data.Foldable.Foldable ORYHydra.Client.MimeResult instance GHC.Base.Functor ORYHydra.Client.MimeResult instance GHC.Show.Show res => GHC.Show.Show (ORYHydra.Client.MimeResult res) instance GHC.Show.Show (ORYHydra.Client.InitRequest req contentType res accept) module ORYHydra.Model newtype All All :: Bool -> All [unAll] :: All -> Bool newtype Client Client :: Text -> Client [unClient] :: Client -> Text newtype ClientId ClientId :: Text -> ClientId [unClientId] :: ClientId -> Text newtype ClientName ClientName :: Text -> ClientName [unClientName] :: ClientName -> Text newtype ClientSecret ClientSecret :: Text -> ClientSecret [unClientSecret] :: ClientSecret -> Text newtype Code Code :: Text -> Code [unCode] :: Code -> Text newtype ConsentChallenge ConsentChallenge :: Text -> ConsentChallenge [unConsentChallenge] :: ConsentChallenge -> Text newtype DefaultItems DefaultItems :: Integer -> DefaultItems [unDefaultItems] :: DefaultItems -> Integer newtype GrantType GrantType :: Text -> GrantType [unGrantType] :: GrantType -> Text newtype Id Id :: Text -> Id [unId] :: Id -> Text newtype Issuer Issuer :: Text -> Issuer [unIssuer] :: Issuer -> Text newtype JsonPatch2 JsonPatch2 :: [JsonPatch] -> JsonPatch2 [unJsonPatch2] :: JsonPatch2 -> [JsonPatch] newtype Kid Kid :: Text -> Kid [unKid] :: Kid -> Text newtype LoginChallenge LoginChallenge :: Text -> LoginChallenge [unLoginChallenge] :: LoginChallenge -> Text newtype LoginSessionId LoginSessionId :: Text -> LoginSessionId [unLoginSessionId] :: LoginSessionId -> Text newtype LogoutChallenge LogoutChallenge :: Text -> LogoutChallenge [unLogoutChallenge] :: LogoutChallenge -> Text newtype MaxItems MaxItems :: Integer -> MaxItems [unMaxItems] :: MaxItems -> Integer newtype Owner Owner :: Text -> Owner [unOwner] :: Owner -> Text newtype PageSize PageSize :: Integer -> PageSize [unPageSize] :: PageSize -> Integer newtype PageToken PageToken :: Text -> PageToken [unPageToken] :: PageToken -> Text newtype RedirectUri RedirectUri :: Text -> RedirectUri [unRedirectUri] :: RedirectUri -> Text newtype RefreshToken RefreshToken :: Text -> RefreshToken [unRefreshToken] :: RefreshToken -> Text newtype Scope Scope :: Text -> Scope [unScope] :: Scope -> Text newtype Set Set :: Text -> Set [unSet] :: Set -> Text newtype Sid Sid :: Text -> Sid [unSid] :: Sid -> Text newtype Subject Subject :: Text -> Subject [unSubject] :: Subject -> Text newtype Token Token :: Text -> Token [unToken] :: Token -> Text -- | AcceptOAuth2ConsentRequest The request payload used to accept a -- consent request. data AcceptOAuth2ConsentRequest AcceptOAuth2ConsentRequest :: Maybe [Text] -> Maybe [Text] -> Maybe DateTime -> Maybe Bool -> Maybe Integer -> Maybe AcceptOAuth2ConsentRequestSession -> AcceptOAuth2ConsentRequest -- | "grant_access_token_audience" [acceptOAuth2ConsentRequestGrantAccessTokenAudience] :: AcceptOAuth2ConsentRequest -> Maybe [Text] -- | "grant_scope" [acceptOAuth2ConsentRequestGrantScope] :: AcceptOAuth2ConsentRequest -> Maybe [Text] -- | "handled_at" [acceptOAuth2ConsentRequestHandledAt] :: AcceptOAuth2ConsentRequest -> Maybe DateTime -- | "remember" - Remember, if set to true, tells ORY Hydra to remember -- this consent authorization and reuse it if the same client asks the -- same user for the same, or a subset of, scope. [acceptOAuth2ConsentRequestRemember] :: AcceptOAuth2ConsentRequest -> Maybe Bool -- | "remember_for" - RememberFor sets how long the consent authorization -- should be remembered for in seconds. If set to `0`, the authorization -- will be remembered indefinitely. [acceptOAuth2ConsentRequestRememberFor] :: AcceptOAuth2ConsentRequest -> Maybe Integer -- | "session" [acceptOAuth2ConsentRequestSession] :: AcceptOAuth2ConsentRequest -> Maybe AcceptOAuth2ConsentRequestSession -- | Construct a value of type AcceptOAuth2ConsentRequest (by -- applying it's required fields, if any) mkAcceptOAuth2ConsentRequest :: AcceptOAuth2ConsentRequest -- | AcceptOAuth2ConsentRequestSession Pass session data to a consent -- request. data AcceptOAuth2ConsentRequestSession AcceptOAuth2ConsentRequestSession :: Maybe Value -> Maybe Value -> AcceptOAuth2ConsentRequestSession -- | "access_token" - AccessToken sets session data for the access and -- refresh token, as well as any future tokens issued by the refresh -- grant. Keep in mind that this data will be available to anyone -- performing OAuth 2.0 Challenge Introspection. If only your services -- can perform OAuth 2.0 Challenge Introspection, this is usually fine. -- But if third parties can access that endpoint as well, sensitive data -- from the session might be exposed to them. Use with care! [acceptOAuth2ConsentRequestSessionAccessToken] :: AcceptOAuth2ConsentRequestSession -> Maybe Value -- | "id_token" - IDToken sets session data for the OpenID Connect ID -- token. Keep in mind that the session'id payloads are readable by -- anyone that has access to the ID Challenge. Use with care! [acceptOAuth2ConsentRequestSessionIdToken] :: AcceptOAuth2ConsentRequestSession -> Maybe Value -- | Construct a value of type AcceptOAuth2ConsentRequestSession (by -- applying it's required fields, if any) mkAcceptOAuth2ConsentRequestSession :: AcceptOAuth2ConsentRequestSession -- | AcceptOAuth2LoginRequest HandledLoginRequest is the request payload -- used to accept a login request. data AcceptOAuth2LoginRequest AcceptOAuth2LoginRequest :: Maybe Text -> Maybe [Text] -> Maybe Value -> Maybe Bool -> Maybe Text -> Maybe Bool -> Maybe Integer -> Text -> AcceptOAuth2LoginRequest -- | "acr" - ACR sets the Authentication AuthorizationContext Class -- Reference value for this authentication session. You can use it to -- express that, for example, a user authenticated using two factor -- authentication. [acceptOAuth2LoginRequestAcr] :: AcceptOAuth2LoginRequest -> Maybe Text -- | "amr" [acceptOAuth2LoginRequestAmr] :: AcceptOAuth2LoginRequest -> Maybe [Text] -- | "context" [acceptOAuth2LoginRequestContext] :: AcceptOAuth2LoginRequest -> Maybe Value -- | "extend_session_lifespan" - Extend OAuth2 authentication session -- lifespan If set to `true`, the OAuth2 authentication cookie lifespan -- is extended. This is for example useful if you want the user to be -- able to use `prompt=none` continuously. This value can only be set to -- `true` if the user has an authentication, which is the case if the -- `skip` value is `true`. [acceptOAuth2LoginRequestExtendSessionLifespan] :: AcceptOAuth2LoginRequest -> Maybe Bool -- | "force_subject_identifier" - ForceSubjectIdentifier forces the -- "pairwise" user ID of the end-user that -- authenticated. The "pairwise" user ID refers to the -- (Pairwise Identifier -- Algorithm)[http:/openid.netspecsopenid-connect-core-1_0.html#PairwiseAlg] -- of the OpenID Connect specification. It allows you to set an -- obfuscated subject ("user") identifier that is -- unique to the client. Please note that this changes the user ID on -- endpoint userinfo and sub claim of the ID Token. It does not -- change the sub claim in the OAuth 2.0 Introspection. Per default, ORY -- Hydra handles this value with its own algorithm. In case you want to -- set this yourself you can use this field. Please note that setting -- this field has no effect if `pairwise` is not configured in ORY Hydra -- or the OAuth 2.0 Client does not expect a pairwise identifier (set via -- `subject_type` key in the client's configuration). Please also be -- aware that ORY Hydra is unable to properly compute this value during -- authentication. This implies that you have to compute this value on -- every authentication process (probably depending on the client ID or -- some other unique value). If you fail to compute the proper value, -- then authentication processes which have id_token_hint set might fail. [acceptOAuth2LoginRequestForceSubjectIdentifier] :: AcceptOAuth2LoginRequest -> Maybe Text -- | "remember" - Remember, if set to true, tells ORY Hydra to remember -- this user by telling the user agent (browser) to store a cookie with -- authentication data. If the same user performs another OAuth 2.0 -- Authorization Request, he/she will not be asked to log in again. [acceptOAuth2LoginRequestRemember] :: AcceptOAuth2LoginRequest -> Maybe Bool -- | "remember_for" - RememberFor sets how long the authentication should -- be remembered for in seconds. If set to `0`, the authorization will be -- remembered for the duration of the browser session (using a session -- cookie). [acceptOAuth2LoginRequestRememberFor] :: AcceptOAuth2LoginRequest -> Maybe Integer -- | Required "subject" - Subject is the user ID of the end-user -- that authenticated. [acceptOAuth2LoginRequestSubject] :: AcceptOAuth2LoginRequest -> Text -- | Construct a value of type AcceptOAuth2LoginRequest (by applying -- it's required fields, if any) mkAcceptOAuth2LoginRequest :: Text -> AcceptOAuth2LoginRequest -- | CreateJsonWebKeySet Create JSON Web Key Set Request Body data CreateJsonWebKeySet CreateJsonWebKeySet :: Text -> Text -> Text -> CreateJsonWebKeySet -- | Required "alg" - JSON Web Key Algorithm The algorithm to be -- used for creating the key. Supports `RS256`, `ES256`, `ES512`, -- `HS512`, and `HS256`. [createJsonWebKeySetAlg] :: CreateJsonWebKeySet -> Text -- | Required "kid" - JSON Web Key ID The Key ID of the key to be -- created. [createJsonWebKeySetKid] :: CreateJsonWebKeySet -> Text -- | Required "use" - JSON Web Key Use The "use" -- (public key use) parameter identifies the intended use of the public -- key. The "use" parameter is employed to indicate -- whether a public key is used for encrypting data or verifying the -- signature on data. Valid values are "enc" and -- "sig". [createJsonWebKeySetUse] :: CreateJsonWebKeySet -> Text -- | Construct a value of type CreateJsonWebKeySet (by applying it's -- required fields, if any) mkCreateJsonWebKeySet :: Text -> Text -> Text -> CreateJsonWebKeySet -- | ErrorOAuth2 Error data ErrorOAuth2 ErrorOAuth2 :: Maybe Text -> Maybe Text -> Maybe Text -> Maybe Text -> Maybe Integer -> ErrorOAuth2 -- | "error" - Error [errorOAuth2Error] :: ErrorOAuth2 -> Maybe Text -- | "error_debug" - Error Debug Information Only available in dev mode. [errorOAuth2ErrorDebug] :: ErrorOAuth2 -> Maybe Text -- | "error_description" - Error Description [errorOAuth2ErrorDescription] :: ErrorOAuth2 -> Maybe Text -- | "error_hint" - Error Hint Helps the user identify the error cause. [errorOAuth2ErrorHint] :: ErrorOAuth2 -> Maybe Text -- | "status_code" - HTTP Status Code [errorOAuth2StatusCode] :: ErrorOAuth2 -> Maybe Integer -- | Construct a value of type ErrorOAuth2 (by applying it's -- required fields, if any) mkErrorOAuth2 :: ErrorOAuth2 -- | GenericError data GenericError GenericError :: Maybe Integer -> Maybe Text -> Maybe Value -> Maybe Text -> Text -> Maybe Text -> Maybe Text -> Maybe Text -> GenericError -- | "code" - The status code [genericErrorCode] :: GenericError -> Maybe Integer -- | "debug" - Debug information This field is often not exposed to protect -- against leaking sensitive information. [genericErrorDebug] :: GenericError -> Maybe Text -- | "details" - Further error details [genericErrorDetails] :: GenericError -> Maybe Value -- | "id" - The error ID Useful when trying to identify various errors in -- application logic. [genericErrorId] :: GenericError -> Maybe Text -- | Required "message" - Error message The error's message. [genericErrorMessage] :: GenericError -> Text -- | "reason" - A human-readable reason for the error [genericErrorReason] :: GenericError -> Maybe Text -- | "request" - The request ID The request ID is often exposed internally -- in order to trace errors across service architectures. This is often a -- UUID. [genericErrorRequest] :: GenericError -> Maybe Text -- | "status" - The status description [genericErrorStatus] :: GenericError -> Maybe Text -- | Construct a value of type GenericError (by applying it's -- required fields, if any) mkGenericError :: Text -> GenericError -- | GetVersion200Response data GetVersion200Response GetVersion200Response :: Maybe Text -> GetVersion200Response -- | "version" - The version of Ory Hydra. [getVersion200ResponseVersion] :: GetVersion200Response -> Maybe Text -- | Construct a value of type GetVersion200Response (by applying -- it's required fields, if any) mkGetVersion200Response :: GetVersion200Response -- | HealthNotReadyStatus data HealthNotReadyStatus HealthNotReadyStatus :: Maybe (Map String Text) -> HealthNotReadyStatus -- | "errors" - Errors contains a list of errors that caused the not ready -- status. [healthNotReadyStatusErrors] :: HealthNotReadyStatus -> Maybe (Map String Text) -- | Construct a value of type HealthNotReadyStatus (by applying -- it's required fields, if any) mkHealthNotReadyStatus :: HealthNotReadyStatus -- | HealthStatus data HealthStatus HealthStatus :: Maybe Text -> HealthStatus -- | "status" - Status always contains "ok". [healthStatusStatus] :: HealthStatus -> Maybe Text -- | Construct a value of type HealthStatus (by applying it's -- required fields, if any) mkHealthStatus :: HealthStatus -- | IntrospectedOAuth2Token Introspection contains an access token's -- session data as specified by IETF RFC 7662 data IntrospectedOAuth2Token IntrospectedOAuth2Token :: Bool -> Maybe [Text] -> Maybe Text -> Maybe Integer -> Maybe (Map String Value) -> Maybe Integer -> Maybe Text -> Maybe Integer -> Maybe Text -> Maybe Text -> Maybe Text -> Maybe Text -> Maybe Text -> Maybe Text -> IntrospectedOAuth2Token -- | Required "active" - Active is a boolean indicator of whether or -- not the presented token is currently active. The specifics of a -- token's "active" state will vary depending on the -- implementation of the authorization server and the information it -- keeps about its tokens, but a "true" value return -- for the "active" property will generally indicate -- that a given token has been issued by this authorization server, has -- not been revoked by the resource owner, and is within its given time -- window of validity (e.g., after its issuance time and before its -- expiration time). [introspectedOAuth2TokenActive] :: IntrospectedOAuth2Token -> Bool -- | "aud" - Audience contains a list of the token's intended audiences. [introspectedOAuth2TokenAud] :: IntrospectedOAuth2Token -> Maybe [Text] -- | "client_id" - ID is aclient identifier for the OAuth 2.0 client that -- requested this token. [introspectedOAuth2TokenClientId] :: IntrospectedOAuth2Token -> Maybe Text -- | "exp" - Expires at is an integer timestamp, measured in the number of -- seconds since January 1 1970 UTC, indicating when this token will -- expire. [introspectedOAuth2TokenExp] :: IntrospectedOAuth2Token -> Maybe Integer -- | "ext" - Extra is arbitrary data set by the session. [introspectedOAuth2TokenExt] :: IntrospectedOAuth2Token -> Maybe (Map String Value) -- | "iat" - Issued at is an integer timestamp, measured in the number of -- seconds since January 1 1970 UTC, indicating when this token was -- originally issued. [introspectedOAuth2TokenIat] :: IntrospectedOAuth2Token -> Maybe Integer -- | "iss" - IssuerURL is a string representing the issuer of this token [introspectedOAuth2TokenIss] :: IntrospectedOAuth2Token -> Maybe Text -- | "nbf" - NotBefore is an integer timestamp, measured in the number of -- seconds since January 1 1970 UTC, indicating when this token is not to -- be used before. [introspectedOAuth2TokenNbf] :: IntrospectedOAuth2Token -> Maybe Integer -- | "obfuscated_subject" - ObfuscatedSubject is set when the subject -- identifier algorithm was set to "pairwise" during -- authorization. It is the `sub` value of the ID Token that was issued. [introspectedOAuth2TokenObfuscatedSubject] :: IntrospectedOAuth2Token -> Maybe Text -- | "scope" - Scope is a JSON string containing a space-separated list of -- scopes associated with this token. [introspectedOAuth2TokenScope] :: IntrospectedOAuth2Token -> Maybe Text -- | "sub" - Subject of the token, as defined in JWT [RFC7519]. Usually a -- machine-readable identifier of the resource owner who authorized this -- token. [introspectedOAuth2TokenSub] :: IntrospectedOAuth2Token -> Maybe Text -- | "token_type" - TokenType is the introspected token's type, typically -- `Bearer`. [introspectedOAuth2TokenTokenType] :: IntrospectedOAuth2Token -> Maybe Text -- | "token_use" - TokenUse is the introspected token's use, for example -- `access_token` or `refresh_token`. [introspectedOAuth2TokenTokenUse] :: IntrospectedOAuth2Token -> Maybe Text -- | "username" - Username is a human-readable identifier for the resource -- owner who authorized this token. [introspectedOAuth2TokenUsername] :: IntrospectedOAuth2Token -> Maybe Text -- | Construct a value of type IntrospectedOAuth2Token (by applying -- it's required fields, if any) mkIntrospectedOAuth2Token :: Bool -> IntrospectedOAuth2Token -- | IsReady200Response data IsReady200Response IsReady200Response :: Maybe Text -> IsReady200Response -- | "status" - Always "ok". [isReady200ResponseStatus] :: IsReady200Response -> Maybe Text -- | Construct a value of type IsReady200Response (by applying it's -- required fields, if any) mkIsReady200Response :: IsReady200Response -- | IsReady503Response data IsReady503Response IsReady503Response :: Maybe (Map String Text) -> IsReady503Response -- | "errors" - Errors contains a list of errors that caused the not ready -- status. [isReady503ResponseErrors] :: IsReady503Response -> Maybe (Map String Text) -- | Construct a value of type IsReady503Response (by applying it's -- required fields, if any) mkIsReady503Response :: IsReady503Response -- | JsonPatch A JSONPatch document as defined by RFC 6902 data JsonPatch JsonPatch :: Maybe Text -> Text -> Text -> Maybe Value -> JsonPatch -- | "from" - This field is used together with operation -- "move" and uses JSON Pointer notation. Learn more -- about JSON Pointers. [jsonPatchFrom] :: JsonPatch -> Maybe Text -- | Required "op" - The operation to be performed. One of -- "add", "remove", -- "replace", "move", -- "copy", or "test". [jsonPatchOp] :: JsonPatch -> Text -- | Required "path" - The path to the target path. Uses JSON -- pointer notation. Learn more about JSON Pointers. [jsonPatchPath] :: JsonPatch -> Text -- | "value" - The value to be used within the operations. Learn more -- about JSON Pointers. [jsonPatchValue] :: JsonPatch -> Maybe Value -- | Construct a value of type JsonPatch (by applying it's required -- fields, if any) mkJsonPatch :: Text -> Text -> JsonPatch -- | JsonWebKey data JsonWebKey JsonWebKey :: Text -> Maybe Text -> Maybe Text -> Maybe Text -> Maybe Text -> Maybe Text -> Maybe Text -> Text -> Text -> Maybe Text -> Maybe Text -> Maybe Text -> Maybe Text -> Text -> Maybe Text -> Maybe [Text] -> Maybe Text -> JsonWebKey -- | Required "alg" - The "alg" (algorithm) -- parameter identifies the algorithm intended for use with the key. The -- values used should either be registered in the IANA "JSON Web -- Signature and Encryption Algorithms" registry established by -- [JWA] or be a value that contains a Collision- Resistant Name. [jsonWebKeyAlg] :: JsonWebKey -> Text -- | "crv" [jsonWebKeyCrv] :: JsonWebKey -> Maybe Text -- | "d" [jsonWebKeyD] :: JsonWebKey -> Maybe Text -- | "dp" [jsonWebKeyDp] :: JsonWebKey -> Maybe Text -- | "dq" [jsonWebKeyDq] :: JsonWebKey -> Maybe Text -- | "e" [jsonWebKeyE] :: JsonWebKey -> Maybe Text -- | "k" [jsonWebKeyK] :: JsonWebKey -> Maybe Text -- | Required "kid" - The "kid" (key ID) parameter -- is used to match a specific key. This is used, for instance, to choose -- among a set of keys within a JWK Set during key rollover. The -- structure of the "kid" value is unspecified. When -- "kid" values are used within a JWK Set, different -- keys within the JWK Set SHOULD use distinct "kid" -- values. (One example in which different keys might use the same -- "kid" value is if they have different -- "kty" (key type) values but are considered to be -- equivalent alternatives by the application using them.) The -- "kid" value is a case-sensitive string. [jsonWebKeyKid] :: JsonWebKey -> Text -- | Required "kty" - The "kty" (key type) -- parameter identifies the cryptographic algorithm family used with the -- key, such as "RSA" or "EC". -- "kty" values should either be registered in the IANA -- "JSON Web Key Types" registry established by [JWA] -- or be a value that contains a Collision- Resistant Name. The -- "kty" value is a case-sensitive string. [jsonWebKeyKty] :: JsonWebKey -> Text -- | "n" [jsonWebKeyN] :: JsonWebKey -> Maybe Text -- | "p" [jsonWebKeyP] :: JsonWebKey -> Maybe Text -- | "q" [jsonWebKeyQ] :: JsonWebKey -> Maybe Text -- | "qi" [jsonWebKeyQi] :: JsonWebKey -> Maybe Text -- | Required "use" - Use ("public key use") -- identifies the intended use of the public key. The -- "use" parameter is employed to indicate whether a -- public key is used for encrypting data or verifying the signature on -- data. Values are commonly "sig" (signature) or -- "enc" (encryption). [jsonWebKeyUse] :: JsonWebKey -> Text -- | "x" [jsonWebKeyX] :: JsonWebKey -> Maybe Text -- | "x5c" - The "x5c" (X.509 certificate chain) -- parameter contains a chain of one or more PKIX certificates [RFC5280]. -- The certificate chain is represented as a JSON array of certificate -- value strings. Each string in the array is a base64-encoded (Section 4 -- of [RFC4648] -- not base64url-encoded) DER [ITU.X690.1994] PKIX -- certificate value. The PKIX certificate containing the key value MUST -- be the first certificate. [jsonWebKeyX5c] :: JsonWebKey -> Maybe [Text] -- | "y" [jsonWebKeyY] :: JsonWebKey -> Maybe Text -- | Construct a value of type JsonWebKey (by applying it's required -- fields, if any) mkJsonWebKey :: Text -> Text -> Text -> Text -> JsonWebKey -- | JsonWebKeySet JSON Web Key Set data JsonWebKeySet JsonWebKeySet :: Maybe [JsonWebKey] -> JsonWebKeySet -- | "keys" - List of JSON Web Keys The value of the -- "keys" parameter is an array of JSON Web Key (JWK) -- values. By default, the order of the JWK values within the array does -- not imply an order of preference among them, although applications of -- JWK Sets can choose to assign a meaning to the order for their -- purposes, if desired. [jsonWebKeySetKeys] :: JsonWebKeySet -> Maybe [JsonWebKey] -- | Construct a value of type JsonWebKeySet (by applying it's -- required fields, if any) mkJsonWebKeySet :: JsonWebKeySet -- | OAuth2Client OAuth 2.0 Client -- -- OAuth 2.0 Clients are used to perform OAuth 2.0 and OpenID Connect -- flows. Usually, OAuth 2.0 clients are generated for applications which -- want to consume your OAuth 2.0 or OpenID Connect capabilities. data OAuth2Client OAuth2Client :: Maybe Text -> Maybe [Text] -> Maybe [Text] -> Maybe Text -> Maybe Text -> Maybe Text -> Maybe Bool -> Maybe Text -> Maybe Text -> Maybe Text -> Maybe Text -> Maybe Text -> Maybe Integer -> Maybe Text -> Maybe [Text] -> Maybe DateTime -> Maybe Bool -> Maybe Text -> Maybe [Text] -> Maybe Text -> Maybe Text -> Maybe Value -> Maybe Text -> Maybe Text -> Maybe Text -> Maybe Value -> Maybe Text -> Maybe Text -> Maybe [Text] -> Maybe [Text] -> Maybe Text -> Maybe Text -> Maybe Text -> Maybe Text -> Maybe Text -> Maybe Text -> Maybe [Text] -> Maybe [Text] -> Maybe Text -> Maybe Text -> Maybe Bool -> Maybe Text -> Maybe Text -> Maybe Text -> Maybe Text -> Maybe DateTime -> Maybe Text -> OAuth2Client -- | "access_token_strategy" - OAuth 2.0 Access Token Strategy -- AccessTokenStrategy is the strategy used to generate access tokens. -- Valid options are `jwt` and `opaque`. `jwt` is a bad idea, see -- https://www.ory.sh/docs/hydra/advanced#json-web-tokens Setting -- the stragegy here overrides the global setting in -- `strategies.access_token`. [oAuth2ClientAccessTokenStrategy] :: OAuth2Client -> Maybe Text -- | "allowed_cors_origins" [oAuth2ClientAllowedCorsOrigins] :: OAuth2Client -> Maybe [Text] -- | "audience" [oAuth2ClientAudience] :: OAuth2Client -> Maybe [Text] -- | "authorization_code_grant_access_token_lifespan" - Specify a time -- duration in milliseconds, seconds, minutes, hours. [oAuth2ClientAuthorizationCodeGrantAccessTokenLifespan] :: OAuth2Client -> Maybe Text -- | "authorization_code_grant_id_token_lifespan" - Specify a time duration -- in milliseconds, seconds, minutes, hours. [oAuth2ClientAuthorizationCodeGrantIdTokenLifespan] :: OAuth2Client -> Maybe Text -- | "authorization_code_grant_refresh_token_lifespan" - Specify a time -- duration in milliseconds, seconds, minutes, hours. [oAuth2ClientAuthorizationCodeGrantRefreshTokenLifespan] :: OAuth2Client -> Maybe Text -- | "backchannel_logout_session_required" - OpenID Connect Back-Channel -- Logout Session Required Boolean value specifying whether the RP -- requires that a sid (session ID) Claim be included in the Logout Token -- to identify the RP session with the OP when the backchannel_logout_uri -- is used. If omitted, the default value is false. [oAuth2ClientBackchannelLogoutSessionRequired] :: OAuth2Client -> Maybe Bool -- | "backchannel_logout_uri" - OpenID Connect Back-Channel Logout URI RP -- URL that will cause the RP to log itself out when sent a Logout Token -- by the OP. [oAuth2ClientBackchannelLogoutUri] :: OAuth2Client -> Maybe Text -- | "client_credentials_grant_access_token_lifespan" - Specify a time -- duration in milliseconds, seconds, minutes, hours. [oAuth2ClientClientCredentialsGrantAccessTokenLifespan] :: OAuth2Client -> Maybe Text -- | "client_id" - OAuth 2.0 Client ID The ID is autogenerated and -- immutable. [oAuth2ClientClientId] :: OAuth2Client -> Maybe Text -- | "client_name" - OAuth 2.0 Client Name The human-readable name of the -- client to be presented to the end-user during authorization. [oAuth2ClientClientName] :: OAuth2Client -> Maybe Text -- | "client_secret" - OAuth 2.0 Client Secret The secret will be included -- in the create request as cleartext, and then never again. The secret -- is kept in hashed format and is not recoverable once lost. [oAuth2ClientClientSecret] :: OAuth2Client -> Maybe Text -- | "client_secret_expires_at" - OAuth 2.0 Client Secret Expires At The -- field is currently not supported and its value is always 0. [oAuth2ClientClientSecretExpiresAt] :: OAuth2Client -> Maybe Integer -- | "client_uri" - OAuth 2.0 Client URI ClientURI is a URL string of a web -- page providing information about the client. If present, the server -- SHOULD display this URL to the end-user in a clickable fashion. [oAuth2ClientClientUri] :: OAuth2Client -> Maybe Text -- | "contacts" [oAuth2ClientContacts] :: OAuth2Client -> Maybe [Text] -- | "created_at" - OAuth 2.0 Client Creation Date CreatedAt returns the -- timestamp of the client's creation. [oAuth2ClientCreatedAt] :: OAuth2Client -> Maybe DateTime -- | "frontchannel_logout_session_required" - OpenID Connect Front-Channel -- Logout Session Required Boolean value specifying whether the RP -- requires that iss (issuer) and sid (session ID) query parameters be -- included to identify the RP session with the OP when the -- frontchannel_logout_uri is used. If omitted, the default value is -- false. [oAuth2ClientFrontchannelLogoutSessionRequired] :: OAuth2Client -> Maybe Bool -- | "frontchannel_logout_uri" - OpenID Connect Front-Channel Logout URI RP -- URL that will cause the RP to log itself out when rendered in an -- iframe by the OP. An iss (issuer) query parameter and a sid (session -- ID) query parameter MAY be included by the OP to enable the RP to -- validate the request and to determine which of the potentially -- multiple sessions is to be logged out; if either is included, both -- MUST be. [oAuth2ClientFrontchannelLogoutUri] :: OAuth2Client -> Maybe Text -- | "grant_types" [oAuth2ClientGrantTypes] :: OAuth2Client -> Maybe [Text] -- | "implicit_grant_access_token_lifespan" - Specify a time duration in -- milliseconds, seconds, minutes, hours. [oAuth2ClientImplicitGrantAccessTokenLifespan] :: OAuth2Client -> Maybe Text -- | "implicit_grant_id_token_lifespan" - Specify a time duration in -- milliseconds, seconds, minutes, hours. [oAuth2ClientImplicitGrantIdTokenLifespan] :: OAuth2Client -> Maybe Text -- | "jwks" - OAuth 2.0 Client JSON Web Key Set Client's JSON Web Key Set -- [JWK] document, passed by value. The semantics of the jwks parameter -- are the same as the jwks_uri parameter, other than that the JWK Set is -- passed by value, rather than by reference. This parameter is intended -- only to be used by Clients that, for some reason, are unable to use -- the jwks_uri parameter, for instance, by native applications that -- might not have a location to host the contents of the JWK Set. If a -- Client can use jwks_uri, it MUST NOT use jwks. One significant -- downside of jwks is that it does not enable key rotation (which -- jwks_uri does, as described in Section 10 of OpenID Connect Core 1.0 -- [OpenID.Core]). The jwks_uri and jwks parameters MUST NOT be used -- together. [oAuth2ClientJwks] :: OAuth2Client -> Maybe Value -- | "jwks_uri" - OAuth 2.0 Client JSON Web Key Set URL URL for the -- Client's JSON Web Key Set [JWK] document. If the Client signs requests -- to the Server, it contains the signing key(s) the Server uses to -- validate signatures from the Client. The JWK Set MAY also contain the -- Client's encryption keys(s), which are used by the Server to encrypt -- responses to the Client. When both signing and encryption keys are -- made available, a use (Key Use) parameter value is REQUIRED for all -- keys in the referenced JWK Set to indicate each key's intended usage. -- Although some algorithms allow the same key to be used for both -- signatures and encryption, doing so is NOT RECOMMENDED, as it is less -- secure. The JWK x5c parameter MAY be used to provide X.509 -- representations of keys provided. When used, the bare key values MUST -- still be present and MUST match those in the certificate. [oAuth2ClientJwksUri] :: OAuth2Client -> Maybe Text -- | "jwt_bearer_grant_access_token_lifespan" - Specify a time duration in -- milliseconds, seconds, minutes, hours. [oAuth2ClientJwtBearerGrantAccessTokenLifespan] :: OAuth2Client -> Maybe Text -- | "logo_uri" - OAuth 2.0 Client Logo URI A URL string referencing the -- client's logo. [oAuth2ClientLogoUri] :: OAuth2Client -> Maybe Text -- | "metadata" [oAuth2ClientMetadata] :: OAuth2Client -> Maybe Value -- | "owner" - OAuth 2.0 Client Owner Owner is a string identifying the -- owner of the OAuth 2.0 Client. [oAuth2ClientOwner] :: OAuth2Client -> Maybe Text -- | "policy_uri" - OAuth 2.0 Client Policy URI PolicyURI is a URL string -- that points to a human-readable privacy policy document that describes -- how the deployment organization collects, uses, retains, and discloses -- personal data. [oAuth2ClientPolicyUri] :: OAuth2Client -> Maybe Text -- | "post_logout_redirect_uris" [oAuth2ClientPostLogoutRedirectUris] :: OAuth2Client -> Maybe [Text] -- | "redirect_uris" [oAuth2ClientRedirectUris] :: OAuth2Client -> Maybe [Text] -- | "refresh_token_grant_access_token_lifespan" - Specify a time duration -- in milliseconds, seconds, minutes, hours. [oAuth2ClientRefreshTokenGrantAccessTokenLifespan] :: OAuth2Client -> Maybe Text -- | "refresh_token_grant_id_token_lifespan" - Specify a time duration in -- milliseconds, seconds, minutes, hours. [oAuth2ClientRefreshTokenGrantIdTokenLifespan] :: OAuth2Client -> Maybe Text -- | "refresh_token_grant_refresh_token_lifespan" - Specify a time duration -- in milliseconds, seconds, minutes, hours. [oAuth2ClientRefreshTokenGrantRefreshTokenLifespan] :: OAuth2Client -> Maybe Text -- | "registration_access_token" - OpenID Connect Dynamic Client -- Registration Access Token RegistrationAccessToken can be used to -- update, get, or delete the OAuth2 Client. It is sent when creating a -- client using Dynamic Client Registration. [oAuth2ClientRegistrationAccessToken] :: OAuth2Client -> Maybe Text -- | "registration_client_uri" - OpenID Connect Dynamic Client Registration -- URL RegistrationClientURI is the URL used to update, get, or delete -- the OAuth2 Client. [oAuth2ClientRegistrationClientUri] :: OAuth2Client -> Maybe Text -- | "request_object_signing_alg" - OpenID Connect Request Object Signing -- Algorithm JWS [JWS] alg algorithm [JWA] that MUST be used for signing -- Request Objects sent to the OP. All Request Objects from this Client -- MUST be rejected, if not signed with this algorithm. [oAuth2ClientRequestObjectSigningAlg] :: OAuth2Client -> Maybe Text -- | "request_uris" [oAuth2ClientRequestUris] :: OAuth2Client -> Maybe [Text] -- | "response_types" [oAuth2ClientResponseTypes] :: OAuth2Client -> Maybe [Text] -- | "scope" - OAuth 2.0 Client Scope Scope is a string containing a -- space-separated list of scope values (as described in Section 3.3 of -- OAuth 2.0 [RFC6749]) that the client can use when requesting access -- tokens. [oAuth2ClientScope] :: OAuth2Client -> Maybe Text -- | "sector_identifier_uri" - OpenID Connect Sector Identifier URI URL -- using the https scheme to be used in calculating Pseudonymous -- Identifiers by the OP. The URL references a file with a single JSON -- array of redirect_uri values. [oAuth2ClientSectorIdentifierUri] :: OAuth2Client -> Maybe Text -- | "skip_consent" - SkipConsent skips the consent screen for this client. -- This field can only be set from the admin API. [oAuth2ClientSkipConsent] :: OAuth2Client -> Maybe Bool -- | "subject_type" - OpenID Connect Subject Type The -- `subject_types_supported` Discovery parameter contains a list of the -- supported subject_type values for this server. Valid types include -- `pairwise` and `public`. [oAuth2ClientSubjectType] :: OAuth2Client -> Maybe Text -- | "token_endpoint_auth_method" - OAuth 2.0 Token Endpoint Authentication -- Method Requested Client Authentication method for the Token Endpoint. -- The options are: `client_secret_basic`: (default) Send `client_id` and -- `client_secret` as `applicationx-www-form-urlencoded` encoded in -- the HTTP Authorization header. `client_secret_post`: Send `client_id` -- and `client_secret` as `applicationx-www-form-urlencoded` in the -- HTTP body. `private_key_jwt`: Use JSON Web Tokens to authenticate the -- client. `none`: Used for public clients (native apps, mobile apps) -- which can not have secrets. [oAuth2ClientTokenEndpointAuthMethod] :: OAuth2Client -> Maybe Text -- | "token_endpoint_auth_signing_alg" - OAuth 2.0 Token Endpoint Signing -- Algorithm Requested Client Authentication signing algorithm for the -- Token Endpoint. [oAuth2ClientTokenEndpointAuthSigningAlg] :: OAuth2Client -> Maybe Text -- | "tos_uri" - OAuth 2.0 Client Terms of Service URI A URL string -- pointing to a human-readable terms of service document for the client -- that describes a contractual relationship between the end-user and the -- client that the end-user accepts when authorizing the client. [oAuth2ClientTosUri] :: OAuth2Client -> Maybe Text -- | "updated_at" - OAuth 2.0 Client Last Update Date UpdatedAt returns the -- timestamp of the last update. [oAuth2ClientUpdatedAt] :: OAuth2Client -> Maybe DateTime -- | "userinfo_signed_response_alg" - OpenID Connect Request Userinfo -- Signed Response Algorithm JWS alg algorithm [JWA] REQUIRED for signing -- UserInfo Responses. If this is specified, the response will be JWT -- [JWT] serialized, and signed using JWS. The default, if omitted, is -- for the UserInfo Response to return the Claims as a UTF-8 encoded JSON -- object using the application/json content-type. [oAuth2ClientUserinfoSignedResponseAlg] :: OAuth2Client -> Maybe Text -- | Construct a value of type OAuth2Client (by applying it's -- required fields, if any) mkOAuth2Client :: OAuth2Client -- | OAuth2ClientTokenLifespans OAuth 2.0 Client Token Lifespans -- -- Lifespans of different token types issued for this OAuth 2.0 Client. data OAuth2ClientTokenLifespans OAuth2ClientTokenLifespans :: Maybe Text -> Maybe Text -> Maybe Text -> Maybe Text -> Maybe Text -> Maybe Text -> Maybe Text -> Maybe Text -> Maybe Text -> Maybe Text -> OAuth2ClientTokenLifespans -- | "authorization_code_grant_access_token_lifespan" - Specify a time -- duration in milliseconds, seconds, minutes, hours. [oAuth2ClientTokenLifespansAuthorizationCodeGrantAccessTokenLifespan] :: OAuth2ClientTokenLifespans -> Maybe Text -- | "authorization_code_grant_id_token_lifespan" - Specify a time duration -- in milliseconds, seconds, minutes, hours. [oAuth2ClientTokenLifespansAuthorizationCodeGrantIdTokenLifespan] :: OAuth2ClientTokenLifespans -> Maybe Text -- | "authorization_code_grant_refresh_token_lifespan" - Specify a time -- duration in milliseconds, seconds, minutes, hours. [oAuth2ClientTokenLifespansAuthorizationCodeGrantRefreshTokenLifespan] :: OAuth2ClientTokenLifespans -> Maybe Text -- | "client_credentials_grant_access_token_lifespan" - Specify a time -- duration in milliseconds, seconds, minutes, hours. [oAuth2ClientTokenLifespansClientCredentialsGrantAccessTokenLifespan] :: OAuth2ClientTokenLifespans -> Maybe Text -- | "implicit_grant_access_token_lifespan" - Specify a time duration in -- milliseconds, seconds, minutes, hours. [oAuth2ClientTokenLifespansImplicitGrantAccessTokenLifespan] :: OAuth2ClientTokenLifespans -> Maybe Text -- | "implicit_grant_id_token_lifespan" - Specify a time duration in -- milliseconds, seconds, minutes, hours. [oAuth2ClientTokenLifespansImplicitGrantIdTokenLifespan] :: OAuth2ClientTokenLifespans -> Maybe Text -- | "jwt_bearer_grant_access_token_lifespan" - Specify a time duration in -- milliseconds, seconds, minutes, hours. [oAuth2ClientTokenLifespansJwtBearerGrantAccessTokenLifespan] :: OAuth2ClientTokenLifespans -> Maybe Text -- | "refresh_token_grant_access_token_lifespan" - Specify a time duration -- in milliseconds, seconds, minutes, hours. [oAuth2ClientTokenLifespansRefreshTokenGrantAccessTokenLifespan] :: OAuth2ClientTokenLifespans -> Maybe Text -- | "refresh_token_grant_id_token_lifespan" - Specify a time duration in -- milliseconds, seconds, minutes, hours. [oAuth2ClientTokenLifespansRefreshTokenGrantIdTokenLifespan] :: OAuth2ClientTokenLifespans -> Maybe Text -- | "refresh_token_grant_refresh_token_lifespan" - Specify a time duration -- in milliseconds, seconds, minutes, hours. [oAuth2ClientTokenLifespansRefreshTokenGrantRefreshTokenLifespan] :: OAuth2ClientTokenLifespans -> Maybe Text -- | Construct a value of type OAuth2ClientTokenLifespans (by -- applying it's required fields, if any) mkOAuth2ClientTokenLifespans :: OAuth2ClientTokenLifespans -- | OAuth2ConsentRequest Contains information on an ongoing consent -- request. data OAuth2ConsentRequest OAuth2ConsentRequest :: Maybe Text -> Maybe [Text] -> Text -> Maybe OAuth2Client -> Maybe Value -> Maybe Text -> Maybe Text -> Maybe OAuth2ConsentRequestOpenIDConnectContext -> Maybe Text -> Maybe [Text] -> Maybe [Text] -> Maybe Bool -> Maybe Text -> OAuth2ConsentRequest -- | "acr" - ACR represents the Authentication AuthorizationContext Class -- Reference value for this authentication session. You can use it to -- express that, for example, a user authenticated using two factor -- authentication. [oAuth2ConsentRequestAcr] :: OAuth2ConsentRequest -> Maybe Text -- | "amr" [oAuth2ConsentRequestAmr] :: OAuth2ConsentRequest -> Maybe [Text] -- | Required "challenge" - ID is the identifier -- ("authorization challenge") of the consent -- authorization request. It is used to identify the session. [oAuth2ConsentRequestChallenge] :: OAuth2ConsentRequest -> Text -- | "client" [oAuth2ConsentRequestClient] :: OAuth2ConsentRequest -> Maybe OAuth2Client -- | "context" [oAuth2ConsentRequestContext] :: OAuth2ConsentRequest -> Maybe Value -- | "login_challenge" - LoginChallenge is the login challenge this consent -- challenge belongs to. It can be used to associate a login and consent -- request in the login & consent app. [oAuth2ConsentRequestLoginChallenge] :: OAuth2ConsentRequest -> Maybe Text -- | "login_session_id" - LoginSessionID is the login session ID. If the -- user-agent reuses a login session (via cookie remember flag) this -- ID will remain the same. If the user-agent did not have an existing -- authentication session (e.g. remember is false) this will be a new -- random value. This value is used as the "sid" -- parameter in the ID Token and in OIDC Front-Back- channel logout. -- It's value can generally be used to associate consecutive login -- requests by a certain user. [oAuth2ConsentRequestLoginSessionId] :: OAuth2ConsentRequest -> Maybe Text -- | "oidc_context" [oAuth2ConsentRequestOidcContext] :: OAuth2ConsentRequest -> Maybe OAuth2ConsentRequestOpenIDConnectContext -- | "request_url" - RequestURL is the original OAuth 2.0 Authorization URL -- requested by the OAuth 2.0 client. It is the URL which initiates the -- OAuth 2.0 Authorization Code or OAuth 2.0 Implicit flow. This URL is -- typically not needed, but might come in handy if you want to deal with -- additional request parameters. [oAuth2ConsentRequestRequestUrl] :: OAuth2ConsentRequest -> Maybe Text -- | "requested_access_token_audience" [oAuth2ConsentRequestRequestedAccessTokenAudience] :: OAuth2ConsentRequest -> Maybe [Text] -- | "requested_scope" [oAuth2ConsentRequestRequestedScope] :: OAuth2ConsentRequest -> Maybe [Text] -- | "skip" - Skip, if true, implies that the client has requested the same -- scopes from the same user previously. If true, you must not ask the -- user to grant the requested scopes. You must however either allow or -- deny the consent request using the usual API call. [oAuth2ConsentRequestSkip] :: OAuth2ConsentRequest -> Maybe Bool -- | "subject" - Subject is the user ID of the end-user that authenticated. -- Now, that end user needs to grant or deny the scope requested by the -- OAuth 2.0 client. [oAuth2ConsentRequestSubject] :: OAuth2ConsentRequest -> Maybe Text -- | Construct a value of type OAuth2ConsentRequest (by applying -- it's required fields, if any) mkOAuth2ConsentRequest :: Text -> OAuth2ConsentRequest -- | OAuth2ConsentRequestOpenIDConnectContext Contains optional information -- about the OpenID Connect request. data OAuth2ConsentRequestOpenIDConnectContext OAuth2ConsentRequestOpenIDConnectContext :: Maybe [Text] -> Maybe Text -> Maybe (Map String Value) -> Maybe Text -> Maybe [Text] -> OAuth2ConsentRequestOpenIDConnectContext -- | "acr_values" - ACRValues is the Authentication AuthorizationContext -- Class Reference requested in the OAuth 2.0 Authorization request. It -- is a parameter defined by OpenID Connect and expresses which level of -- authentication (e.g. 2FA) is required. OpenID Connect defines it as -- follows: > Requested Authentication AuthorizationContext Class -- Reference values. Space-separated string that specifies the acr values -- that the Authorization Server is being requested to use for processing -- this Authentication Request, with the values appearing in order of -- preference. The Authentication AuthorizationContext Class satisfied by -- the authentication performed is returned as the acr Claim Value, as -- specified in Section 2. The acr Claim is requested as a Voluntary -- Claim by this parameter. [oAuth2ConsentRequestOpenIDConnectContextAcrValues] :: OAuth2ConsentRequestOpenIDConnectContext -> Maybe [Text] -- | "display" - Display is a string value that specifies how the -- Authorization Server displays the authentication and consent user -- interface pages to the End-User. The defined values are: page: The -- Authorization Server SHOULD display the authentication and consent UI -- consistent with a full User Agent page view. If the display parameter -- is not specified, this is the default display mode. popup: The -- Authorization Server SHOULD display the authentication and consent UI -- consistent with a popup User Agent window. The popup User Agent window -- should be of an appropriate size for a login-focused dialog and should -- not obscure the entire window that it is popping up over. touch: The -- Authorization Server SHOULD display the authentication and consent UI -- consistent with a device that leverages a touch interface. wap: The -- Authorization Server SHOULD display the authentication and consent UI -- consistent with a "feature phone" type display. The -- Authorization Server MAY also attempt to detect the capabilities of -- the User Agent and present an appropriate display. [oAuth2ConsentRequestOpenIDConnectContextDisplay] :: OAuth2ConsentRequestOpenIDConnectContext -> Maybe Text -- | "id_token_hint_claims" - IDTokenHintClaims are the claims of the ID -- Token previously issued by the Authorization Server being passed as a -- hint about the End-User's current or past authenticated session with -- the Client. [oAuth2ConsentRequestOpenIDConnectContextIdTokenHintClaims] :: OAuth2ConsentRequestOpenIDConnectContext -> Maybe (Map String Value) -- | "login_hint" - LoginHint hints about the login identifier the End-User -- might use to log in (if necessary). This hint can be used by an RP if -- it first asks the End-User for their e-mail address (or other -- identifier) and then wants to pass that value as a hint to the -- discovered authorization service. This value MAY also be a phone -- number in the format specified for the phone_number Claim. The use of -- this parameter is optional. [oAuth2ConsentRequestOpenIDConnectContextLoginHint] :: OAuth2ConsentRequestOpenIDConnectContext -> Maybe Text -- | "ui_locales" - UILocales is the End-User'id preferred languages and -- scripts for the user interface, represented as a space-separated list -- of BCP47 [RFC5646] language tag values, ordered by preference. For -- instance, the value "fr-CA fr en" represents a -- preference for French as spoken in Canada, then French (without a -- region designation), followed by English (without a region -- designation). An error SHOULD NOT result if some or all of the -- requested locales are not supported by the OpenID Provider. [oAuth2ConsentRequestOpenIDConnectContextUiLocales] :: OAuth2ConsentRequestOpenIDConnectContext -> Maybe [Text] -- | Construct a value of type -- OAuth2ConsentRequestOpenIDConnectContext (by applying it's -- required fields, if any) mkOAuth2ConsentRequestOpenIDConnectContext :: OAuth2ConsentRequestOpenIDConnectContext -- | OAuth2ConsentSession OAuth 2.0 Consent Session -- -- A completed OAuth 2.0 Consent Session. data OAuth2ConsentSession OAuth2ConsentSession :: Maybe OAuth2ConsentRequest -> Maybe OAuth2ConsentSessionExpiresAt -> Maybe [Text] -> Maybe [Text] -> Maybe DateTime -> Maybe Bool -> Maybe Integer -> Maybe AcceptOAuth2ConsentRequestSession -> OAuth2ConsentSession -- | "consent_request" [oAuth2ConsentSessionConsentRequest] :: OAuth2ConsentSession -> Maybe OAuth2ConsentRequest -- | "expires_at" [oAuth2ConsentSessionExpiresAt] :: OAuth2ConsentSession -> Maybe OAuth2ConsentSessionExpiresAt -- | "grant_access_token_audience" [oAuth2ConsentSessionGrantAccessTokenAudience] :: OAuth2ConsentSession -> Maybe [Text] -- | "grant_scope" [oAuth2ConsentSessionGrantScope] :: OAuth2ConsentSession -> Maybe [Text] -- | "handled_at" [oAuth2ConsentSessionHandledAt] :: OAuth2ConsentSession -> Maybe DateTime -- | "remember" - Remember Consent Remember, if set to true, tells ORY -- Hydra to remember this consent authorization and reuse it if the same -- client asks the same user for the same, or a subset of, scope. [oAuth2ConsentSessionRemember] :: OAuth2ConsentSession -> Maybe Bool -- | "remember_for" - Remember Consent For RememberFor sets how long the -- consent authorization should be remembered for in seconds. If set to -- `0`, the authorization will be remembered indefinitely. [oAuth2ConsentSessionRememberFor] :: OAuth2ConsentSession -> Maybe Integer -- | "session" [oAuth2ConsentSessionSession] :: OAuth2ConsentSession -> Maybe AcceptOAuth2ConsentRequestSession -- | Construct a value of type OAuth2ConsentSession (by applying -- it's required fields, if any) mkOAuth2ConsentSession :: OAuth2ConsentSession -- | OAuth2ConsentSessionExpiresAt data OAuth2ConsentSessionExpiresAt OAuth2ConsentSessionExpiresAt :: Maybe DateTime -> Maybe DateTime -> Maybe DateTime -> Maybe DateTime -> Maybe DateTime -> OAuth2ConsentSessionExpiresAt -- | "access_token" [oAuth2ConsentSessionExpiresAtAccessToken] :: OAuth2ConsentSessionExpiresAt -> Maybe DateTime -- | "authorize_code" [oAuth2ConsentSessionExpiresAtAuthorizeCode] :: OAuth2ConsentSessionExpiresAt -> Maybe DateTime -- | "id_token" [oAuth2ConsentSessionExpiresAtIdToken] :: OAuth2ConsentSessionExpiresAt -> Maybe DateTime -- | "par_context" [oAuth2ConsentSessionExpiresAtParContext] :: OAuth2ConsentSessionExpiresAt -> Maybe DateTime -- | "refresh_token" [oAuth2ConsentSessionExpiresAtRefreshToken] :: OAuth2ConsentSessionExpiresAt -> Maybe DateTime -- | Construct a value of type OAuth2ConsentSessionExpiresAt (by -- applying it's required fields, if any) mkOAuth2ConsentSessionExpiresAt :: OAuth2ConsentSessionExpiresAt -- | OAuth2LoginRequest Contains information on an ongoing login request. data OAuth2LoginRequest OAuth2LoginRequest :: Text -> OAuth2Client -> Maybe OAuth2ConsentRequestOpenIDConnectContext -> Text -> [Text] -> [Text] -> Maybe Text -> Bool -> Text -> OAuth2LoginRequest -- | Required "challenge" - ID is the identifier ("login -- challenge") of the login request. It is used to identify the -- session. [oAuth2LoginRequestChallenge] :: OAuth2LoginRequest -> Text -- | Required "client" [oAuth2LoginRequestClient] :: OAuth2LoginRequest -> OAuth2Client -- | "oidc_context" [oAuth2LoginRequestOidcContext] :: OAuth2LoginRequest -> Maybe OAuth2ConsentRequestOpenIDConnectContext -- | Required "request_url" - RequestURL is the original OAuth 2.0 -- Authorization URL requested by the OAuth 2.0 client. It is the URL -- which initiates the OAuth 2.0 Authorization Code or OAuth 2.0 Implicit -- flow. This URL is typically not needed, but might come in handy if you -- want to deal with additional request parameters. [oAuth2LoginRequestRequestUrl] :: OAuth2LoginRequest -> Text -- | Required "requested_access_token_audience" [oAuth2LoginRequestRequestedAccessTokenAudience] :: OAuth2LoginRequest -> [Text] -- | Required "requested_scope" [oAuth2LoginRequestRequestedScope] :: OAuth2LoginRequest -> [Text] -- | "session_id" - SessionID is the login session ID. If the user-agent -- reuses a login session (via cookie remember flag) this ID will -- remain the same. If the user-agent did not have an existing -- authentication session (e.g. remember is false) this will be a new -- random value. This value is used as the "sid" -- parameter in the ID Token and in OIDC Front-Back- channel logout. -- It's value can generally be used to associate consecutive login -- requests by a certain user. [oAuth2LoginRequestSessionId] :: OAuth2LoginRequest -> Maybe Text -- | Required "skip" - Skip, if true, implies that the client has -- requested the same scopes from the same user previously. If true, you -- can skip asking the user to grant the requested scopes, and simply -- forward the user to the redirect URL. This feature allows you to -- update / set session information. [oAuth2LoginRequestSkip] :: OAuth2LoginRequest -> Bool -- | Required "subject" - Subject is the user ID of the end-user -- that authenticated. Now, that end user needs to grant or deny the -- scope requested by the OAuth 2.0 client. If this value is set and -- `skip` is true, you MUST include this subject type when accepting the -- login request, or the request will fail. [oAuth2LoginRequestSubject] :: OAuth2LoginRequest -> Text -- | Construct a value of type OAuth2LoginRequest (by applying it's -- required fields, if any) mkOAuth2LoginRequest :: Text -> OAuth2Client -> Text -> [Text] -> [Text] -> Bool -> Text -> OAuth2LoginRequest -- | OAuth2LogoutRequest Contains information about an ongoing logout -- request. data OAuth2LogoutRequest OAuth2LogoutRequest :: Maybe Text -> Maybe OAuth2Client -> Maybe Text -> Maybe Bool -> Maybe Text -> Maybe Text -> OAuth2LogoutRequest -- | "challenge" - Challenge is the identifier ("logout -- challenge") of the logout authentication request. It is used -- to identify the session. [oAuth2LogoutRequestChallenge] :: OAuth2LogoutRequest -> Maybe Text -- | "client" [oAuth2LogoutRequestClient] :: OAuth2LogoutRequest -> Maybe OAuth2Client -- | "request_url" - RequestURL is the original Logout URL requested. [oAuth2LogoutRequestRequestUrl] :: OAuth2LogoutRequest -> Maybe Text -- | "rp_initiated" - RPInitiated is set to true if the request was -- initiated by a Relying Party (RP), also known as an OAuth 2.0 Client. [oAuth2LogoutRequestRpInitiated] :: OAuth2LogoutRequest -> Maybe Bool -- | "sid" - SessionID is the login session ID that was requested to log -- out. [oAuth2LogoutRequestSid] :: OAuth2LogoutRequest -> Maybe Text -- | "subject" - Subject is the user for whom the logout was request. [oAuth2LogoutRequestSubject] :: OAuth2LogoutRequest -> Maybe Text -- | Construct a value of type OAuth2LogoutRequest (by applying it's -- required fields, if any) mkOAuth2LogoutRequest :: OAuth2LogoutRequest -- | OAuth2RedirectTo OAuth 2.0 Redirect Browser To -- -- Contains a redirect URL used to complete a login, consent, or logout -- request. data OAuth2RedirectTo OAuth2RedirectTo :: Text -> OAuth2RedirectTo -- | Required "redirect_to" - RedirectURL is the URL which you -- should redirect the user's browser to once the authentication process -- is completed. [oAuth2RedirectToRedirectTo] :: OAuth2RedirectTo -> Text -- | Construct a value of type OAuth2RedirectTo (by applying it's -- required fields, if any) mkOAuth2RedirectTo :: Text -> OAuth2RedirectTo -- | OAuth2TokenExchange OAuth2 Token Exchange Result data OAuth2TokenExchange OAuth2TokenExchange :: Maybe Text -> Maybe Integer -> Maybe Integer -> Maybe Text -> Maybe Text -> Maybe Text -> OAuth2TokenExchange -- | "access_token" - The access token issued by the authorization server. [oAuth2TokenExchangeAccessToken] :: OAuth2TokenExchange -> Maybe Text -- | "expires_in" - The lifetime in seconds of the access token. For -- example, the value "3600" denotes that the access -- token will expire in one hour from the time the response was -- generated. [oAuth2TokenExchangeExpiresIn] :: OAuth2TokenExchange -> Maybe Integer -- | "id_token" - To retrieve a refresh token request the id_token scope. [oAuth2TokenExchangeIdToken] :: OAuth2TokenExchange -> Maybe Integer -- | "refresh_token" - The refresh token, which can be used to obtain new -- access tokens. To retrieve it add the scope -- "offline" to your access token request. [oAuth2TokenExchangeRefreshToken] :: OAuth2TokenExchange -> Maybe Text -- | "scope" - The scope of the access token [oAuth2TokenExchangeScope] :: OAuth2TokenExchange -> Maybe Text -- | "token_type" - The type of the token issued [oAuth2TokenExchangeTokenType] :: OAuth2TokenExchange -> Maybe Text -- | Construct a value of type OAuth2TokenExchange (by applying it's -- required fields, if any) mkOAuth2TokenExchange :: OAuth2TokenExchange -- | OidcConfiguration OpenID Connect Discovery Metadata -- -- Includes links to several endpoints (for example `oauth2token`) -- and exposes information on supported signature algorithms among -- others. data OidcConfiguration OidcConfiguration :: Text -> Maybe Bool -> Maybe Bool -> Maybe Bool -> Maybe [Text] -> Maybe [Text] -> Maybe Text -> Maybe Bool -> Maybe Bool -> Maybe [Text] -> [Text] -> [Text] -> Text -> Text -> Maybe Text -> Maybe [Text] -> Maybe Bool -> Maybe Bool -> Maybe Bool -> Maybe [Text] -> [Text] -> Maybe Text -> Maybe [Text] -> [Text] -> Text -> Maybe [Text] -> Maybe Text -> [Text] -> Maybe [Text] -> OidcConfiguration -- | Required "authorization_endpoint" - OAuth 2.0 Authorization -- Endpoint URL [oidcConfigurationAuthorizationEndpoint] :: OidcConfiguration -> Text -- | "backchannel_logout_session_supported" - OpenID Connect Back-Channel -- Logout Session Required Boolean value specifying whether the OP can -- pass a sid (session ID) Claim in the Logout Token to identify the RP -- session with the OP. If supported, the sid Claim is also included in -- ID Tokens issued by the OP [oidcConfigurationBackchannelLogoutSessionSupported] :: OidcConfiguration -> Maybe Bool -- | "backchannel_logout_supported" - OpenID Connect Back-Channel Logout -- Supported Boolean value specifying whether the OP supports -- back-channel logout, with true indicating support. [oidcConfigurationBackchannelLogoutSupported] :: OidcConfiguration -> Maybe Bool -- | "claims_parameter_supported" - OpenID Connect Claims Parameter -- Parameter Supported Boolean value specifying whether the OP supports -- use of the claims parameter, with true indicating support. [oidcConfigurationClaimsParameterSupported] :: OidcConfiguration -> Maybe Bool -- | "claims_supported" - OpenID Connect Supported Claims JSON array -- containing a list of the Claim Names of the Claims that the OpenID -- Provider MAY be able to supply values for. Note that for privacy or -- other reasons, this might not be an exhaustive list. [oidcConfigurationClaimsSupported] :: OidcConfiguration -> Maybe [Text] -- | "code_challenge_methods_supported" - OAuth 2.0 PKCE Supported Code -- Challenge Methods JSON array containing a list of Proof Key for Code -- Exchange (PKCE) [RFC7636] code challenge methods supported by this -- authorization server. [oidcConfigurationCodeChallengeMethodsSupported] :: OidcConfiguration -> Maybe [Text] -- | "end_session_endpoint" - OpenID Connect End-Session Endpoint URL at -- the OP to which an RP can perform a redirect to request that the -- End-User be logged out at the OP. [oidcConfigurationEndSessionEndpoint] :: OidcConfiguration -> Maybe Text -- | "frontchannel_logout_session_supported" - OpenID Connect Front-Channel -- Logout Session Required Boolean value specifying whether the OP can -- pass iss (issuer) and sid (session ID) query parameters to identify -- the RP session with the OP when the frontchannel_logout_uri is used. -- If supported, the sid Claim is also included in ID Tokens issued by -- the OP. [oidcConfigurationFrontchannelLogoutSessionSupported] :: OidcConfiguration -> Maybe Bool -- | "frontchannel_logout_supported" - OpenID Connect Front-Channel Logout -- Supported Boolean value specifying whether the OP supports HTTP-based -- logout, with true indicating support. [oidcConfigurationFrontchannelLogoutSupported] :: OidcConfiguration -> Maybe Bool -- | "grant_types_supported" - OAuth 2.0 Supported Grant Types JSON array -- containing a list of the OAuth 2.0 Grant Type values that this OP -- supports. [oidcConfigurationGrantTypesSupported] :: OidcConfiguration -> Maybe [Text] -- | Required "id_token_signed_response_alg" - OpenID Connect -- Default ID Token Signing Algorithms Algorithm used to sign OpenID -- Connect ID Tokens. [oidcConfigurationIdTokenSignedResponseAlg] :: OidcConfiguration -> [Text] -- | Required "id_token_signing_alg_values_supported" - OpenID -- Connect Supported ID Token Signing Algorithms JSON array containing a -- list of the JWS signing algorithms (alg values) supported by the OP -- for the ID Token to encode the Claims in a JWT. [oidcConfigurationIdTokenSigningAlgValuesSupported] :: OidcConfiguration -> [Text] -- | Required "issuer" - OpenID Connect Issuer URL An URL using the -- https scheme with no query or fragment component that the OP asserts -- as its IssuerURL Identifier. If IssuerURL discovery is supported , -- this value MUST be identical to the issuer value returned by -- WebFinger. This also MUST be identical to the iss Claim value in ID -- Tokens issued from this IssuerURL. [oidcConfigurationIssuer] :: OidcConfiguration -> Text -- | Required "jwks_uri" - OpenID Connect Well-Known JSON Web Keys -- URL URL of the OP's JSON Web Key Set [JWK] document. This contains the -- signing key(s) the RP uses to validate signatures from the OP. The JWK -- Set MAY also contain the Server's encryption key(s), which are used by -- RPs to encrypt requests to the Server. When both signing and -- encryption keys are made available, a use (Key Use) parameter value is -- REQUIRED for all keys in the referenced JWK Set to indicate each key's -- intended usage. Although some algorithms allow the same key to be used -- for both signatures and encryption, doing so is NOT RECOMMENDED, as it -- is less secure. The JWK x5c parameter MAY be used to provide X.509 -- representations of keys provided. When used, the bare key values MUST -- still be present and MUST match those in the certificate. [oidcConfigurationJwksUri] :: OidcConfiguration -> Text -- | "registration_endpoint" - OpenID Connect Dynamic Client Registration -- Endpoint URL [oidcConfigurationRegistrationEndpoint] :: OidcConfiguration -> Maybe Text -- | "request_object_signing_alg_values_supported" - OpenID Connect -- Supported Request Object Signing Algorithms JSON array containing a -- list of the JWS signing algorithms (alg values) supported by the OP -- for Request Objects, which are described in Section 6.1 of OpenID -- Connect Core 1.0 [OpenID.Core]. These algorithms are used both when -- the Request Object is passed by value (using the request parameter) -- and when it is passed by reference (using the request_uri parameter). [oidcConfigurationRequestObjectSigningAlgValuesSupported] :: OidcConfiguration -> Maybe [Text] -- | "request_parameter_supported" - OpenID Connect Request Parameter -- Supported Boolean value specifying whether the OP supports use of the -- request parameter, with true indicating support. [oidcConfigurationRequestParameterSupported] :: OidcConfiguration -> Maybe Bool -- | "request_uri_parameter_supported" - OpenID Connect Request URI -- Parameter Supported Boolean value specifying whether the OP supports -- use of the request_uri parameter, with true indicating support. [oidcConfigurationRequestUriParameterSupported] :: OidcConfiguration -> Maybe Bool -- | "require_request_uri_registration" - OpenID Connect Requires Request -- URI Registration Boolean value specifying whether the OP requires any -- request_uri values used to be pre-registered using the request_uris -- registration parameter. [oidcConfigurationRequireRequestUriRegistration] :: OidcConfiguration -> Maybe Bool -- | "response_modes_supported" - OAuth 2.0 Supported Response Modes JSON -- array containing a list of the OAuth 2.0 response_mode values that -- this OP supports. [oidcConfigurationResponseModesSupported] :: OidcConfiguration -> Maybe [Text] -- | Required "response_types_supported" - OAuth 2.0 Supported -- Response Types JSON array containing a list of the OAuth 2.0 -- response_type values that this OP supports. Dynamic OpenID Providers -- MUST support the code, id_token, and the token id_token Response Type -- values. [oidcConfigurationResponseTypesSupported] :: OidcConfiguration -> [Text] -- | "revocation_endpoint" - OAuth 2.0 Token Revocation URL URL of the -- authorization server's OAuth 2.0 revocation endpoint. [oidcConfigurationRevocationEndpoint] :: OidcConfiguration -> Maybe Text -- | "scopes_supported" - OAuth 2.0 Supported Scope Values JSON array -- containing a list of the OAuth 2.0 [RFC6749] scope values that this -- server supports. The server MUST support the openid scope value. -- Servers MAY choose not to advertise some supported scope values even -- when this parameter is used [oidcConfigurationScopesSupported] :: OidcConfiguration -> Maybe [Text] -- | Required "subject_types_supported" - OpenID Connect Supported -- Subject Types JSON array containing a list of the Subject Identifier -- types that this OP supports. Valid types include pairwise and public. [oidcConfigurationSubjectTypesSupported] :: OidcConfiguration -> [Text] -- | Required "token_endpoint" - OAuth 2.0 Token Endpoint URL [oidcConfigurationTokenEndpoint] :: OidcConfiguration -> Text -- | "token_endpoint_auth_methods_supported" - OAuth 2.0 Supported Client -- Authentication Methods JSON array containing a list of Client -- Authentication methods supported by this Token Endpoint. The options -- are client_secret_post, client_secret_basic, client_secret_jwt, and -- private_key_jwt, as described in Section 9 of OpenID Connect Core 1.0 [oidcConfigurationTokenEndpointAuthMethodsSupported] :: OidcConfiguration -> Maybe [Text] -- | "userinfo_endpoint" - OpenID Connect Userinfo URL URL of the OP's -- UserInfo Endpoint. [oidcConfigurationUserinfoEndpoint] :: OidcConfiguration -> Maybe Text -- | Required "userinfo_signed_response_alg" - OpenID Connect User -- Userinfo Signing Algorithm Algorithm used to sign OpenID Connect -- Userinfo Responses. [oidcConfigurationUserinfoSignedResponseAlg] :: OidcConfiguration -> [Text] -- | "userinfo_signing_alg_values_supported" - OpenID Connect Supported -- Userinfo Signing Algorithm JSON array containing a list of the JWS -- [JWS] signing algorithms (alg values) [JWA] supported by the UserInfo -- Endpoint to encode the Claims in a JWT [JWT]. [oidcConfigurationUserinfoSigningAlgValuesSupported] :: OidcConfiguration -> Maybe [Text] -- | Construct a value of type OidcConfiguration (by applying it's -- required fields, if any) mkOidcConfiguration :: Text -> [Text] -> [Text] -> Text -> Text -> [Text] -> [Text] -> Text -> [Text] -> OidcConfiguration -- | OidcUserInfo OpenID Connect Userinfo data OidcUserInfo OidcUserInfo :: Maybe Text -> Maybe Text -> Maybe Bool -> Maybe Text -> Maybe Text -> Maybe Text -> Maybe Text -> Maybe Text -> Maybe Text -> Maybe Text -> Maybe Text -> Maybe Bool -> Maybe Text -> Maybe Text -> Maybe Text -> Maybe Text -> Maybe Integer -> Maybe Text -> Maybe Text -> OidcUserInfo -- | "birthdate" - End-User's birthday, represented as an ISO 8601:2004 -- [ISO8601‑2004] YYYY-MM-DD format. The year MAY be 0000, indicating -- that it is omitted. To represent only the year, YYYY format is -- allowed. Note that depending on the underlying platform's date related -- function, providing just year can result in varying month and day, so -- the implementers need to take this factor into account to correctly -- process the dates. [oidcUserInfoBirthdate] :: OidcUserInfo -> Maybe Text -- | "email" - End-User's preferred e-mail address. Its value MUST conform -- to the RFC 5322 [RFC5322] addr-spec syntax. The RP MUST NOT rely upon -- this value being unique, as discussed in Section 5.7. [oidcUserInfoEmail] :: OidcUserInfo -> Maybe Text -- | "email_verified" - True if the End-User's e-mail address has been -- verified; otherwise false. When this Claim Value is true, this means -- that the OP took affirmative steps to ensure that this e-mail address -- was controlled by the End-User at the time the verification was -- performed. The means by which an e-mail address is verified is -- context-specific, and dependent upon the trust framework or -- contractual agreements within which the parties are operating. [oidcUserInfoEmailVerified] :: OidcUserInfo -> Maybe Bool -- | "family_name" - Surname(s) or last name(s) of the End-User. Note that -- in some cultures, people can have multiple family names or no family -- name; all can be present, with the names being separated by space -- characters. [oidcUserInfoFamilyName] :: OidcUserInfo -> Maybe Text -- | "gender" - End-User's gender. Values defined by this specification are -- female and male. Other values MAY be used when neither of the defined -- values are applicable. [oidcUserInfoGender] :: OidcUserInfo -> Maybe Text -- | "given_name" - Given name(s) or first name(s) of the End-User. Note -- that in some cultures, people can have multiple given names; all can -- be present, with the names being separated by space characters. [oidcUserInfoGivenName] :: OidcUserInfo -> Maybe Text -- | "locale" - End-User's locale, represented as a BCP47 [RFC5646] -- language tag. This is typically an ISO 639-1 Alpha-2 [ISO639‑1] -- language code in lowercase and an ISO 3166-1 Alpha-2 [ISO3166‑1] -- country code in uppercase, separated by a dash. For example, en-US or -- fr-CA. As a compatibility note, some implementations have used an -- underscore as the separator rather than a dash, for example, en_US; -- Relying Parties MAY choose to accept this locale syntax as well. [oidcUserInfoLocale] :: OidcUserInfo -> Maybe Text -- | "middle_name" - Middle name(s) of the End-User. Note that in some -- cultures, people can have multiple middle names; all can be present, -- with the names being separated by space characters. Also note that in -- some cultures, middle names are not used. [oidcUserInfoMiddleName] :: OidcUserInfo -> Maybe Text -- | "name" - End-User's full name in displayable form including all name -- parts, possibly including titles and suffixes, ordered according to -- the End-User's locale and preferences. [oidcUserInfoName] :: OidcUserInfo -> Maybe Text -- | "nickname" - Casual name of the End-User that may or may not be the -- same as the given_name. For instance, a nickname value of Mike might -- be returned alongside a given_name value of Michael. [oidcUserInfoNickname] :: OidcUserInfo -> Maybe Text -- | "phone_number" - End-User's preferred telephone number. E.164 [E.164] -- is RECOMMENDED as the format of this Claim, for example, +1 (425) -- 555-1212 or +56 (2) 687 2400. If the phone number contains an -- extension, it is RECOMMENDED that the extension be represented using -- the RFC 3966 [RFC3966] extension syntax, for example, +1 (604) -- 555-1234;ext=5678. [oidcUserInfoPhoneNumber] :: OidcUserInfo -> Maybe Text -- | "phone_number_verified" - True if the End-User's phone number has been -- verified; otherwise false. When this Claim Value is true, this means -- that the OP took affirmative steps to ensure that this phone number -- was controlled by the End-User at the time the verification was -- performed. The means by which a phone number is verified is -- context-specific, and dependent upon the trust framework or -- contractual agreements within which the parties are operating. When -- true, the phone_number Claim MUST be in E.164 format and any -- extensions MUST be represented in RFC 3966 format. [oidcUserInfoPhoneNumberVerified] :: OidcUserInfo -> Maybe Bool -- | "picture" - URL of the End-User's profile picture. This URL MUST refer -- to an image file (for example, a PNG, JPEG, or GIF image file), rather -- than to a Web page containing an image. Note that this URL SHOULD -- specifically reference a profile photo of the End-User suitable for -- displaying when describing the End-User, rather than an arbitrary -- photo taken by the End-User. [oidcUserInfoPicture] :: OidcUserInfo -> Maybe Text -- | "preferred_username" - Non-unique shorthand name by which the End-User -- wishes to be referred to at the RP, such as janedoe or j.doe. This -- value MAY be any valid JSON string including special characters such -- as @, /, or whitespace. [oidcUserInfoPreferredUsername] :: OidcUserInfo -> Maybe Text -- | "profile" - URL of the End-User's profile page. The contents of this -- Web page SHOULD be about the End-User. [oidcUserInfoProfile] :: OidcUserInfo -> Maybe Text -- | "sub" - Subject - Identifier for the End-User at the IssuerURL. [oidcUserInfoSub] :: OidcUserInfo -> Maybe Text -- | "updated_at" - Time the End-User's information was last updated. Its -- value is a JSON number representing the number of seconds from -- 1970-01-01T0:0:0Z as measured in UTC until the date/time. [oidcUserInfoUpdatedAt] :: OidcUserInfo -> Maybe Integer -- | "website" - URL of the End-User's Web page or blog. This Web page -- SHOULD contain information published by the End-User or an -- organization that the End-User is affiliated with. [oidcUserInfoWebsite] :: OidcUserInfo -> Maybe Text -- | "zoneinfo" - String from zoneinfo [zoneinfo] time zone database -- representing the End-User's time zone. For example, EuropeParis or -- AmericaLos_Angeles. [oidcUserInfoZoneinfo] :: OidcUserInfo -> Maybe Text -- | Construct a value of type OidcUserInfo (by applying it's -- required fields, if any) mkOidcUserInfo :: OidcUserInfo -- | Pagination data Pagination Pagination :: Maybe Integer -> Maybe Text -> Pagination -- | "page_size" - Items per page This is the number of items per page to -- return. For details on pagination please head over to the -- pagination documentation. [paginationPageSize] :: Pagination -> Maybe Integer -- | "page_token" - Next Page Token The next page token. For details on -- pagination please head over to the pagination documentation. [paginationPageToken] :: Pagination -> Maybe Text -- | Construct a value of type Pagination (by applying it's required -- fields, if any) mkPagination :: Pagination -- | PaginationHeaders data PaginationHeaders PaginationHeaders :: Maybe Text -> Maybe Text -> PaginationHeaders -- | "link" - The link header contains pagination links. For details on -- pagination please head over to the pagination documentation. -- in: header [paginationHeadersLink] :: PaginationHeaders -> Maybe Text -- | "x-total-count" - The total number of clients. in: header [paginationHeadersXTotalCount] :: PaginationHeaders -> Maybe Text -- | Construct a value of type PaginationHeaders (by applying it's -- required fields, if any) mkPaginationHeaders :: PaginationHeaders -- | RejectOAuth2Request The request payload used to accept a login or -- consent request. data RejectOAuth2Request RejectOAuth2Request :: Maybe Text -> Maybe Text -> Maybe Text -> Maybe Text -> Maybe Integer -> RejectOAuth2Request -- | "error" - The error should follow the OAuth2 error format (e.g. -- `invalid_request`, `login_required`). Defaults to `request_denied`. [rejectOAuth2RequestError] :: RejectOAuth2Request -> Maybe Text -- | "error_debug" - Debug contains information to help resolve the problem -- as a developer. Usually not exposed to the public but only in the -- server logs. [rejectOAuth2RequestErrorDebug] :: RejectOAuth2Request -> Maybe Text -- | "error_description" - Description of the error in a human readable -- format. [rejectOAuth2RequestErrorDescription] :: RejectOAuth2Request -> Maybe Text -- | "error_hint" - Hint to help resolve the error. [rejectOAuth2RequestErrorHint] :: RejectOAuth2Request -> Maybe Text -- | "status_code" - Represents the HTTP status code of the error (e.g. 401 -- or 403) Defaults to 400 [rejectOAuth2RequestStatusCode] :: RejectOAuth2Request -> Maybe Integer -- | Construct a value of type RejectOAuth2Request (by applying it's -- required fields, if any) mkRejectOAuth2Request :: RejectOAuth2Request -- | TokenPagination data TokenPagination TokenPagination :: Maybe Integer -> Maybe Text -> TokenPagination -- | "page_size" - Items per page This is the number of items per page to -- return. For details on pagination please head over to the -- pagination documentation. [tokenPaginationPageSize] :: TokenPagination -> Maybe Integer -- | "page_token" - Next Page Token The next page token. For details on -- pagination please head over to the pagination documentation. [tokenPaginationPageToken] :: TokenPagination -> Maybe Text -- | Construct a value of type TokenPagination (by applying it's -- required fields, if any) mkTokenPagination :: TokenPagination -- | TokenPaginationHeaders data TokenPaginationHeaders TokenPaginationHeaders :: Maybe Text -> Maybe Text -> TokenPaginationHeaders -- | "link" - The link header contains pagination links. For details on -- pagination please head over to the pagination documentation. -- in: header [tokenPaginationHeadersLink] :: TokenPaginationHeaders -> Maybe Text -- | "x-total-count" - The total number of clients. in: header [tokenPaginationHeadersXTotalCount] :: TokenPaginationHeaders -> Maybe Text -- | Construct a value of type TokenPaginationHeaders (by applying -- it's required fields, if any) mkTokenPaginationHeaders :: TokenPaginationHeaders -- | TokenPaginationRequestParameters Pagination Request Parameters -- -- The Link HTTP header contains multiple links (first, -- next, last, previous) formatted as: -- `https://{project-slug}.projects.oryapis.com/admin/clients?page_size={limit}&page_token={offset}; -- rel="{page}"` For details on pagination please head over to the -- pagination documentation. data TokenPaginationRequestParameters TokenPaginationRequestParameters :: Maybe Integer -> Maybe Text -> TokenPaginationRequestParameters -- | "page_size" - Items per Page This is the number of items per page to -- return. For details on pagination please head over to the -- pagination documentation. [tokenPaginationRequestParametersPageSize] :: TokenPaginationRequestParameters -> Maybe Integer -- | "page_token" - Next Page Token The next page token. For details on -- pagination please head over to the pagination documentation. [tokenPaginationRequestParametersPageToken] :: TokenPaginationRequestParameters -> Maybe Text -- | Construct a value of type TokenPaginationRequestParameters (by -- applying it's required fields, if any) mkTokenPaginationRequestParameters :: TokenPaginationRequestParameters -- | TokenPaginationResponseHeaders Pagination Response Header -- -- The Link HTTP header contains multiple links (first, -- next, last, previous) formatted as: -- `https://{project-slug}.projects.oryapis.com/admin/clients?page_size={limit}&page_token={offset}; -- rel="{page}"` For details on pagination please head over to the -- pagination documentation. data TokenPaginationResponseHeaders TokenPaginationResponseHeaders :: Maybe Text -> Maybe Integer -> TokenPaginationResponseHeaders -- | "link" - The Link HTTP Header The `Link` header contains a -- comma-delimited list of links to the following pages: first: The first -- page of results. next: The next page of results. prev: The previous -- page of results. last: The last page of results. Pages are omitted if -- they do not exist. For example, if there is no next page, the `next` -- link is omitted. Examples: -- <clients?page_size=5&page_token=0>; -- rel="first",<clients?page_size=5&page_token=15>; -- rel="next",<clients?page_size=5&page_token=5>; -- rel="prev",<clients?page_size=5&page_token=20>; -- rel="last" [tokenPaginationResponseHeadersLink] :: TokenPaginationResponseHeaders -> Maybe Text -- | "x-total-count" - The X-Total-Count HTTP Header The `X-Total-Count` -- header contains the total number of items in the collection. [tokenPaginationResponseHeadersXTotalCount] :: TokenPaginationResponseHeaders -> Maybe Integer -- | Construct a value of type TokenPaginationResponseHeaders (by -- applying it's required fields, if any) mkTokenPaginationResponseHeaders :: TokenPaginationResponseHeaders -- | TrustOAuth2JwtGrantIssuer Trust OAuth2 JWT Bearer Grant Type Issuer -- Request Body data TrustOAuth2JwtGrantIssuer TrustOAuth2JwtGrantIssuer :: Maybe Bool -> DateTime -> Text -> JsonWebKey -> [Text] -> Maybe Text -> TrustOAuth2JwtGrantIssuer -- | "allow_any_subject" - The "allow_any_subject" -- indicates that the issuer is allowed to have any principal as the -- subject of the JWT. [trustOAuth2JwtGrantIssuerAllowAnySubject] :: TrustOAuth2JwtGrantIssuer -> Maybe Bool -- | Required "expires_at" - The "expires_at" -- indicates, when grant will expire, so we will reject assertion from -- "issuer" targeting "subject". [trustOAuth2JwtGrantIssuerExpiresAt] :: TrustOAuth2JwtGrantIssuer -> DateTime -- | Required "issuer" - The "issuer" identifies -- the principal that issued the JWT assertion (same as -- "iss" claim in JWT). [trustOAuth2JwtGrantIssuerIssuer] :: TrustOAuth2JwtGrantIssuer -> Text -- | Required "jwk" [trustOAuth2JwtGrantIssuerJwk] :: TrustOAuth2JwtGrantIssuer -> JsonWebKey -- | Required "scope" - The "scope" contains list -- of scope values (as described in Section 3.3 of OAuth 2.0 [RFC6749]) [trustOAuth2JwtGrantIssuerScope] :: TrustOAuth2JwtGrantIssuer -> [Text] -- | "subject" - The "subject" identifies the principal -- that is the subject of the JWT. [trustOAuth2JwtGrantIssuerSubject] :: TrustOAuth2JwtGrantIssuer -> Maybe Text -- | Construct a value of type TrustOAuth2JwtGrantIssuer (by -- applying it's required fields, if any) mkTrustOAuth2JwtGrantIssuer :: DateTime -> Text -> JsonWebKey -> [Text] -> TrustOAuth2JwtGrantIssuer -- | TrustedOAuth2JwtGrantIssuer OAuth2 JWT Bearer Grant Type Issuer Trust -- Relationship data TrustedOAuth2JwtGrantIssuer TrustedOAuth2JwtGrantIssuer :: Maybe Bool -> Maybe DateTime -> Maybe DateTime -> Maybe Text -> Maybe Text -> Maybe TrustedOAuth2JwtGrantJsonWebKey -> Maybe [Text] -> Maybe Text -> TrustedOAuth2JwtGrantIssuer -- | "allow_any_subject" - The "allow_any_subject" -- indicates that the issuer is allowed to have any principal as the -- subject of the JWT. [trustedOAuth2JwtGrantIssuerAllowAnySubject] :: TrustedOAuth2JwtGrantIssuer -> Maybe Bool -- | "created_at" - The "created_at" indicates, when -- grant was created. [trustedOAuth2JwtGrantIssuerCreatedAt] :: TrustedOAuth2JwtGrantIssuer -> Maybe DateTime -- | "expires_at" - The "expires_at" indicates, when -- grant will expire, so we will reject assertion from -- "issuer" targeting "subject". [trustedOAuth2JwtGrantIssuerExpiresAt] :: TrustedOAuth2JwtGrantIssuer -> Maybe DateTime -- | "id" [trustedOAuth2JwtGrantIssuerId] :: TrustedOAuth2JwtGrantIssuer -> Maybe Text -- | "issuer" - The "issuer" identifies the principal -- that issued the JWT assertion (same as "iss" claim -- in JWT). [trustedOAuth2JwtGrantIssuerIssuer] :: TrustedOAuth2JwtGrantIssuer -> Maybe Text -- | "public_key" [trustedOAuth2JwtGrantIssuerPublicKey] :: TrustedOAuth2JwtGrantIssuer -> Maybe TrustedOAuth2JwtGrantJsonWebKey -- | "scope" - The "scope" contains list of scope values -- (as described in Section 3.3 of OAuth 2.0 [RFC6749]) [trustedOAuth2JwtGrantIssuerScope] :: TrustedOAuth2JwtGrantIssuer -> Maybe [Text] -- | "subject" - The "subject" identifies the principal -- that is the subject of the JWT. [trustedOAuth2JwtGrantIssuerSubject] :: TrustedOAuth2JwtGrantIssuer -> Maybe Text -- | Construct a value of type TrustedOAuth2JwtGrantIssuer (by -- applying it's required fields, if any) mkTrustedOAuth2JwtGrantIssuer :: TrustedOAuth2JwtGrantIssuer -- | TrustedOAuth2JwtGrantJsonWebKey OAuth2 JWT Bearer Grant Type Issuer -- Trusted JSON Web Key data TrustedOAuth2JwtGrantJsonWebKey TrustedOAuth2JwtGrantJsonWebKey :: Maybe Text -> Maybe Text -> TrustedOAuth2JwtGrantJsonWebKey -- | "kid" - The "key_id" is key unique identifier (same -- as kid header in jws/jwt). [trustedOAuth2JwtGrantJsonWebKeyKid] :: TrustedOAuth2JwtGrantJsonWebKey -> Maybe Text -- | "set" - The "set" is basically a name for a -- group(set) of keys. Will be the same as "issuer" in -- grant. [trustedOAuth2JwtGrantJsonWebKeySet] :: TrustedOAuth2JwtGrantJsonWebKey -> Maybe Text -- | Construct a value of type TrustedOAuth2JwtGrantJsonWebKey (by -- applying it's required fields, if any) mkTrustedOAuth2JwtGrantJsonWebKey :: TrustedOAuth2JwtGrantJsonWebKey -- | Version data Version Version :: Maybe Text -> Version -- | "version" - Version is the service's version. [versionVersion] :: Version -> Maybe Text -- | Construct a value of type Version (by applying it's required -- fields, if any) mkVersion :: Version data AuthBasicBasic -- | username password AuthBasicBasic :: ByteString -> ByteString -> AuthBasicBasic data AuthBasicBearer -- | username password AuthBasicBearer :: ByteString -> ByteString -> AuthBasicBearer data AuthOAuthOauth2 -- | secret AuthOAuthOauth2 :: Text -> AuthOAuthOauth2 instance GHC.Show.Show ORYHydra.Model.All instance GHC.Classes.Eq ORYHydra.Model.All instance GHC.Show.Show ORYHydra.Model.Client instance GHC.Classes.Eq ORYHydra.Model.Client instance GHC.Show.Show ORYHydra.Model.ClientId instance GHC.Classes.Eq ORYHydra.Model.ClientId instance GHC.Show.Show ORYHydra.Model.ClientName instance GHC.Classes.Eq ORYHydra.Model.ClientName instance GHC.Show.Show ORYHydra.Model.ClientSecret instance GHC.Classes.Eq ORYHydra.Model.ClientSecret instance GHC.Show.Show ORYHydra.Model.Code instance GHC.Classes.Eq ORYHydra.Model.Code instance GHC.Show.Show ORYHydra.Model.ConsentChallenge instance GHC.Classes.Eq ORYHydra.Model.ConsentChallenge instance GHC.Show.Show ORYHydra.Model.DefaultItems instance GHC.Classes.Eq ORYHydra.Model.DefaultItems instance GHC.Show.Show ORYHydra.Model.GrantType instance GHC.Classes.Eq ORYHydra.Model.GrantType instance GHC.Show.Show ORYHydra.Model.Id instance GHC.Classes.Eq ORYHydra.Model.Id instance GHC.Show.Show ORYHydra.Model.Issuer instance GHC.Classes.Eq ORYHydra.Model.Issuer instance GHC.Show.Show ORYHydra.Model.Kid instance GHC.Classes.Eq ORYHydra.Model.Kid instance GHC.Show.Show ORYHydra.Model.LoginChallenge instance GHC.Classes.Eq ORYHydra.Model.LoginChallenge instance GHC.Show.Show ORYHydra.Model.LoginSessionId instance GHC.Classes.Eq ORYHydra.Model.LoginSessionId instance GHC.Show.Show ORYHydra.Model.LogoutChallenge instance GHC.Classes.Eq ORYHydra.Model.LogoutChallenge instance GHC.Show.Show ORYHydra.Model.MaxItems instance GHC.Classes.Eq ORYHydra.Model.MaxItems instance GHC.Show.Show ORYHydra.Model.Owner instance GHC.Classes.Eq ORYHydra.Model.Owner instance GHC.Show.Show ORYHydra.Model.PageSize instance GHC.Classes.Eq ORYHydra.Model.PageSize instance GHC.Show.Show ORYHydra.Model.PageToken instance GHC.Classes.Eq ORYHydra.Model.PageToken instance GHC.Show.Show ORYHydra.Model.RedirectUri instance GHC.Classes.Eq ORYHydra.Model.RedirectUri instance GHC.Show.Show ORYHydra.Model.RefreshToken instance GHC.Classes.Eq ORYHydra.Model.RefreshToken instance GHC.Show.Show ORYHydra.Model.Scope instance GHC.Classes.Eq ORYHydra.Model.Scope instance GHC.Show.Show ORYHydra.Model.Set instance GHC.Classes.Eq ORYHydra.Model.Set instance GHC.Show.Show ORYHydra.Model.Sid instance GHC.Classes.Eq ORYHydra.Model.Sid instance GHC.Show.Show ORYHydra.Model.Subject instance GHC.Classes.Eq ORYHydra.Model.Subject instance GHC.Show.Show ORYHydra.Model.Token instance GHC.Classes.Eq ORYHydra.Model.Token instance GHC.Classes.Eq ORYHydra.Model.AcceptOAuth2ConsentRequestSession instance GHC.Show.Show ORYHydra.Model.AcceptOAuth2ConsentRequestSession instance GHC.Classes.Eq ORYHydra.Model.AcceptOAuth2ConsentRequest instance GHC.Show.Show ORYHydra.Model.AcceptOAuth2ConsentRequest instance GHC.Classes.Eq ORYHydra.Model.AcceptOAuth2LoginRequest instance GHC.Show.Show ORYHydra.Model.AcceptOAuth2LoginRequest instance GHC.Classes.Eq ORYHydra.Model.CreateJsonWebKeySet instance GHC.Show.Show ORYHydra.Model.CreateJsonWebKeySet instance GHC.Classes.Eq ORYHydra.Model.ErrorOAuth2 instance GHC.Show.Show ORYHydra.Model.ErrorOAuth2 instance GHC.Classes.Eq ORYHydra.Model.GenericError instance GHC.Show.Show ORYHydra.Model.GenericError instance GHC.Classes.Eq ORYHydra.Model.GetVersion200Response instance GHC.Show.Show ORYHydra.Model.GetVersion200Response instance GHC.Classes.Eq ORYHydra.Model.HealthNotReadyStatus instance GHC.Show.Show ORYHydra.Model.HealthNotReadyStatus instance GHC.Classes.Eq ORYHydra.Model.HealthStatus instance GHC.Show.Show ORYHydra.Model.HealthStatus instance GHC.Classes.Eq ORYHydra.Model.IntrospectedOAuth2Token instance GHC.Show.Show ORYHydra.Model.IntrospectedOAuth2Token instance GHC.Classes.Eq ORYHydra.Model.IsReady200Response instance GHC.Show.Show ORYHydra.Model.IsReady200Response instance GHC.Classes.Eq ORYHydra.Model.IsReady503Response instance GHC.Show.Show ORYHydra.Model.IsReady503Response instance GHC.Classes.Eq ORYHydra.Model.JsonPatch instance GHC.Show.Show ORYHydra.Model.JsonPatch instance Data.Aeson.Types.ToJSON.ToJSON ORYHydra.Model.JsonPatch2 instance GHC.Show.Show ORYHydra.Model.JsonPatch2 instance GHC.Classes.Eq ORYHydra.Model.JsonPatch2 instance GHC.Classes.Eq ORYHydra.Model.JsonWebKey instance GHC.Show.Show ORYHydra.Model.JsonWebKey instance GHC.Classes.Eq ORYHydra.Model.JsonWebKeySet instance GHC.Show.Show ORYHydra.Model.JsonWebKeySet instance GHC.Classes.Eq ORYHydra.Model.OAuth2Client instance GHC.Show.Show ORYHydra.Model.OAuth2Client instance GHC.Classes.Eq ORYHydra.Model.OAuth2ClientTokenLifespans instance GHC.Show.Show ORYHydra.Model.OAuth2ClientTokenLifespans instance GHC.Classes.Eq ORYHydra.Model.OAuth2ConsentRequestOpenIDConnectContext instance GHC.Show.Show ORYHydra.Model.OAuth2ConsentRequestOpenIDConnectContext instance GHC.Classes.Eq ORYHydra.Model.OAuth2ConsentRequest instance GHC.Show.Show ORYHydra.Model.OAuth2ConsentRequest instance GHC.Classes.Eq ORYHydra.Model.OAuth2ConsentSessionExpiresAt instance GHC.Show.Show ORYHydra.Model.OAuth2ConsentSessionExpiresAt instance GHC.Classes.Eq ORYHydra.Model.OAuth2ConsentSession instance GHC.Show.Show ORYHydra.Model.OAuth2ConsentSession instance GHC.Classes.Eq ORYHydra.Model.OAuth2LoginRequest instance GHC.Show.Show ORYHydra.Model.OAuth2LoginRequest instance GHC.Classes.Eq ORYHydra.Model.OAuth2LogoutRequest instance GHC.Show.Show ORYHydra.Model.OAuth2LogoutRequest instance GHC.Classes.Eq ORYHydra.Model.OAuth2RedirectTo instance GHC.Show.Show ORYHydra.Model.OAuth2RedirectTo instance GHC.Classes.Eq ORYHydra.Model.OAuth2TokenExchange instance GHC.Show.Show ORYHydra.Model.OAuth2TokenExchange instance GHC.Classes.Eq ORYHydra.Model.OidcConfiguration instance GHC.Show.Show ORYHydra.Model.OidcConfiguration instance GHC.Classes.Eq ORYHydra.Model.OidcUserInfo instance GHC.Show.Show ORYHydra.Model.OidcUserInfo instance GHC.Classes.Eq ORYHydra.Model.Pagination instance GHC.Show.Show ORYHydra.Model.Pagination instance GHC.Classes.Eq ORYHydra.Model.PaginationHeaders instance GHC.Show.Show ORYHydra.Model.PaginationHeaders instance GHC.Classes.Eq ORYHydra.Model.RejectOAuth2Request instance GHC.Show.Show ORYHydra.Model.RejectOAuth2Request instance GHC.Classes.Eq ORYHydra.Model.TokenPagination instance GHC.Show.Show ORYHydra.Model.TokenPagination instance GHC.Classes.Eq ORYHydra.Model.TokenPaginationHeaders instance GHC.Show.Show ORYHydra.Model.TokenPaginationHeaders instance GHC.Classes.Eq ORYHydra.Model.TokenPaginationRequestParameters instance GHC.Show.Show ORYHydra.Model.TokenPaginationRequestParameters instance GHC.Classes.Eq ORYHydra.Model.TokenPaginationResponseHeaders instance GHC.Show.Show ORYHydra.Model.TokenPaginationResponseHeaders instance GHC.Classes.Eq ORYHydra.Model.TrustOAuth2JwtGrantIssuer instance GHC.Show.Show ORYHydra.Model.TrustOAuth2JwtGrantIssuer instance GHC.Classes.Eq ORYHydra.Model.TrustedOAuth2JwtGrantJsonWebKey instance GHC.Show.Show ORYHydra.Model.TrustedOAuth2JwtGrantJsonWebKey instance GHC.Classes.Eq ORYHydra.Model.TrustedOAuth2JwtGrantIssuer instance GHC.Show.Show ORYHydra.Model.TrustedOAuth2JwtGrantIssuer instance GHC.Classes.Eq ORYHydra.Model.Version instance GHC.Show.Show ORYHydra.Model.Version instance GHC.Show.Show ORYHydra.Model.AuthBasicBasic instance GHC.Classes.Eq ORYHydra.Model.AuthBasicBasic instance GHC.Show.Show ORYHydra.Model.AuthBasicBearer instance GHC.Classes.Eq ORYHydra.Model.AuthBasicBearer instance GHC.Show.Show ORYHydra.Model.AuthOAuthOauth2 instance GHC.Classes.Eq ORYHydra.Model.AuthOAuthOauth2 instance ORYHydra.Core.AuthMethod ORYHydra.Model.AuthOAuthOauth2 instance ORYHydra.Core.AuthMethod ORYHydra.Model.AuthBasicBearer instance ORYHydra.Core.AuthMethod ORYHydra.Model.AuthBasicBasic instance Data.Aeson.Types.FromJSON.FromJSON ORYHydra.Model.Version instance Data.Aeson.Types.ToJSON.ToJSON ORYHydra.Model.Version instance Data.Aeson.Types.FromJSON.FromJSON ORYHydra.Model.TrustedOAuth2JwtGrantIssuer instance Data.Aeson.Types.ToJSON.ToJSON ORYHydra.Model.TrustedOAuth2JwtGrantIssuer instance Data.Aeson.Types.FromJSON.FromJSON ORYHydra.Model.TrustedOAuth2JwtGrantJsonWebKey instance Data.Aeson.Types.ToJSON.ToJSON ORYHydra.Model.TrustedOAuth2JwtGrantJsonWebKey instance Data.Aeson.Types.FromJSON.FromJSON ORYHydra.Model.TrustOAuth2JwtGrantIssuer instance Data.Aeson.Types.ToJSON.ToJSON ORYHydra.Model.TrustOAuth2JwtGrantIssuer instance Data.Aeson.Types.FromJSON.FromJSON ORYHydra.Model.TokenPaginationResponseHeaders instance Data.Aeson.Types.ToJSON.ToJSON ORYHydra.Model.TokenPaginationResponseHeaders instance Data.Aeson.Types.FromJSON.FromJSON ORYHydra.Model.TokenPaginationRequestParameters instance Data.Aeson.Types.ToJSON.ToJSON ORYHydra.Model.TokenPaginationRequestParameters instance Data.Aeson.Types.FromJSON.FromJSON ORYHydra.Model.TokenPaginationHeaders instance Data.Aeson.Types.ToJSON.ToJSON ORYHydra.Model.TokenPaginationHeaders instance Data.Aeson.Types.FromJSON.FromJSON ORYHydra.Model.TokenPagination instance Data.Aeson.Types.ToJSON.ToJSON ORYHydra.Model.TokenPagination instance Data.Aeson.Types.FromJSON.FromJSON ORYHydra.Model.RejectOAuth2Request instance Data.Aeson.Types.ToJSON.ToJSON ORYHydra.Model.RejectOAuth2Request instance Data.Aeson.Types.FromJSON.FromJSON ORYHydra.Model.PaginationHeaders instance Data.Aeson.Types.ToJSON.ToJSON ORYHydra.Model.PaginationHeaders instance Data.Aeson.Types.FromJSON.FromJSON ORYHydra.Model.Pagination instance Data.Aeson.Types.ToJSON.ToJSON ORYHydra.Model.Pagination instance Data.Aeson.Types.FromJSON.FromJSON ORYHydra.Model.OidcUserInfo instance Data.Aeson.Types.ToJSON.ToJSON ORYHydra.Model.OidcUserInfo instance Data.Aeson.Types.FromJSON.FromJSON ORYHydra.Model.OidcConfiguration instance Data.Aeson.Types.ToJSON.ToJSON ORYHydra.Model.OidcConfiguration instance Data.Aeson.Types.FromJSON.FromJSON ORYHydra.Model.OAuth2TokenExchange instance Data.Aeson.Types.ToJSON.ToJSON ORYHydra.Model.OAuth2TokenExchange instance Data.Aeson.Types.FromJSON.FromJSON ORYHydra.Model.OAuth2RedirectTo instance Data.Aeson.Types.ToJSON.ToJSON ORYHydra.Model.OAuth2RedirectTo instance Data.Aeson.Types.FromJSON.FromJSON ORYHydra.Model.OAuth2LogoutRequest instance Data.Aeson.Types.ToJSON.ToJSON ORYHydra.Model.OAuth2LogoutRequest instance Data.Aeson.Types.FromJSON.FromJSON ORYHydra.Model.OAuth2LoginRequest instance Data.Aeson.Types.ToJSON.ToJSON ORYHydra.Model.OAuth2LoginRequest instance Data.Aeson.Types.FromJSON.FromJSON ORYHydra.Model.OAuth2ConsentSession instance Data.Aeson.Types.ToJSON.ToJSON ORYHydra.Model.OAuth2ConsentSession instance Data.Aeson.Types.FromJSON.FromJSON ORYHydra.Model.OAuth2ConsentSessionExpiresAt instance Data.Aeson.Types.ToJSON.ToJSON ORYHydra.Model.OAuth2ConsentSessionExpiresAt instance Data.Aeson.Types.FromJSON.FromJSON ORYHydra.Model.OAuth2ConsentRequest instance Data.Aeson.Types.ToJSON.ToJSON ORYHydra.Model.OAuth2ConsentRequest instance Data.Aeson.Types.FromJSON.FromJSON ORYHydra.Model.OAuth2ConsentRequestOpenIDConnectContext instance Data.Aeson.Types.ToJSON.ToJSON ORYHydra.Model.OAuth2ConsentRequestOpenIDConnectContext instance Data.Aeson.Types.FromJSON.FromJSON ORYHydra.Model.OAuth2ClientTokenLifespans instance Data.Aeson.Types.ToJSON.ToJSON ORYHydra.Model.OAuth2ClientTokenLifespans instance Data.Aeson.Types.FromJSON.FromJSON ORYHydra.Model.OAuth2Client instance Data.Aeson.Types.ToJSON.ToJSON ORYHydra.Model.OAuth2Client instance Data.Aeson.Types.FromJSON.FromJSON ORYHydra.Model.JsonWebKeySet instance Data.Aeson.Types.ToJSON.ToJSON ORYHydra.Model.JsonWebKeySet instance Data.Aeson.Types.FromJSON.FromJSON ORYHydra.Model.JsonWebKey instance Data.Aeson.Types.ToJSON.ToJSON ORYHydra.Model.JsonWebKey instance Data.Aeson.Types.FromJSON.FromJSON ORYHydra.Model.JsonPatch instance Data.Aeson.Types.ToJSON.ToJSON ORYHydra.Model.JsonPatch instance Data.Aeson.Types.FromJSON.FromJSON ORYHydra.Model.IsReady503Response instance Data.Aeson.Types.ToJSON.ToJSON ORYHydra.Model.IsReady503Response instance Data.Aeson.Types.FromJSON.FromJSON ORYHydra.Model.IsReady200Response instance Data.Aeson.Types.ToJSON.ToJSON ORYHydra.Model.IsReady200Response instance Data.Aeson.Types.FromJSON.FromJSON ORYHydra.Model.IntrospectedOAuth2Token instance Data.Aeson.Types.ToJSON.ToJSON ORYHydra.Model.IntrospectedOAuth2Token instance Data.Aeson.Types.FromJSON.FromJSON ORYHydra.Model.HealthStatus instance Data.Aeson.Types.ToJSON.ToJSON ORYHydra.Model.HealthStatus instance Data.Aeson.Types.FromJSON.FromJSON ORYHydra.Model.HealthNotReadyStatus instance Data.Aeson.Types.ToJSON.ToJSON ORYHydra.Model.HealthNotReadyStatus instance Data.Aeson.Types.FromJSON.FromJSON ORYHydra.Model.GetVersion200Response instance Data.Aeson.Types.ToJSON.ToJSON ORYHydra.Model.GetVersion200Response instance Data.Aeson.Types.FromJSON.FromJSON ORYHydra.Model.GenericError instance Data.Aeson.Types.ToJSON.ToJSON ORYHydra.Model.GenericError instance Data.Aeson.Types.FromJSON.FromJSON ORYHydra.Model.ErrorOAuth2 instance Data.Aeson.Types.ToJSON.ToJSON ORYHydra.Model.ErrorOAuth2 instance Data.Aeson.Types.FromJSON.FromJSON ORYHydra.Model.CreateJsonWebKeySet instance Data.Aeson.Types.ToJSON.ToJSON ORYHydra.Model.CreateJsonWebKeySet instance Data.Aeson.Types.FromJSON.FromJSON ORYHydra.Model.AcceptOAuth2LoginRequest instance Data.Aeson.Types.ToJSON.ToJSON ORYHydra.Model.AcceptOAuth2LoginRequest instance Data.Aeson.Types.FromJSON.FromJSON ORYHydra.Model.AcceptOAuth2ConsentRequest instance Data.Aeson.Types.ToJSON.ToJSON ORYHydra.Model.AcceptOAuth2ConsentRequest instance Data.Aeson.Types.FromJSON.FromJSON ORYHydra.Model.AcceptOAuth2ConsentRequestSession instance Data.Aeson.Types.ToJSON.ToJSON ORYHydra.Model.AcceptOAuth2ConsentRequestSession module ORYHydra.API.Wellknown -- |
-- GET /.well-known/jwks.json ---- -- Discover Well-Known JSON Web Keys -- -- This endpoint returns JSON Web Keys required to verifying OpenID -- Connect ID Tokens and, if enabled, OAuth 2.0 JWT Access Tokens. This -- endpoint can be used with client libraries like node-jwks-rsa -- among others. discoverJsonWebKeys :: ORYHydraRequest DiscoverJsonWebKeys MimeNoContent JsonWebKeySet MimeJSON data DiscoverJsonWebKeys instance ORYHydra.MimeTypes.Produces ORYHydra.API.Wellknown.DiscoverJsonWebKeys ORYHydra.MimeTypes.MimeJSON module ORYHydra.API.Oidc -- |
-- POST /oauth2/register ---- -- Register OAuth2 Client using OpenID Dynamic Client Registration -- -- This endpoint behaves like the administrative counterpart -- (createOAuth2Client) but is capable of facing the public -- internet directly and can be used in self-service. It implements the -- OpenID Connect Dynamic Client Registration Protocol. This feature -- needs to be enabled in the configuration. This endpoint is disabled by -- default. It can be enabled by an administrator. Please note that using -- this endpoint you are not able to choose the client_secret -- nor the client_id as those values will be server generated -- when specifying token_endpoint_auth_method as -- client_secret_basic or client_secret_post. The -- client_secret will be returned in the response and you will -- not be able to retrieve it later on. Write the secret down and keep it -- somewhere safe. createOidcDynamicClient :: (Consumes CreateOidcDynamicClient MimeJSON, MimeRender MimeJSON OAuth2Client) => OAuth2Client -> ORYHydraRequest CreateOidcDynamicClient MimeJSON OAuth2Client MimeJSON data CreateOidcDynamicClient -- |
-- DELETE /oauth2/register/{id}
--
--
-- Delete OAuth 2.0 Client using the OpenID Dynamic Client Registration
-- Management Protocol
--
-- This endpoint behaves like the administrative counterpart
-- (deleteOAuth2Client) but is capable of facing the public
-- internet directly and can be used in self-service. It implements the
-- OpenID Connect Dynamic Client Registration Protocol. This feature
-- needs to be enabled in the configuration. This endpoint is disabled by
-- default. It can be enabled by an administrator. To use this endpoint,
-- you will need to present the client's authentication credentials. If
-- the OAuth2 Client uses the Token Endpoint Authentication Method
-- client_secret_post, you need to present the client secret in
-- the URL query. If it uses client_secret_basic, present the
-- Client ID and the Client Secret in the Authorization header. OAuth 2.0
-- clients are used to perform OAuth 2.0 and OpenID Connect flows.
-- Usually, OAuth 2.0 clients are generated for applications which want
-- to consume your OAuth 2.0 or OpenID Connect capabilities.
--
-- AuthMethod: AuthBasicBearer
deleteOidcDynamicClient :: Id -> ORYHydraRequest DeleteOidcDynamicClient MimeNoContent NoContent MimeNoContent
data DeleteOidcDynamicClient
-- | -- GET /.well-known/openid-configuration ---- -- OpenID Connect Discovery -- -- A mechanism for an OpenID Connect Relying Party to discover the -- End-User's OpenID Provider and obtain information needed to interact -- with it, including its OAuth 2.0 endpoint locations. Popular libraries -- for OpenID Connect clients include oidc-client-js (JavaScript), -- go-oidc (Golang), and others. For a full list of clients go here: -- https://openid.net/developers/certified/ discoverOidcConfiguration :: ORYHydraRequest DiscoverOidcConfiguration MimeNoContent OidcConfiguration MimeJSON data DiscoverOidcConfiguration -- |
-- GET /oauth2/register/{id}
--
--
-- Get OAuth2 Client using OpenID Dynamic Client Registration
--
-- This endpoint behaves like the administrative counterpart
-- (getOAuth2Client) but is capable of facing the public
-- internet directly and can be used in self-service. It implements the
-- OpenID Connect Dynamic Client Registration Protocol. To use this
-- endpoint, you will need to present the client's authentication
-- credentials. If the OAuth2 Client uses the Token Endpoint
-- Authentication Method client_secret_post, you need to present
-- the client secret in the URL query. If it uses
-- client_secret_basic, present the Client ID and the Client
-- Secret in the Authorization header.
--
-- AuthMethod: AuthBasicBearer
getOidcDynamicClient :: Id -> ORYHydraRequest GetOidcDynamicClient MimeNoContent OAuth2Client MimeJSON
data GetOidcDynamicClient
-- | -- GET /userinfo ---- -- OpenID Connect Userinfo -- -- This endpoint returns the payload of the ID Token, including -- `session.id_token` values, of the provided OAuth 2.0 Access Token's -- consent request. In the case of authentication error, a -- WWW-Authenticate header might be set in the response with more -- information about the error. See the spec for more details -- about header format. -- -- AuthMethod: AuthOAuthOauth2 getOidcUserInfo :: ORYHydraRequest GetOidcUserInfo MimeNoContent OidcUserInfo MimeJSON data GetOidcUserInfo -- |
-- GET /oauth2/sessions/logout ---- -- OpenID Connect Front- and Back-channel Enabled Logout -- -- This endpoint initiates and completes user logout at the Ory OAuth2 -- & OpenID provider and initiates OpenID Connect Front- -- Back-channel logout: -- https:openid.netspecsopenid-connect-frontchannel-1_0.html -- https:openid.netspecs/openid-connect-backchannel-1_0.html -- Back-channel logout is performed asynchronously and does not affect -- logout flow. revokeOidcSession :: ORYHydraRequest RevokeOidcSession MimeNoContent NoContent MimeNoContent data RevokeOidcSession -- |
-- PUT /oauth2/register/{id}
--
--
-- Set OAuth2 Client using OpenID Dynamic Client Registration
--
-- This endpoint behaves like the administrative counterpart
-- (setOAuth2Client) but is capable of facing the public
-- internet directly to be used by third parties. It implements the
-- OpenID Connect Dynamic Client Registration Protocol. This feature is
-- disabled per default. It can be enabled by a system administrator. If
-- you pass client_secret the secret is used, otherwise the
-- existing secret is used. If set, the secret is echoed in the response.
-- It is not possible to retrieve it later on. To use this endpoint, you
-- will need to present the client's authentication credentials. If the
-- OAuth2 Client uses the Token Endpoint Authentication Method
-- client_secret_post, you need to present the client secret in
-- the URL query. If it uses client_secret_basic, present the
-- Client ID and the Client Secret in the Authorization header. OAuth 2.0
-- clients are used to perform OAuth 2.0 and OpenID Connect flows.
-- Usually, OAuth 2.0 clients are generated for applications which want
-- to consume your OAuth 2.0 or OpenID Connect capabilities.
--
-- AuthMethod: AuthBasicBearer
setOidcDynamicClient :: (Consumes SetOidcDynamicClient MimeJSON, MimeRender MimeJSON OAuth2Client) => OAuth2Client -> Id -> ORYHydraRequest SetOidcDynamicClient MimeJSON OAuth2Client MimeJSON
data SetOidcDynamicClient
instance ORYHydra.Core.HasBodyParam ORYHydra.API.Oidc.SetOidcDynamicClient ORYHydra.Model.OAuth2Client
instance ORYHydra.MimeTypes.Consumes ORYHydra.API.Oidc.SetOidcDynamicClient ORYHydra.MimeTypes.MimeJSON
instance ORYHydra.MimeTypes.Produces ORYHydra.API.Oidc.SetOidcDynamicClient ORYHydra.MimeTypes.MimeJSON
instance ORYHydra.MimeTypes.Produces ORYHydra.API.Oidc.RevokeOidcSession ORYHydra.MimeTypes.MimeNoContent
instance ORYHydra.MimeTypes.Produces ORYHydra.API.Oidc.GetOidcUserInfo ORYHydra.MimeTypes.MimeJSON
instance ORYHydra.MimeTypes.Produces ORYHydra.API.Oidc.GetOidcDynamicClient ORYHydra.MimeTypes.MimeJSON
instance ORYHydra.MimeTypes.Produces ORYHydra.API.Oidc.DiscoverOidcConfiguration ORYHydra.MimeTypes.MimeJSON
instance ORYHydra.MimeTypes.Produces ORYHydra.API.Oidc.DeleteOidcDynamicClient ORYHydra.MimeTypes.MimeNoContent
instance ORYHydra.Core.HasBodyParam ORYHydra.API.Oidc.CreateOidcDynamicClient ORYHydra.Model.OAuth2Client
instance ORYHydra.MimeTypes.Consumes ORYHydra.API.Oidc.CreateOidcDynamicClient ORYHydra.MimeTypes.MimeJSON
instance ORYHydra.MimeTypes.Produces ORYHydra.API.Oidc.CreateOidcDynamicClient ORYHydra.MimeTypes.MimeJSON
module ORYHydra.API.OAuth2
-- | -- PUT /admin/oauth2/auth/requests/consent/accept ---- -- Accept OAuth 2.0 Consent Request -- -- When an authorization code, hybrid, or implicit OAuth 2.0 Flow is -- initiated, Ory asks the login provider to authenticate the subject and -- then tell Ory now about it. If the subject authenticated, heshe -- must now be asked if the OAuth 2.0 Client which initiated the flow -- should be allowed to access the resources on the subject's behalf. The -- consent challenge is appended to the consent provider's URL to which -- the subject's user-agent (browser) is redirected to. The consent -- provider uses that challenge to fetch information on the OAuth2 -- request and then tells Ory if the subject accepted or rejected the -- request. This endpoint tells Ory that the subject has authorized the -- OAuth 2.0 client to access resources on hisher behalf. The consent -- provider includes additional information, such as session data for -- access and ID tokens, and if the consent request should be used as -- basis for future requests. The response contains a redirect URL which -- the consent provider should redirect the user-agent to. The default -- consent provider is available via the Ory Managed Account Experience. -- To customize the consent provider, please head over to the OAuth 2.0 -- documentation. acceptOAuth2ConsentRequest0 :: Consumes AcceptOAuth2ConsentRequest0 MimeJSON => ConsentChallenge -> ORYHydraRequest AcceptOAuth2ConsentRequest0 MimeJSON OAuth2RedirectTo MimeJSON data AcceptOAuth2ConsentRequest0 -- |
-- PUT /admin/oauth2/auth/requests/login/accept ---- -- Accept OAuth 2.0 Login Request -- -- When an authorization code, hybrid, or implicit OAuth 2.0 Flow is -- initiated, Ory asks the login provider to authenticate the subject and -- then tell the Ory OAuth2 Service about it. The authentication -- challenge is appended to the login provider URL to which the subject's -- user-agent (browser) is redirected to. The login provider uses that -- challenge to fetch information on the OAuth2 request and then accept -- or reject the requested authentication process. This endpoint tells -- Ory that the subject has successfully authenticated and includes -- additional information such as the subject's ID and if Ory should -- remember the subject's subject agent for future authentication -- attempts by setting a cookie. The response contains a redirect URL -- which the login provider should redirect the user-agent to. acceptOAuth2LoginRequest0 :: Consumes AcceptOAuth2LoginRequest0 MimeJSON => LoginChallenge -> ORYHydraRequest AcceptOAuth2LoginRequest0 MimeJSON OAuth2RedirectTo MimeJSON data AcceptOAuth2LoginRequest0 -- |
-- PUT /admin/oauth2/auth/requests/logout/accept ---- -- Accept OAuth 2.0 Session Logout Request -- -- When a user or an application requests Ory OAuth 2.0 to remove the -- session state of a subject, this endpoint is used to confirm that -- logout request. The response contains a redirect URL which the consent -- provider should redirect the user-agent to. acceptOAuth2LogoutRequest :: LogoutChallenge -> ORYHydraRequest AcceptOAuth2LogoutRequest MimeNoContent OAuth2RedirectTo MimeJSON data AcceptOAuth2LogoutRequest -- |
-- POST /admin/clients ---- -- Create OAuth 2.0 Client -- -- Create a new OAuth 2.0 client. If you pass client_secret the -- secret is used, otherwise a random secret is generated. The secret is -- echoed in the response. It is not possible to retrieve it later on. createOAuth2Client :: (Consumes CreateOAuth2Client MimeJSON, MimeRender MimeJSON OAuth2Client) => OAuth2Client -> ORYHydraRequest CreateOAuth2Client MimeJSON OAuth2Client MimeJSON data CreateOAuth2Client -- |
-- DELETE /admin/clients/{id}
--
--
-- Delete OAuth 2.0 Client
--
-- Delete an existing OAuth 2.0 Client by its ID. OAuth 2.0 clients are
-- used to perform OAuth 2.0 and OpenID Connect flows. Usually, OAuth 2.0
-- clients are generated for applications which want to consume your
-- OAuth 2.0 or OpenID Connect capabilities. Make sure that this endpoint
-- is well protected and only callable by first-party components.
deleteOAuth2Client :: Id -> ORYHydraRequest DeleteOAuth2Client MimeNoContent NoContent MimeNoContent
data DeleteOAuth2Client
-- | -- DELETE /admin/oauth2/tokens ---- -- Delete OAuth 2.0 Access Tokens from specific OAuth 2.0 Client -- -- This endpoint deletes OAuth2 access tokens issued to an OAuth 2.0 -- Client from the database. deleteOAuth2Token :: ClientId -> ORYHydraRequest DeleteOAuth2Token MimeNoContent NoContent MimeNoContent data DeleteOAuth2Token -- |
-- DELETE /admin/trust/grants/jwt-bearer/issuers/{id}
--
--
-- Delete Trusted OAuth2 JWT Bearer Grant Type Issuer
--
-- Use this endpoint to delete trusted JWT Bearer Grant Type Issuer. The
-- ID is the one returned when you created the trust relationship. Once
-- deleted, the associated issuer will no longer be able to perform the
-- JSON Web Token (JWT) Profile for OAuth 2.0 Client Authentication and
-- Authorization Grant.
deleteTrustedOAuth2JwtGrantIssuer :: Id -> ORYHydraRequest DeleteTrustedOAuth2JwtGrantIssuer MimeNoContent NoContent MimeNoContent
data DeleteTrustedOAuth2JwtGrantIssuer
-- |
-- GET /admin/clients/{id}
--
--
-- Get an OAuth 2.0 Client
--
-- Get an OAuth 2.0 client by its ID. This endpoint never returns the
-- client secret. OAuth 2.0 clients are used to perform OAuth 2.0 and
-- OpenID Connect flows. Usually, OAuth 2.0 clients are generated for
-- applications which want to consume your OAuth 2.0 or OpenID Connect
-- capabilities.
getOAuth2Client :: Id -> ORYHydraRequest GetOAuth2Client MimeNoContent OAuth2Client MimeJSON
data GetOAuth2Client
-- | -- GET /admin/oauth2/auth/requests/consent ---- -- Get OAuth 2.0 Consent Request -- -- When an authorization code, hybrid, or implicit OAuth 2.0 Flow is -- initiated, Ory asks the login provider to authenticate the subject and -- then tell Ory now about it. If the subject authenticated, he/she must -- now be asked if the OAuth 2.0 Client which initiated the flow should -- be allowed to access the resources on the subject's behalf. The -- consent challenge is appended to the consent provider's URL to which -- the subject's user-agent (browser) is redirected to. The consent -- provider uses that challenge to fetch information on the OAuth2 -- request and then tells Ory if the subject accepted or rejected the -- request. The default consent provider is available via the Ory Managed -- Account Experience. To customize the consent provider, please head -- over to the OAuth 2.0 documentation. getOAuth2ConsentRequest :: ConsentChallenge -> ORYHydraRequest GetOAuth2ConsentRequest MimeNoContent OAuth2ConsentRequest MimeJSON data GetOAuth2ConsentRequest -- |
-- GET /admin/oauth2/auth/requests/login ---- -- Get OAuth 2.0 Login Request -- -- When an authorization code, hybrid, or implicit OAuth 2.0 Flow is -- initiated, Ory asks the login provider to authenticate the subject and -- then tell the Ory OAuth2 Service about it. Per default, the login -- provider is Ory itself. You may use a different login provider which -- needs to be a web-app you write and host, and it must be able to -- authenticate ("show the subject a login screen") a subject (in OAuth2 -- the proper name for subject is "resource owner"). The authentication -- challenge is appended to the login provider URL to which the subject's -- user-agent (browser) is redirected to. The login provider uses that -- challenge to fetch information on the OAuth2 request and then accept -- or reject the requested authentication process. getOAuth2LoginRequest :: LoginChallenge -> ORYHydraRequest GetOAuth2LoginRequest MimeNoContent OAuth2LoginRequest MimeJSON data GetOAuth2LoginRequest -- |
-- GET /admin/oauth2/auth/requests/logout ---- -- Get OAuth 2.0 Session Logout Request -- -- Use this endpoint to fetch an Ory OAuth 2.0 logout request. getOAuth2LogoutRequest :: LogoutChallenge -> ORYHydraRequest GetOAuth2LogoutRequest MimeNoContent OAuth2LogoutRequest MimeJSON data GetOAuth2LogoutRequest -- |
-- GET /admin/trust/grants/jwt-bearer/issuers/{id}
--
--
-- Get Trusted OAuth2 JWT Bearer Grant Type Issuer
--
-- Use this endpoint to get a trusted JWT Bearer Grant Type Issuer. The
-- ID is the one returned when you created the trust relationship.
getTrustedOAuth2JwtGrantIssuer :: Id -> ORYHydraRequest GetTrustedOAuth2JwtGrantIssuer MimeNoContent TrustedOAuth2JwtGrantIssuer MimeJSON
data GetTrustedOAuth2JwtGrantIssuer
-- | -- POST /admin/oauth2/introspect ---- -- Introspect OAuth2 Access and Refresh Tokens -- -- The introspection endpoint allows to check if a token (both refresh -- and access) is active or not. An active token is neither expired nor -- revoked. If a token is active, additional information on the token -- will be included. You can set additional data for a token by setting -- `session.access_token` during the consent flow. introspectOAuth2Token :: Consumes IntrospectOAuth2Token MimeFormUrlEncoded => Token -> ORYHydraRequest IntrospectOAuth2Token MimeFormUrlEncoded IntrospectedOAuth2Token MimeJSON data IntrospectOAuth2Token -- |
-- GET /admin/clients ---- -- List OAuth 2.0 Clients -- -- This endpoint lists all clients in the database, and never returns -- client secrets. As a default it lists the first 100 clients. listOAuth2Clients :: ORYHydraRequest ListOAuth2Clients MimeNoContent [OAuth2Client] MimeJSON data ListOAuth2Clients -- |
-- GET /admin/oauth2/auth/sessions/consent ---- -- List OAuth 2.0 Consent Sessions of a Subject -- -- This endpoint lists all subject's granted consent sessions, including -- client and granted scope. If the subject is unknown or has not granted -- any consent sessions yet, the endpoint returns an empty JSON array -- with status code 200 OK. listOAuth2ConsentSessions :: Subject -> ORYHydraRequest ListOAuth2ConsentSessions MimeNoContent [OAuth2ConsentSession] MimeJSON data ListOAuth2ConsentSessions -- |
-- GET /admin/trust/grants/jwt-bearer/issuers ---- -- List Trusted OAuth2 JWT Bearer Grant Type Issuers -- -- Use this endpoint to list all trusted JWT Bearer Grant Type Issuers. listTrustedOAuth2JwtGrantIssuers :: ORYHydraRequest ListTrustedOAuth2JwtGrantIssuers MimeNoContent [TrustedOAuth2JwtGrantIssuer] MimeJSON data ListTrustedOAuth2JwtGrantIssuers -- |
-- GET /oauth2/auth ---- -- OAuth 2.0 Authorize Endpoint -- -- Use open source libraries to perform OAuth 2.0 and OpenID Connect -- available for any programming language. You can find a list of -- libraries at https://oauth.net/code/ The Ory SDK is not yet -- able to this endpoint properly. oAuth2Authorize :: ORYHydraRequest OAuth2Authorize MimeNoContent ErrorOAuth2 MimeJSON data OAuth2Authorize -- |
-- POST /oauth2/token ---- -- The OAuth 2.0 Token Endpoint -- -- Use open source libraries to perform OAuth 2.0 and OpenID Connect -- available for any programming language. You can find a list of -- libraries here https://oauth.net/code/ The Ory SDK is not yet -- able to this endpoint properly. -- -- AuthMethod: AuthBasicBasic, AuthOAuthOauth2 oauth2TokenExchange :: Consumes Oauth2TokenExchange MimeFormUrlEncoded => GrantType -> ORYHydraRequest Oauth2TokenExchange MimeFormUrlEncoded OAuth2TokenExchange MimeJSON data Oauth2TokenExchange -- |
-- PATCH /admin/clients/{id}
--
--
-- Patch OAuth 2.0 Client
--
-- Patch an existing OAuth 2.0 Client using JSON Patch. If you pass
-- client_secret the secret will be updated and returned via the
-- API. This is the only time you will be able to retrieve the client
-- secret, so write it down and keep it safe. OAuth 2.0 clients are used
-- to perform OAuth 2.0 and OpenID Connect flows. Usually, OAuth 2.0
-- clients are generated for applications which want to consume your
-- OAuth 2.0 or OpenID Connect capabilities.
patchOAuth2Client :: (Consumes PatchOAuth2Client MimeJSON, MimeRender MimeJSON JsonPatch2) => JsonPatch2 -> Id -> ORYHydraRequest PatchOAuth2Client MimeJSON OAuth2Client MimeJSON
data PatchOAuth2Client
-- | -- PUT /admin/oauth2/auth/requests/consent/reject ---- -- Reject OAuth 2.0 Consent Request -- -- When an authorization code, hybrid, or implicit OAuth 2.0 Flow is -- initiated, Ory asks the login provider to authenticate the subject and -- then tell Ory now about it. If the subject authenticated, heshe -- must now be asked if the OAuth 2.0 Client which initiated the flow -- should be allowed to access the resources on the subject's behalf. The -- consent challenge is appended to the consent provider's URL to which -- the subject's user-agent (browser) is redirected to. The consent -- provider uses that challenge to fetch information on the OAuth2 -- request and then tells Ory if the subject accepted or rejected the -- request. This endpoint tells Ory that the subject has not authorized -- the OAuth 2.0 client to access resources on hisher behalf. The -- consent provider must include a reason why the consent was not -- granted. The response contains a redirect URL which the consent -- provider should redirect the user-agent to. The default consent -- provider is available via the Ory Managed Account Experience. To -- customize the consent provider, please head over to the OAuth 2.0 -- documentation. rejectOAuth2ConsentRequest :: Consumes RejectOAuth2ConsentRequest MimeJSON => ConsentChallenge -> ORYHydraRequest RejectOAuth2ConsentRequest MimeJSON OAuth2RedirectTo MimeJSON data RejectOAuth2ConsentRequest -- |
-- PUT /admin/oauth2/auth/requests/login/reject ---- -- Reject OAuth 2.0 Login Request -- -- When an authorization code, hybrid, or implicit OAuth 2.0 Flow is -- initiated, Ory asks the login provider to authenticate the subject and -- then tell the Ory OAuth2 Service about it. The authentication -- challenge is appended to the login provider URL to which the subject's -- user-agent (browser) is redirected to. The login provider uses that -- challenge to fetch information on the OAuth2 request and then accept -- or reject the requested authentication process. This endpoint tells -- Ory that the subject has not authenticated and includes a reason why -- the authentication was denied. The response contains a redirect URL -- which the login provider should redirect the user-agent to. rejectOAuth2LoginRequest :: Consumes RejectOAuth2LoginRequest MimeJSON => LoginChallenge -> ORYHydraRequest RejectOAuth2LoginRequest MimeJSON OAuth2RedirectTo MimeJSON data RejectOAuth2LoginRequest -- |
-- PUT /admin/oauth2/auth/requests/logout/reject ---- -- Reject OAuth 2.0 Session Logout Request -- -- When a user or an application requests Ory OAuth 2.0 to remove the -- session state of a subject, this endpoint is used to deny that logout -- request. No HTTP request body is required. The response is empty as -- the logout provider has to chose what action to perform next. rejectOAuth2LogoutRequest :: LogoutChallenge -> ORYHydraRequest RejectOAuth2LogoutRequest MimeNoContent NoContent MimeNoContent data RejectOAuth2LogoutRequest -- |
-- DELETE /admin/oauth2/auth/sessions/consent ---- -- Revoke OAuth 2.0 Consent Sessions of a Subject -- -- This endpoint revokes a subject's granted consent sessions and -- invalidates all associated OAuth 2.0 Access Tokens. You may also only -- revoke sessions for a specific OAuth 2.0 Client ID. revokeOAuth2ConsentSessions :: Subject -> ORYHydraRequest RevokeOAuth2ConsentSessions MimeNoContent NoContent MimeNoContent data RevokeOAuth2ConsentSessions -- |
-- DELETE /admin/oauth2/auth/sessions/login ---- -- Revokes OAuth 2.0 Login Sessions by either a Subject or a SessionID -- -- This endpoint invalidates authentication sessions. After revoking the -- authentication session(s), the subject has to re-authenticate at the -- Ory OAuth2 Provider. This endpoint does not invalidate any tokens. If -- you send the subject in a query param, all authentication sessions -- that belong to that subject are revoked. No OpennID Connect Front- or -- Back-channel logout is performed in this case. Alternatively, you can -- send a SessionID via sid query param, in which case, only the -- session that is connected to that SessionID is revoked. OpenID Connect -- Back-channel logout is performed in this case. revokeOAuth2LoginSessions :: ORYHydraRequest RevokeOAuth2LoginSessions MimeNoContent NoContent MimeNoContent data RevokeOAuth2LoginSessions -- |
-- POST /oauth2/revoke ---- -- Revoke OAuth 2.0 Access or Refresh Token -- -- Revoking a token (both access and refresh) means that the tokens will -- be invalid. A revoked access token can no longer be used to make -- access requests, and a revoked refresh token can no longer be used to -- refresh an access token. Revoking a refresh token also invalidates the -- access token that was created with it. A token may only be revoked by -- the client the token was generated for. -- -- AuthMethod: AuthBasicBasic, AuthOAuthOauth2 revokeOAuth2Token :: Consumes RevokeOAuth2Token MimeFormUrlEncoded => Token -> ORYHydraRequest RevokeOAuth2Token MimeFormUrlEncoded NoContent MimeNoContent data RevokeOAuth2Token -- |
-- PUT /admin/clients/{id}
--
--
-- Set OAuth 2.0 Client
--
-- Replaces an existing OAuth 2.0 Client with the payload you send. If
-- you pass client_secret the secret is used, otherwise the
-- existing secret is used. If set, the secret is echoed in the response.
-- It is not possible to retrieve it later on. OAuth 2.0 Clients are used
-- to perform OAuth 2.0 and OpenID Connect flows. Usually, OAuth 2.0
-- clients are generated for applications which want to consume your
-- OAuth 2.0 or OpenID Connect capabilities.
setOAuth2Client :: (Consumes SetOAuth2Client MimeJSON, MimeRender MimeJSON OAuth2Client) => OAuth2Client -> Id -> ORYHydraRequest SetOAuth2Client MimeJSON OAuth2Client MimeJSON
data SetOAuth2Client
-- |
-- PUT /admin/clients/{id}/lifespans
--
--
-- Set OAuth2 Client Token Lifespans
--
-- Set lifespans of different token types issued for this OAuth 2.0
-- client. Does not modify other fields.
setOAuth2ClientLifespans :: Consumes SetOAuth2ClientLifespans MimeJSON => Id -> ORYHydraRequest SetOAuth2ClientLifespans MimeJSON OAuth2Client MimeJSON
data SetOAuth2ClientLifespans
-- | -- POST /admin/trust/grants/jwt-bearer/issuers ---- -- Trust OAuth2 JWT Bearer Grant Type Issuer -- -- Use this endpoint to establish a trust relationship for a JWT issuer -- to perform JSON Web Token (JWT) Profile for OAuth 2.0 Client -- Authentication and Authorization Grants RFC7523. trustOAuth2JwtGrantIssuer0 :: Consumes TrustOAuth2JwtGrantIssuer0 MimeJSON => ORYHydraRequest TrustOAuth2JwtGrantIssuer0 MimeJSON TrustedOAuth2JwtGrantIssuer MimeJSON data TrustOAuth2JwtGrantIssuer0 instance ORYHydra.Core.HasBodyParam ORYHydra.API.OAuth2.TrustOAuth2JwtGrantIssuer0 ORYHydra.Model.TrustOAuth2JwtGrantIssuer instance ORYHydra.MimeTypes.Consumes ORYHydra.API.OAuth2.TrustOAuth2JwtGrantIssuer0 ORYHydra.MimeTypes.MimeJSON instance ORYHydra.MimeTypes.Produces ORYHydra.API.OAuth2.TrustOAuth2JwtGrantIssuer0 ORYHydra.MimeTypes.MimeJSON instance ORYHydra.Core.HasBodyParam ORYHydra.API.OAuth2.SetOAuth2ClientLifespans ORYHydra.Model.OAuth2ClientTokenLifespans instance ORYHydra.MimeTypes.Consumes ORYHydra.API.OAuth2.SetOAuth2ClientLifespans ORYHydra.MimeTypes.MimeJSON instance ORYHydra.MimeTypes.Produces ORYHydra.API.OAuth2.SetOAuth2ClientLifespans ORYHydra.MimeTypes.MimeJSON instance ORYHydra.Core.HasBodyParam ORYHydra.API.OAuth2.SetOAuth2Client ORYHydra.Model.OAuth2Client instance ORYHydra.MimeTypes.Consumes ORYHydra.API.OAuth2.SetOAuth2Client ORYHydra.MimeTypes.MimeJSON instance ORYHydra.MimeTypes.Produces ORYHydra.API.OAuth2.SetOAuth2Client ORYHydra.MimeTypes.MimeJSON instance ORYHydra.Core.HasOptionalParam ORYHydra.API.OAuth2.RevokeOAuth2Token ORYHydra.Model.ClientId instance ORYHydra.Core.HasOptionalParam ORYHydra.API.OAuth2.RevokeOAuth2Token ORYHydra.Model.ClientSecret instance ORYHydra.MimeTypes.Consumes ORYHydra.API.OAuth2.RevokeOAuth2Token ORYHydra.MimeTypes.MimeFormUrlEncoded instance ORYHydra.MimeTypes.Produces ORYHydra.API.OAuth2.RevokeOAuth2Token ORYHydra.MimeTypes.MimeNoContent instance ORYHydra.Core.HasOptionalParam ORYHydra.API.OAuth2.RevokeOAuth2LoginSessions ORYHydra.Model.Subject instance ORYHydra.Core.HasOptionalParam ORYHydra.API.OAuth2.RevokeOAuth2LoginSessions ORYHydra.Model.Sid instance ORYHydra.MimeTypes.Produces ORYHydra.API.OAuth2.RevokeOAuth2LoginSessions ORYHydra.MimeTypes.MimeNoContent instance ORYHydra.Core.HasOptionalParam ORYHydra.API.OAuth2.RevokeOAuth2ConsentSessions ORYHydra.Model.Client instance ORYHydra.Core.HasOptionalParam ORYHydra.API.OAuth2.RevokeOAuth2ConsentSessions ORYHydra.Model.All instance ORYHydra.MimeTypes.Produces ORYHydra.API.OAuth2.RevokeOAuth2ConsentSessions ORYHydra.MimeTypes.MimeNoContent instance ORYHydra.MimeTypes.Produces ORYHydra.API.OAuth2.RejectOAuth2LogoutRequest ORYHydra.MimeTypes.MimeNoContent instance ORYHydra.Core.HasBodyParam ORYHydra.API.OAuth2.RejectOAuth2LoginRequest ORYHydra.Model.RejectOAuth2Request instance ORYHydra.MimeTypes.Consumes ORYHydra.API.OAuth2.RejectOAuth2LoginRequest ORYHydra.MimeTypes.MimeJSON instance ORYHydra.MimeTypes.Produces ORYHydra.API.OAuth2.RejectOAuth2LoginRequest ORYHydra.MimeTypes.MimeJSON instance ORYHydra.Core.HasBodyParam ORYHydra.API.OAuth2.RejectOAuth2ConsentRequest ORYHydra.Model.RejectOAuth2Request instance ORYHydra.MimeTypes.Consumes ORYHydra.API.OAuth2.RejectOAuth2ConsentRequest ORYHydra.MimeTypes.MimeJSON instance ORYHydra.MimeTypes.Produces ORYHydra.API.OAuth2.RejectOAuth2ConsentRequest ORYHydra.MimeTypes.MimeJSON instance ORYHydra.Core.HasBodyParam ORYHydra.API.OAuth2.PatchOAuth2Client ORYHydra.Model.JsonPatch2 instance ORYHydra.MimeTypes.Consumes ORYHydra.API.OAuth2.PatchOAuth2Client ORYHydra.MimeTypes.MimeJSON instance ORYHydra.MimeTypes.Produces ORYHydra.API.OAuth2.PatchOAuth2Client ORYHydra.MimeTypes.MimeJSON instance ORYHydra.Core.HasOptionalParam ORYHydra.API.OAuth2.Oauth2TokenExchange ORYHydra.Model.ClientId instance ORYHydra.Core.HasOptionalParam ORYHydra.API.OAuth2.Oauth2TokenExchange ORYHydra.Model.Code instance ORYHydra.Core.HasOptionalParam ORYHydra.API.OAuth2.Oauth2TokenExchange ORYHydra.Model.RedirectUri instance ORYHydra.Core.HasOptionalParam ORYHydra.API.OAuth2.Oauth2TokenExchange ORYHydra.Model.RefreshToken instance ORYHydra.MimeTypes.Consumes ORYHydra.API.OAuth2.Oauth2TokenExchange ORYHydra.MimeTypes.MimeFormUrlEncoded instance ORYHydra.MimeTypes.Produces ORYHydra.API.OAuth2.Oauth2TokenExchange ORYHydra.MimeTypes.MimeJSON instance ORYHydra.MimeTypes.Produces ORYHydra.API.OAuth2.OAuth2Authorize ORYHydra.MimeTypes.MimeJSON instance ORYHydra.Core.HasOptionalParam ORYHydra.API.OAuth2.ListTrustedOAuth2JwtGrantIssuers ORYHydra.Model.MaxItems instance ORYHydra.Core.HasOptionalParam ORYHydra.API.OAuth2.ListTrustedOAuth2JwtGrantIssuers ORYHydra.Model.DefaultItems instance ORYHydra.Core.HasOptionalParam ORYHydra.API.OAuth2.ListTrustedOAuth2JwtGrantIssuers ORYHydra.Model.Issuer instance ORYHydra.MimeTypes.Produces ORYHydra.API.OAuth2.ListTrustedOAuth2JwtGrantIssuers ORYHydra.MimeTypes.MimeJSON instance ORYHydra.Core.HasOptionalParam ORYHydra.API.OAuth2.ListOAuth2ConsentSessions ORYHydra.Model.PageSize instance ORYHydra.Core.HasOptionalParam ORYHydra.API.OAuth2.ListOAuth2ConsentSessions ORYHydra.Model.PageToken instance ORYHydra.Core.HasOptionalParam ORYHydra.API.OAuth2.ListOAuth2ConsentSessions ORYHydra.Model.LoginSessionId instance ORYHydra.MimeTypes.Produces ORYHydra.API.OAuth2.ListOAuth2ConsentSessions ORYHydra.MimeTypes.MimeJSON instance ORYHydra.Core.HasOptionalParam ORYHydra.API.OAuth2.ListOAuth2Clients ORYHydra.Model.PageSize instance ORYHydra.Core.HasOptionalParam ORYHydra.API.OAuth2.ListOAuth2Clients ORYHydra.Model.PageToken instance ORYHydra.Core.HasOptionalParam ORYHydra.API.OAuth2.ListOAuth2Clients ORYHydra.Model.ClientName instance ORYHydra.Core.HasOptionalParam ORYHydra.API.OAuth2.ListOAuth2Clients ORYHydra.Model.Owner instance ORYHydra.MimeTypes.Produces ORYHydra.API.OAuth2.ListOAuth2Clients ORYHydra.MimeTypes.MimeJSON instance ORYHydra.Core.HasOptionalParam ORYHydra.API.OAuth2.IntrospectOAuth2Token ORYHydra.Model.Scope instance ORYHydra.MimeTypes.Consumes ORYHydra.API.OAuth2.IntrospectOAuth2Token ORYHydra.MimeTypes.MimeFormUrlEncoded instance ORYHydra.MimeTypes.Produces ORYHydra.API.OAuth2.IntrospectOAuth2Token ORYHydra.MimeTypes.MimeJSON instance ORYHydra.MimeTypes.Produces ORYHydra.API.OAuth2.GetTrustedOAuth2JwtGrantIssuer ORYHydra.MimeTypes.MimeJSON instance ORYHydra.MimeTypes.Produces ORYHydra.API.OAuth2.GetOAuth2LogoutRequest ORYHydra.MimeTypes.MimeJSON instance ORYHydra.MimeTypes.Produces ORYHydra.API.OAuth2.GetOAuth2LoginRequest ORYHydra.MimeTypes.MimeJSON instance ORYHydra.MimeTypes.Produces ORYHydra.API.OAuth2.GetOAuth2ConsentRequest ORYHydra.MimeTypes.MimeJSON instance ORYHydra.MimeTypes.Produces ORYHydra.API.OAuth2.GetOAuth2Client ORYHydra.MimeTypes.MimeJSON instance ORYHydra.MimeTypes.Produces ORYHydra.API.OAuth2.DeleteTrustedOAuth2JwtGrantIssuer ORYHydra.MimeTypes.MimeNoContent instance ORYHydra.MimeTypes.Produces ORYHydra.API.OAuth2.DeleteOAuth2Token ORYHydra.MimeTypes.MimeNoContent instance ORYHydra.MimeTypes.Produces ORYHydra.API.OAuth2.DeleteOAuth2Client ORYHydra.MimeTypes.MimeNoContent instance ORYHydra.Core.HasBodyParam ORYHydra.API.OAuth2.CreateOAuth2Client ORYHydra.Model.OAuth2Client instance ORYHydra.MimeTypes.Consumes ORYHydra.API.OAuth2.CreateOAuth2Client ORYHydra.MimeTypes.MimeJSON instance ORYHydra.MimeTypes.Produces ORYHydra.API.OAuth2.CreateOAuth2Client ORYHydra.MimeTypes.MimeJSON instance ORYHydra.MimeTypes.Produces ORYHydra.API.OAuth2.AcceptOAuth2LogoutRequest ORYHydra.MimeTypes.MimeJSON instance ORYHydra.Core.HasBodyParam ORYHydra.API.OAuth2.AcceptOAuth2LoginRequest0 ORYHydra.Model.AcceptOAuth2LoginRequest instance ORYHydra.MimeTypes.Consumes ORYHydra.API.OAuth2.AcceptOAuth2LoginRequest0 ORYHydra.MimeTypes.MimeJSON instance ORYHydra.MimeTypes.Produces ORYHydra.API.OAuth2.AcceptOAuth2LoginRequest0 ORYHydra.MimeTypes.MimeJSON instance ORYHydra.Core.HasBodyParam ORYHydra.API.OAuth2.AcceptOAuth2ConsentRequest0 ORYHydra.Model.AcceptOAuth2ConsentRequest instance ORYHydra.MimeTypes.Consumes ORYHydra.API.OAuth2.AcceptOAuth2ConsentRequest0 ORYHydra.MimeTypes.MimeJSON instance ORYHydra.MimeTypes.Produces ORYHydra.API.OAuth2.AcceptOAuth2ConsentRequest0 ORYHydra.MimeTypes.MimeJSON module ORYHydra.API.Metadata -- |
-- GET /version ---- -- Return Running Software Version. -- -- This endpoint returns the version of Ory Hydra. If the service -- supports TLS Edge Termination, this endpoint does not require the -- `X-Forwarded-Proto` header to be set. Be aware that if you are running -- multiple nodes of this service, the version will never refer to the -- cluster state, only to a single instance. getVersion :: ORYHydraRequest GetVersion MimeNoContent GetVersion200Response MimeJSON data GetVersion -- |
-- GET /health/alive ---- -- Check HTTP Server Status -- -- This endpoint returns a HTTP 200 status code when Ory Hydra is -- accepting incoming HTTP requests. This status does currently not -- include checks whether the database connection is working. If the -- service supports TLS Edge Termination, this endpoint does not require -- the `X-Forwarded-Proto` header to be set. Be aware that if you are -- running multiple nodes of this service, the health status will never -- refer to the cluster state, only to a single instance. isAlive :: ORYHydraRequest IsAlive MimeNoContent HealthStatus MimeJSON data IsAlive -- |
-- GET /health/ready ---- -- Check HTTP Server and Database Status -- -- This endpoint returns a HTTP 200 status code when Ory Hydra is up -- running and the environment dependencies (e.g. the database) are -- responsive as well. If the service supports TLS Edge Termination, this -- endpoint does not require the `X-Forwarded-Proto` header to be set. Be -- aware that if you are running multiple nodes of Ory Hydra, the health -- status will never refer to the cluster state, only to a single -- instance. isReady :: ORYHydraRequest IsReady MimeNoContent IsReady200Response MimeJSON data IsReady instance ORYHydra.MimeTypes.Produces ORYHydra.API.Metadata.IsReady ORYHydra.MimeTypes.MimeJSON instance ORYHydra.MimeTypes.Produces ORYHydra.API.Metadata.IsAlive ORYHydra.MimeTypes.MimeJSON instance ORYHydra.MimeTypes.Produces ORYHydra.API.Metadata.GetVersion ORYHydra.MimeTypes.MimeJSON module ORYHydra.API.Jwk -- |
-- POST /admin/keys/{set}
--
--
-- Create JSON Web Key
--
-- This endpoint is capable of generating JSON Web Key Sets for you.
-- There a different strategies available, such as symmetric
-- cryptographic keys (HS256, HS512) and asymetric cryptographic keys
-- (RS256, ECDSA). If the specified JSON Web Key Set does not exist, it
-- will be created. A JSON Web Key (JWK) is a JavaScript Object Notation
-- (JSON) data structure that represents a cryptographic key. A JWK Set
-- is a JSON data structure that represents a set of JWKs. A JSON Web Key
-- is identified by its set and key id. ORY Hydra uses this functionality
-- to store cryptographic keys used for TLS and JSON Web Tokens (such as
-- OpenID Connect ID tokens), and allows storing user-defined keys as
-- well.
createJsonWebKeySet0 :: (Consumes CreateJsonWebKeySet0 MimeJSON, MimeRender MimeJSON CreateJsonWebKeySet) => CreateJsonWebKeySet -> Set -> ORYHydraRequest CreateJsonWebKeySet0 MimeJSON JsonWebKeySet MimeJSON
data CreateJsonWebKeySet0
-- |
-- DELETE /admin/keys/{set}/{kid}
--
--
-- Delete JSON Web Key
--
-- Use this endpoint to delete a single JSON Web Key. A JSON Web Key
-- (JWK) is a JavaScript Object Notation (JSON) data structure that
-- represents a cryptographic key. A JWK Set is a JSON data structure
-- that represents a set of JWKs. A JSON Web Key is identified by its set
-- and key id. ORY Hydra uses this functionality to store cryptographic
-- keys used for TLS and JSON Web Tokens (such as OpenID Connect ID
-- tokens), and allows storing user-defined keys as well.
deleteJsonWebKey :: Set -> Kid -> ORYHydraRequest DeleteJsonWebKey MimeNoContent NoContent MimeNoContent
data DeleteJsonWebKey
-- |
-- DELETE /admin/keys/{set}
--
--
-- Delete JSON Web Key Set
--
-- Use this endpoint to delete a complete JSON Web Key Set and all the
-- keys in that set. A JSON Web Key (JWK) is a JavaScript Object Notation
-- (JSON) data structure that represents a cryptographic key. A JWK Set
-- is a JSON data structure that represents a set of JWKs. A JSON Web Key
-- is identified by its set and key id. ORY Hydra uses this functionality
-- to store cryptographic keys used for TLS and JSON Web Tokens (such as
-- OpenID Connect ID tokens), and allows storing user-defined keys as
-- well.
deleteJsonWebKeySet :: Set -> ORYHydraRequest DeleteJsonWebKeySet MimeNoContent NoContent MimeNoContent
data DeleteJsonWebKeySet
-- |
-- GET /admin/keys/{set}/{kid}
--
--
-- Get JSON Web Key
--
-- This endpoint returns a singular JSON Web Key contained in a set. It
-- is identified by the set and the specific key ID (kid).
getJsonWebKey :: Set -> Kid -> ORYHydraRequest GetJsonWebKey MimeNoContent JsonWebKeySet MimeJSON
data GetJsonWebKey
-- |
-- GET /admin/keys/{set}
--
--
-- Retrieve a JSON Web Key Set
--
-- This endpoint can be used to retrieve JWK Sets stored in ORY Hydra. A
-- JSON Web Key (JWK) is a JavaScript Object Notation (JSON) data
-- structure that represents a cryptographic key. A JWK Set is a JSON
-- data structure that represents a set of JWKs. A JSON Web Key is
-- identified by its set and key id. ORY Hydra uses this functionality to
-- store cryptographic keys used for TLS and JSON Web Tokens (such as
-- OpenID Connect ID tokens), and allows storing user-defined keys as
-- well.
getJsonWebKeySet :: Set -> ORYHydraRequest GetJsonWebKeySet MimeNoContent JsonWebKeySet MimeJSON
data GetJsonWebKeySet
-- |
-- PUT /admin/keys/{set}/{kid}
--
--
-- Set JSON Web Key
--
-- Use this method if you do not want to let Hydra generate the JWKs for
-- you, but instead save your own. A JSON Web Key (JWK) is a JavaScript
-- Object Notation (JSON) data structure that represents a cryptographic
-- key. A JWK Set is a JSON data structure that represents a set of JWKs.
-- A JSON Web Key is identified by its set and key id. ORY Hydra uses
-- this functionality to store cryptographic keys used for TLS and JSON
-- Web Tokens (such as OpenID Connect ID tokens), and allows storing
-- user-defined keys as well.
setJsonWebKey :: Consumes SetJsonWebKey MimeJSON => Set -> Kid -> ORYHydraRequest SetJsonWebKey MimeJSON JsonWebKey MimeJSON
data SetJsonWebKey
-- |
-- PUT /admin/keys/{set}
--
--
-- Update a JSON Web Key Set
--
-- Use this method if you do not want to let Hydra generate the JWKs for
-- you, but instead save your own. A JSON Web Key (JWK) is a JavaScript
-- Object Notation (JSON) data structure that represents a cryptographic
-- key. A JWK Set is a JSON data structure that represents a set of JWKs.
-- A JSON Web Key is identified by its set and key id. ORY Hydra uses
-- this functionality to store cryptographic keys used for TLS and JSON
-- Web Tokens (such as OpenID Connect ID tokens), and allows storing
-- user-defined keys as well.
setJsonWebKeySet :: Consumes SetJsonWebKeySet MimeJSON => Set -> ORYHydraRequest SetJsonWebKeySet MimeJSON JsonWebKeySet MimeJSON
data SetJsonWebKeySet
instance ORYHydra.Core.HasBodyParam ORYHydra.API.Jwk.SetJsonWebKeySet ORYHydra.Model.JsonWebKeySet
instance ORYHydra.MimeTypes.Consumes ORYHydra.API.Jwk.SetJsonWebKeySet ORYHydra.MimeTypes.MimeJSON
instance ORYHydra.MimeTypes.Produces ORYHydra.API.Jwk.SetJsonWebKeySet ORYHydra.MimeTypes.MimeJSON
instance ORYHydra.Core.HasBodyParam ORYHydra.API.Jwk.SetJsonWebKey ORYHydra.Model.JsonWebKey
instance ORYHydra.MimeTypes.Consumes ORYHydra.API.Jwk.SetJsonWebKey ORYHydra.MimeTypes.MimeJSON
instance ORYHydra.MimeTypes.Produces ORYHydra.API.Jwk.SetJsonWebKey ORYHydra.MimeTypes.MimeJSON
instance ORYHydra.MimeTypes.Produces ORYHydra.API.Jwk.GetJsonWebKeySet ORYHydra.MimeTypes.MimeJSON
instance ORYHydra.MimeTypes.Produces ORYHydra.API.Jwk.GetJsonWebKey ORYHydra.MimeTypes.MimeJSON
instance ORYHydra.MimeTypes.Produces ORYHydra.API.Jwk.DeleteJsonWebKeySet ORYHydra.MimeTypes.MimeNoContent
instance ORYHydra.MimeTypes.Produces ORYHydra.API.Jwk.DeleteJsonWebKey ORYHydra.MimeTypes.MimeNoContent
instance ORYHydra.Core.HasBodyParam ORYHydra.API.Jwk.CreateJsonWebKeySet0 ORYHydra.Model.CreateJsonWebKeySet
instance ORYHydra.MimeTypes.Consumes ORYHydra.API.Jwk.CreateJsonWebKeySet0 ORYHydra.MimeTypes.MimeJSON
instance ORYHydra.MimeTypes.Produces ORYHydra.API.Jwk.CreateJsonWebKeySet0 ORYHydra.MimeTypes.MimeJSON
module ORYHydra.ModelLens
-- | acceptOAuth2ConsentRequestGrantAccessTokenAudience Lens
acceptOAuth2ConsentRequestGrantAccessTokenAudienceL :: Lens_' AcceptOAuth2ConsentRequest (Maybe [Text])
-- | acceptOAuth2ConsentRequestGrantScope Lens
acceptOAuth2ConsentRequestGrantScopeL :: Lens_' AcceptOAuth2ConsentRequest (Maybe [Text])
-- | acceptOAuth2ConsentRequestHandledAt Lens
acceptOAuth2ConsentRequestHandledAtL :: Lens_' AcceptOAuth2ConsentRequest (Maybe DateTime)
-- | acceptOAuth2ConsentRequestRemember Lens
acceptOAuth2ConsentRequestRememberL :: Lens_' AcceptOAuth2ConsentRequest (Maybe Bool)
-- | acceptOAuth2ConsentRequestRememberFor Lens
acceptOAuth2ConsentRequestRememberForL :: Lens_' AcceptOAuth2ConsentRequest (Maybe Integer)
-- | acceptOAuth2ConsentRequestSession Lens
acceptOAuth2ConsentRequestSessionL :: Lens_' AcceptOAuth2ConsentRequest (Maybe AcceptOAuth2ConsentRequestSession)
-- | acceptOAuth2ConsentRequestSessionAccessToken Lens
acceptOAuth2ConsentRequestSessionAccessTokenL :: Lens_' AcceptOAuth2ConsentRequestSession (Maybe Value)
-- | acceptOAuth2ConsentRequestSessionIdToken Lens
acceptOAuth2ConsentRequestSessionIdTokenL :: Lens_' AcceptOAuth2ConsentRequestSession (Maybe Value)
-- | acceptOAuth2LoginRequestAcr Lens
acceptOAuth2LoginRequestAcrL :: Lens_' AcceptOAuth2LoginRequest (Maybe Text)
-- | acceptOAuth2LoginRequestAmr Lens
acceptOAuth2LoginRequestAmrL :: Lens_' AcceptOAuth2LoginRequest (Maybe [Text])
-- | acceptOAuth2LoginRequestContext Lens
acceptOAuth2LoginRequestContextL :: Lens_' AcceptOAuth2LoginRequest (Maybe Value)
-- | acceptOAuth2LoginRequestExtendSessionLifespan Lens
acceptOAuth2LoginRequestExtendSessionLifespanL :: Lens_' AcceptOAuth2LoginRequest (Maybe Bool)
-- | acceptOAuth2LoginRequestForceSubjectIdentifier Lens
acceptOAuth2LoginRequestForceSubjectIdentifierL :: Lens_' AcceptOAuth2LoginRequest (Maybe Text)
-- | acceptOAuth2LoginRequestRemember Lens
acceptOAuth2LoginRequestRememberL :: Lens_' AcceptOAuth2LoginRequest (Maybe Bool)
-- | acceptOAuth2LoginRequestRememberFor Lens
acceptOAuth2LoginRequestRememberForL :: Lens_' AcceptOAuth2LoginRequest (Maybe Integer)
-- | acceptOAuth2LoginRequestSubject Lens
acceptOAuth2LoginRequestSubjectL :: Lens_' AcceptOAuth2LoginRequest Text
-- | createJsonWebKeySetAlg Lens
createJsonWebKeySetAlgL :: Lens_' CreateJsonWebKeySet Text
-- | createJsonWebKeySetKid Lens
createJsonWebKeySetKidL :: Lens_' CreateJsonWebKeySet Text
-- | createJsonWebKeySetUse Lens
createJsonWebKeySetUseL :: Lens_' CreateJsonWebKeySet Text
-- | errorOAuth2Error Lens
errorOAuth2ErrorL :: Lens_' ErrorOAuth2 (Maybe Text)
-- | errorOAuth2ErrorDebug Lens
errorOAuth2ErrorDebugL :: Lens_' ErrorOAuth2 (Maybe Text)
-- | errorOAuth2ErrorDescription Lens
errorOAuth2ErrorDescriptionL :: Lens_' ErrorOAuth2 (Maybe Text)
-- | errorOAuth2ErrorHint Lens
errorOAuth2ErrorHintL :: Lens_' ErrorOAuth2 (Maybe Text)
-- | errorOAuth2StatusCode Lens
errorOAuth2StatusCodeL :: Lens_' ErrorOAuth2 (Maybe Integer)
-- | genericErrorCode Lens
genericErrorCodeL :: Lens_' GenericError (Maybe Integer)
-- | genericErrorDebug Lens
genericErrorDebugL :: Lens_' GenericError (Maybe Text)
-- | genericErrorDetails Lens
genericErrorDetailsL :: Lens_' GenericError (Maybe Value)
-- | genericErrorId Lens
genericErrorIdL :: Lens_' GenericError (Maybe Text)
-- | genericErrorMessage Lens
genericErrorMessageL :: Lens_' GenericError Text
-- | genericErrorReason Lens
genericErrorReasonL :: Lens_' GenericError (Maybe Text)
-- | genericErrorRequest Lens
genericErrorRequestL :: Lens_' GenericError (Maybe Text)
-- | genericErrorStatus Lens
genericErrorStatusL :: Lens_' GenericError (Maybe Text)
-- | getVersion200ResponseVersion Lens
getVersion200ResponseVersionL :: Lens_' GetVersion200Response (Maybe Text)
-- | healthNotReadyStatusErrors Lens
healthNotReadyStatusErrorsL :: Lens_' HealthNotReadyStatus (Maybe (Map String Text))
-- | healthStatusStatus Lens
healthStatusStatusL :: Lens_' HealthStatus (Maybe Text)
-- | introspectedOAuth2TokenActive Lens
introspectedOAuth2TokenActiveL :: Lens_' IntrospectedOAuth2Token Bool
-- | introspectedOAuth2TokenAud Lens
introspectedOAuth2TokenAudL :: Lens_' IntrospectedOAuth2Token (Maybe [Text])
-- | introspectedOAuth2TokenClientId Lens
introspectedOAuth2TokenClientIdL :: Lens_' IntrospectedOAuth2Token (Maybe Text)
-- | introspectedOAuth2TokenExp Lens
introspectedOAuth2TokenExpL :: Lens_' IntrospectedOAuth2Token (Maybe Integer)
-- | introspectedOAuth2TokenExt Lens
introspectedOAuth2TokenExtL :: Lens_' IntrospectedOAuth2Token (Maybe (Map String Value))
-- | introspectedOAuth2TokenIat Lens
introspectedOAuth2TokenIatL :: Lens_' IntrospectedOAuth2Token (Maybe Integer)
-- | introspectedOAuth2TokenIss Lens
introspectedOAuth2TokenIssL :: Lens_' IntrospectedOAuth2Token (Maybe Text)
-- | introspectedOAuth2TokenNbf Lens
introspectedOAuth2TokenNbfL :: Lens_' IntrospectedOAuth2Token (Maybe Integer)
-- | introspectedOAuth2TokenObfuscatedSubject Lens
introspectedOAuth2TokenObfuscatedSubjectL :: Lens_' IntrospectedOAuth2Token (Maybe Text)
-- | introspectedOAuth2TokenScope Lens
introspectedOAuth2TokenScopeL :: Lens_' IntrospectedOAuth2Token (Maybe Text)
-- | introspectedOAuth2TokenSub Lens
introspectedOAuth2TokenSubL :: Lens_' IntrospectedOAuth2Token (Maybe Text)
-- | introspectedOAuth2TokenTokenType Lens
introspectedOAuth2TokenTokenTypeL :: Lens_' IntrospectedOAuth2Token (Maybe Text)
-- | introspectedOAuth2TokenTokenUse Lens
introspectedOAuth2TokenTokenUseL :: Lens_' IntrospectedOAuth2Token (Maybe Text)
-- | introspectedOAuth2TokenUsername Lens
introspectedOAuth2TokenUsernameL :: Lens_' IntrospectedOAuth2Token (Maybe Text)
-- | isReady200ResponseStatus Lens
isReady200ResponseStatusL :: Lens_' IsReady200Response (Maybe Text)
-- | isReady503ResponseErrors Lens
isReady503ResponseErrorsL :: Lens_' IsReady503Response (Maybe (Map String Text))
-- | jsonPatchFrom Lens
jsonPatchFromL :: Lens_' JsonPatch (Maybe Text)
-- | jsonPatchOp Lens
jsonPatchOpL :: Lens_' JsonPatch Text
-- | jsonPatchPath Lens
jsonPatchPathL :: Lens_' JsonPatch Text
-- | jsonPatchValue Lens
jsonPatchValueL :: Lens_' JsonPatch (Maybe Value)
-- | jsonWebKeyAlg Lens
jsonWebKeyAlgL :: Lens_' JsonWebKey Text
-- | jsonWebKeyCrv Lens
jsonWebKeyCrvL :: Lens_' JsonWebKey (Maybe Text)
-- | jsonWebKeyD Lens
jsonWebKeyDL :: Lens_' JsonWebKey (Maybe Text)
-- | jsonWebKeyDp Lens
jsonWebKeyDpL :: Lens_' JsonWebKey (Maybe Text)
-- | jsonWebKeyDq Lens
jsonWebKeyDqL :: Lens_' JsonWebKey (Maybe Text)
-- | jsonWebKeyE Lens
jsonWebKeyEL :: Lens_' JsonWebKey (Maybe Text)
-- | jsonWebKeyK Lens
jsonWebKeyKL :: Lens_' JsonWebKey (Maybe Text)
-- | jsonWebKeyKid Lens
jsonWebKeyKidL :: Lens_' JsonWebKey Text
-- | jsonWebKeyKty Lens
jsonWebKeyKtyL :: Lens_' JsonWebKey Text
-- | jsonWebKeyN Lens
jsonWebKeyNL :: Lens_' JsonWebKey (Maybe Text)
-- | jsonWebKeyP Lens
jsonWebKeyPL :: Lens_' JsonWebKey (Maybe Text)
-- | jsonWebKeyQ Lens
jsonWebKeyQL :: Lens_' JsonWebKey (Maybe Text)
-- | jsonWebKeyQi Lens
jsonWebKeyQiL :: Lens_' JsonWebKey (Maybe Text)
-- | jsonWebKeyUse Lens
jsonWebKeyUseL :: Lens_' JsonWebKey Text
-- | jsonWebKeyX Lens
jsonWebKeyXL :: Lens_' JsonWebKey (Maybe Text)
-- | jsonWebKeyX5c Lens
jsonWebKeyX5cL :: Lens_' JsonWebKey (Maybe [Text])
-- | jsonWebKeyY Lens
jsonWebKeyYL :: Lens_' JsonWebKey (Maybe Text)
-- | jsonWebKeySetKeys Lens
jsonWebKeySetKeysL :: Lens_' JsonWebKeySet (Maybe [JsonWebKey])
-- | oAuth2ClientAccessTokenStrategy Lens
oAuth2ClientAccessTokenStrategyL :: Lens_' OAuth2Client (Maybe Text)
-- | oAuth2ClientAllowedCorsOrigins Lens
oAuth2ClientAllowedCorsOriginsL :: Lens_' OAuth2Client (Maybe [Text])
-- | oAuth2ClientAudience Lens
oAuth2ClientAudienceL :: Lens_' OAuth2Client (Maybe [Text])
-- | oAuth2ClientAuthorizationCodeGrantAccessTokenLifespan Lens
oAuth2ClientAuthorizationCodeGrantAccessTokenLifespanL :: Lens_' OAuth2Client (Maybe Text)
-- | oAuth2ClientAuthorizationCodeGrantIdTokenLifespan Lens
oAuth2ClientAuthorizationCodeGrantIdTokenLifespanL :: Lens_' OAuth2Client (Maybe Text)
-- | oAuth2ClientAuthorizationCodeGrantRefreshTokenLifespan Lens
oAuth2ClientAuthorizationCodeGrantRefreshTokenLifespanL :: Lens_' OAuth2Client (Maybe Text)
-- | oAuth2ClientBackchannelLogoutSessionRequired Lens
oAuth2ClientBackchannelLogoutSessionRequiredL :: Lens_' OAuth2Client (Maybe Bool)
-- | oAuth2ClientBackchannelLogoutUri Lens
oAuth2ClientBackchannelLogoutUriL :: Lens_' OAuth2Client (Maybe Text)
-- | oAuth2ClientClientCredentialsGrantAccessTokenLifespan Lens
oAuth2ClientClientCredentialsGrantAccessTokenLifespanL :: Lens_' OAuth2Client (Maybe Text)
-- | oAuth2ClientClientId Lens
oAuth2ClientClientIdL :: Lens_' OAuth2Client (Maybe Text)
-- | oAuth2ClientClientName Lens
oAuth2ClientClientNameL :: Lens_' OAuth2Client (Maybe Text)
-- | oAuth2ClientClientSecret Lens
oAuth2ClientClientSecretL :: Lens_' OAuth2Client (Maybe Text)
-- | oAuth2ClientClientSecretExpiresAt Lens
oAuth2ClientClientSecretExpiresAtL :: Lens_' OAuth2Client (Maybe Integer)
-- | oAuth2ClientClientUri Lens
oAuth2ClientClientUriL :: Lens_' OAuth2Client (Maybe Text)
-- | oAuth2ClientContacts Lens
oAuth2ClientContactsL :: Lens_' OAuth2Client (Maybe [Text])
-- | oAuth2ClientCreatedAt Lens
oAuth2ClientCreatedAtL :: Lens_' OAuth2Client (Maybe DateTime)
-- | oAuth2ClientFrontchannelLogoutSessionRequired Lens
oAuth2ClientFrontchannelLogoutSessionRequiredL :: Lens_' OAuth2Client (Maybe Bool)
-- | oAuth2ClientFrontchannelLogoutUri Lens
oAuth2ClientFrontchannelLogoutUriL :: Lens_' OAuth2Client (Maybe Text)
-- | oAuth2ClientGrantTypes Lens
oAuth2ClientGrantTypesL :: Lens_' OAuth2Client (Maybe [Text])
-- | oAuth2ClientImplicitGrantAccessTokenLifespan Lens
oAuth2ClientImplicitGrantAccessTokenLifespanL :: Lens_' OAuth2Client (Maybe Text)
-- | oAuth2ClientImplicitGrantIdTokenLifespan Lens
oAuth2ClientImplicitGrantIdTokenLifespanL :: Lens_' OAuth2Client (Maybe Text)
-- | oAuth2ClientJwks Lens
oAuth2ClientJwksL :: Lens_' OAuth2Client (Maybe Value)
-- | oAuth2ClientJwksUri Lens
oAuth2ClientJwksUriL :: Lens_' OAuth2Client (Maybe Text)
-- | oAuth2ClientJwtBearerGrantAccessTokenLifespan Lens
oAuth2ClientJwtBearerGrantAccessTokenLifespanL :: Lens_' OAuth2Client (Maybe Text)
-- | oAuth2ClientLogoUri Lens
oAuth2ClientLogoUriL :: Lens_' OAuth2Client (Maybe Text)
-- | oAuth2ClientMetadata Lens
oAuth2ClientMetadataL :: Lens_' OAuth2Client (Maybe Value)
-- | oAuth2ClientOwner Lens
oAuth2ClientOwnerL :: Lens_' OAuth2Client (Maybe Text)
-- | oAuth2ClientPolicyUri Lens
oAuth2ClientPolicyUriL :: Lens_' OAuth2Client (Maybe Text)
-- | oAuth2ClientPostLogoutRedirectUris Lens
oAuth2ClientPostLogoutRedirectUrisL :: Lens_' OAuth2Client (Maybe [Text])
-- | oAuth2ClientRedirectUris Lens
oAuth2ClientRedirectUrisL :: Lens_' OAuth2Client (Maybe [Text])
-- | oAuth2ClientRefreshTokenGrantAccessTokenLifespan Lens
oAuth2ClientRefreshTokenGrantAccessTokenLifespanL :: Lens_' OAuth2Client (Maybe Text)
-- | oAuth2ClientRefreshTokenGrantIdTokenLifespan Lens
oAuth2ClientRefreshTokenGrantIdTokenLifespanL :: Lens_' OAuth2Client (Maybe Text)
-- | oAuth2ClientRefreshTokenGrantRefreshTokenLifespan Lens
oAuth2ClientRefreshTokenGrantRefreshTokenLifespanL :: Lens_' OAuth2Client (Maybe Text)
-- | oAuth2ClientRegistrationAccessToken Lens
oAuth2ClientRegistrationAccessTokenL :: Lens_' OAuth2Client (Maybe Text)
-- | oAuth2ClientRegistrationClientUri Lens
oAuth2ClientRegistrationClientUriL :: Lens_' OAuth2Client (Maybe Text)
-- | oAuth2ClientRequestObjectSigningAlg Lens
oAuth2ClientRequestObjectSigningAlgL :: Lens_' OAuth2Client (Maybe Text)
-- | oAuth2ClientRequestUris Lens
oAuth2ClientRequestUrisL :: Lens_' OAuth2Client (Maybe [Text])
-- | oAuth2ClientResponseTypes Lens
oAuth2ClientResponseTypesL :: Lens_' OAuth2Client (Maybe [Text])
-- | oAuth2ClientScope Lens
oAuth2ClientScopeL :: Lens_' OAuth2Client (Maybe Text)
-- | oAuth2ClientSectorIdentifierUri Lens
oAuth2ClientSectorIdentifierUriL :: Lens_' OAuth2Client (Maybe Text)
-- | oAuth2ClientSkipConsent Lens
oAuth2ClientSkipConsentL :: Lens_' OAuth2Client (Maybe Bool)
-- | oAuth2ClientSubjectType Lens
oAuth2ClientSubjectTypeL :: Lens_' OAuth2Client (Maybe Text)
-- | oAuth2ClientTokenEndpointAuthMethod Lens
oAuth2ClientTokenEndpointAuthMethodL :: Lens_' OAuth2Client (Maybe Text)
-- | oAuth2ClientTokenEndpointAuthSigningAlg Lens
oAuth2ClientTokenEndpointAuthSigningAlgL :: Lens_' OAuth2Client (Maybe Text)
-- | oAuth2ClientTosUri Lens
oAuth2ClientTosUriL :: Lens_' OAuth2Client (Maybe Text)
-- | oAuth2ClientUpdatedAt Lens
oAuth2ClientUpdatedAtL :: Lens_' OAuth2Client (Maybe DateTime)
-- | oAuth2ClientUserinfoSignedResponseAlg Lens
oAuth2ClientUserinfoSignedResponseAlgL :: Lens_' OAuth2Client (Maybe Text)
-- |
-- oAuth2ClientTokenLifespansAuthorizationCodeGrantAccessTokenLifespan
-- Lens
oAuth2ClientTokenLifespansAuthorizationCodeGrantAccessTokenLifespanL :: Lens_' OAuth2ClientTokenLifespans (Maybe Text)
-- | oAuth2ClientTokenLifespansAuthorizationCodeGrantIdTokenLifespan
-- Lens
oAuth2ClientTokenLifespansAuthorizationCodeGrantIdTokenLifespanL :: Lens_' OAuth2ClientTokenLifespans (Maybe Text)
-- |
-- oAuth2ClientTokenLifespansAuthorizationCodeGrantRefreshTokenLifespan
-- Lens
oAuth2ClientTokenLifespansAuthorizationCodeGrantRefreshTokenLifespanL :: Lens_' OAuth2ClientTokenLifespans (Maybe Text)
-- |
-- oAuth2ClientTokenLifespansClientCredentialsGrantAccessTokenLifespan
-- Lens
oAuth2ClientTokenLifespansClientCredentialsGrantAccessTokenLifespanL :: Lens_' OAuth2ClientTokenLifespans (Maybe Text)
-- | oAuth2ClientTokenLifespansImplicitGrantAccessTokenLifespan Lens
oAuth2ClientTokenLifespansImplicitGrantAccessTokenLifespanL :: Lens_' OAuth2ClientTokenLifespans (Maybe Text)
-- | oAuth2ClientTokenLifespansImplicitGrantIdTokenLifespan Lens
oAuth2ClientTokenLifespansImplicitGrantIdTokenLifespanL :: Lens_' OAuth2ClientTokenLifespans (Maybe Text)
-- | oAuth2ClientTokenLifespansJwtBearerGrantAccessTokenLifespan
-- Lens
oAuth2ClientTokenLifespansJwtBearerGrantAccessTokenLifespanL :: Lens_' OAuth2ClientTokenLifespans (Maybe Text)
-- | oAuth2ClientTokenLifespansRefreshTokenGrantAccessTokenLifespan
-- Lens
oAuth2ClientTokenLifespansRefreshTokenGrantAccessTokenLifespanL :: Lens_' OAuth2ClientTokenLifespans (Maybe Text)
-- | oAuth2ClientTokenLifespansRefreshTokenGrantIdTokenLifespan Lens
oAuth2ClientTokenLifespansRefreshTokenGrantIdTokenLifespanL :: Lens_' OAuth2ClientTokenLifespans (Maybe Text)
-- | oAuth2ClientTokenLifespansRefreshTokenGrantRefreshTokenLifespan
-- Lens
oAuth2ClientTokenLifespansRefreshTokenGrantRefreshTokenLifespanL :: Lens_' OAuth2ClientTokenLifespans (Maybe Text)
-- | oAuth2ConsentRequestAcr Lens
oAuth2ConsentRequestAcrL :: Lens_' OAuth2ConsentRequest (Maybe Text)
-- | oAuth2ConsentRequestAmr Lens
oAuth2ConsentRequestAmrL :: Lens_' OAuth2ConsentRequest (Maybe [Text])
-- | oAuth2ConsentRequestChallenge Lens
oAuth2ConsentRequestChallengeL :: Lens_' OAuth2ConsentRequest Text
-- | oAuth2ConsentRequestClient Lens
oAuth2ConsentRequestClientL :: Lens_' OAuth2ConsentRequest (Maybe OAuth2Client)
-- | oAuth2ConsentRequestContext Lens
oAuth2ConsentRequestContextL :: Lens_' OAuth2ConsentRequest (Maybe Value)
-- | oAuth2ConsentRequestLoginChallenge Lens
oAuth2ConsentRequestLoginChallengeL :: Lens_' OAuth2ConsentRequest (Maybe Text)
-- | oAuth2ConsentRequestLoginSessionId Lens
oAuth2ConsentRequestLoginSessionIdL :: Lens_' OAuth2ConsentRequest (Maybe Text)
-- | oAuth2ConsentRequestOidcContext Lens
oAuth2ConsentRequestOidcContextL :: Lens_' OAuth2ConsentRequest (Maybe OAuth2ConsentRequestOpenIDConnectContext)
-- | oAuth2ConsentRequestRequestUrl Lens
oAuth2ConsentRequestRequestUrlL :: Lens_' OAuth2ConsentRequest (Maybe Text)
-- | oAuth2ConsentRequestRequestedAccessTokenAudience Lens
oAuth2ConsentRequestRequestedAccessTokenAudienceL :: Lens_' OAuth2ConsentRequest (Maybe [Text])
-- | oAuth2ConsentRequestRequestedScope Lens
oAuth2ConsentRequestRequestedScopeL :: Lens_' OAuth2ConsentRequest (Maybe [Text])
-- | oAuth2ConsentRequestSkip Lens
oAuth2ConsentRequestSkipL :: Lens_' OAuth2ConsentRequest (Maybe Bool)
-- | oAuth2ConsentRequestSubject Lens
oAuth2ConsentRequestSubjectL :: Lens_' OAuth2ConsentRequest (Maybe Text)
-- | oAuth2ConsentRequestOpenIDConnectContextAcrValues Lens
oAuth2ConsentRequestOpenIDConnectContextAcrValuesL :: Lens_' OAuth2ConsentRequestOpenIDConnectContext (Maybe [Text])
-- | oAuth2ConsentRequestOpenIDConnectContextDisplay Lens
oAuth2ConsentRequestOpenIDConnectContextDisplayL :: Lens_' OAuth2ConsentRequestOpenIDConnectContext (Maybe Text)
-- | oAuth2ConsentRequestOpenIDConnectContextIdTokenHintClaims Lens
oAuth2ConsentRequestOpenIDConnectContextIdTokenHintClaimsL :: Lens_' OAuth2ConsentRequestOpenIDConnectContext (Maybe (Map String Value))
-- | oAuth2ConsentRequestOpenIDConnectContextLoginHint Lens
oAuth2ConsentRequestOpenIDConnectContextLoginHintL :: Lens_' OAuth2ConsentRequestOpenIDConnectContext (Maybe Text)
-- | oAuth2ConsentRequestOpenIDConnectContextUiLocales Lens
oAuth2ConsentRequestOpenIDConnectContextUiLocalesL :: Lens_' OAuth2ConsentRequestOpenIDConnectContext (Maybe [Text])
-- | oAuth2ConsentSessionConsentRequest Lens
oAuth2ConsentSessionConsentRequestL :: Lens_' OAuth2ConsentSession (Maybe OAuth2ConsentRequest)
-- | oAuth2ConsentSessionExpiresAt Lens
oAuth2ConsentSessionExpiresAtL :: Lens_' OAuth2ConsentSession (Maybe OAuth2ConsentSessionExpiresAt)
-- | oAuth2ConsentSessionGrantAccessTokenAudience Lens
oAuth2ConsentSessionGrantAccessTokenAudienceL :: Lens_' OAuth2ConsentSession (Maybe [Text])
-- | oAuth2ConsentSessionGrantScope Lens
oAuth2ConsentSessionGrantScopeL :: Lens_' OAuth2ConsentSession (Maybe [Text])
-- | oAuth2ConsentSessionHandledAt Lens
oAuth2ConsentSessionHandledAtL :: Lens_' OAuth2ConsentSession (Maybe DateTime)
-- | oAuth2ConsentSessionRemember Lens
oAuth2ConsentSessionRememberL :: Lens_' OAuth2ConsentSession (Maybe Bool)
-- | oAuth2ConsentSessionRememberFor Lens
oAuth2ConsentSessionRememberForL :: Lens_' OAuth2ConsentSession (Maybe Integer)
-- | oAuth2ConsentSessionSession Lens
oAuth2ConsentSessionSessionL :: Lens_' OAuth2ConsentSession (Maybe AcceptOAuth2ConsentRequestSession)
-- | oAuth2ConsentSessionExpiresAtAccessToken Lens
oAuth2ConsentSessionExpiresAtAccessTokenL :: Lens_' OAuth2ConsentSessionExpiresAt (Maybe DateTime)
-- | oAuth2ConsentSessionExpiresAtAuthorizeCode Lens
oAuth2ConsentSessionExpiresAtAuthorizeCodeL :: Lens_' OAuth2ConsentSessionExpiresAt (Maybe DateTime)
-- | oAuth2ConsentSessionExpiresAtIdToken Lens
oAuth2ConsentSessionExpiresAtIdTokenL :: Lens_' OAuth2ConsentSessionExpiresAt (Maybe DateTime)
-- | oAuth2ConsentSessionExpiresAtParContext Lens
oAuth2ConsentSessionExpiresAtParContextL :: Lens_' OAuth2ConsentSessionExpiresAt (Maybe DateTime)
-- | oAuth2ConsentSessionExpiresAtRefreshToken Lens
oAuth2ConsentSessionExpiresAtRefreshTokenL :: Lens_' OAuth2ConsentSessionExpiresAt (Maybe DateTime)
-- | oAuth2LoginRequestChallenge Lens
oAuth2LoginRequestChallengeL :: Lens_' OAuth2LoginRequest Text
-- | oAuth2LoginRequestClient Lens
oAuth2LoginRequestClientL :: Lens_' OAuth2LoginRequest OAuth2Client
-- | oAuth2LoginRequestOidcContext Lens
oAuth2LoginRequestOidcContextL :: Lens_' OAuth2LoginRequest (Maybe OAuth2ConsentRequestOpenIDConnectContext)
-- | oAuth2LoginRequestRequestUrl Lens
oAuth2LoginRequestRequestUrlL :: Lens_' OAuth2LoginRequest Text
-- | oAuth2LoginRequestRequestedAccessTokenAudience Lens
oAuth2LoginRequestRequestedAccessTokenAudienceL :: Lens_' OAuth2LoginRequest [Text]
-- | oAuth2LoginRequestRequestedScope Lens
oAuth2LoginRequestRequestedScopeL :: Lens_' OAuth2LoginRequest [Text]
-- | oAuth2LoginRequestSessionId Lens
oAuth2LoginRequestSessionIdL :: Lens_' OAuth2LoginRequest (Maybe Text)
-- | oAuth2LoginRequestSkip Lens
oAuth2LoginRequestSkipL :: Lens_' OAuth2LoginRequest Bool
-- | oAuth2LoginRequestSubject Lens
oAuth2LoginRequestSubjectL :: Lens_' OAuth2LoginRequest Text
-- | oAuth2LogoutRequestChallenge Lens
oAuth2LogoutRequestChallengeL :: Lens_' OAuth2LogoutRequest (Maybe Text)
-- | oAuth2LogoutRequestClient Lens
oAuth2LogoutRequestClientL :: Lens_' OAuth2LogoutRequest (Maybe OAuth2Client)
-- | oAuth2LogoutRequestRequestUrl Lens
oAuth2LogoutRequestRequestUrlL :: Lens_' OAuth2LogoutRequest (Maybe Text)
-- | oAuth2LogoutRequestRpInitiated Lens
oAuth2LogoutRequestRpInitiatedL :: Lens_' OAuth2LogoutRequest (Maybe Bool)
-- | oAuth2LogoutRequestSid Lens
oAuth2LogoutRequestSidL :: Lens_' OAuth2LogoutRequest (Maybe Text)
-- | oAuth2LogoutRequestSubject Lens
oAuth2LogoutRequestSubjectL :: Lens_' OAuth2LogoutRequest (Maybe Text)
-- | oAuth2RedirectToRedirectTo Lens
oAuth2RedirectToRedirectToL :: Lens_' OAuth2RedirectTo Text
-- | oAuth2TokenExchangeAccessToken Lens
oAuth2TokenExchangeAccessTokenL :: Lens_' OAuth2TokenExchange (Maybe Text)
-- | oAuth2TokenExchangeExpiresIn Lens
oAuth2TokenExchangeExpiresInL :: Lens_' OAuth2TokenExchange (Maybe Integer)
-- | oAuth2TokenExchangeIdToken Lens
oAuth2TokenExchangeIdTokenL :: Lens_' OAuth2TokenExchange (Maybe Integer)
-- | oAuth2TokenExchangeRefreshToken Lens
oAuth2TokenExchangeRefreshTokenL :: Lens_' OAuth2TokenExchange (Maybe Text)
-- | oAuth2TokenExchangeScope Lens
oAuth2TokenExchangeScopeL :: Lens_' OAuth2TokenExchange (Maybe Text)
-- | oAuth2TokenExchangeTokenType Lens
oAuth2TokenExchangeTokenTypeL :: Lens_' OAuth2TokenExchange (Maybe Text)
-- | oidcConfigurationAuthorizationEndpoint Lens
oidcConfigurationAuthorizationEndpointL :: Lens_' OidcConfiguration Text
-- | oidcConfigurationBackchannelLogoutSessionSupported Lens
oidcConfigurationBackchannelLogoutSessionSupportedL :: Lens_' OidcConfiguration (Maybe Bool)
-- | oidcConfigurationBackchannelLogoutSupported Lens
oidcConfigurationBackchannelLogoutSupportedL :: Lens_' OidcConfiguration (Maybe Bool)
-- | oidcConfigurationClaimsParameterSupported Lens
oidcConfigurationClaimsParameterSupportedL :: Lens_' OidcConfiguration (Maybe Bool)
-- | oidcConfigurationClaimsSupported Lens
oidcConfigurationClaimsSupportedL :: Lens_' OidcConfiguration (Maybe [Text])
-- | oidcConfigurationCodeChallengeMethodsSupported Lens
oidcConfigurationCodeChallengeMethodsSupportedL :: Lens_' OidcConfiguration (Maybe [Text])
-- | oidcConfigurationEndSessionEndpoint Lens
oidcConfigurationEndSessionEndpointL :: Lens_' OidcConfiguration (Maybe Text)
-- | oidcConfigurationFrontchannelLogoutSessionSupported Lens
oidcConfigurationFrontchannelLogoutSessionSupportedL :: Lens_' OidcConfiguration (Maybe Bool)
-- | oidcConfigurationFrontchannelLogoutSupported Lens
oidcConfigurationFrontchannelLogoutSupportedL :: Lens_' OidcConfiguration (Maybe Bool)
-- | oidcConfigurationGrantTypesSupported Lens
oidcConfigurationGrantTypesSupportedL :: Lens_' OidcConfiguration (Maybe [Text])
-- | oidcConfigurationIdTokenSignedResponseAlg Lens
oidcConfigurationIdTokenSignedResponseAlgL :: Lens_' OidcConfiguration [Text]
-- | oidcConfigurationIdTokenSigningAlgValuesSupported Lens
oidcConfigurationIdTokenSigningAlgValuesSupportedL :: Lens_' OidcConfiguration [Text]
-- | oidcConfigurationIssuer Lens
oidcConfigurationIssuerL :: Lens_' OidcConfiguration Text
-- | oidcConfigurationJwksUri Lens
oidcConfigurationJwksUriL :: Lens_' OidcConfiguration Text
-- | oidcConfigurationRegistrationEndpoint Lens
oidcConfigurationRegistrationEndpointL :: Lens_' OidcConfiguration (Maybe Text)
-- | oidcConfigurationRequestObjectSigningAlgValuesSupported Lens
oidcConfigurationRequestObjectSigningAlgValuesSupportedL :: Lens_' OidcConfiguration (Maybe [Text])
-- | oidcConfigurationRequestParameterSupported Lens
oidcConfigurationRequestParameterSupportedL :: Lens_' OidcConfiguration (Maybe Bool)
-- | oidcConfigurationRequestUriParameterSupported Lens
oidcConfigurationRequestUriParameterSupportedL :: Lens_' OidcConfiguration (Maybe Bool)
-- | oidcConfigurationRequireRequestUriRegistration Lens
oidcConfigurationRequireRequestUriRegistrationL :: Lens_' OidcConfiguration (Maybe Bool)
-- | oidcConfigurationResponseModesSupported Lens
oidcConfigurationResponseModesSupportedL :: Lens_' OidcConfiguration (Maybe [Text])
-- | oidcConfigurationResponseTypesSupported Lens
oidcConfigurationResponseTypesSupportedL :: Lens_' OidcConfiguration [Text]
-- | oidcConfigurationRevocationEndpoint Lens
oidcConfigurationRevocationEndpointL :: Lens_' OidcConfiguration (Maybe Text)
-- | oidcConfigurationScopesSupported Lens
oidcConfigurationScopesSupportedL :: Lens_' OidcConfiguration (Maybe [Text])
-- | oidcConfigurationSubjectTypesSupported Lens
oidcConfigurationSubjectTypesSupportedL :: Lens_' OidcConfiguration [Text]
-- | oidcConfigurationTokenEndpoint Lens
oidcConfigurationTokenEndpointL :: Lens_' OidcConfiguration Text
-- | oidcConfigurationTokenEndpointAuthMethodsSupported Lens
oidcConfigurationTokenEndpointAuthMethodsSupportedL :: Lens_' OidcConfiguration (Maybe [Text])
-- | oidcConfigurationUserinfoEndpoint Lens
oidcConfigurationUserinfoEndpointL :: Lens_' OidcConfiguration (Maybe Text)
-- | oidcConfigurationUserinfoSignedResponseAlg Lens
oidcConfigurationUserinfoSignedResponseAlgL :: Lens_' OidcConfiguration [Text]
-- | oidcConfigurationUserinfoSigningAlgValuesSupported Lens
oidcConfigurationUserinfoSigningAlgValuesSupportedL :: Lens_' OidcConfiguration (Maybe [Text])
-- | oidcUserInfoBirthdate Lens
oidcUserInfoBirthdateL :: Lens_' OidcUserInfo (Maybe Text)
-- | oidcUserInfoEmail Lens
oidcUserInfoEmailL :: Lens_' OidcUserInfo (Maybe Text)
-- | oidcUserInfoEmailVerified Lens
oidcUserInfoEmailVerifiedL :: Lens_' OidcUserInfo (Maybe Bool)
-- | oidcUserInfoFamilyName Lens
oidcUserInfoFamilyNameL :: Lens_' OidcUserInfo (Maybe Text)
-- | oidcUserInfoGender Lens
oidcUserInfoGenderL :: Lens_' OidcUserInfo (Maybe Text)
-- | oidcUserInfoGivenName Lens
oidcUserInfoGivenNameL :: Lens_' OidcUserInfo (Maybe Text)
-- | oidcUserInfoLocale Lens
oidcUserInfoLocaleL :: Lens_' OidcUserInfo (Maybe Text)
-- | oidcUserInfoMiddleName Lens
oidcUserInfoMiddleNameL :: Lens_' OidcUserInfo (Maybe Text)
-- | oidcUserInfoName Lens
oidcUserInfoNameL :: Lens_' OidcUserInfo (Maybe Text)
-- | oidcUserInfoNickname Lens
oidcUserInfoNicknameL :: Lens_' OidcUserInfo (Maybe Text)
-- | oidcUserInfoPhoneNumber Lens
oidcUserInfoPhoneNumberL :: Lens_' OidcUserInfo (Maybe Text)
-- | oidcUserInfoPhoneNumberVerified Lens
oidcUserInfoPhoneNumberVerifiedL :: Lens_' OidcUserInfo (Maybe Bool)
-- | oidcUserInfoPicture Lens
oidcUserInfoPictureL :: Lens_' OidcUserInfo (Maybe Text)
-- | oidcUserInfoPreferredUsername Lens
oidcUserInfoPreferredUsernameL :: Lens_' OidcUserInfo (Maybe Text)
-- | oidcUserInfoProfile Lens
oidcUserInfoProfileL :: Lens_' OidcUserInfo (Maybe Text)
-- | oidcUserInfoSub Lens
oidcUserInfoSubL :: Lens_' OidcUserInfo (Maybe Text)
-- | oidcUserInfoUpdatedAt Lens
oidcUserInfoUpdatedAtL :: Lens_' OidcUserInfo (Maybe Integer)
-- | oidcUserInfoWebsite Lens
oidcUserInfoWebsiteL :: Lens_' OidcUserInfo (Maybe Text)
-- | oidcUserInfoZoneinfo Lens
oidcUserInfoZoneinfoL :: Lens_' OidcUserInfo (Maybe Text)
-- | paginationPageSize Lens
paginationPageSizeL :: Lens_' Pagination (Maybe Integer)
-- | paginationPageToken Lens
paginationPageTokenL :: Lens_' Pagination (Maybe Text)
-- | paginationHeadersLink Lens
paginationHeadersLinkL :: Lens_' PaginationHeaders (Maybe Text)
-- | paginationHeadersXTotalCount Lens
paginationHeadersXTotalCountL :: Lens_' PaginationHeaders (Maybe Text)
-- | rejectOAuth2RequestError Lens
rejectOAuth2RequestErrorL :: Lens_' RejectOAuth2Request (Maybe Text)
-- | rejectOAuth2RequestErrorDebug Lens
rejectOAuth2RequestErrorDebugL :: Lens_' RejectOAuth2Request (Maybe Text)
-- | rejectOAuth2RequestErrorDescription Lens
rejectOAuth2RequestErrorDescriptionL :: Lens_' RejectOAuth2Request (Maybe Text)
-- | rejectOAuth2RequestErrorHint Lens
rejectOAuth2RequestErrorHintL :: Lens_' RejectOAuth2Request (Maybe Text)
-- | rejectOAuth2RequestStatusCode Lens
rejectOAuth2RequestStatusCodeL :: Lens_' RejectOAuth2Request (Maybe Integer)
-- | tokenPaginationPageSize Lens
tokenPaginationPageSizeL :: Lens_' TokenPagination (Maybe Integer)
-- | tokenPaginationPageToken Lens
tokenPaginationPageTokenL :: Lens_' TokenPagination (Maybe Text)
-- | tokenPaginationHeadersLink Lens
tokenPaginationHeadersLinkL :: Lens_' TokenPaginationHeaders (Maybe Text)
-- | tokenPaginationHeadersXTotalCount Lens
tokenPaginationHeadersXTotalCountL :: Lens_' TokenPaginationHeaders (Maybe Text)
-- | tokenPaginationRequestParametersPageSize Lens
tokenPaginationRequestParametersPageSizeL :: Lens_' TokenPaginationRequestParameters (Maybe Integer)
-- | tokenPaginationRequestParametersPageToken Lens
tokenPaginationRequestParametersPageTokenL :: Lens_' TokenPaginationRequestParameters (Maybe Text)
-- | tokenPaginationResponseHeadersLink Lens
tokenPaginationResponseHeadersLinkL :: Lens_' TokenPaginationResponseHeaders (Maybe Text)
-- | tokenPaginationResponseHeadersXTotalCount Lens
tokenPaginationResponseHeadersXTotalCountL :: Lens_' TokenPaginationResponseHeaders (Maybe Integer)
-- | trustOAuth2JwtGrantIssuerAllowAnySubject Lens
trustOAuth2JwtGrantIssuerAllowAnySubjectL :: Lens_' TrustOAuth2JwtGrantIssuer (Maybe Bool)
-- | trustOAuth2JwtGrantIssuerExpiresAt Lens
trustOAuth2JwtGrantIssuerExpiresAtL :: Lens_' TrustOAuth2JwtGrantIssuer DateTime
-- | trustOAuth2JwtGrantIssuerIssuer Lens
trustOAuth2JwtGrantIssuerIssuerL :: Lens_' TrustOAuth2JwtGrantIssuer Text
-- | trustOAuth2JwtGrantIssuerJwk Lens
trustOAuth2JwtGrantIssuerJwkL :: Lens_' TrustOAuth2JwtGrantIssuer JsonWebKey
-- | trustOAuth2JwtGrantIssuerScope Lens
trustOAuth2JwtGrantIssuerScopeL :: Lens_' TrustOAuth2JwtGrantIssuer [Text]
-- | trustOAuth2JwtGrantIssuerSubject Lens
trustOAuth2JwtGrantIssuerSubjectL :: Lens_' TrustOAuth2JwtGrantIssuer (Maybe Text)
-- | trustedOAuth2JwtGrantIssuerAllowAnySubject Lens
trustedOAuth2JwtGrantIssuerAllowAnySubjectL :: Lens_' TrustedOAuth2JwtGrantIssuer (Maybe Bool)
-- | trustedOAuth2JwtGrantIssuerCreatedAt Lens
trustedOAuth2JwtGrantIssuerCreatedAtL :: Lens_' TrustedOAuth2JwtGrantIssuer (Maybe DateTime)
-- | trustedOAuth2JwtGrantIssuerExpiresAt Lens
trustedOAuth2JwtGrantIssuerExpiresAtL :: Lens_' TrustedOAuth2JwtGrantIssuer (Maybe DateTime)
-- | trustedOAuth2JwtGrantIssuerId Lens
trustedOAuth2JwtGrantIssuerIdL :: Lens_' TrustedOAuth2JwtGrantIssuer (Maybe Text)
-- | trustedOAuth2JwtGrantIssuerIssuer Lens
trustedOAuth2JwtGrantIssuerIssuerL :: Lens_' TrustedOAuth2JwtGrantIssuer (Maybe Text)
-- | trustedOAuth2JwtGrantIssuerPublicKey Lens
trustedOAuth2JwtGrantIssuerPublicKeyL :: Lens_' TrustedOAuth2JwtGrantIssuer (Maybe TrustedOAuth2JwtGrantJsonWebKey)
-- | trustedOAuth2JwtGrantIssuerScope Lens
trustedOAuth2JwtGrantIssuerScopeL :: Lens_' TrustedOAuth2JwtGrantIssuer (Maybe [Text])
-- | trustedOAuth2JwtGrantIssuerSubject Lens
trustedOAuth2JwtGrantIssuerSubjectL :: Lens_' TrustedOAuth2JwtGrantIssuer (Maybe Text)
-- | trustedOAuth2JwtGrantJsonWebKeyKid Lens
trustedOAuth2JwtGrantJsonWebKeyKidL :: Lens_' TrustedOAuth2JwtGrantJsonWebKey (Maybe Text)
-- | trustedOAuth2JwtGrantJsonWebKeySet Lens
trustedOAuth2JwtGrantJsonWebKeySetL :: Lens_' TrustedOAuth2JwtGrantJsonWebKey (Maybe Text)
-- | versionVersion Lens
versionVersionL :: Lens_' Version (Maybe Text)
module ORYHydra