{-
   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.Oidc
-}

{-# 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.Oidc 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


-- ** Oidc

-- *** createOidcDynamicClient

-- | @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 -- ^ "oAuth2Client" -  Dynamic Client Registration Request Body
  -> OryHydraRequest CreateOidcDynamicClient MimeJSON OAuth2Client MimeJSON
createOidcDynamicClient :: (Consumes CreateOidcDynamicClient MimeJSON,
 MimeRender MimeJSON OAuth2Client) =>
OAuth2Client
-> OryHydraRequest
     CreateOidcDynamicClient MimeJSON OAuth2Client MimeJSON
createOidcDynamicClient OAuth2Client
oAuth2Client =
  forall req contentType res accept.
Method
-> [ByteString] -> OryHydraRequest req contentType res accept
_mkRequest Method
"POST" [ByteString
"/oauth2/register"]
    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 CreateOidcDynamicClient 

-- | /Body Param/ "OAuth2Client" - Dynamic Client Registration Request Body
instance HasBodyParam CreateOidcDynamicClient OAuth2Client 

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

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


-- *** deleteOidcDynamicClient

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

data DeleteOidcDynamicClient  
instance Produces DeleteOidcDynamicClient MimeNoContent


-- *** discoverOidcConfiguration

-- | @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
discoverOidcConfiguration :: OryHydraRequest
  DiscoverOidcConfiguration MimeNoContent OidcConfiguration MimeJSON
discoverOidcConfiguration =
  forall req contentType res accept.
Method
-> [ByteString] -> OryHydraRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/.well-known/openid-configuration"]

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


-- *** getOidcDynamicClient

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

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


-- *** getOidcUserInfo

-- | @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](https://datatracker.ietf.org/doc/html/rfc6750#section-3) for more details about header format.
-- 
-- AuthMethod: 'AuthOAuthOauth2'
-- 
getOidcUserInfo
  :: OryHydraRequest GetOidcUserInfo MimeNoContent OidcUserInfo MimeJSON
getOidcUserInfo :: OryHydraRequest GetOidcUserInfo MimeNoContent OidcUserInfo MimeJSON
getOidcUserInfo =
  forall req contentType res accept.
Method
-> [ByteString] -> OryHydraRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/userinfo"]
    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)

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


-- *** revokeOidcSession

-- | @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.net/specs/openid-connect-frontchannel-1_0.html https://openid.net/specs/openid-connect-backchannel-1_0.html  Back-channel logout is performed asynchronously and does not affect logout flow.
-- 
revokeOidcSession
  :: OryHydraRequest RevokeOidcSession MimeNoContent NoContent MimeNoContent
revokeOidcSession :: OryHydraRequest
  RevokeOidcSession MimeNoContent NoContent MimeNoContent
revokeOidcSession =
  forall req contentType res accept.
Method
-> [ByteString] -> OryHydraRequest req contentType res accept
_mkRequest Method
"GET" [ByteString
"/oauth2/sessions/logout"]

data RevokeOidcSession  
instance Produces RevokeOidcSession MimeNoContent


-- *** setOidcDynamicClient

-- | @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 -- ^ "oAuth2Client" -  OAuth 2.0 Client Request Body
  -> Id -- ^ "id" -  OAuth 2.0 Client ID
  -> OryHydraRequest SetOidcDynamicClient MimeJSON OAuth2Client MimeJSON
setOidcDynamicClient :: (Consumes SetOidcDynamicClient MimeJSON,
 MimeRender MimeJSON OAuth2Client) =>
OAuth2Client
-> Id
-> OryHydraRequest
     SetOidcDynamicClient MimeJSON OAuth2Client MimeJSON
setOidcDynamicClient OAuth2Client
oAuth2Client (Id Text
id) =
  forall req contentType res accept.
Method
-> [ByteString] -> OryHydraRequest req contentType res accept
_mkRequest Method
"PUT" [ByteString
"/oauth2/register/",forall a. ToHttpApiData a => a -> ByteString
toPath Text
id]
    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 AuthBasicBearer)
    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 SetOidcDynamicClient 

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

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

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