{-
   Ory Hydra API

   Documentation for all of Ory Hydra's APIs. 

   OpenAPI Version: 3.0.3
   Ory Hydra API API version: 
   Contact: hi@ory.sh
   Generated by OpenAPI Generator (https://openapi-generator.tech)
-}

{-|
Module : OryHydra.API.OAuth2
-}

{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MonoLocalBinds #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
{-# OPTIONS_GHC -fno-warn-name-shadowing -fno-warn-unused-binds -fno-warn-unused-imports #-}

module OryHydra.API.OAuth2 where

import OryHydra.Core
import OryHydra.MimeTypes
import OryHydra.Model as M

import qualified Data.Aeson as A
import qualified Data.ByteString as B
import qualified Data.ByteString.Lazy as BL
import qualified Data.Data as P (Typeable, TypeRep, typeOf, typeRep)
import qualified Data.Foldable as P
import qualified Data.Map as Map
import qualified Data.Maybe as P
import qualified Data.Proxy as P (Proxy(..))
import qualified Data.Set as Set
import qualified Data.String as P
import qualified Data.Text as T
import qualified Data.Text.Encoding as T
import qualified Data.Text.Lazy as TL
import qualified Data.Text.Lazy.Encoding as TL
import qualified Data.Time as TI
import qualified Network.HTTP.Client.MultipartFormData as NH
import qualified Network.HTTP.Media as ME
import qualified Network.HTTP.Types as NH
import qualified Web.FormUrlEncoded as WH
import qualified Web.HttpApiData as WH

import Data.Text (Text)
import GHC.Base ((<|>))

import Prelude ((==),(/=),($), (.),(<$>),(<*>),(>>=),Maybe(..),Bool(..),Char,Double,FilePath,Float,Int,Integer,String,fmap,undefined,mempty,maybe,pure,Monad,Applicative,Functor)
import qualified Prelude as P

-- * Operations


-- ** OAuth2

-- *** acceptOAuth2ConsentRequest0

-- | @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, 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.  This endpoint tells Ory that the subject has authorized the OAuth 2.0 client to access resources on his/her 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 -- ^ "consentChallenge" -  OAuth 2.0 Consent Request Challenge
  -> OryHydraRequest AcceptOAuth2ConsentRequest0 MimeJSON OAuth2RedirectTo MimeJSON
acceptOAuth2ConsentRequest0 :: Consumes AcceptOAuth2ConsentRequest0 MimeJSON =>
ConsentChallenge
-> OryHydraRequest
     AcceptOAuth2ConsentRequest0 MimeJSON OAuth2RedirectTo MimeJSON
acceptOAuth2ConsentRequest0 (ConsentChallenge Text
consentChallenge) =
  forall req contentType res accept.
Method
-> [ByteString] -> OryHydraRequest req contentType res accept
_mkRequest Method
"PUT" [ByteString
"/admin/oauth2/auth/requests/consent/accept"]
    forall req contentType res accept.
OryHydraRequest req contentType res accept
-> [QueryItem] -> OryHydraRequest req contentType res accept
`addQuery` forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"consent_challenge", forall a. a -> Maybe a
Just Text
consentChallenge)

data AcceptOAuth2ConsentRequest0 
instance HasBodyParam AcceptOAuth2ConsentRequest0 AcceptOAuth2ConsentRequest 

-- | @application/json@
instance Consumes AcceptOAuth2ConsentRequest0 MimeJSON

-- | @application/json@
instance Produces AcceptOAuth2ConsentRequest0 MimeJSON


-- *** acceptOAuth2LoginRequest0

-- | @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 -- ^ "loginChallenge" -  OAuth 2.0 Login Request Challenge
  -> OryHydraRequest AcceptOAuth2LoginRequest0 MimeJSON OAuth2RedirectTo MimeJSON
acceptOAuth2LoginRequest0 :: Consumes AcceptOAuth2LoginRequest0 MimeJSON =>
LoginChallenge
-> OryHydraRequest
     AcceptOAuth2LoginRequest0 MimeJSON OAuth2RedirectTo MimeJSON
acceptOAuth2LoginRequest0 (LoginChallenge Text
loginChallenge) =
  forall req contentType res accept.
Method
-> [ByteString] -> OryHydraRequest req contentType res accept
_mkRequest Method
"PUT" [ByteString
"/admin/oauth2/auth/requests/login/accept"]
    forall req contentType res accept.
OryHydraRequest req contentType res accept
-> [QueryItem] -> OryHydraRequest req contentType res accept
`addQuery` forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"login_challenge", forall a. a -> Maybe a
Just Text
loginChallenge)

data AcceptOAuth2LoginRequest0 
instance HasBodyParam AcceptOAuth2LoginRequest0 AcceptOAuth2LoginRequest 

-- | @application/json@
instance Consumes AcceptOAuth2LoginRequest0 MimeJSON

-- | @application/json@
instance Produces AcceptOAuth2LoginRequest0 MimeJSON


-- *** acceptOAuth2LogoutRequest

-- | @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 -- ^ "logoutChallenge" -  OAuth 2.0 Logout Request Challenge
  -> OryHydraRequest AcceptOAuth2LogoutRequest MimeNoContent OAuth2RedirectTo MimeJSON
acceptOAuth2LogoutRequest :: LogoutChallenge
-> OryHydraRequest
     AcceptOAuth2LogoutRequest MimeNoContent OAuth2RedirectTo MimeJSON
acceptOAuth2LogoutRequest (LogoutChallenge Text
logoutChallenge) =
  forall req contentType res accept.
Method
-> [ByteString] -> OryHydraRequest req contentType res accept
_mkRequest Method
"PUT" [ByteString
"/admin/oauth2/auth/requests/logout/accept"]
    forall req contentType res accept.
OryHydraRequest req contentType res accept
-> [QueryItem] -> OryHydraRequest req contentType res accept
`addQuery` forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"logout_challenge", forall a. a -> Maybe a
Just Text
logoutChallenge)

data AcceptOAuth2LogoutRequest  
-- | @application/json@
instance Produces AcceptOAuth2LogoutRequest MimeJSON


-- *** createOAuth2Client

-- | @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 -- ^ "oAuth2Client" -  OAuth 2.0 Client Request Body
  -> OryHydraRequest CreateOAuth2Client MimeJSON OAuth2Client MimeJSON
createOAuth2Client :: (Consumes CreateOAuth2Client MimeJSON,
 MimeRender MimeJSON OAuth2Client) =>
OAuth2Client
-> OryHydraRequest
     CreateOAuth2Client MimeJSON OAuth2Client MimeJSON
createOAuth2Client OAuth2Client
oAuth2Client =
  forall req contentType res accept.
Method
-> [ByteString] -> OryHydraRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/admin/clients"]
    forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
OryHydraRequest req contentType res accept
-> param -> OryHydraRequest req contentType res accept
`setBodyParam` OAuth2Client
oAuth2Client

data CreateOAuth2Client 

-- | /Body Param/ "OAuth2Client" - OAuth 2.0 Client Request Body
instance HasBodyParam CreateOAuth2Client OAuth2Client 

-- | @application/json@
instance Consumes CreateOAuth2Client MimeJSON

-- | @application/json@
instance Produces CreateOAuth2Client MimeJSON


-- *** deleteOAuth2Client

-- | @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 -- ^ "id" -  The id of the OAuth 2.0 Client.
  -> OryHydraRequest DeleteOAuth2Client MimeNoContent NoContent MimeNoContent
deleteOAuth2Client :: Id
-> OryHydraRequest
     DeleteOAuth2Client MimeNoContent NoContent MimeNoContent
deleteOAuth2Client (Id Text
id) =
  forall req contentType res accept.
Method
-> [ByteString] -> OryHydraRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/admin/clients/",forall a. ToHttpApiData a => a -> ByteString
toPath Text
id]

data DeleteOAuth2Client  
instance Produces DeleteOAuth2Client MimeNoContent


-- *** deleteOAuth2Token

-- | @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 -- ^ "clientId" -  OAuth 2.0 Client ID
  -> OryHydraRequest DeleteOAuth2Token MimeNoContent NoContent MimeNoContent
deleteOAuth2Token :: ClientId
-> OryHydraRequest
     DeleteOAuth2Token MimeNoContent NoContent MimeNoContent
deleteOAuth2Token (ClientId Text
clientId) =
  forall req contentType res accept.
Method
-> [ByteString] -> OryHydraRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/admin/oauth2/tokens"]
    forall req contentType res accept.
OryHydraRequest req contentType res accept
-> [QueryItem] -> OryHydraRequest req contentType res accept
`addQuery` forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"client_id", forall a. a -> Maybe a
Just Text
clientId)

data DeleteOAuth2Token  
instance Produces DeleteOAuth2Token MimeNoContent


-- *** deleteTrustedOAuth2JwtGrantIssuer

-- | @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 -- ^ "id" -  The id of the desired grant
  -> OryHydraRequest DeleteTrustedOAuth2JwtGrantIssuer MimeNoContent NoContent MimeNoContent
deleteTrustedOAuth2JwtGrantIssuer :: Id
-> OryHydraRequest
     DeleteTrustedOAuth2JwtGrantIssuer
     MimeNoContent
     NoContent
     MimeNoContent
deleteTrustedOAuth2JwtGrantIssuer (Id Text
id) =
  forall req contentType res accept.
Method
-> [ByteString] -> OryHydraRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/admin/trust/grants/jwt-bearer/issuers/",forall a. ToHttpApiData a => a -> ByteString
toPath Text
id]

data DeleteTrustedOAuth2JwtGrantIssuer  
instance Produces DeleteTrustedOAuth2JwtGrantIssuer MimeNoContent


-- *** getOAuth2Client

-- | @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 -- ^ "id" -  The id of the OAuth 2.0 Client.
  -> OryHydraRequest GetOAuth2Client MimeNoContent OAuth2Client MimeJSON
getOAuth2Client :: Id
-> OryHydraRequest
     GetOAuth2Client MimeNoContent OAuth2Client MimeJSON
getOAuth2Client (Id Text
id) =
  forall req contentType res accept.
Method
-> [ByteString] -> OryHydraRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/admin/clients/",forall a. ToHttpApiData a => a -> ByteString
toPath Text
id]

data GetOAuth2Client  
-- | @application/json@
instance Produces GetOAuth2Client MimeJSON


-- *** getOAuth2ConsentRequest

-- | @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 -- ^ "consentChallenge" -  OAuth 2.0 Consent Request Challenge
  -> OryHydraRequest GetOAuth2ConsentRequest MimeNoContent OAuth2ConsentRequest MimeJSON
getOAuth2ConsentRequest :: ConsentChallenge
-> OryHydraRequest
     GetOAuth2ConsentRequest MimeNoContent OAuth2ConsentRequest MimeJSON
getOAuth2ConsentRequest (ConsentChallenge Text
consentChallenge) =
  forall req contentType res accept.
Method
-> [ByteString] -> OryHydraRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/admin/oauth2/auth/requests/consent"]
    forall req contentType res accept.
OryHydraRequest req contentType res accept
-> [QueryItem] -> OryHydraRequest req contentType res accept
`addQuery` forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"consent_challenge", forall a. a -> Maybe a
Just Text
consentChallenge)

data GetOAuth2ConsentRequest  
-- | @application/json@
instance Produces GetOAuth2ConsentRequest MimeJSON


-- *** getOAuth2LoginRequest

-- | @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 -- ^ "loginChallenge" -  OAuth 2.0 Login Request Challenge
  -> OryHydraRequest GetOAuth2LoginRequest MimeNoContent OAuth2LoginRequest MimeJSON
getOAuth2LoginRequest :: LoginChallenge
-> OryHydraRequest
     GetOAuth2LoginRequest MimeNoContent OAuth2LoginRequest MimeJSON
getOAuth2LoginRequest (LoginChallenge Text
loginChallenge) =
  forall req contentType res accept.
Method
-> [ByteString] -> OryHydraRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/admin/oauth2/auth/requests/login"]
    forall req contentType res accept.
OryHydraRequest req contentType res accept
-> [QueryItem] -> OryHydraRequest req contentType res accept
`addQuery` forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"login_challenge", forall a. a -> Maybe a
Just Text
loginChallenge)

data GetOAuth2LoginRequest  
-- | @application/json@
instance Produces GetOAuth2LoginRequest MimeJSON


-- *** getOAuth2LogoutRequest

-- | @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 -- ^ "logoutChallenge"
  -> OryHydraRequest GetOAuth2LogoutRequest MimeNoContent OAuth2LogoutRequest MimeJSON
getOAuth2LogoutRequest :: LogoutChallenge
-> OryHydraRequest
     GetOAuth2LogoutRequest MimeNoContent OAuth2LogoutRequest MimeJSON
getOAuth2LogoutRequest (LogoutChallenge Text
logoutChallenge) =
  forall req contentType res accept.
Method
-> [ByteString] -> OryHydraRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/admin/oauth2/auth/requests/logout"]
    forall req contentType res accept.
OryHydraRequest req contentType res accept
-> [QueryItem] -> OryHydraRequest req contentType res accept
`addQuery` forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"logout_challenge", forall a. a -> Maybe a
Just Text
logoutChallenge)

data GetOAuth2LogoutRequest  
-- | @application/json@
instance Produces GetOAuth2LogoutRequest MimeJSON


-- *** getTrustedOAuth2JwtGrantIssuer

-- | @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 -- ^ "id" -  The id of the desired grant
  -> OryHydraRequest GetTrustedOAuth2JwtGrantIssuer MimeNoContent TrustedOAuth2JwtGrantIssuer MimeJSON
getTrustedOAuth2JwtGrantIssuer :: Id
-> OryHydraRequest
     GetTrustedOAuth2JwtGrantIssuer
     MimeNoContent
     TrustedOAuth2JwtGrantIssuer
     MimeJSON
getTrustedOAuth2JwtGrantIssuer (Id Text
id) =
  forall req contentType res accept.
Method
-> [ByteString] -> OryHydraRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/admin/trust/grants/jwt-bearer/issuers/",forall a. ToHttpApiData a => a -> ByteString
toPath Text
id]

data GetTrustedOAuth2JwtGrantIssuer  
-- | @application/json@
instance Produces GetTrustedOAuth2JwtGrantIssuer MimeJSON


-- *** introspectOAuth2Token

-- | @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 -- ^ "token" -  The string value of the token. For access tokens, this is the \\\"access_token\\\" value returned from the token endpoint defined in OAuth 2.0. For refresh tokens, this is the \\\"refresh_token\\\" value returned.
  -> OryHydraRequest IntrospectOAuth2Token MimeFormUrlEncoded IntrospectedOAuth2Token MimeJSON
introspectOAuth2Token :: Consumes IntrospectOAuth2Token MimeFormUrlEncoded =>
Token
-> OryHydraRequest
     IntrospectOAuth2Token
     MimeFormUrlEncoded
     IntrospectedOAuth2Token
     MimeJSON
introspectOAuth2Token (Token Text
token) =
  forall req contentType res accept.
Method
-> [ByteString] -> OryHydraRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/admin/oauth2/introspect"]
    forall req contentType res accept.
OryHydraRequest req contentType res accept
-> Form -> OryHydraRequest req contentType res accept
`addForm` forall v. ToHttpApiData v => (Method, v) -> Form
toForm (Method
"token", Text
token)

data IntrospectOAuth2Token  

-- | /Optional Param/ "scope" - An optional, space separated list of required scopes. If the access token was not granted one of the scopes, the result of active will be false.
instance HasOptionalParam IntrospectOAuth2Token Scope where
  applyOptionalParam :: forall contentType res accept.
OryHydraRequest IntrospectOAuth2Token contentType res accept
-> Scope
-> OryHydraRequest IntrospectOAuth2Token contentType res accept
applyOptionalParam OryHydraRequest IntrospectOAuth2Token contentType res accept
req (Scope Text
xs) =
    OryHydraRequest IntrospectOAuth2Token contentType res accept
req forall req contentType res accept.
OryHydraRequest req contentType res accept
-> Form -> OryHydraRequest req contentType res accept
`addForm` forall v. ToHttpApiData v => (Method, v) -> Form
toForm (Method
"scope", Text
xs)

-- | @application/x-www-form-urlencoded@
instance Consumes IntrospectOAuth2Token MimeFormUrlEncoded

-- | @application/json@
instance Produces IntrospectOAuth2Token MimeJSON


-- *** listOAuth2Clients

-- | @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
listOAuth2Clients :: OryHydraRequest
  ListOAuth2Clients MimeNoContent [OAuth2Client] MimeJSON
listOAuth2Clients =
  forall req contentType res accept.
Method
-> [ByteString] -> OryHydraRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/admin/clients"]

data ListOAuth2Clients  

-- | /Optional Param/ "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](https://www.ory.sh/docs/ecosystem/api-design#pagination).
instance HasOptionalParam ListOAuth2Clients PageSize where
  applyOptionalParam :: forall contentType res accept.
OryHydraRequest ListOAuth2Clients contentType res accept
-> PageSize
-> OryHydraRequest ListOAuth2Clients contentType res accept
applyOptionalParam OryHydraRequest ListOAuth2Clients contentType res accept
req (PageSize Integer
xs) =
    OryHydraRequest ListOAuth2Clients contentType res accept
req forall req contentType res accept.
OryHydraRequest req contentType res accept
-> [QueryItem] -> OryHydraRequest req contentType res accept
`addQuery` forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"page_size", forall a. a -> Maybe a
Just Integer
xs)

-- | /Optional Param/ "page_token" - Next Page Token  The next page token. For details on pagination please head over to the [pagination documentation](https://www.ory.sh/docs/ecosystem/api-design#pagination).
instance HasOptionalParam ListOAuth2Clients PageToken where
  applyOptionalParam :: forall contentType res accept.
OryHydraRequest ListOAuth2Clients contentType res accept
-> PageToken
-> OryHydraRequest ListOAuth2Clients contentType res accept
applyOptionalParam OryHydraRequest ListOAuth2Clients contentType res accept
req (PageToken Text
xs) =
    OryHydraRequest ListOAuth2Clients contentType res accept
req forall req contentType res accept.
OryHydraRequest req contentType res accept
-> [QueryItem] -> OryHydraRequest req contentType res accept
`addQuery` forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"page_token", forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "client_name" - The name of the clients to filter by.
instance HasOptionalParam ListOAuth2Clients ClientName where
  applyOptionalParam :: forall contentType res accept.
OryHydraRequest ListOAuth2Clients contentType res accept
-> ClientName
-> OryHydraRequest ListOAuth2Clients contentType res accept
applyOptionalParam OryHydraRequest ListOAuth2Clients contentType res accept
req (ClientName Text
xs) =
    OryHydraRequest ListOAuth2Clients contentType res accept
req forall req contentType res accept.
OryHydraRequest req contentType res accept
-> [QueryItem] -> OryHydraRequest req contentType res accept
`addQuery` forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"client_name", forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "owner" - The owner of the clients to filter by.
instance HasOptionalParam ListOAuth2Clients Owner where
  applyOptionalParam :: forall contentType res accept.
OryHydraRequest ListOAuth2Clients contentType res accept
-> Owner
-> OryHydraRequest ListOAuth2Clients contentType res accept
applyOptionalParam OryHydraRequest ListOAuth2Clients contentType res accept
req (Owner Text
xs) =
    OryHydraRequest ListOAuth2Clients contentType res accept
req forall req contentType res accept.
OryHydraRequest req contentType res accept
-> [QueryItem] -> OryHydraRequest req contentType res accept
`addQuery` forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"owner", forall a. a -> Maybe a
Just Text
xs)
-- | @application/json@
instance Produces ListOAuth2Clients MimeJSON


-- *** listOAuth2ConsentSessions

-- | @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 -- ^ "subject" -  The subject to list the consent sessions for.
  -> OryHydraRequest ListOAuth2ConsentSessions MimeNoContent [OAuth2ConsentSession] MimeJSON
listOAuth2ConsentSessions :: Subject
-> OryHydraRequest
     ListOAuth2ConsentSessions
     MimeNoContent
     [OAuth2ConsentSession]
     MimeJSON
listOAuth2ConsentSessions (Subject Text
subject) =
  forall req contentType res accept.
Method
-> [ByteString] -> OryHydraRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/admin/oauth2/auth/sessions/consent"]
    forall req contentType res accept.
OryHydraRequest req contentType res accept
-> [QueryItem] -> OryHydraRequest req contentType res accept
`addQuery` forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"subject", forall a. a -> Maybe a
Just Text
subject)

data ListOAuth2ConsentSessions  

-- | /Optional Param/ "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](https://www.ory.sh/docs/ecosystem/api-design#pagination).
instance HasOptionalParam ListOAuth2ConsentSessions PageSize where
  applyOptionalParam :: forall contentType res accept.
OryHydraRequest ListOAuth2ConsentSessions contentType res accept
-> PageSize
-> OryHydraRequest ListOAuth2ConsentSessions contentType res accept
applyOptionalParam OryHydraRequest ListOAuth2ConsentSessions contentType res accept
req (PageSize Integer
xs) =
    OryHydraRequest ListOAuth2ConsentSessions contentType res accept
req forall req contentType res accept.
OryHydraRequest req contentType res accept
-> [QueryItem] -> OryHydraRequest req contentType res accept
`addQuery` forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"page_size", forall a. a -> Maybe a
Just Integer
xs)

-- | /Optional Param/ "page_token" - Next Page Token  The next page token. For details on pagination please head over to the [pagination documentation](https://www.ory.sh/docs/ecosystem/api-design#pagination).
instance HasOptionalParam ListOAuth2ConsentSessions PageToken where
  applyOptionalParam :: forall contentType res accept.
OryHydraRequest ListOAuth2ConsentSessions contentType res accept
-> PageToken
-> OryHydraRequest ListOAuth2ConsentSessions contentType res accept
applyOptionalParam OryHydraRequest ListOAuth2ConsentSessions contentType res accept
req (PageToken Text
xs) =
    OryHydraRequest ListOAuth2ConsentSessions contentType res accept
req forall req contentType res accept.
OryHydraRequest req contentType res accept
-> [QueryItem] -> OryHydraRequest req contentType res accept
`addQuery` forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"page_token", forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "login_session_id" - The login session id to list the consent sessions for.
instance HasOptionalParam ListOAuth2ConsentSessions LoginSessionId where
  applyOptionalParam :: forall contentType res accept.
OryHydraRequest ListOAuth2ConsentSessions contentType res accept
-> LoginSessionId
-> OryHydraRequest ListOAuth2ConsentSessions contentType res accept
applyOptionalParam OryHydraRequest ListOAuth2ConsentSessions contentType res accept
req (LoginSessionId Text
xs) =
    OryHydraRequest ListOAuth2ConsentSessions contentType res accept
req forall req contentType res accept.
OryHydraRequest req contentType res accept
-> [QueryItem] -> OryHydraRequest req contentType res accept
`addQuery` forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"login_session_id", forall a. a -> Maybe a
Just Text
xs)
-- | @application/json@
instance Produces ListOAuth2ConsentSessions MimeJSON


-- *** listTrustedOAuth2JwtGrantIssuers

-- | @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
listTrustedOAuth2JwtGrantIssuers :: OryHydraRequest
  ListTrustedOAuth2JwtGrantIssuers
  MimeNoContent
  [TrustedOAuth2JwtGrantIssuer]
  MimeJSON
listTrustedOAuth2JwtGrantIssuers =
  forall req contentType res accept.
Method
-> [ByteString] -> OryHydraRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/admin/trust/grants/jwt-bearer/issuers"]

data ListTrustedOAuth2JwtGrantIssuers  
instance HasOptionalParam ListTrustedOAuth2JwtGrantIssuers MaxItems where
  applyOptionalParam :: forall contentType res accept.
OryHydraRequest
  ListTrustedOAuth2JwtGrantIssuers contentType res accept
-> MaxItems
-> OryHydraRequest
     ListTrustedOAuth2JwtGrantIssuers contentType res accept
applyOptionalParam OryHydraRequest
  ListTrustedOAuth2JwtGrantIssuers contentType res accept
req (MaxItems Integer
xs) =
    OryHydraRequest
  ListTrustedOAuth2JwtGrantIssuers contentType res accept
req forall req contentType res accept.
OryHydraRequest req contentType res accept
-> [QueryItem] -> OryHydraRequest req contentType res accept
`addQuery` forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"MaxItems", forall a. a -> Maybe a
Just Integer
xs)
instance HasOptionalParam ListTrustedOAuth2JwtGrantIssuers DefaultItems where
  applyOptionalParam :: forall contentType res accept.
OryHydraRequest
  ListTrustedOAuth2JwtGrantIssuers contentType res accept
-> DefaultItems
-> OryHydraRequest
     ListTrustedOAuth2JwtGrantIssuers contentType res accept
applyOptionalParam OryHydraRequest
  ListTrustedOAuth2JwtGrantIssuers contentType res accept
req (DefaultItems Integer
xs) =
    OryHydraRequest
  ListTrustedOAuth2JwtGrantIssuers contentType res accept
req forall req contentType res accept.
OryHydraRequest req contentType res accept
-> [QueryItem] -> OryHydraRequest req contentType res accept
`addQuery` forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"DefaultItems", forall a. a -> Maybe a
Just Integer
xs)

-- | /Optional Param/ "issuer" - If optional \"issuer\" is supplied, only jwt-bearer grants with this issuer will be returned.
instance HasOptionalParam ListTrustedOAuth2JwtGrantIssuers Issuer where
  applyOptionalParam :: forall contentType res accept.
OryHydraRequest
  ListTrustedOAuth2JwtGrantIssuers contentType res accept
-> Issuer
-> OryHydraRequest
     ListTrustedOAuth2JwtGrantIssuers contentType res accept
applyOptionalParam OryHydraRequest
  ListTrustedOAuth2JwtGrantIssuers contentType res accept
req (Issuer Text
xs) =
    OryHydraRequest
  ListTrustedOAuth2JwtGrantIssuers contentType res accept
req forall req contentType res accept.
OryHydraRequest req contentType res accept
-> [QueryItem] -> OryHydraRequest req contentType res accept
`addQuery` forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"issuer", forall a. a -> Maybe a
Just Text
xs)
-- | @application/json@
instance Produces ListTrustedOAuth2JwtGrantIssuers MimeJSON


-- *** oAuth2Authorize

-- | @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
oAuth2Authorize :: OryHydraRequest OAuth2Authorize MimeNoContent ErrorOAuth2 MimeJSON
oAuth2Authorize =
  forall req contentType res accept.
Method
-> [ByteString] -> OryHydraRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/oauth2/auth"]

data OAuth2Authorize  
-- | @application/json@
instance Produces OAuth2Authorize MimeJSON


-- *** oauth2TokenExchange

-- | @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 -- ^ "grantType"
  -> OryHydraRequest Oauth2TokenExchange MimeFormUrlEncoded OAuth2TokenExchange MimeJSON
oauth2TokenExchange :: Consumes Oauth2TokenExchange MimeFormUrlEncoded =>
GrantType
-> OryHydraRequest
     Oauth2TokenExchange MimeFormUrlEncoded OAuth2TokenExchange MimeJSON
oauth2TokenExchange (GrantType Text
grantType) =
  forall req contentType res accept.
Method
-> [ByteString] -> OryHydraRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/oauth2/token"]
    forall authMethod req contentType res accept.
AuthMethod authMethod =>
OryHydraRequest req contentType res accept
-> Proxy authMethod -> OryHydraRequest req contentType res accept
`_hasAuthType` (forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasic)
    forall authMethod req contentType res accept.
AuthMethod authMethod =>
OryHydraRequest req contentType res accept
-> Proxy authMethod -> OryHydraRequest req contentType res accept
`_hasAuthType` (forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthOAuthOauth2)
    forall req contentType res accept.
OryHydraRequest req contentType res accept
-> Form -> OryHydraRequest req contentType res accept
`addForm` forall v. ToHttpApiData v => (Method, v) -> Form
toForm (Method
"grant_type", Text
grantType)

data Oauth2TokenExchange  
instance HasOptionalParam Oauth2TokenExchange ClientId where
  applyOptionalParam :: forall contentType res accept.
OryHydraRequest Oauth2TokenExchange contentType res accept
-> ClientId
-> OryHydraRequest Oauth2TokenExchange contentType res accept
applyOptionalParam OryHydraRequest Oauth2TokenExchange contentType res accept
req (ClientId Text
xs) =
    OryHydraRequest Oauth2TokenExchange contentType res accept
req forall req contentType res accept.
OryHydraRequest req contentType res accept
-> Form -> OryHydraRequest req contentType res accept
`addForm` forall v. ToHttpApiData v => (Method, v) -> Form
toForm (Method
"client_id", Text
xs)
instance HasOptionalParam Oauth2TokenExchange Code where
  applyOptionalParam :: forall contentType res accept.
OryHydraRequest Oauth2TokenExchange contentType res accept
-> Code
-> OryHydraRequest Oauth2TokenExchange contentType res accept
applyOptionalParam OryHydraRequest Oauth2TokenExchange contentType res accept
req (Code Text
xs) =
    OryHydraRequest Oauth2TokenExchange contentType res accept
req forall req contentType res accept.
OryHydraRequest req contentType res accept
-> Form -> OryHydraRequest req contentType res accept
`addForm` forall v. ToHttpApiData v => (Method, v) -> Form
toForm (Method
"code", Text
xs)
instance HasOptionalParam Oauth2TokenExchange RedirectUri where
  applyOptionalParam :: forall contentType res accept.
OryHydraRequest Oauth2TokenExchange contentType res accept
-> RedirectUri
-> OryHydraRequest Oauth2TokenExchange contentType res accept
applyOptionalParam OryHydraRequest Oauth2TokenExchange contentType res accept
req (RedirectUri Text
xs) =
    OryHydraRequest Oauth2TokenExchange contentType res accept
req forall req contentType res accept.
OryHydraRequest req contentType res accept
-> Form -> OryHydraRequest req contentType res accept
`addForm` forall v. ToHttpApiData v => (Method, v) -> Form
toForm (Method
"redirect_uri", Text
xs)
instance HasOptionalParam Oauth2TokenExchange RefreshToken where
  applyOptionalParam :: forall contentType res accept.
OryHydraRequest Oauth2TokenExchange contentType res accept
-> RefreshToken
-> OryHydraRequest Oauth2TokenExchange contentType res accept
applyOptionalParam OryHydraRequest Oauth2TokenExchange contentType res accept
req (RefreshToken Text
xs) =
    OryHydraRequest Oauth2TokenExchange contentType res accept
req forall req contentType res accept.
OryHydraRequest req contentType res accept
-> Form -> OryHydraRequest req contentType res accept
`addForm` forall v. ToHttpApiData v => (Method, v) -> Form
toForm (Method
"refresh_token", Text
xs)

-- | @application/x-www-form-urlencoded@
instance Consumes Oauth2TokenExchange MimeFormUrlEncoded

-- | @application/json@
instance Produces Oauth2TokenExchange MimeJSON


-- *** patchOAuth2Client

-- | @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 -- ^ "jsonPatch" -  OAuth 2.0 Client JSON Patch Body
  -> Id -- ^ "id" -  The id of the OAuth 2.0 Client.
  -> OryHydraRequest PatchOAuth2Client MimeJSON OAuth2Client MimeJSON
patchOAuth2Client :: (Consumes PatchOAuth2Client MimeJSON,
 MimeRender MimeJSON JsonPatch2) =>
JsonPatch2
-> Id
-> OryHydraRequest PatchOAuth2Client MimeJSON OAuth2Client MimeJSON
patchOAuth2Client JsonPatch2
jsonPatch (Id Text
id) =
  forall req contentType res accept.
Method
-> [ByteString] -> OryHydraRequest req contentType res accept
_mkRequest Method
"PATCH" [ByteString
"/admin/clients/",forall a. ToHttpApiData a => a -> ByteString
toPath Text
id]
    forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
OryHydraRequest req contentType res accept
-> param -> OryHydraRequest req contentType res accept
`setBodyParam` JsonPatch2
jsonPatch

data PatchOAuth2Client 

-- | /Body Param/ "JsonPatch" - OAuth 2.0 Client JSON Patch Body
instance HasBodyParam PatchOAuth2Client JsonPatch2 

-- | @application/json@
instance Consumes PatchOAuth2Client MimeJSON

-- | @application/json@
instance Produces PatchOAuth2Client MimeJSON


-- *** rejectOAuth2ConsentRequest

-- | @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, 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.  This endpoint tells Ory that the subject has not authorized the OAuth 2.0 client to access resources on his/her 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 -- ^ "consentChallenge" -  OAuth 2.0 Consent Request Challenge
  -> OryHydraRequest RejectOAuth2ConsentRequest MimeJSON OAuth2RedirectTo MimeJSON
rejectOAuth2ConsentRequest :: Consumes RejectOAuth2ConsentRequest MimeJSON =>
ConsentChallenge
-> OryHydraRequest
     RejectOAuth2ConsentRequest MimeJSON OAuth2RedirectTo MimeJSON
rejectOAuth2ConsentRequest (ConsentChallenge Text
consentChallenge) =
  forall req contentType res accept.
Method
-> [ByteString] -> OryHydraRequest req contentType res accept
_mkRequest Method
"PUT" [ByteString
"/admin/oauth2/auth/requests/consent/reject"]
    forall req contentType res accept.
OryHydraRequest req contentType res accept
-> [QueryItem] -> OryHydraRequest req contentType res accept
`addQuery` forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"consent_challenge", forall a. a -> Maybe a
Just Text
consentChallenge)

data RejectOAuth2ConsentRequest 
instance HasBodyParam RejectOAuth2ConsentRequest RejectOAuth2Request 

-- | @application/json@
instance Consumes RejectOAuth2ConsentRequest MimeJSON

-- | @application/json@
instance Produces RejectOAuth2ConsentRequest MimeJSON


-- *** rejectOAuth2LoginRequest

-- | @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 -- ^ "loginChallenge" -  OAuth 2.0 Login Request Challenge
  -> OryHydraRequest RejectOAuth2LoginRequest MimeJSON OAuth2RedirectTo MimeJSON
rejectOAuth2LoginRequest :: Consumes RejectOAuth2LoginRequest MimeJSON =>
LoginChallenge
-> OryHydraRequest
     RejectOAuth2LoginRequest MimeJSON OAuth2RedirectTo MimeJSON
rejectOAuth2LoginRequest (LoginChallenge Text
loginChallenge) =
  forall req contentType res accept.
Method
-> [ByteString] -> OryHydraRequest req contentType res accept
_mkRequest Method
"PUT" [ByteString
"/admin/oauth2/auth/requests/login/reject"]
    forall req contentType res accept.
OryHydraRequest req contentType res accept
-> [QueryItem] -> OryHydraRequest req contentType res accept
`addQuery` forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"login_challenge", forall a. a -> Maybe a
Just Text
loginChallenge)

data RejectOAuth2LoginRequest 
instance HasBodyParam RejectOAuth2LoginRequest RejectOAuth2Request 

-- | @application/json@
instance Consumes RejectOAuth2LoginRequest MimeJSON

-- | @application/json@
instance Produces RejectOAuth2LoginRequest MimeJSON


-- *** rejectOAuth2LogoutRequest

-- | @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 -- ^ "logoutChallenge"
  -> OryHydraRequest RejectOAuth2LogoutRequest MimeNoContent NoContent MimeNoContent
rejectOAuth2LogoutRequest :: LogoutChallenge
-> OryHydraRequest
     RejectOAuth2LogoutRequest MimeNoContent NoContent MimeNoContent
rejectOAuth2LogoutRequest (LogoutChallenge Text
logoutChallenge) =
  forall req contentType res accept.
Method
-> [ByteString] -> OryHydraRequest req contentType res accept
_mkRequest Method
"PUT" [ByteString
"/admin/oauth2/auth/requests/logout/reject"]
    forall req contentType res accept.
OryHydraRequest req contentType res accept
-> [QueryItem] -> OryHydraRequest req contentType res accept
`addQuery` forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"logout_challenge", forall a. a -> Maybe a
Just Text
logoutChallenge)

data RejectOAuth2LogoutRequest  
instance Produces RejectOAuth2LogoutRequest MimeNoContent


-- *** revokeOAuth2ConsentSessions

-- | @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 -- ^ "subject" -  OAuth 2.0 Consent Subject  The subject whose consent sessions should be deleted.
  -> OryHydraRequest RevokeOAuth2ConsentSessions MimeNoContent NoContent MimeNoContent
revokeOAuth2ConsentSessions :: Subject
-> OryHydraRequest
     RevokeOAuth2ConsentSessions MimeNoContent NoContent MimeNoContent
revokeOAuth2ConsentSessions (Subject Text
subject) =
  forall req contentType res accept.
Method
-> [ByteString] -> OryHydraRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/admin/oauth2/auth/sessions/consent"]
    forall req contentType res accept.
OryHydraRequest req contentType res accept
-> [QueryItem] -> OryHydraRequest req contentType res accept
`addQuery` forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"subject", forall a. a -> Maybe a
Just Text
subject)

data RevokeOAuth2ConsentSessions  

-- | /Optional Param/ "client" - OAuth 2.0 Client ID  If set, deletes only those consent sessions that have been granted to the specified OAuth 2.0 Client ID.
instance HasOptionalParam RevokeOAuth2ConsentSessions Client where
  applyOptionalParam :: forall contentType res accept.
OryHydraRequest RevokeOAuth2ConsentSessions contentType res accept
-> Client
-> OryHydraRequest
     RevokeOAuth2ConsentSessions contentType res accept
applyOptionalParam OryHydraRequest RevokeOAuth2ConsentSessions contentType res accept
req (Client Text
xs) =
    OryHydraRequest RevokeOAuth2ConsentSessions contentType res accept
req forall req contentType res accept.
OryHydraRequest req contentType res accept
-> [QueryItem] -> OryHydraRequest req contentType res accept
`addQuery` forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"client", forall a. a -> Maybe a
Just Text
xs)

-- | /Optional Param/ "all" - Revoke All Consent Sessions  If set to `true` deletes all consent sessions by the Subject that have been granted.
instance HasOptionalParam RevokeOAuth2ConsentSessions All where
  applyOptionalParam :: forall contentType res accept.
OryHydraRequest RevokeOAuth2ConsentSessions contentType res accept
-> All
-> OryHydraRequest
     RevokeOAuth2ConsentSessions contentType res accept
applyOptionalParam OryHydraRequest RevokeOAuth2ConsentSessions contentType res accept
req (All Bool
xs) =
    OryHydraRequest RevokeOAuth2ConsentSessions contentType res accept
req forall req contentType res accept.
OryHydraRequest req contentType res accept
-> [QueryItem] -> OryHydraRequest req contentType res accept
`addQuery` forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"all", forall a. a -> Maybe a
Just Bool
xs)
instance Produces RevokeOAuth2ConsentSessions MimeNoContent


-- *** revokeOAuth2LoginSessions

-- | @DELETE \/admin\/oauth2\/auth\/sessions\/login@
-- 
-- Revokes All OAuth 2.0 Login Sessions of a Subject
-- 
-- This endpoint invalidates a subject's authentication session. After revoking the authentication session, the subject has to re-authenticate at the Ory OAuth2 Provider. This endpoint does not invalidate any tokens and does not work with OpenID Connect Front- or Back-channel logout.
-- 
revokeOAuth2LoginSessions
  :: Subject -- ^ "subject" -  OAuth 2.0 Subject  The subject to revoke authentication sessions for.
  -> OryHydraRequest RevokeOAuth2LoginSessions MimeNoContent NoContent MimeNoContent
revokeOAuth2LoginSessions :: Subject
-> OryHydraRequest
     RevokeOAuth2LoginSessions MimeNoContent NoContent MimeNoContent
revokeOAuth2LoginSessions (Subject Text
subject) =
  forall req contentType res accept.
Method
-> [ByteString] -> OryHydraRequest req contentType res accept
_mkRequest Method
"DELETE" [ByteString
"/admin/oauth2/auth/sessions/login"]
    forall req contentType res accept.
OryHydraRequest req contentType res accept
-> [QueryItem] -> OryHydraRequest req contentType res accept
`addQuery` forall a. ToHttpApiData a => (Method, Maybe a) -> [QueryItem]
toQuery (Method
"subject", forall a. a -> Maybe a
Just Text
subject)

data RevokeOAuth2LoginSessions  
instance Produces RevokeOAuth2LoginSessions MimeNoContent


-- *** revokeOAuth2Token

-- | @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 -- ^ "token"
  -> OryHydraRequest RevokeOAuth2Token MimeFormUrlEncoded NoContent MimeNoContent
revokeOAuth2Token :: Consumes RevokeOAuth2Token MimeFormUrlEncoded =>
Token
-> OryHydraRequest
     RevokeOAuth2Token MimeFormUrlEncoded NoContent MimeNoContent
revokeOAuth2Token (Token Text
token) =
  forall req contentType res accept.
Method
-> [ByteString] -> OryHydraRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/oauth2/revoke"]
    forall authMethod req contentType res accept.
AuthMethod authMethod =>
OryHydraRequest req contentType res accept
-> Proxy authMethod -> OryHydraRequest req contentType res accept
`_hasAuthType` (forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthBasicBasic)
    forall authMethod req contentType res accept.
AuthMethod authMethod =>
OryHydraRequest req contentType res accept
-> Proxy authMethod -> OryHydraRequest req contentType res accept
`_hasAuthType` (forall {k} (t :: k). Proxy t
P.Proxy :: P.Proxy AuthOAuthOauth2)
    forall req contentType res accept.
OryHydraRequest req contentType res accept
-> Form -> OryHydraRequest req contentType res accept
`addForm` forall v. ToHttpApiData v => (Method, v) -> Form
toForm (Method
"token", Text
token)

data RevokeOAuth2Token  
instance HasOptionalParam RevokeOAuth2Token ClientId where
  applyOptionalParam :: forall contentType res accept.
OryHydraRequest RevokeOAuth2Token contentType res accept
-> ClientId
-> OryHydraRequest RevokeOAuth2Token contentType res accept
applyOptionalParam OryHydraRequest RevokeOAuth2Token contentType res accept
req (ClientId Text
xs) =
    OryHydraRequest RevokeOAuth2Token contentType res accept
req forall req contentType res accept.
OryHydraRequest req contentType res accept
-> Form -> OryHydraRequest req contentType res accept
`addForm` forall v. ToHttpApiData v => (Method, v) -> Form
toForm (Method
"client_id", Text
xs)
instance HasOptionalParam RevokeOAuth2Token ClientSecret where
  applyOptionalParam :: forall contentType res accept.
OryHydraRequest RevokeOAuth2Token contentType res accept
-> ClientSecret
-> OryHydraRequest RevokeOAuth2Token contentType res accept
applyOptionalParam OryHydraRequest RevokeOAuth2Token contentType res accept
req (ClientSecret Text
xs) =
    OryHydraRequest RevokeOAuth2Token contentType res accept
req forall req contentType res accept.
OryHydraRequest req contentType res accept
-> Form -> OryHydraRequest req contentType res accept
`addForm` forall v. ToHttpApiData v => (Method, v) -> Form
toForm (Method
"client_secret", Text
xs)

-- | @application/x-www-form-urlencoded@
instance Consumes RevokeOAuth2Token MimeFormUrlEncoded

instance Produces RevokeOAuth2Token MimeNoContent


-- *** setOAuth2Client

-- | @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 -- ^ "oAuth2Client" -  OAuth 2.0 Client Request Body
  -> Id -- ^ "id" -  OAuth 2.0 Client ID
  -> OryHydraRequest SetOAuth2Client MimeJSON OAuth2Client MimeJSON
setOAuth2Client :: (Consumes SetOAuth2Client MimeJSON,
 MimeRender MimeJSON OAuth2Client) =>
OAuth2Client
-> Id
-> OryHydraRequest SetOAuth2Client MimeJSON OAuth2Client MimeJSON
setOAuth2Client OAuth2Client
oAuth2Client (Id Text
id) =
  forall req contentType res accept.
Method
-> [ByteString] -> OryHydraRequest req contentType res accept
_mkRequest Method
"PUT" [ByteString
"/admin/clients/",forall a. ToHttpApiData a => a -> ByteString
toPath Text
id]
    forall req param contentType res accept.
(HasBodyParam req param, Consumes req contentType,
 MimeRender contentType param) =>
OryHydraRequest req contentType res accept
-> param -> OryHydraRequest req contentType res accept
`setBodyParam` OAuth2Client
oAuth2Client

data SetOAuth2Client 

-- | /Body Param/ "OAuth2Client" - OAuth 2.0 Client Request Body
instance HasBodyParam SetOAuth2Client OAuth2Client 

-- | @application/json@
instance Consumes SetOAuth2Client MimeJSON

-- | @application/json@
instance Produces SetOAuth2Client MimeJSON


-- *** setOAuth2ClientLifespans

-- | @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 -- ^ "id" -  OAuth 2.0 Client ID
  -> OryHydraRequest SetOAuth2ClientLifespans MimeJSON OAuth2Client MimeJSON
setOAuth2ClientLifespans :: Consumes SetOAuth2ClientLifespans MimeJSON =>
Id
-> OryHydraRequest
     SetOAuth2ClientLifespans MimeJSON OAuth2Client MimeJSON
setOAuth2ClientLifespans (Id Text
id) =
  forall req contentType res accept.
Method
-> [ByteString] -> OryHydraRequest req contentType res accept
_mkRequest Method
"PUT" [ByteString
"/admin/clients/",forall a. ToHttpApiData a => a -> ByteString
toPath Text
id,ByteString
"/lifespans"]

data SetOAuth2ClientLifespans 
instance HasBodyParam SetOAuth2ClientLifespans OAuth2ClientTokenLifespans 

-- | @application/json@
instance Consumes SetOAuth2ClientLifespans MimeJSON

-- | @application/json@
instance Produces SetOAuth2ClientLifespans MimeJSON


-- *** trustOAuth2JwtGrantIssuer0

-- | @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](https://datatracker.ietf.org/doc/html/rfc7523).
-- 
trustOAuth2JwtGrantIssuer0
  :: (Consumes TrustOAuth2JwtGrantIssuer0 MimeJSON)
  => OryHydraRequest TrustOAuth2JwtGrantIssuer0 MimeJSON TrustedOAuth2JwtGrantIssuer MimeJSON
trustOAuth2JwtGrantIssuer0 :: Consumes TrustOAuth2JwtGrantIssuer0 MimeJSON =>
OryHydraRequest
  TrustOAuth2JwtGrantIssuer0
  MimeJSON
  TrustedOAuth2JwtGrantIssuer
  MimeJSON
trustOAuth2JwtGrantIssuer0 =
  forall req contentType res accept.
Method
-> [ByteString] -> OryHydraRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/admin/trust/grants/jwt-bearer/issuers"]

data TrustOAuth2JwtGrantIssuer0 
instance HasBodyParam TrustOAuth2JwtGrantIssuer0 TrustOAuth2JwtGrantIssuer 

-- | @application/json@
instance Consumes TrustOAuth2JwtGrantIssuer0 MimeJSON

-- | @application/json@
instance Produces TrustOAuth2JwtGrantIssuer0 MimeJSON